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