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