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