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