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