@@ -102,64 +102,6 @@ void realloc_sym_storage();
102102#define NEWSYM (sptr ) \
103103 sptr = (SPTR)STG_NEXT(stb);
104104
105- #define NEWDPSHAPE (ishape ) \
106- ishape = STG_NEXT(stb.dpinfo);
107-
108- #define NEWDPMEMDIM (imemid ) \
109- imemid = STG_NEXT(stb.dpdim);
110-
111- #define NEWDPSUBREG (isubid ) \
112- isubid = STG_NEXT(stb.dpreg);
113-
114- #define NEWDPPOLICYIDX (ipolicyid ) \
115- ipolicyid = STG_NEXT(stb.dppolicyidx);
116-
117- #define NEWDPPOLICYMEM (ipolicymemid ) \
118- ipolicymemid = STG_NEXT(stb.dppolicymem);
119-
120- #define DP_FIRSTSHAPE (dtype ) stb.dt_shapemap.stg_base[dtype]
121- #define DP_FIRSTPOLICY (dtype ) stb.dt_shapemap.stg_base[dtype+1 ]
122- /* if this structure/union type, does it include any dynamic member
123- * in this descendants */
124- #define DP_INCLUDEDYN (dtype ) stb.dt_shapemap.stg_base[dtype+2 ]
125- #define DP_INCDYN_FLG_UNSET (0 )
126- #define DP_INCDYN_FLG_HASDYN (1 )
127- #define DP_INCDYN_FLG_NODYN (2 )
128-
129- #define DP_SHAPE_NEXT (ishape ) stb.dpinfo.stg_base[ishape].next
130- #define DP_SHAPE_NAME (ishape ) stb.dpinfo.stg_base[ishape].sptr
131- #define DP_SHAPE_LINENO (ishape ) stb.dpinfo.stg_base[ishape].lineno
132- #define DP_SHAPE_PARENT_TYPE (ishape ) stb.dpinfo.stg_base[ishape].typeidx
133- #define DP_SHAPE_PARENT_TNAME (ishape ) stb.dpinfo.stg_base[ishape].typesptr
134- #define DP_SHAPE_INEX (ishape ) stb.dpinfo.stg_base[ishape].inex
135- #define DP_SHAPE_1ST_MEMID (ishape ) stb.dpinfo.stg_base[ishape].memid
136-
137- #define DP_MEMID_MAP_SPTR (memid ) stb.dpdim.stg_base[memid].sptr
138- #define DP_MEMID_LINENO (memid ) stb.dpdim.stg_base[memid].lineno
139- #define DP_MEMID_TYPE (memid ) stb.dpdim.stg_base[memid].type
140- #define DP_MEMID_NEXT (memid ) stb.dpdim.stg_base[memid].next
141- #define DP_MEMID_1ST_SUBREGION (memid ) stb.dpdim.stg_base[memid].subregion
142-
143- #define DP_SUBREGION_LOW (isubid ) stb.dpreg.stg_base[isubid].low
144- #define DP_SUBREGION_LOW_TYPE (isubid ) stb.dpreg.stg_base[isubid].lowtype
145- #define DP_SUBREGION_HIGH (isubid ) stb.dpreg.stg_base[isubid].upper
146- #define DP_SUBREGION_HIGH_TYPE (isubid ) stb.dpreg.stg_base[isubid].uppertype
147- #define DP_SUBREGION_NEXT (isubid ) stb.dpreg.stg_base[isubid].next
148-
149- #define DP_POLICY_NAME (ipolicyid ) stb.dppolicyidx.stg_base[ipolicyid].sptr
150- #define DP_POLICY_SHAPEID (ipolicyid ) stb.dppolicyidx.stg_base[ipolicyid].shapeid
151- #define DP_POLICY_LINENO (ipolicyid ) stb.dppolicyidx.stg_base[ipolicyid].lineno
152- #define DP_POLICY_PARENT_TYPE (ipolicyid ) stb.dppolicyidx.stg_base[ipolicyid].typeidx
153- #define DP_POLICY_PARENT_TNAME (ipolicyid ) stb.dppolicyidx.stg_base[ipolicyid].typesptr
154- #define DP_POLICY_1ST_MEMID (ipolicyid ) stb.dppolicyidx.stg_base[ipolicyid].memid
155- #define DP_POLICY_INEX_FLAG (ipolicyid ) stb.dppolicyidx.stg_base[ipolicyid].inex
156- #define DP_POLICY_NEXT (ipolicyid ) stb.dppolicyidx.stg_base[ipolicyid].next
157-
158- #define DP_POLICYMEM_NAME (ipolicymemid ) stb.dppolicymem.stg_base[ipolicymemid].sptr
159- #define DP_POLICYMEM_MOTION_TYPE (ipolicymemid ) stb.dppolicymem.stg_base[ipolicymemid].mtype
160- #define DP_POLICYMEM_POLICYIDX (ipolicymemid ) stb.dppolicymem.stg_base[ipolicymemid].policyidx
161- #define DP_POLICYMEM_NEXT (ipolicymemid ) stb.dppolicymem.stg_base[ipolicymemid].next
162-
163105#define LINKSYM (sptr, hashval ) \
164106 HASHLKP (sptr, stb.hashtb[hashval]); \
165107 stb.hashtb[hashval] = sptr
@@ -232,102 +174,6 @@ typedef struct SYM {
232174 INT w40;
233175} SYM;
234176
235- typedef struct DPSHAPE {
236- int sptr; /* name of current shape*/
237- int typeidx; /* this is type in which shape dir applies */
238- int typesptr; /* parent type name, DTYPEG(typesptr)
239- * should equal to typeidx */
240- int memid; /* shape info for the first mem*/
241- /* default(include/exclude) clause
242- * 0: default clause not appear
243- * 1: default is include
244- * 2: default is exclude */
245- int inex;
246- int lineno;
247- int next; /* next shape */
248- }DPSHAPE;
249-
250- typedef enum ACC_DP_SH_TYPE {
251- ACC_DP_SH_TUNKNOWN = 0 ,
252- ACC_DP_SH_TARRAY_SD, /* array section description */
253- ACC_DP_SH_TINIT_NEEDED,
254- ACC_DP_SH_RELATIVE
255- }ACC_DP_SH_TYPE;
256-
257- typedef struct DPMEMDIM {
258- int sptr; /* entry to the name of struct/union/class member */
259- /* if sptr is a scalar, subregion is 0
260- * it means this scalar var is init_needed */
261- int subregion;
262- int lineno;
263- int type;
264- int next;
265- }DPMEMDIM;
266-
267- typedef enum DPBNDTYPE {
268- DP_BND_UNKNOWN,
269- DP_BND_CONST, /* compilation time known constant */
270- DP_BND_SIBLING_MEM, /* sibling scalar members */
271- DP_BND_GBL_VAR, /* global variable which will be translated into ptr */
272- DP_BND_EXP, /* it is an expression. */
273- DP_BND_TAG /* it is only used to identify pointers
274- * in relative clause (not start ptr) */
275- }DPBNDTYPE;
276-
277- typedef struct DPSUBREG {
278- int low; /* constant */
279- DPBNDTYPE lowtype; /* const, sibling mem entry, expression */
280- int upper;
281- DPBNDTYPE uppertype; /* const, sibling mem entry, expression */
282- int next; /* next dimensional info */
283- }DPSUBREG;
284-
285- typedef enum ACC_DP_DEFAULTVALUE {
286- ACC_DP_DEFAULT_NONE=0 ,
287- ACC_DP_DEFAULT_INCLUDE,
288- ACC_DP_DEFAULT_EXCLUDE
289- }ACC_DP_DEFAULTVALUE;
290-
291- typedef struct DP_POLICY_IDX {
292- int sptr; /* policy name */
293- int shapeid; /* which shape is used by this policy directive */
294- int typeidx; /* this is type in which policy is declared */
295- int typesptr; /* parent type name, DTYPEG(typesptr)
296- * should equal to typeidx */
297- int memid; /* first member */
298- /* default(include/exclude) clause
299- * 0: default clause not appear
300- * 1: default is include
301- * 2: default is exclude */
302- int inex;
303- int lineno;
304- int next; /* next policy */
305- }DP_POLICY_IDX;
306-
307- /* deepcopy policy motion type
308- * If this order is changed, the same order
309- * must be changes in runtime unified.h */
310- typedef enum DP_POLICY_MTYPE {
311- ACC_DP_UNKNOWN=0 ,
312- ACC_DP_COPYIN,
313- ACC_DP_COPYOUT,
314- ACC_DP_COPY,
315- ACC_DP_CREATE,
316- ACC_DP_UPDATE,
317- ACC_DP_DEVPTR,
318- ACC_DP_NOCREATE, /* NOT IMPLEMENT */
319- ACC_DP_PRESENT /* NOT IMPLEMENT */
320- }DP_POLICY_MTYPE;
321-
322- /* Policy Members */
323- typedef struct DP_POLICY_MEM {
324- int sptr; /* member name */
325- DP_POLICY_MTYPE mtype; /* motion type */
326- int policyidx;
327- int lineno;
328- int next; /* next mem in this policy */
329- }DP_POLICY_MEM;
330-
331177/* symbol table data declarations: */
332178typedef struct {
333179 const char *stypes[ST_MAX + 1 ];
@@ -345,24 +191,10 @@ typedef struct {
345191 struct {
346192 STG_MEMBERS (ISZ_T);
347193 }dt;
348- struct {
349- STG_MEMBERS (ISZ_T);
350- }dt_shapemap;
351194 int curr_scope;
352195 SPTR hashtb[HASHSIZE + 1 ];
353196 SPTR firstusym, firstosym;
354197 STG_MEMBERS (SYM);
355- /* shape info for aggregate data type */
356- STG_DECLARE (dpinfo, DPSHAPE);
357- /* deepcopy dimensional info for each mem in a data type
358- * it points entries in dpreg */
359- STG_DECLARE (dpdim, DPMEMDIM);
360- /* low/upper bound of each dim */
361- STG_DECLARE (dpreg, DPSUBREG);
362- /* Policy ID */
363- STG_DECLARE (dppolicyidx, DP_POLICY_IDX);
364- /* Mem motion definition in the policy directive */
365- STG_DECLARE (dppolicymem, DP_POLICY_MEM);
366198 char *n_base;
367199 int n_size;
368200 int namavl;
0 commit comments