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