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