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