* src/SDCC.y (enum_specifier, enumerator_list, opt_assign_expr),
[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_BIT,
45     TYPEOF_BITFIELD,
46     TYPEOF_SBIT,
47     TYPEOF_SFR,
48     TYPEOF_VOID,
49     TYPEOF_STRUCT,
50     TYPEOF_ARRAY,
51     TYPEOF_FUNCTION,
52     TYPEOF_POINTER,
53     TYPEOF_FPOINTER,
54     TYPEOF_CPOINTER,
55     TYPEOF_GPOINTER,
56     TYPEOF_PPOINTER,
57     TYPEOF_IPOINTER,
58     TYPEOF_EEPPOINTER
59 };
60
61 // values for first byte of generic pointer.
62 #define GPTYPE_NEAR     0
63 #define GPTYPE_FAR      1
64 #define GPTYPE_CODE     2
65 #define GPTYPE_XSTACK   3
66 #define GPTYPE_GPTR     4       // Never used?
67 #define GPTYPE_IDATA    5
68
69 #define HASHTAB_SIZE 256
70
71 /* hash table bucket */
72 typedef struct bucket
73   {
74     void *sym;                  /* pointer to the object   */
75     char name[SDCC_NAME_MAX + 1];       /* name of this symbol          */
76     int level;                  /* nest level for this symbol   */
77     int block;                  /* belongs to which block */
78     struct bucket *prev;        /* ptr 2 previous bucket   */
79     struct bucket *next;        /* ptr 2 next bucket       */
80   }
81 bucket;
82
83 typedef struct structdef
84   {
85     char tag[SDCC_NAME_MAX + 1];        /* tag part of structure      */
86     unsigned char level;        /* Nesting level         */
87     struct symbol *fields;      /* pointer to fields     */
88     unsigned size;              /* sizeof the table in bytes  */
89     int type;                   /* STRUCT or UNION */
90   }
91 structdef;
92
93 /* noun definitions */
94 typedef enum
95   {
96     V_INT = 1,
97     V_FLOAT,
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 val */
160         double      v_float;    /*          floating point constant value */
161         struct symbol *v_enum;  /* ptr 2 enum_list if enum==1 */
162       }
163     const_val;
164     struct structdef *v_struct; /* structure pointer      */
165   }
166 specifier;
167
168 /* types of declarators */
169 typedef enum
170   {
171     POINTER = 0,                /* pointer to near data */
172     FPOINTER,                   /* pointer to far data  */
173     CPOINTER,                   /* pointer to code space */
174     GPOINTER,                   /* _generic pointer     */
175     PPOINTER,                   /* paged area pointer   */
176     IPOINTER,                   /* pointer to upper 128 bytes */
177     UPOINTER,                   /* unknown pointer used only when parsing */
178     EEPPOINTER,                 /* pointer to eeprom     */
179     ARRAY,
180     FUNCTION
181   }
182 DECLARATOR_TYPE;
183
184 typedef struct declarator
185   {
186     DECLARATOR_TYPE dcl_type;   /* POINTER,ARRAY or FUNCTION  */
187     unsigned int num_elem;      /* # of elems if type==array  */
188     unsigned ptr_const:1;       /* pointer is constant        */
189     unsigned ptr_volatile:1;    /* pointer is volatile        */
190     struct sym_link *tspec;     /* pointer type specifier     */
191   }
192 declarator;
193
194 typedef enum {
195   DECLARATOR=1,
196   SPECIFIER
197 } SYM_LINK_CLASS;
198 #define DECLSPEC2TXT(select) (select==DECLARATOR?"DECLARATOR":select==SPECIFIER?"SPECIFIER":"UNKNOW")
199
200 typedef struct sym_link
201   {
202     SYM_LINK_CLASS class;       /* DECLARATOR or SPECIFIER    */
203     unsigned tdef:1;            /* current link created by    */
204     /* typedef if this flag is set */
205     union
206       {
207         specifier s;            /* if CLASS == SPECIFIER      */
208         declarator d;           /* if CLASS == DECLARATOR     */
209       } select;
210
211     /* function attributes */
212     struct {
213       struct value *args;       /* the defined arguments      */
214       unsigned hasVargs:1;      /* functions has varargs      */
215       unsigned calleeSaves:1;   /* functions uses callee save */
216       unsigned hasbody:1;       /* function body defined      */
217       unsigned hasFcall:1;      /* does it call other functions */
218       unsigned reent:1;         /* function is reentrant      */
219       unsigned naked:1;         /* naked function             */
220
221       unsigned nonbanked:1;     /* function has the nonbanked attribute */
222       unsigned banked:1;        /* function has the banked attribute */
223       unsigned critical:1;      /* critical function          */
224       unsigned intrtn:1;        /* this is an interrupt routin */
225       unsigned rbank:1;         /* seperate register bank     */
226       unsigned intno;           /* 1=Interrupt svc routine    */
227       unsigned regbank;         /* register bank 2b used      */
228       unsigned builtin;         /* is a builtin function      */
229       unsigned javaNative;      /* is a JavaNative Function (TININative ONLY) */
230       unsigned overlay;         /* force parameters & locals into overlay segment */
231       unsigned hasStackParms;   /* function has parameters on stack */
232     } funcAttrs;
233
234     struct sym_link *next;      /* next element on the chain  */
235   }
236 sym_link;
237
238 typedef struct symbol
239   {
240     char name[SDCC_SYMNAME_MAX + 1];    /* Input Variable Name     */
241     char rname[SDCC_NAME_MAX + 1];      /* internal name           */
242
243     short level;                /* declration lev,fld offset */
244     short block;                /* sequential block # of defintion */
245     int key;
246     unsigned implicit:1;        /* implicit flag                     */
247     unsigned undefined:1;       /* undefined variable                */
248     unsigned _isparm:1;         /* is a parameter          */
249     unsigned ismyparm:1;        /* is parameter of the function being generated */
250     unsigned isitmp:1;          /* is an intermediate temp */
251     unsigned islbl:1;           /* is a temporary label */
252     unsigned isref:1;           /* has been referenced  */
253     unsigned isind:1;           /* is a induction variable */
254     unsigned isinvariant:1;     /* is a loop invariant  */
255     unsigned cdef:1;            /* compiler defined symbol */
256     unsigned addrtaken:1;       /* address of the symbol was taken */
257     unsigned isreqv:1;          /* is the register quivalent of a symbol */
258     unsigned udChked:1;         /* use def checking has been already done */
259
260     /* following flags are used by the backend
261        for code generation and can be changed
262        if a better scheme for backend is thought of */
263     unsigned isLiveFcall:1;     /* is live at or across a function call */
264     unsigned isspilt:1;         /* has to be spilt */
265     unsigned spillA:1;          /* spilt be register allocator */
266     unsigned remat:1;           /* can be remateriazed */
267     unsigned isptr:1;           /* is a pointer */
268     unsigned uptr:1;            /* used as a pointer */
269     unsigned isFree:1;          /* used by register allocator */
270     unsigned islocal:1;         /* is a local variable        */
271     unsigned blockSpil:1;       /* spilt at block level       */
272     unsigned remainSpil:1;      /* spilt because not used in remainder */
273     unsigned stackSpil:1;       /* has been spilt on temp stack location */
274     unsigned onStack:1;         /* this symbol allocated on the stack */
275     unsigned iaccess:1;         /* indirect access      */
276     unsigned ruonly:1;          /* used in return statement only */
277     unsigned spildir:1;         /* spilt in direct space */
278     unsigned ptrreg:1;          /* this symbol assigned to a ptr reg */
279     unsigned noSpilLoc:1;       /* cannot be assigned a spil location */
280     unsigned isstrlit;          /* is a string literal and it's usage count  */
281     unsigned accuse;            /* can be left in the accumulator
282                                    On the Z80 accuse is devided into
283                                    ACCUSE_A and ACCUSE_HL as the idea
284                                    is quite similar.
285                                  */
286     unsigned dptr;              /* 8051 variants with multiple DPTRS
287                                    currently implemented in DS390 only
288                                 */
289     int allocreq ;              /* allocation is required for this variable */
290     int stack;                  /* offset on stack      */
291     int xstack;                 /* offset on xternal stack */
292     short nRegs;                /* number of registers required */
293     short regType;              /* type of register required    */
294
295     struct regs *regs[4];       /* can have at the most 4 registers */
296     struct asmop *aop;          /* asmoperand for this symbol */
297     struct iCode *fuse;         /* furthest use */
298     struct iCode *rematiCode;   /* rematerialse with which instruction */
299     struct operand *reqv;       /* register equivalent of a local variable */
300     union
301       {
302         struct symbol *spillLoc;        /* register spil location */
303         struct set *itmpStack;  /* symbols spilt @ this stack location */
304       }
305     usl;
306     short bitVar;               /* this is a bit variable    */
307     unsigned offset;            /* offset from top if struct */
308
309     int lineDef;                /* defined line number        */
310     int lastLine;               /* for functions the last line */
311     struct sym_link *type;      /* 1st link to declator chain */
312     struct sym_link *etype;     /* last link to declarator chn */
313     struct symbol *next;        /* crosslink to next symbol   */
314     struct symbol *localof;     /* local variable of which function */
315     struct initList *ival;      /* ptr to initializer if any  */
316     struct bitVect *defs;       /* bit vector for definitions */
317     struct bitVect *uses;       /* bit vector for uses        */
318     struct bitVect *regsUsed;   /* for functions registers used */
319     int liveFrom;               /* live from iCode sequence number */
320     int liveTo;                 /* live to sequence number */
321     int used;                   /* no. of times this was used */
322     int recvSize;               /* size of first argument  */
323     struct bitVect *clashes;    /* overlaps with what other symbols */
324   }
325 symbol;
326
327 extern sym_link *validateLink(sym_link  *l, 
328                                const char       *macro,
329                                const char       *args,
330                                const char       select,
331                                const char       *file, 
332                                unsigned         line);
333 /* Easy Access Macros */
334 #define DCL_TYPE(l)  validateLink(l, "DCL_TYPE", #l, DECLARATOR, __FILE__, __LINE__)->select.d.dcl_type
335 #define DCL_ELEM(l)  validateLink(l, "DCL_ELEM", #l, DECLARATOR, __FILE__, __LINE__)->select.d.num_elem
336 #define DCL_PTR_CONST(l) validateLink(l, "DCL_PTR_CONST", #l, DECLARATOR, __FILE__, __LINE__)->select.d.ptr_const
337 #define DCL_PTR_VOLATILE(l) validateLink(l, "DCL_PTR_VOLATILE", #l, DECLARATOR, __FILE__, __LINE__)->select.d.ptr_volatile
338 #define DCL_TSPEC(l) validateLink(l, "DCL_TSPEC", #l, DECLARATOR, __FILE__, __LINE__)->select.d.tspec
339
340 #define FUNC_DEBUG //assert(IS_FUNC(x));
341 #define FUNC_HASVARARGS(x) (x->funcAttrs.hasVargs)
342 #define IFFUNC_HASVARARGS(x) (IS_FUNC(x) && FUNC_HASVARARGS(x))
343 #define FUNC_ARGS(x) (x->funcAttrs.args)
344 #define IFFUNC_ARGS(x) (IS_FUNC(x) && FUNC_ARGS(x))
345 #define FUNC_HASFCALL(x) (x->funcAttrs.hasFcall)
346 #define IFFUNC_HASFCALL(x) (IS_FUNC(x) && FUNC_HASFCALL(x))
347 #define FUNC_HASBODY(x) (x->funcAttrs.hasbody)
348 #define IFFUNC_HASBODY(x) (IS_FUNC(x) && FUNC_HASBODY(x))
349 #define FUNC_CALLEESAVES(x) (x->funcAttrs.calleeSaves)
350 #define IFFUNC_CALLEESAVES(x) (IS_FUNC(x) && FUNC_CALLEESAVES(x))
351 #define FUNC_ISISR(x) (x->funcAttrs.intrtn)
352 #define IFFUNC_ISISR(x) (IS_FUNC(x) && FUNC_ISISR(x))
353 #define IFFUNC_RBANK(x) (IS_FUNC(x) && FUNC_RBANK(x))
354 #define FUNC_INTNO(x) (x->funcAttrs.intno)
355 #define FUNC_REGBANK(x) (x->funcAttrs.regbank)
356 #define FUNC_HASSTACKPARM(x) (x->funcAttrs.hasStackParms)
357
358 #define FUNC_ISREENT(x) (x->funcAttrs.reent)
359 #define IFFUNC_ISREENT(x) (IS_FUNC(x) && FUNC_ISREENT(x))
360 #define FUNC_ISNAKED(x) (x->funcAttrs.naked)
361 #define IFFUNC_ISNAKED(x) (IS_FUNC(x) && FUNC_ISNAKED(x))
362 #define FUNC_NONBANKED(x) (x->funcAttrs.nonbanked)
363 #define IFFUNC_NONBANKED(x) (IS_FUNC(x) && FUNC_NONBANKED(x))
364 #define FUNC_BANKED(x) (x->funcAttrs.banked)
365 #define IFFUNC_BANKED(x) (IS_FUNC(x) && FUNC_BANKED(x))
366 #define FUNC_ISCRITICAL(x) (x->funcAttrs.critical)
367 #define IFFUNC_ISCRITICAL(x) (IS_FUNC(x) && FUNC_ISCRITICAL(x))
368 #define FUNC_ISBUILTIN(x) (x->funcAttrs.builtin)
369 #define IFFUNC_ISBUILTIN(x) (IS_FUNC(x) && FUNC_ISBUILTIN(x))
370 #define FUNC_ISJAVANATIVE(x) (x->funcAttrs.javaNative)
371 #define IFFUNC_ISJAVANATIVE(x) (IS_FUNC(x) && FUNC_ISJAVANATIVE(x))
372 #define FUNC_ISOVERLAY(x) (x->funcAttrs.overlay)
373 #define IFFUNC_ISOVERLAY(x) (IS_FUNC(x) && FUNC_ISOVERLAY(x))
374
375 #define IFFUNC_ISBANKEDCALL(x) (!IFFUNC_NONBANKED(x) && \
376   (options.model == MODEL_LARGE || \
377    options.model == MODEL_MEDIUM || \
378   IFFUNC_BANKED(x)))
379
380 #define SPEC_NOUN(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s.noun
381 #define SPEC_LONG(x) validateLink(x, "SPEC_LONG", #x, SPECIFIER, __FILE__, __LINE__)->select.s._long
382 #define SPEC_SHORT(x) validateLink(x, "SPEC_LONG", #x, SPECIFIER, __FILE__, __LINE__)->select.s._short
383 #define SPEC_USIGN(x) validateLink(x, "SPEC_USIGN", #x, SPECIFIER, __FILE__, __LINE__)->select.s._unsigned
384 #define SPEC_SCLS(x) validateLink(x, "SPEC_SCLS", #x, SPECIFIER, __FILE__, __LINE__)->select.s.sclass
385 #define SPEC_ENUM(x) validateLink(x, "SPEC_ENUM", #x, SPECIFIER, __FILE__, __LINE__)->select.s._isenum
386 #define SPEC_OCLS(x) validateLink(x, "SPEC_OCLS", #x, SPECIFIER, __FILE__, __LINE__)->select.s.oclass
387 #define SPEC_STAT(x) validateLink(x, "SPEC_STAT", #x, SPECIFIER, __FILE__, __LINE__)->select.s._static
388 #define SPEC_EXTR(x) validateLink(x, "SPEC_EXTR", #x, SPECIFIER, __FILE__, __LINE__)->select.s._extern
389 #define SPEC_CODE(x) validateLink(x, "SPEC_CODE", #x, SPECIFIER, __FILE__, __LINE__)->select.s._codesg
390 #define SPEC_ABSA(x) validateLink(x, "SPEC_ABSA", #x, SPECIFIER, __FILE__, __LINE__)->select.s._absadr
391 #define SPEC_BANK(x) validateLink(x, "SPEC_BANK", #x, SPECIFIER, __FILE__, __LINE__)->select.s._regbank
392 #define SPEC_ADDR(x) validateLink(x, "SPEC_ADDR", #x, SPECIFIER, __FILE__, __LINE__)->select.s._addr
393 #define SPEC_STAK(x) validateLink(x, "SPEC_STAK", #x, SPECIFIER, __FILE__, __LINE__)->select.s._stack
394 #define SPEC_CVAL(x) validateLink(x, "SPEC_CVAL", #x, SPECIFIER, __FILE__, __LINE__)->select.s.const_val
395 #define SPEC_BSTR(x) validateLink(x, "SPEC_BSTR", #x, SPECIFIER, __FILE__, __LINE__)->select.s._bitStart
396 #define SPEC_BLEN(x) validateLink(x, "SPEC_BLEN", #x, SPECIFIER, __FILE__, __LINE__)->select.s._bitLength
397
398 /* Sleaze: SPEC_ISR_SAVED_BANKS is only used on 
399  * function type symbols, which obviously cannot
400  * be of BIT type. Therefore, we recycle the 
401  * _bitStart field instead of defining a new field.
402  */
403 #define SPEC_ISR_SAVED_BANKS(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s._bitStart
404 #define SPEC_VOLATILE(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s._volatile
405 #define SPEC_CONST(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s._const
406 #define SPEC_STRUCT(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s.v_struct
407 #define SPEC_TYPEDEF(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s._typedef
408 #define SPEC_REGPARM(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s._isregparm
409 #define SPEC_ARGREG(x) validateLink(x, "SPEC_NOUN", #x, SPECIFIER, __FILE__, __LINE__)->select.s.argreg
410
411 /* type check macros */
412 #define IS_DECL(x)   ( x && x->class == DECLARATOR      )
413 #define IS_SPEC(x)   ( x && x->class == SPECIFIER  )
414 #define IS_ARRAY(x)  (IS_DECL(x) && DCL_TYPE(x) == ARRAY)
415 #define IS_DATA_PTR(x) (IS_DECL(x) && DCL_TYPE(x) == POINTER)
416 #define IS_PTR(x)    (IS_DECL(x) && (DCL_TYPE(x) == POINTER    ||    \
417                                      DCL_TYPE(x) == FPOINTER   ||    \
418                                      DCL_TYPE(x) == GPOINTER   ||    \
419                                      DCL_TYPE(x) == IPOINTER   ||    \
420                                      DCL_TYPE(x) == PPOINTER   ||    \
421                                      DCL_TYPE(x) == EEPPOINTER ||    \
422                                      DCL_TYPE(x) == CPOINTER   ||    \
423                                      DCL_TYPE(x) == UPOINTER  ))
424 #define IS_PTR_CONST(x) (IS_PTR(x) && DCL_PTR_CONST(x))
425 #define IS_FARPTR(x) (IS_DECL(x) && DCL_TYPE(x) == FPOINTER)
426 #define IS_CODEPTR(x) (IS_DECL(x) && DCL_TYPE(x) == CPOINTER)
427 #define IS_GENPTR(x) (IS_DECL(x) && DCL_TYPE(x) == GPOINTER)
428 #define IS_FUNC(x)   (IS_DECL(x) && DCL_TYPE(x) == FUNCTION)
429 #define IS_LONG(x)   (IS_SPEC(x) && x->select.s._long)
430 #define IS_UNSIGNED(x) (IS_SPEC(x) && x->select.s._unsigned)
431 #define IS_TYPEDEF(x)(IS_SPEC(x) && x->select.s._typedef)
432 #define IS_CONSTANT(x)  (!x ? 0 : \
433                            IS_SPEC(x) ? \
434                            x->select.s._const : \
435                            x->select.d.ptr_const)
436 #define IS_STRUCT(x) (IS_SPEC(x) && x->select.s.noun == V_STRUCT)
437 #define IS_ABSOLUTE(x)  (IS_SPEC(x) && x->select.s._absadr )
438 #define IS_REGISTER(x)  (IS_SPEC(x) && SPEC_SCLS(x) == S_REGISTER)
439 #define IS_RENT(x)   (IS_SPEC(x) && x->select.s._reent )
440 #define IS_STATIC(x) (IS_SPEC(x) && SPEC_STAT(x))
441 #define IS_INT(x)    (IS_SPEC(x) && x->select.s.noun == V_INT)
442 #define IS_VOID(x)   (IS_SPEC(x) && x->select.s.noun == V_VOID)
443 #define IS_CHAR(x)   (IS_SPEC(x) && x->select.s.noun == V_CHAR)
444 #define IS_EXTERN(x)    (IS_SPEC(x) && x->select.s._extern)
445 #define IS_VOLATILE(x)  (!x ? 0 : \
446                            IS_SPEC(x) ? \
447                            x->select.s._volatile : \
448                            x->select.d.ptr_volatile)
449 #define IS_INTEGRAL(x) (IS_SPEC(x) && (x->select.s.noun == V_INT ||  \
450                                        x->select.s.noun == V_CHAR || \
451                                        x->select.s.noun == V_BITFIELD || \
452                                        x->select.s.noun == V_BIT ||  \
453                                        x->select.s.noun == V_SBIT ))
454 #define IS_BITFIELD(x) (IS_SPEC(x) && (x->select.s.noun == V_BITFIELD))
455 #define IS_BITVAR(x) (IS_SPEC(x) && (x->select.s.noun == V_BITFIELD || \
456                                      x->select.s.noun  == V_BIT ||   \
457                                      x->select.s.noun == V_SBIT ))
458 #define IS_FLOAT(x)  (IS_SPEC(x) && x->select.s.noun == V_FLOAT)
459 #define IS_ARITHMETIC(x) (IS_INTEGRAL(x) || IS_FLOAT(x))
460 #define IS_AGGREGATE(x) (IS_ARRAY(x) || IS_STRUCT(x))
461 #define IS_LITERAL(x)   (IS_SPEC(x)  && x->select.s.sclass == S_LITERAL)
462 #define IS_CODE(x)      (IS_SPEC(x)  && SPEC_SCLS(x) == S_CODE)
463 #define IS_REGPARM(x)   (IS_SPEC(x) && SPEC_REGPARM(x))
464
465 /* forward declaration for the global vars */
466 extern bucket *SymbolTab[];
467 extern bucket *StructTab[];
468 extern bucket *TypedefTab[];
469 extern bucket *LabelTab[];
470 extern bucket *enumTab[];
471 extern symbol *__fsadd;
472 extern symbol *__fssub;
473 extern symbol *__fsmul;
474 extern symbol *__fsdiv;
475 extern symbol *__fseq;
476 extern symbol *__fsneq;
477 extern symbol *__fslt;
478 extern symbol *__fslteq;
479 extern symbol *__fsgt;
480 extern symbol *__fsgteq;
481
482 /* Dims: mul/div/mod, BYTE/WORD/DWORD, SIGNED/UNSIGNED */
483 extern symbol *__muldiv[3][3][2];
484 /* Dims: BYTE/WORD/DWORD SIGNED/UNSIGNED */
485 extern sym_link *__multypes[3][2];
486 /* Dims: to/from float, BYTE/WORD/DWORD, SIGNED/USIGNED */
487 extern symbol *__conv[2][3][2];
488 /* Dims: shift left/shift right, BYTE/WORD/DWORD, SIGNED/UNSIGNED */
489 extern symbol *__rlrr[2][3][2];
490
491 #define CHARTYPE        __multypes[0][0]
492 #define UCHARTYPE       __multypes[0][1]
493 #define INTTYPE         __multypes[1][0]
494 #define UINTTYPE        __multypes[1][1]
495 #define LONGTYPE        __multypes[2][0]
496 #define ULONGTYPE       __multypes[2][1]
497
498
499 extern sym_link *floatType;
500
501 #include "SDCCval.h"
502
503 /* forward definitions for the symbol table related functions */
504 void initSymt ();
505 symbol *newSymbol (char *, int);
506 sym_link *newLink (SYM_LINK_CLASS);
507 sym_link *newFloatLink ();
508 structdef *newStruct (char *);
509 void addDecl (symbol *, int, sym_link *);
510 sym_link *mergeSpec (sym_link *, sym_link *, char *name);
511 symbol *reverseSyms (symbol *);
512 sym_link *reverseLink (sym_link *);
513 symbol *copySymbol (symbol *);
514 symbol *copySymbolChain (symbol *);
515 void printSymChain (symbol *, int);
516 void printStruct (structdef *, int);
517 char *genSymName (int);
518 sym_link *getSpec (sym_link *);
519 char *genSymName (int);
520 int compStructSize (int, structdef *);
521 sym_link *copyLinkChain (sym_link *);
522 int checkDecl (symbol *, int);
523 void checkBasic (sym_link *, sym_link *);
524 value *checkPointerIval (sym_link *, value *);
525 value *checkStructIval (symbol *, value *);
526 value *checkArrayIval (sym_link *, value *);
527 value *checkIval (sym_link *, value *);
528 unsigned int getSize (sym_link *);
529 unsigned int bitsForType (sym_link *);
530 sym_link *newIntLink ();
531 sym_link *newCharLink ();
532 sym_link *newLongLink ();
533 int compareType (sym_link *, sym_link *);
534 int compareTypeExact (sym_link *, sym_link *, int);
535 int checkFunction (symbol *, symbol *);
536 void cleanUpLevel (bucket **, int);
537 void cleanUpBlock (bucket **, int);
538 int funcInChain (sym_link *);
539 void addSymChain (symbol *);
540 sym_link *structElemType (sym_link *, value *);
541 symbol *getStructElement (structdef *, symbol *);
542 sym_link *computeType (sym_link *, sym_link *, bool promoteCharToInt);
543 void processFuncArgs (symbol *);
544 int isSymbolEqual (symbol *, symbol *);
545 int powof2 (TYPE_UDWORD);
546 void printTypeChain (sym_link *, FILE *);
547 void printTypeChainRaw (sym_link *, FILE *);
548 void initCSupport ();
549 void initBuiltIns ();
550 void pointerTypes (sym_link *, sym_link *);
551 void cdbStructBlock (int);
552 void initHashT ();
553 bucket *newBucket ();
554 void addSym (bucket **, void *, char *, int, int, int checkType);
555 void deleteSym (bucket **, void *, char *);
556 void *findSym (bucket **, void *, const char *);
557 void *findSymWithLevel (bucket **, struct symbol *);
558 void *findSymWithBlock (bucket **, struct symbol *, int);
559 void changePointer (symbol * sym);
560 void checkTypeSanity(sym_link *etype, char *name);
561 sym_link *typeFromStr (char *) ;
562 STORAGE_CLASS sclsFromPtr(sym_link *ptr);
563 sym_link *newEnumType (symbol *);
564
565
566 extern char *nounName(sym_link *); /* noun strings */
567 extern void printFromToType (sym_link *, sym_link *);
568
569 #endif