1/*	Id: pass1.h,v 1.237 2012/03/22 18:51:40 plunky Exp 	*/
2/*	$NetBSD: pass1.h,v 1.1.1.4.4.2 2012/04/03 16:36:21 riz Exp $	*/
3/*
4 * Copyright(C) Caldera International Inc. 2001-2002. All rights reserved.
5 *
6 * Redistribution and use in source and binary forms, with or without
7 * modification, are permitted provided that the following conditions
8 * are met:
9 *
10 * Redistributions of source code and documentation must retain the above
11 * copyright notice, this list of conditions and the following disclaimer.
12 * Redistributions in binary form must reproduce the above copyright
13 * notice, this list of conditionsand the following disclaimer in the
14 * documentation and/or other materials provided with the distribution.
15 * All advertising materials mentioning features or use of this software
16 * must display the following acknowledgement:
17 * 	This product includes software developed or owned by Caldera
18 *	International, Inc.
19 * Neither the name of Caldera International, Inc. nor the names of other
20 * contributors may be used to endorse or promote products derived from
21 * this software without specific prior written permission.
22 *
23 * USE OF THE SOFTWARE PROVIDED FOR UNDER THIS LICENSE BY CALDERA
24 * INTERNATIONAL, INC. AND CONTRIBUTORS ``AS IS'' AND ANY EXPRESS OR
25 * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
26 * WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
27 * DISCLAIMED.  IN NO EVENT SHALL CALDERA INTERNATIONAL, INC. BE LIABLE
28 * FOR ANY DIRECT, INDIRECT INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
29 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
30 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
31 * HOWEVER CAUSED AND ON ANY THEORY OFLIABILITY, WHETHER IN CONTRACT,
32 * STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING
33 * IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
34 * POSSIBILITY OF SUCH DAMAGE.
35 */
36
37#include "config.h"
38
39#include <sys/types.h>
40#include <stdarg.h>
41#include <string.h>
42#ifdef HAVE_STDINT_H
43#include <stdint.h>
44#endif
45
46#ifndef MKEXT
47#include "external.h"
48#else
49typedef unsigned int bittype; /* XXX - for basicblock */
50#endif
51#include "manifest.h"
52
53/*
54 * Storage classes
55 */
56#define SNULL		0
57#define AUTO		1
58#define EXTERN		2
59#define STATIC		3
60#define REGISTER	4
61#define EXTDEF		5
62/* #define LABEL	6*/
63/* #define ULABEL	7*/
64#define MOS		8
65#define PARAM		9
66#define STNAME		10
67#define MOU		11
68#define UNAME		12
69#define TYPEDEF		13
70/* #define FORTRAN		14 */
71#define ENAME		15
72#define MOE		16
73/* #define UFORTRAN 	17 */
74#define USTATIC		18
75
76	/* field size is ORed in */
77#define FIELD		0200
78#define FLDSIZ		0177
79extern	char *scnames(int);
80
81/*
82 * Symbol table flags
83 */
84#define	SNORMAL		0
85#define	STAGNAME	01
86#define	SLBLNAME	02
87#define	SMOSNAME	03
88#define	SSTRING		04
89#define	NSTYPES		05
90#define	SMASK		07
91
92#define	STLS		00010	/* Thread Local Support variable */
93/* #define SREF		00020 */
94#define SNOCREAT	00040	/* don't create a symbol in lookup() */
95#define STEMP		00100	/* Allocate symtab from temp or perm mem */
96#define	SDYNARRAY	00200	/* symbol is dynamic array on stack */
97#define	SINLINE		00400	/* function is of type inline */
98#define	STNODE		01000	/* symbol shall be a temporary node */
99#define	SASG		04000	/* symbol is assigned to already */
100#define	SLOCAL1		010000
101#define	SLOCAL2		020000
102#define	SLOCAL3		040000
103
104	/* alignment of initialized quantities */
105#ifndef AL_INIT
106#define	AL_INIT ALINT
107#endif
108
109struct rstack;
110struct symtab;
111union arglist;
112#ifdef GCC_COMPAT
113struct gcc_attr_pack;
114#endif
115
116/*
117 * Dimension/prototype information.
118 * 	ddim > 0 holds the dimension of an array.
119 *	ddim < 0 is a dynamic array and refers to a tempnode.
120 *	...unless:
121 *		ddim == NOOFFSET, an array without dimenston, "[]"
122 *		ddim == -1, dynamic array while building before defid.
123 */
124union dimfun {
125	int	ddim;		/* Dimension of an array */
126	union arglist *dfun;	/* Prototype index */
127};
128
129/*
130 * Argument list member info when storing prototypes.
131 */
132union arglist {
133	TWORD type;
134	union dimfun *df;
135	struct attr *sap;
136};
137#define TNULL		INCREF(FARG) /* pointer to FARG -- impossible type */
138#define TELLIPSIS 	INCREF(INCREF(FARG))
139
140/*
141 * Symbol table definition.
142 */
143struct	symtab {
144	struct	symtab *snext;	/* link to other symbols in the same scope */
145	int	soffset;	/* offset or value */
146	char	sclass;		/* storage class */
147	char	slevel;		/* scope level */
148	short	sflags;		/* flags, see below */
149	char	*sname;		/* Symbol name */
150	char	*soname;	/* Written-out name */
151	TWORD	stype;		/* type word */
152	TWORD	squal;		/* qualifier word */
153	union	dimfun *sdf;	/* ptr to the dimension/prototype array */
154	struct	attr *sap;	/* the base type attribute list */
155};
156
157#define	ISSOU(ty)   ((ty) == STRTY || (ty) == UNIONTY)
158
159/*
160 * External definitions
161 */
162struct swents {			/* switch table */
163	struct swents *next;	/* Next struct in linked list */
164	CONSZ	sval;		/* case value */
165	int	slab;		/* associated label */
166};
167int mygenswitch(int, TWORD, struct swents **, int);
168
169extern	int blevel;
170extern	int instruct, got_type;
171extern	int oldstyle;
172
173extern	int lineno, nerrors;
174
175extern	char *ftitle;
176extern	struct symtab *cftnsp;
177extern	int autooff, maxautooff, argoff, strucoff;
178extern	int brkflag;
179
180extern	OFFSZ inoff;
181
182extern	int reached;
183extern	int isinlining;
184extern	int xinline, xgnu89, xgnu99;
185extern	int bdebug, ddebug, edebug, idebug, ndebug;
186extern	int odebug, pdebug, sdebug, tdebug, xdebug;
187
188/* various labels */
189extern	int brklab;
190extern	int contlab;
191extern	int flostat;
192extern	int retlab;
193extern	int doing_init, statinit;
194extern	short sztable[];
195extern	char *astypnames[];
196
197/* pragma globals */
198extern int pragma_allpacked, pragma_packed, pragma_aligned;
199extern char *pragma_renamed;
200
201/*
202 * Flags used in the (elementary) flow analysis ...
203 */
204#define FBRK		02
205#define FCONT		04
206#define FDEF		010
207#define FLOOP		020
208
209/*
210 * Location counters
211 */
212#define NOSEG		-1
213#define PROG		0		/* (ro) program segment */
214#define DATA		1		/* (rw) data segment */
215#define RDATA		2		/* (ro) data segment */
216#define LDATA		3		/* (rw) local data */
217#define UDATA		4		/* (rw) uninitialized data */
218#define STRNG		5		/* (ro) string segment */
219#define PICDATA		6		/* (rw) relocatable data segment */
220#define PICRDATA	7		/* (ro) relocatable data segment */
221#define PICLDATA	8		/* (rw) local relocatable data */
222#define TLSDATA		9		/* (rw) TLS data segment */
223#define TLSUDATA	10		/* (rw) TLS uninitialized segment */
224#define CTORS		11		/* constructor */
225#define DTORS		12		/* destructor */
226#define	NMSEG		13		/* other (named) segment */
227
228extern int lastloc, nextloc;
229void locctr(int type, struct symtab *sp);
230void setseg(int type, char *name);
231void defalign(int al);
232void symdirec(struct symtab *sp);
233
234/*	mark an offset which is undefined */
235
236#define NOOFFSET	(-10201)
237
238/* declarations of various functions */
239extern	NODE
240	*buildtree(int, NODE *, NODE *r),
241	*mkty(unsigned, union dimfun *, struct attr *),
242	*rstruct(char *, int),
243	*dclstruct(struct rstack *),
244	*strend(int gtype, char *),
245	*tymerge(NODE *, NODE *),
246	*stref(NODE *),
247#ifdef WORD_ADDRESSED
248	*offcon(OFFSZ, TWORD, union dimfun *, struct attr *),
249#endif
250	*bcon(int),
251	*xbcon(CONSZ, struct symtab *, TWORD),
252	*bpsize(NODE *),
253	*convert(NODE *, int),
254	*pconvert(NODE *),
255	*oconvert(NODE *),
256	*ptmatch(NODE *),
257	*makety(NODE *, TWORD, TWORD, union dimfun *, struct attr *),
258	*block(int, NODE *, NODE *, TWORD, union dimfun *, struct attr *),
259	*doszof(NODE *),
260	*talloc(void),
261	*optim(NODE *),
262	*clocal(NODE *),
263	*ccopy(NODE *),
264	*tempnode(int, TWORD, union dimfun *, struct attr *),
265	*eve(NODE *),
266	*doacall(struct symtab *, NODE *, NODE *);
267NODE	*intprom(NODE *);
268OFFSZ	tsize(TWORD, union dimfun *, struct attr *),
269	psize(NODE *);
270NODE *	typenode(NODE *new);
271void	spalloc(NODE *, NODE *, OFFSZ);
272char	*exname(char *);
273NODE	*floatcon(char *);
274NODE	*fhexcon(char *);
275NODE	*bdty(int op, ...);
276extern struct rstack *rpole;
277
278int oalloc(struct symtab *, int *);
279void deflabel(char *, NODE *);
280void gotolabel(char *);
281unsigned int esccon(char **);
282void inline_start(struct symtab *);
283void inline_end(void);
284void inline_addarg(struct interpass *);
285void inline_ref(struct symtab *);
286void inline_prtout(void);
287void inline_args(struct symtab **, int);
288NODE *inlinetree(struct symtab *, NODE *, NODE *);
289void ftnarg(NODE *);
290struct rstack *bstruct(char *, int, NODE *);
291void moedef(char *);
292void beginit(struct symtab *);
293void simpleinit(struct symtab *, NODE *);
294struct symtab *lookup(char *, int);
295struct symtab *getsymtab(char *, int);
296char *addstring(char *);
297char *addname(char *);
298void symclear(int);
299struct symtab *hide(struct symtab *);
300void soumemb(NODE *, char *, int);
301int talign(unsigned int, struct attr *);
302void bfcode(struct symtab **, int);
303int chkftn(union arglist *, union arglist *);
304void branch(int);
305void cbranch(NODE *, NODE *);
306void extdec(struct symtab *);
307void defzero(struct symtab *);
308int falloc(struct symtab *, int, NODE *);
309TWORD ctype(TWORD);
310void inval(CONSZ, int, NODE *);
311int ninval(CONSZ, int, NODE *);
312void infld(CONSZ, int, CONSZ);
313void zbits(CONSZ, int);
314void instring(struct symtab *);
315void inwstring(struct symtab *);
316void plabel(int);
317void bjobcode(void);
318void ejobcode(int);
319void calldec(NODE *, NODE *);
320int cisreg(TWORD);
321char *tmpsprintf(char *, ...);
322char *tmpvsprintf(char *, va_list);
323void asginit(NODE *);
324void desinit(NODE *);
325void endinit(int);
326void endictx(void);
327void sspinit(void);
328void sspstart(void);
329void sspend(void);
330void ilbrace(void);
331void irbrace(void);
332CONSZ scalinit(NODE *);
333void p1print(char *, ...);
334char *copst(int);
335int cdope(int);
336void myp2tree(NODE *);
337void lcommprint(void);
338void lcommdel(struct symtab *);
339NODE *funcode(NODE *);
340struct symtab *enumhd(char *);
341NODE *enumdcl(struct symtab *);
342NODE *enumref(char *);
343CONSZ icons(NODE *);
344CONSZ valcast(CONSZ v, TWORD t);
345int mypragma(char *);
346char *pragtok(char *);
347int eat(int);
348void fixdef(struct symtab *);
349int cqual(TWORD, TWORD);
350void defloc(struct symtab *);
351int fldchk(int);
352int nncon(NODE *);
353void cunput(char);
354NODE *nametree(struct symtab *sp);
355void *inlalloc(int size);
356void *blkalloc(int size);
357void pass1_lastchance(struct interpass *);
358void fldty(struct symtab *p);
359int getlab(void);
360struct suedef *sueget(struct suedef *p);
361void complinit(void);
362NODE *structref(NODE *p, int f, char *name);
363NODE *cxop(int op, NODE *l, NODE *r);
364NODE *imop(int op, NODE *l, NODE *r);
365NODE *cxelem(int op, NODE *p);
366NODE *cxconj(NODE *p);
367NODE *cxret(NODE *p, NODE *q);
368NODE *cast(NODE *p, TWORD t, TWORD q);
369NODE *ccast(NODE *p, TWORD t, TWORD u, union dimfun *df, struct attr *sue);
370int andable(NODE *);
371int conval(NODE *, int, NODE *);
372int ispow2(CONSZ);
373void defid(NODE *q, int class);
374void efcode(void);
375void ecomp(NODE *p);
376int upoff(int size, int alignment, int *poff);
377void nidcl(NODE *p, int class);
378void eprint(NODE *, int, int *, int *);
379int uclass(int class);
380int notlval(NODE *);
381void ecode(NODE *p);
382void ftnend(void);
383void dclargs(void);
384int suemeq(struct attr *s1, struct attr *s2);
385struct symtab *strmemb(struct attr *ap);
386int yylex(void);
387void yyerror(char *);
388int pragmas_gcc(char *t);
389NODE *cstknode(TWORD t, union dimfun *df, struct attr *ap);
390int concast(NODE *p, TWORD t);
391NODE *builtin_check(NODE *f, NODE *a);
392NODE *rmpconv(NODE *);
393NODE *nlabel(int label);
394
395
396#ifdef SOFTFLOAT
397typedef struct softfloat SF;
398SF soft_neg(SF);
399SF soft_cast(CONSZ v, TWORD);
400SF soft_plus(SF, SF);
401SF soft_minus(SF, SF);
402SF soft_mul(SF, SF);
403SF soft_div(SF, SF);
404int soft_cmp_eq(SF, SF);
405int soft_cmp_ne(SF, SF);
406int soft_cmp_ge(SF, SF);
407int soft_cmp_gt(SF, SF);
408int soft_cmp_le(SF, SF);
409int soft_cmp_lt(SF, SF);
410int soft_isz(SF);
411CONSZ soft_val(SF);
412#define FLOAT_NEG(sf)		soft_neg(sf)
413#define	FLOAT_CAST(v,t)		soft_cast(v, t)
414#define	FLOAT_PLUS(x1,x2)	soft_plus(x1, x2)
415#define	FLOAT_MINUS(x1,x2)	soft_minus(x1, x2)
416#define	FLOAT_MUL(x1,x2)	soft_mul(x1, x2)
417#define	FLOAT_DIV(x1,x2)	soft_div(x1, x2)
418#define	FLOAT_ISZERO(sf)	soft_isz(sf)
419#define	FLOAT_VAL(sf)		soft_val(sf)
420#define FLOAT_EQ(x1,x2)		soft_cmp_eq(x1, x2)
421#define FLOAT_NE(x1,x2)		soft_cmp_ne(x1, x2)
422#define FLOAT_GE(x1,x2)		soft_cmp_ge(x1, x2)
423#define FLOAT_GT(x1,x2)		soft_cmp_gt(x1, x2)
424#define FLOAT_LE(x1,x2)		soft_cmp_le(x1, x2)
425#define FLOAT_LT(x1,x2)		soft_cmp_lt(x1, x2)
426#else
427#define	FLOAT_NEG(p)		-(p)
428#define	FLOAT_CAST(p,v)		(ISUNSIGNED(v) ? \
429		(long double)(U_CONSZ)(p) : (long double)(CONSZ)(p))
430#define	FLOAT_PLUS(x1,x2)	(x1) + (x2)
431#define	FLOAT_MINUS(x1,x2)	(x1) - (x2)
432#define	FLOAT_MUL(x1,x2)	(x1) * (x2)
433#define	FLOAT_DIV(x1,x2)	(x1) / (x2)
434#define	FLOAT_ISZERO(p)		(p) == 0.0
435#define FLOAT_VAL(p)		(CONSZ)(p)
436#define FLOAT_EQ(x1,x2)		(x1) == (x2)
437#define FLOAT_NE(x1,x2)		(x1) != (x2)
438#define FLOAT_GE(x1,x2)		(x1) >= (x2)
439#define FLOAT_GT(x1,x2)		(x1) > (x2)
440#define FLOAT_LE(x1,x2)		(x1) <= (x2)
441#define FLOAT_LT(x1,x2)		(x1) < (x2)
442#endif
443
444enum {	ATTR_NONE,
445
446	/* PCC used attributes */
447	ATTR_COMPLEX,	/* Internal definition of complex */
448	xxxATTR_BASETYP,	/* Internal; see below */
449	ATTR_QUALTYP,	/* Internal; const/volatile, see below */
450	ATTR_STRUCT,	/* Internal; element list */
451#define	ATTR_MAX ATTR_STRUCT
452
453#ifdef GCC_COMPAT
454	/* type attributes */
455	GCC_ATYP_ALIGNED,
456	GCC_ATYP_PACKED,
457	GCC_ATYP_SECTION,
458	GCC_ATYP_TRANSP_UNION,
459	GCC_ATYP_UNUSED,
460	GCC_ATYP_DEPRECATED,
461	GCC_ATYP_MAYALIAS,
462
463	/* variable attributes */
464	GCC_ATYP_MODE,
465
466	/* function attributes */
467	GCC_ATYP_NORETURN,
468	GCC_ATYP_FORMAT,
469	GCC_ATYP_NONNULL,
470	GCC_ATYP_SENTINEL,
471	GCC_ATYP_WEAK,
472	GCC_ATYP_FORMATARG,
473	GCC_ATYP_GNU_INLINE,
474	GCC_ATYP_MALLOC,
475	GCC_ATYP_NOTHROW,
476	GCC_ATYP_CONST,
477	GCC_ATYP_PURE,
478	GCC_ATYP_CONSTRUCTOR,
479	GCC_ATYP_DESTRUCTOR,
480	GCC_ATYP_VISIBILITY,
481	GCC_ATYP_STDCALL,
482	GCC_ATYP_CDECL,
483	GCC_ATYP_WARN_UNUSED_RESULT,
484	GCC_ATYP_USED,
485	GCC_ATYP_NO_INSTR_FUN,
486	GCC_ATYP_NOINLINE,
487	GCC_ATYP_ALIAS,
488	GCC_ATYP_WEAKREF,
489	GCC_ATYP_ALLOCSZ,
490	GCC_ATYP_ALW_INL,
491	GCC_ATYP_TLSMODEL,
492	GCC_ATYP_ALIASWEAK,
493	GCC_ATYP_RETURNS_TWICE,
494
495	/* other stuff */
496	GCC_ATYP_BOUNDED,	/* OpenBSD extra boundary checks */
497
498	GCC_ATYP_MAX
499#endif
500};
501
502
503/*
504#ifdef notdef
505 * ATTR_BASETYP has the following layout:
506 * aa[0].iarg has size
507 * aa[1].iarg has alignment
508#endif
509 * ATTR_QUALTYP has the following layout:
510 * aa[0].iarg has CON/VOL + FUN/ARY/PTR
511 * Not defined yet...
512 * aa[3].iarg is dimension for arrays (XXX future)
513 * aa[3].varg is function defs for functions.
514 */
515#ifdef notdef
516#define	atypsz	aa[0].iarg
517#define	aalign	aa[1].iarg
518#endif
519
520/*
521 * ATTR_STRUCT member list.
522 */
523#define amlist  aa[0].varg
524#define amsize  aa[1].iarg
525#define	strattr(x)	(attr_find(x, ATTR_STRUCT))
526
527#define	iarg(x)	aa[x].iarg
528#define	sarg(x)	aa[x].sarg
529#define	varg(x)	aa[x].varg
530
531void gcc_init(void);
532int gcc_keyword(char *, NODE **);
533struct attr *gcc_attr_parse(NODE *);
534void gcc_tcattrfix(NODE *);
535struct gcc_attrib *gcc_get_attr(struct suedef *, int);
536void dump_attr(struct attr *gap);
537
538struct attr *attr_add(struct attr *orig, struct attr *new);
539struct attr *attr_new(int, int);
540struct attr *attr_find(struct attr *, int);
541struct attr *attr_copy(struct attr *src, struct attr *dst, int nelem);
542struct attr *attr_dup(struct attr *ap, int n);
543
544#ifdef STABS
545void stabs_init(void);
546void stabs_file(char *);
547void stabs_efile(char *);
548void stabs_line(int);
549void stabs_rbrac(int);
550void stabs_lbrac(int);
551void stabs_func(struct symtab *);
552void stabs_newsym(struct symtab *);
553void stabs_chgsym(struct symtab *);
554void stabs_struct(struct symtab *, struct attr *);
555#endif
556
557#ifndef CHARCAST
558/* to make character constants into character connstants */
559/* this is a macro to defend against cross-compilers, etc. */
560#define CHARCAST(x) (char)(x)
561#endif
562
563/* sometimes int is smaller than pointers */
564#if SZPOINT(CHAR) <= SZINT
565#define INTPTR  INT
566#elif SZPOINT(CHAR) <= SZLONG
567#define INTPTR  LONG
568#elif SZPOINT(CHAR) <= SZLONGLONG
569#define INTPTR  LONGLONG
570#else
571#error int size unknown
572#endif
573
574/* Generate a bitmask from a given type size */
575#define SZMASK(y) ((((1LL << ((y)-1))-1) << 1) | 1)
576
577/*
578 * C compiler first pass extra defines.
579 */
580#define	QUALIFIER	(MAXOP+1)
581#define	CLASS		(MAXOP+2)
582#define	RB		(MAXOP+3)
583#define	DOT		(MAXOP+4)
584#define	ELLIPSIS	(MAXOP+5)
585#define	TYPE		(MAXOP+6)
586#define	LB		(MAXOP+7)
587#define	COMOP		(MAXOP+8)
588#define	QUEST		(MAXOP+9)
589#define	COLON		(MAXOP+10)
590#define	ANDAND		(MAXOP+11)
591#define	OROR		(MAXOP+12)
592#define	NOT		(MAXOP+13)
593#define	CAST		(MAXOP+14)
594#define	STRING		(MAXOP+15)
595
596/* The following must be in the same order as their NOASG counterparts */
597#define	PLUSEQ		(MAXOP+16)
598#define	MINUSEQ		(MAXOP+17)
599#define	DIVEQ		(MAXOP+18)
600#define	MODEQ		(MAXOP+19)
601#define	MULEQ		(MAXOP+20)
602#define	ANDEQ		(MAXOP+21)
603#define	OREQ		(MAXOP+22)
604#define	EREQ		(MAXOP+23)
605#define	LSEQ		(MAXOP+24)
606#define	RSEQ		(MAXOP+25)
607
608#define	UNASG		(-(PLUSEQ-PLUS))+
609
610#define INCR		(MAXOP+26)
611#define DECR		(MAXOP+27)
612#define SZOF		(MAXOP+28)
613#define CLOP		(MAXOP+29)
614#define ATTRIB		(MAXOP+30)
615#define XREAL		(MAXOP+31)
616#define XIMAG		(MAXOP+32)
617#define TYMERGE		(MAXOP+33)
618#define LABEL		(MAXOP+34)
619
620
621/*
622 * The following types are only used in pass1.
623 */
624#define SIGNED		(MAXTYPES+1)
625#define FARG		(MAXTYPES+2)
626#define	FIMAG		(MAXTYPES+3)
627#define	IMAG		(MAXTYPES+4)
628#define	LIMAG		(MAXTYPES+5)
629#define	FCOMPLEX	(MAXTYPES+6)
630#define	COMPLEX		(MAXTYPES+7)
631#define	LCOMPLEX	(MAXTYPES+8)
632#define	ENUMTY		(MAXTYPES+9)
633
634#define	ISFTY(x)	((x) >= FLOAT && (x) <= LDOUBLE)
635#define	ISCTY(x)	((x) >= FCOMPLEX && (x) <= LCOMPLEX)
636#define	ISITY(x)	((x) >= FIMAG && (x) <= LIMAG)
637#define ANYCX(p) (p->n_type == STRTY && attr_find(p->n_ap, ATTR_COMPLEX))
638
639#define coptype(o)	(cdope(o)&TYFLG)
640#define clogop(o)	(cdope(o)&LOGFLG)
641#define casgop(o)	(cdope(o)&ASGFLG)
642
643