* as/hc08/asmain.c (asexit),
[fw/sdcc] / src / SDCCsymt.h
1 /*-------------------------------------------------------------------------
2   SDCCsymt.h - Header file for Symbols table related structures and MACRO's.
3               Written By -  Sandeep Dutta . sandeep.dutta@usa.net (1998)
4
5    This program is free software; you can redistribute it and/or modify it
6    under the terms of the GNU General Public License as published by the
7    Free Software Foundation; either version 2, or (at your option) any
8    later version.
9
10    This program is distributed in the hope that it will be useful,
11    but WITHOUT ANY WARRANTY; without even the implied warranty of
12    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
13    GNU General Public License for more details.
14
15    You should have received a copy of the GNU General Public License
16    along with this program; if not, write to the Free Software
17    Foundation, 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
18
19    In other words, you are welcome to use, share and improve this program.
20    You are forbidden to forbid anyone else to use, share and improve
21    what you give them.   Help stamp out software-hoarding!
22 -------------------------------------------------------------------------*/
23
24 #ifndef  SDCCSYMT_H
25 #define  SDCCSYMT_H
26
27 #define MAX_NEST_LEVEL  256
28 #define SDCC_SYMNAME_MAX 64
29 #define SDCC_NAME_MAX  3*SDCC_SYMNAME_MAX // big enough for _<func>_<var>_etc
30 #include "SDCChasht.h"
31 #include "SDCCglobl.h"
32
33 #define INTNO_MAX 255                   /* maximum allowed interrupt number */
34 #define INTNO_UNSPEC (INTNO_MAX+1)      /* interrupt number unspecified */
35
36 #define BITVAR_PAD -1
37
38 enum {
39     TYPEOF_INT=1,
40     TYPEOF_SHORT,
41     TYPEOF_CHAR,
42     TYPEOF_LONG,
43     TYPEOF_FLOAT,
44     TYPEOF_FIXED16X16,
45     TYPEOF_BIT,
46     TYPEOF_BITFIELD,
47     TYPEOF_SBIT,
48     TYPEOF_SFR,
49     TYPEOF_VOID,
50     TYPEOF_STRUCT,
51     TYPEOF_ARRAY,
52     TYPEOF_FUNCTION,
53     TYPEOF_POINTER,
54     TYPEOF_FPOINTER,
55     TYPEOF_CPOINTER,
56     TYPEOF_GPOINTER,
57     TYPEOF_PPOINTER,
58     TYPEOF_IPOINTER,
59     TYPEOF_EEPPOINTER
60 };
61
62 // values for first byte (or 3 most significant bits) of generic pointer.
63 #define GPTYPE_FAR       0x00
64 #define GPTYPE_NEAR      0x40
65 #define GPTYPE_XSTACK    0x60
66 #define GPTYPE_CODE      0x80
67
68 #define HASHTAB_SIZE 256
69
70 /* hash table bucket */
71 typedef struct bucket
72   {
73     void *sym;                          /* pointer to the object   */
74     char name[SDCC_NAME_MAX + 1];       /* name of this symbol          */
75     int level;                          /* nest level for this symbol   */
76     int block;                          /* belongs to which block */
77     struct bucket *prev;                /* ptr 2 previous bucket   */
78     struct bucket *next;                /* ptr 2 next bucket       */
79   }
80 bucket;
81
82 typedef struct structdef
83   {
84     char tag[SDCC_NAME_MAX + 1];        /* tag part of structure      */
85     unsigned char level;                /* Nesting level         */
86     struct symbol *fields;              /* pointer to fields     */
87     unsigned size;                      /* sizeof the table in bytes  */
88     int type;                           /* STRUCT or UNION */
89     bool b_flexArrayMember;             /* has got an flexible array member,
90                                            only needed for syntax checks */
91   }
92 structdef;
93
94 /* noun definitions */
95 typedef enum
96   {
97     V_INT = 1,
98     V_FLOAT,
99     V_FIXED16X16,
100     V_CHAR,
101     V_VOID,
102     V_STRUCT,
103     V_LABEL,
104     V_BIT,
105     V_BITFIELD,
106     V_SBIT,
107     V_DOUBLE
108   }
109 NOUN;
110
111 /* storage class    */
112 typedef enum
113   {
114     S_FIXED = 0,
115     S_AUTO,
116     S_REGISTER,
117     S_SFR,
118     S_SBIT,
119     S_CODE,
120     S_XDATA,
121     S_DATA,
122     S_IDATA,
123     S_PDATA,
124     S_LITERAL,
125     S_STACK,
126     S_XSTACK,
127     S_BIT,
128     S_EEPROM
129   }
130 STORAGE_CLASS;
131
132 /* specifier is the last in the type-chain */
133 typedef struct specifier
134   {
135     NOUN noun;                          /* CHAR INT STRUCTURE LABEL   */
136     STORAGE_CLASS sclass;               /* REGISTER,AUTO,FIX,CONSTANT */
137     struct memmap *oclass;              /* output storage class       */
138     unsigned b_long:1;                  /* 1=long                     */
139     unsigned b_short:1;                 /* 1=short int                */
140     unsigned b_unsigned:1;              /* 1=unsigned, 0=signed       */
141     unsigned b_signed:1;                /* just for sanity checks only*/
142     unsigned b_static:1;                /* 1=static keyword found     */
143     unsigned b_extern:1;                /* 1=extern found             */
144     unsigned b_absadr:1;                /* absolute address specfied  */
145     unsigned b_volatile:1;              /* is marked as volatile      */
146     unsigned b_const:1;                 /* is a constant              */
147     unsigned b_typedef:1;               /* is typedefed               */
148     unsigned b_isregparm:1;             /* is the first parameter     */
149     unsigned b_isenum:1;                /* is an enumerated type      */
150     unsigned _addr;                     /* address of symbol          */
151     unsigned _stack;                    /* stack offset for stacked v */
152     unsigned _bitStart;                 /* bit start position         */
153     int _bitLength;                     /* bit length                 */
154     int argreg;                         /* reg no for regparm         */
155     union
156       {                                 /* Values if constant or enum */
157         TYPE_WORD   v_int;              /* 2 bytes: int and char values           */
158         char       *v_char;             /*          character string              */
159         TYPE_UWORD  v_uint;             /* 2 bytes: unsigned int const value      */
160         TYPE_DWORD  v_long;             /* 4 bytes: long constant value           */
161         TYPE_UDWORD v_ulong;            /* 4 bytes: unsigned long constant value  */
162         double      v_float;            /*          floating point constant value */
163         TYPE_UDWORD v_fixed16x16;       /* 4 bytes: fixed floating point constant value */
164         struct symbol *v_enum;          /* ptr to enum_list if enum==1            */
165       }
166     const_val;
167     struct structdef *v_struct;         /* structure pointer      */
168   }
169 specifier;
170
171 /* types of declarators */
172 typedef enum
173   {
174     POINTER = 0,                        /* pointer to near data */
175     FPOINTER,                           /* pointer to far data  */
176     CPOINTER,                           /* pointer to code space */
177     GPOINTER,                           /* _generic pointer     */
178     PPOINTER,                           /* paged area pointer   */
179     IPOINTER,                           /* pointer to upper 128 bytes */
180     UPOINTER,                           /* unknown pointer used only when parsing */
181     EEPPOINTER,                         /* pointer to eeprom     */
182     ARRAY,
183     FUNCTION
184   }
185 DECLARATOR_TYPE;
186
187 typedef struct declarator
188   {
189     DECLARATOR_TYPE dcl_type;           /* POINTER,ARRAY or FUNCTION  */
190     unsigned int num_elem;              /* # of elems if type==array, */
191                                         /* always 0 for flexible arrays */
192     unsigned ptr_const:1;               /* pointer is constant        */
193     unsigned ptr_volatile:1;            /* pointer is volatile        */
194     struct sym_link *tspec;             /* pointer type specifier     */
195   }
196 declarator;
197
198 typedef enum {
199   DECLARATOR=1,
200   SPECIFIER
201 } SYM_LINK_CLASS;
202 #define DECLSPEC2TXT(select) (select==DECLARATOR?"DECLARATOR":select==SPECIFIER?"SPECIFIER":"UNKNOW")
203
204 typedef struct sym_link
205   {
206     SYM_LINK_CLASS class;               /* DECLARATOR or SPECIFIER    */
207     unsigned tdef:1;                    /* current link created by    */
208     /* typedef if this flag is set */
209     union
210       {
211         specifier s;                    /* if CLASS == SPECIFIER      */
212         declarator d;                   /* if CLASS == DECLARATOR     */
213       } select;
214
215     /* function attributes */
216     struct {
217       struct value *args;               /* the defined arguments      */
218       unsigned hasVargs:1;              /* functions has varargs      */
219       unsigned calleeSaves:1;           /* functions uses callee save */
220       unsigned hasbody:1;               /* function body defined      */
221       unsigned hasFcall:1;              /* does it call other functions */
222       unsigned reent:1;                 /* function is reentrant      */
223       unsigned naked:1;                 /* naked function             */
224
225       unsigned shadowregs:1;            /* function uses shadow registers (pic16 port) */
226       unsigned wparam:1;                /* first byte of arguments is passed via WREG (pic16 port) */
227       unsigned nonbanked:1;             /* function has the nonbanked attribute */
228       unsigned banked:1;                /* function has the banked attribute */
229       unsigned critical:1;              /* critical function          */
230       unsigned intrtn:1;                /* this is an interrupt routine */
231       unsigned rbank:1;                 /* seperate register bank     */
232       unsigned intno;                   /* 1=Interrupt svc routine    */
233       short    regbank;                 /* register bank 2b used      */
234       unsigned builtin;                 /* is a builtin function      */
235       unsigned javaNative;              /* is a JavaNative Function (TININative ONLY) */
236       unsigned overlay;                 /* force parameters & locals into overlay segment */
237       unsigned hasStackParms;           /* function has parameters on stack */
238     } funcAttrs;
239
240     struct sym_link *next;              /* next element on the chain  */
241   }
242 sym_link;
243
244 typedef struct symbol
245   {
246     char name[SDCC_SYMNAME_MAX + 1];    /* Input Variable Name     */
247     char rname[SDCC_NAME_MAX + 1];      /* internal name           */
248
249     short level;                        /* declaration lev,fld offset */
250     short block;                        /* sequential block # of definition */
251     int key;
252     unsigned flexArrayLength;           /* if the symbol specifies a struct
253     with a "flexible array member", then the additional length in bytes for
254     the "fam" is stored here. Because the lenght can be different from symbol
255     to symbol AND v_struct isn't copied in copyLinkChain(), it's located here
256     in the symbol and not in v_struct or the declarator */
257     unsigned implicit:1;                /* implicit flag                     */
258     unsigned undefined:1;               /* undefined variable                */
259     unsigned infertype:1;               /* type should be inferred from first assign */
260     unsigned _isparm:1;                 /* is a parameter          */
261     unsigned ismyparm:1;                /* is parameter of the function being generated */
262     unsigned isitmp:1;                  /* is an intermediate temp */
263     unsigned islbl:1;                   /* is a temporary label */
264     unsigned isref:1;                   /* has been referenced  */
265     unsigned isind:1;                   /* is a induction variable */
266     unsigned isinvariant:1;             /* is a loop invariant  */
267     unsigned cdef:1;                    /* compiler defined symbol */
268     unsigned addrtaken:1;               /* address of the symbol was taken */
269     unsigned isreqv:1;                  /* is the register quivalent of a symbol */
270     unsigned udChked:1;                 /* use def checking has been already done */
271
272     /* following flags are used by the backend
273        for code generation and can be changed
274        if a better scheme for backend is thought of */
275     unsigned isLiveFcall:1;             /* is live at or across a function call */
276     unsigned isspilt:1;                 /* has to be spilt */
277     unsigned spillA:1;                  /* spilt be register allocator */
278     unsigned remat:1;                   /* can be remateriazed */
279     unsigned isptr:1;                   /* is a pointer */
280     unsigned uptr:1;                    /* used as a pointer */
281     unsigned isFree:1;                  /* used by register allocator */
282     unsigned islocal:1;                 /* is a local variable        */
283     unsigned blockSpil:1;               /* spilt at block level       */
284     unsigned remainSpil:1;              /* spilt because not used in remainder */
285     unsigned stackSpil:1;               /* has been spilt on temp stack location */
286     unsigned onStack:1;                 /* this symbol allocated on the stack */
287     unsigned iaccess:1;                 /* indirect access      */
288     unsigned ruonly:1;                  /* used in return statement only */
289     unsigned spildir:1;                 /* spilt in direct space */
290     unsigned ptrreg:1;                  /* this symbol assigned to a ptr reg */
291     unsigned noSpilLoc:1;               /* cannot be assigned a spil location */
292     unsigned isstrlit;                  /* is a string literal and it's usage count  */
293     unsigned accuse;                    /* can be left in the accumulator
294                                            On the Z80 accuse is divided into
295                                            ACCUSE_A and ACCUSE_HL as the idea
296                                            is quite similar.
297                                          */
298     unsigned dptr;                      /* 8051 variants with multiple DPTRS
299                                            currently implemented in DS390 only
300                                         */
301     int allocreq ;                      /* allocation is required for this variable */
302     int stack;                          /* offset on stack      */
303     int xstack;                         /* offset on xternal stack */
304     short nRegs;                        /* number of registers required */
305     short regType;                      /* type of register required    */
306
307     struct regs *regs[4];               /* can have at the most 4 registers */
308     struct asmop *aop;                  /* asmoperand for this symbol */
309     struct iCode *fuse;                 /* furthest use */
310     struct iCode *rematiCode;           /* rematerialise with which instruction */
311     struct operand *reqv;               /* register equivalent of a local variable */
312     struct symbol *prereqv;             /* symbol before register equiv. substituion */
313     struct symbol *psbase;              /* if pseudo symbol, the symbol it is based on */
314     union
315       {
316         struct symbol *spillLoc;        /* register spil location */
317         struct set *itmpStack;          /* symbols spilt @ this stack location */
318       }
319     usl;
320     short bitVar;                       /* this is a bit variable    */
321     unsigned offset;                    /* offset from top if struct */
322
323     int lineDef;                        /* defined line number        */
324     char *fileDef;                      /* defined filename           */
325     int lastLine;                       /* for functions the last line */
326     struct sym_link *type;              /* 1st link to declarator chain */
327     struct sym_link *etype;             /* last link to declarator chain */
328     struct symbol *next;                /* crosslink to next symbol   */
329     struct symbol *localof;             /* local variable of which function */
330     struct initList *ival;              /* ptr to initializer if any  */
331     struct bitVect *defs;               /* bit vector for definitions */
332     struct bitVect *uses;               /* bit vector for uses        */
333     struct bitVect *regsUsed;           /* for functions registers used */
334     int liveFrom;                       /* live from iCode sequence number */
335     int liveTo;                         /* live to sequence number */
336     int used;                           /* no. of times this was used */
337     int recvSize;                       /* size of first argument  */
338     struct bitVect *clashes;            /* overlaps with what other symbols */
339   }
340 symbol;
341
342 extern sym_link *validateLink(sym_link  *l,
343                                const char       *macro,
344                                const char       *args,
345                                const char       select,
346                                const char       *file,
347                                unsigned         line);
348 /* Easy Access Macros */
349 #define DCL_TYPE(l)  validateLink(l, "DCL_TYPE", #l, DECLARATOR, __FILE__, __LINE__)->select.d.dcl_type
350 #define DCL_ELEM(l)  validateLink(l, "DCL_ELEM", #l, DECLARATOR, __FILE__, __LINE__)->select.d.num_elem
351 #define DCL_PTR_CONST(l) validateLink(l, "DCL_PTR_CONST", #l, DECLARATOR, __FILE__, __LINE__)->select.d.ptr_const
352 #define DCL_PTR_VOLATILE(l) validateLink(l, "DCL_PTR_VOLATILE", #l, DECLARATOR, __FILE__, __LINE__)->select.d.ptr_volatile
353 #define DCL_TSPEC(l) validateLink(l, "DCL_TSPEC", #l, DECLARATOR, __FILE__, __LINE__)->select.d.tspec
354
355 #define FUNC_DEBUG //assert(IS_FUNC(x));
356 #define FUNC_HASVARARGS(x) (x->funcAttrs.hasVargs)
357 #define IFFUNC_HASVARARGS(x) (IS_FUNC(x) && FUNC_HASVARARGS(x))
358 #define FUNC_ARGS(x) (x->funcAttrs.args)
359 #define IFFUNC_ARGS(x) (IS_FUNC(x) && FUNC_ARGS(x))
360 #define FUNC_HASFCALL(x) (x->funcAttrs.hasFcall)
361 #define IFFUNC_HASFCALL(x) (IS_FUNC(x) && FUNC_HASFCALL(x))
362 #define FUNC_HASBODY(x) (x->funcAttrs.hasbody)
363 #define IFFUNC_HASBODY(x) (IS_FUNC(x) && FUNC_HASBODY(x))
364 #define FUNC_CALLEESAVES(x) (x->funcAttrs.calleeSaves)
365 #define IFFUNC_CALLEESAVES(x) (IS_FUNC(x) && FUNC_CALLEESAVES(x))
366 #define FUNC_ISISR(x) (x->funcAttrs.intrtn)
367 #define IFFUNC_ISISR(x) (IS_FUNC(x) && FUNC_ISISR(x))
368 #define IFFUNC_RBANK(x) (IS_FUNC(x) && FUNC_RBANK(x))
369 #define FUNC_INTNO(x) (x->funcAttrs.intno)
370 #define FUNC_REGBANK(x) (x->funcAttrs.regbank)
371 #define FUNC_HASSTACKPARM(x) (x->funcAttrs.hasStackParms)
372
373 #define FUNC_ISREENT(x) (x->funcAttrs.reent)
374 #define IFFUNC_ISREENT(x) (IS_FUNC(x) && FUNC_ISREENT(x))
375 #define FUNC_ISSHADOWREGS(x) (x->funcAttrs.shadowregs)
376 #define IFFUNC_ISSHADOWREGS(x) (IS_FUNC(x) && FUNC_ISSHADOWREGS(x))
377 #define FUNC_ISWPARAM(x) (x->funcAttrs.wparam)
378 #define IFFUNC_ISWPARAM(x) (IS_FUNC(x) && FUNC_ISWPARAM(x))
379 #define FUNC_ISNAKED(x) (x->funcAttrs.naked)
380 #define IFFUNC_ISNAKED(x) (IS_FUNC(x) && FUNC_ISNAKED(x))
381 #define FUNC_NONBANKED(x) (x->funcAttrs.nonbanked)
382 #define IFFUNC_NONBANKED(x) (IS_FUNC(x) && FUNC_NONBANKED(x))
383 #define FUNC_BANKED(x) (x->funcAttrs.banked)
384 #define IFFUNC_BANKED(x) (IS_FUNC(x) && FUNC_BANKED(x))
385 #define FUNC_ISCRITICAL(x) (x->funcAttrs.critical)
386 #define IFFUNC_ISCRITICAL(x) (IS_FUNC(x) && FUNC_ISCRITICAL(x))
387 #define FUNC_ISBUILTIN(x) (x->funcAttrs.builtin)
388 #define IFFUNC_ISBUILTIN(x) (IS_FUNC(x) && FUNC_ISBUILTIN(x))
389 #define FUNC_ISJAVANATIVE(x) (x->funcAttrs.javaNative)
390 #define IFFUNC_ISJAVANATIVE(x) (IS_FUNC(x) && FUNC_ISJAVANATIVE(x))
391 #define FUNC_ISOVERLAY(x) (x->funcAttrs.overlay)
392 #define IFFUNC_ISOVERLAY(x) (IS_FUNC(x) && FUNC_ISOVERLAY(x))
393
394 #define IFFUNC_ISBANKEDCALL(x) (!IFFUNC_NONBANKED(x) && \
395   (options.model == MODEL_HUGE || \
396    ((options.model == MODEL_LARGE || options.model == MODEL_MEDIUM) && \
397    (TARGET_IS_Z80 || TARGET_IS_GBZ80)) || \
398   IFFUNC_BANKED(x)))
399
400 #define SPEC_NOUN(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s.noun
401 #define SPEC_LONG(x) validateLink(x, "SPEC_LONG", #x, SPECIFIER, __FILE__, __LINE__)->select.s.b_long
402 #define SPEC_SHORT(x) validateLink(x, "SPEC_LONG", #x, SPECIFIER, __FILE__, __LINE__)->select.s.b_short
403 #define SPEC_USIGN(x) validateLink(x, "SPEC_USIGN", #x, SPECIFIER, __FILE__, __LINE__)->select.s.b_unsigned
404 #define SPEC_SCLS(x) validateLink(x, "SPEC_SCLS", #x, SPECIFIER, __FILE__, __LINE__)->select.s.sclass
405 #define SPEC_ENUM(x) validateLink(x, "SPEC_ENUM", #x, SPECIFIER, __FILE__, __LINE__)->select.s.b_isenum
406 #define SPEC_OCLS(x) validateLink(x, "SPEC_OCLS", #x, SPECIFIER, __FILE__, __LINE__)->select.s.oclass
407 #define SPEC_STAT(x) validateLink(x, "SPEC_STAT", #x, SPECIFIER, __FILE__, __LINE__)->select.s.b_static
408 #define SPEC_EXTR(x) validateLink(x, "SPEC_EXTR", #x, SPECIFIER, __FILE__, __LINE__)->select.s.b_extern
409 #define SPEC_CODE(x) validateLink(x, "SPEC_CODE", #x, SPECIFIER, __FILE__, __LINE__)->select.s._codesg
410 #define SPEC_ABSA(x) validateLink(x, "SPEC_ABSA", #x, SPECIFIER, __FILE__, __LINE__)->select.s.b_absadr
411 #define SPEC_BANK(x) validateLink(x, "SPEC_BANK", #x, SPECIFIER, __FILE__, __LINE__)->select.s._regbank
412 #define SPEC_ADDR(x) validateLink(x, "SPEC_ADDR", #x, SPECIFIER, __FILE__, __LINE__)->select.s._addr
413 #define SPEC_STAK(x) validateLink(x, "SPEC_STAK", #x, SPECIFIER, __FILE__, __LINE__)->select.s._stack
414 #define SPEC_CVAL(x) validateLink(x, "SPEC_CVAL", #x, SPECIFIER, __FILE__, __LINE__)->select.s.const_val
415 #define SPEC_BSTR(x) validateLink(x, "SPEC_BSTR", #x, SPECIFIER, __FILE__, __LINE__)->select.s._bitStart
416 #define SPEC_BLEN(x) validateLink(x, "SPEC_BLEN", #x, SPECIFIER, __FILE__, __LINE__)->select.s._bitLength
417
418 /* Sleaze: SPEC_ISR_SAVED_BANKS is only used on
419  * function type symbols, which obviously cannot
420  * be of BIT type. Therefore, we recycle the
421  * _bitStart field instead of defining a new field.
422  */
423 #define SPEC_ISR_SAVED_BANKS(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s._bitStart
424 #define SPEC_VOLATILE(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s.b_volatile
425 #define SPEC_CONST(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s.b_const
426 #define SPEC_STRUCT(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s.v_struct
427 #define SPEC_TYPEDEF(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s.b_typedef
428 #define SPEC_REGPARM(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s.b_isregparm
429 #define SPEC_ARGREG(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s.argreg
430
431 /* type check macros */
432 #define IS_DECL(x)   ( x && x->class == DECLARATOR      )
433 #define IS_SPEC(x)   ( x && x->class == SPECIFIER  )
434 #define IS_ARRAY(x)  (IS_DECL(x) && DCL_TYPE(x) == ARRAY)
435 #define IS_DATA_PTR(x) (IS_DECL(x) && DCL_TYPE(x) == POINTER)
436 #define IS_PTR(x)    (IS_DECL(x) && (DCL_TYPE(x) == POINTER    ||    \
437                                      DCL_TYPE(x) == FPOINTER   ||    \
438                                      DCL_TYPE(x) == GPOINTER   ||    \
439                                      DCL_TYPE(x) == IPOINTER   ||    \
440                                      DCL_TYPE(x) == PPOINTER   ||    \
441                                      DCL_TYPE(x) == EEPPOINTER ||    \
442                                      DCL_TYPE(x) == CPOINTER   ||    \
443                                      DCL_TYPE(x) == UPOINTER  ))
444 #define IS_PTR_CONST(x) (IS_PTR(x) && DCL_PTR_CONST(x))
445 #define IS_FARPTR(x) (IS_DECL(x) && DCL_TYPE(x) == FPOINTER)
446 #define IS_CODEPTR(x) (IS_DECL(x) && DCL_TYPE(x) == CPOINTER)
447 #define IS_GENPTR(x) (IS_DECL(x) && DCL_TYPE(x) == GPOINTER)
448 #define IS_FUNCPTR(x) (IS_DECL(x) && (DCL_TYPE(x) == CPOINTER || DCL_TYPE(x) == GPOINTER) && IS_FUNC(x->next))
449 #define IS_FUNC(x)   (IS_DECL(x) && DCL_TYPE(x) == FUNCTION)
450 #define IS_LONG(x)   (IS_SPEC(x) && x->select.s.b_long)
451 #define IS_UNSIGNED(x) (IS_SPEC(x) && x->select.s.b_unsigned)
452 #define IS_TYPEDEF(x)(IS_SPEC(x) && x->select.s.b_typedef)
453 #define IS_CONSTANT(x)  (!x ? 0 : \
454                            IS_SPEC(x) ? \
455                            x->select.s.b_const : \
456                            x->select.d.ptr_const)
457 #define IS_STRUCT(x) (IS_SPEC(x) && x->select.s.noun == V_STRUCT)
458 #define IS_ABSOLUTE(x)  (IS_SPEC(x) && x->select.s.b_absadr )
459 #define IS_REGISTER(x)  (IS_SPEC(x) && SPEC_SCLS(x) == S_REGISTER)
460 #define IS_RENT(x)   (IS_SPEC(x) && x->select.s._reent )
461 #define IS_STATIC(x) (IS_SPEC(x) && SPEC_STAT(x))
462 #define IS_INT(x)    (IS_SPEC(x) && x->select.s.noun == V_INT)
463 #define IS_VOID(x)   (IS_SPEC(x) && x->select.s.noun == V_VOID)
464 #define IS_CHAR(x)   (IS_SPEC(x) && x->select.s.noun == V_CHAR)
465 #define IS_EXTERN(x)    (IS_SPEC(x) && x->select.s.b_extern)
466 #define IS_VOLATILE(x)  (!x ? 0 : \
467                            IS_SPEC(x) ? \
468                            x->select.s.b_volatile : \
469                            x->select.d.ptr_volatile)
470 #define IS_INTEGRAL(x) (IS_SPEC(x) && (x->select.s.noun == V_INT ||  \
471                                        x->select.s.noun == V_CHAR || \
472                                        x->select.s.noun == V_BITFIELD || \
473                                        x->select.s.noun == V_BIT ||  \
474                                        x->select.s.noun == V_SBIT ))
475 #define IS_BITFIELD(x) (IS_SPEC(x) && (x->select.s.noun == V_BITFIELD))
476 #define IS_BITVAR(x) (IS_SPEC(x) && (x->select.s.noun == V_BITFIELD || \
477                                      x->select.s.noun  == V_BIT ||   \
478                                      x->select.s.noun == V_SBIT ))
479 #define IS_BIT(x) (IS_SPEC(x) && (x->select.s.noun  == V_BIT ||   \
480                                   x->select.s.noun == V_SBIT ))
481 #define IS_FLOAT(x)  (IS_SPEC(x) && x->select.s.noun == V_FLOAT)
482 #define IS_FIXED16X16(x)  (IS_SPEC(x) && x->select.s.noun == V_FIXED16X16)
483 #define IS_FIXED(x) (IS_FIXED16X16(x))
484 #define IS_ARITHMETIC(x) (IS_INTEGRAL(x) || IS_FLOAT(x) || IS_FIXED(x))
485 #define IS_AGGREGATE(x) (IS_ARRAY(x) || IS_STRUCT(x))
486 #define IS_LITERAL(x)   (IS_SPEC(x)  && x->select.s.sclass == S_LITERAL)
487 #define IS_CODE(x)      (IS_SPEC(x)  && SPEC_SCLS(x) == S_CODE)
488 #define IS_REGPARM(x)   (IS_SPEC(x) && SPEC_REGPARM(x))
489
490 /* symbol check macros */
491 #define IS_AUTO(x) (x->level && !IS_STATIC(x->etype) && !IS_EXTERN(x->etype))
492
493 /* forward declaration for the global vars */
494 extern bucket *SymbolTab[];
495 extern bucket *StructTab[];
496 extern bucket *TypedefTab[];
497 extern bucket *LabelTab[];
498 extern bucket *enumTab[];
499 extern symbol *__fsadd;
500 extern symbol *__fssub;
501 extern symbol *__fsmul;
502 extern symbol *__fsdiv;
503 extern symbol *__fseq;
504 extern symbol *__fsneq;
505 extern symbol *__fslt;
506 extern symbol *__fslteq;
507 extern symbol *__fsgt;
508 extern symbol *__fsgteq;
509
510 extern symbol *__fps16x16_add;
511 extern symbol *__fps16x16_sub;
512 extern symbol *__fps16x16_mul;
513 extern symbol *__fps16x16_div;
514 extern symbol *__fps16x16_eq;
515 extern symbol *__fps16x16_neq;
516 extern symbol *__fps16x16_lt;
517 extern symbol *__fps16x16_lteq;
518 extern symbol *__fps16x16_gt;
519 extern symbol *__fps16x16_gteq;
520
521 /* Dims: mul/div/mod, BYTE/WORD/DWORD, SIGNED/UNSIGNED */
522 extern symbol *__muldiv[3][3][2];
523 /* Dims: BYTE/WORD/DWORD SIGNED/UNSIGNED */
524 extern sym_link *__multypes[3][2];
525 /* Dims: to/from float, BYTE/WORD/DWORD, SIGNED/USIGNED */
526 extern symbol *__conv[2][3][2];
527 /* Dims: to/from fixed16x16, BYTE/WORD/DWORD/FLOAT, SIGNED/USIGNED */
528 extern symbol *__fp16x16conv[2][4][2];
529 /* Dims: shift left/shift right, BYTE/WORD/DWORD, SIGNED/UNSIGNED */
530 extern symbol *__rlrr[2][3][2];
531
532 #define CHARTYPE        __multypes[0][0]
533 #define UCHARTYPE       __multypes[0][1]
534 #define INTTYPE         __multypes[1][0]
535 #define UINTTYPE        __multypes[1][1]
536 #define LONGTYPE        __multypes[2][0]
537 #define ULONGTYPE       __multypes[2][1]
538
539 extern sym_link *floatType;
540 extern sym_link *fixed16x16Type;
541
542 #include "SDCCval.h"
543
544 typedef enum
545 {
546   RESULT_TYPE_NONE = 0, /* operands will be promoted to int */
547   RESULT_TYPE_BIT,
548   RESULT_TYPE_CHAR,
549   RESULT_TYPE_INT,
550   RESULT_TYPE_OTHER,    /* operands will be promoted to int */
551   RESULT_TYPE_IFX,
552 } RESULT_TYPE;
553
554 /* forward definitions for the symbol table related functions */
555 void initSymt ();
556 symbol *newSymbol (char *, int);
557 sym_link *newLink (SYM_LINK_CLASS);
558 sym_link *newFloatLink ();
559 structdef *newStruct (char *);
560 void addDecl (symbol *, int, sym_link *);
561 sym_link *mergeSpec (sym_link *, sym_link *, char *name);
562 symbol *reverseSyms (symbol *);
563 sym_link *reverseLink (sym_link *);
564 symbol *copySymbol (symbol *);
565 symbol *copySymbolChain (symbol *);
566 void printSymChain (symbol *, int);
567 void printStruct (structdef *, int);
568 char *genSymName (int);
569 sym_link *getSpec (sym_link *);
570 int compStructSize (int, structdef *);
571 sym_link *copyLinkChain (sym_link *);
572 int checkDecl (symbol *, int);
573 void checkBasic (sym_link *, sym_link *);
574 value *checkPointerIval (sym_link *, value *);
575 value *checkStructIval (symbol *, value *);
576 value *checkArrayIval (sym_link *, value *);
577 value *checkIval (sym_link *, value *);
578 unsigned int getSize (sym_link *);
579 unsigned int bitsForType (sym_link *);
580 sym_link *newIntLink ();
581 sym_link *newCharLink ();
582 sym_link *newLongLink ();
583 sym_link *newBoolLink ();
584 int compareType (sym_link *, sym_link *);
585 int compareTypeExact (sym_link *, sym_link *, int);
586 int checkFunction (symbol *, symbol *);
587 void cleanUpLevel (bucket **, int);
588 void cleanUpBlock (bucket **, int);
589 int funcInChain (sym_link *);
590 void addSymChain (symbol **);
591 sym_link *structElemType (sym_link *, value *);
592 symbol *getStructElement (structdef *, symbol *);
593 sym_link *computeType (sym_link *, sym_link *, RESULT_TYPE, int);
594 void processFuncPtrArgs (sym_link *);
595 void processFuncArgs (symbol *);
596 int isSymbolEqual (symbol *, symbol *);
597 int powof2 (TYPE_UDWORD);
598 void printTypeChain (sym_link *, FILE *);
599 void printTypeChainRaw (sym_link *, FILE *);
600 void initCSupport ();
601 void initBuiltIns ();
602 void pointerTypes (sym_link *, sym_link *);
603 void cdbStructBlock (int);
604 void initHashT ();
605 bucket *newBucket ();
606 void addSym (bucket **, void *, char *, int, int, int checkType);
607 void deleteSym (bucket **, void *, char *);
608 void *findSym (bucket **, void *, const char *);
609 void *findSymWithLevel (bucket **, struct symbol *);
610 void *findSymWithBlock (bucket **, struct symbol *, int);
611 void changePointer (sym_link * p);
612 void checkTypeSanity(sym_link *etype, char *name);
613 sym_link *typeFromStr (char *) ;
614 STORAGE_CLASS sclsFromPtr(sym_link *ptr);
615 sym_link *newEnumType (symbol *);
616 void  promoteAnonStructs (int, structdef *);
617
618
619 extern char *nounName(sym_link *); /* noun strings */
620 extern void printFromToType (sym_link *, sym_link *);
621
622 #endif