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