scc

simple c99 compiler
git clone git://git.simple-cc.org/scc
Log | Files | Refs | Submodules | README | LICENSE

decl.c (19218B)


      1 #include <assert.h>
      2 #include <stdarg.h>
      3 #include <stdlib.h>
      4 #include <string.h>
      5 
      6 #include <scc/cstd.h>
      7 #include <scc/scc.h>
      8 #include "cc1.h"
      9 
     10 #define NOSCLASS  0
     11 
     12 #define NOREP 0
     13 #define REP 1
     14 #define QUIET   1
     15 #define NOQUIET 0
     16 
     17 #define NR_DCL_TYP (NR_DECLARATORS+NR_FUNPARAM)
     18 #define NR_DCL_SYM (NR_DECLARATORS+NR_FUNPARAM+1)
     19 
     20 struct declarators {
     21 	unsigned nr;
     22 	unsigned ns;
     23 	struct decl *dcl;
     24 	unsigned nr_types;
     25 	Type **tpars;
     26 	Symbol **pars;
     27 	struct declarator {
     28 		unsigned char op;
     29 		TINT  nelem;
     30 		Symbol *sym;
     31 		Type **tpars;
     32 		Symbol **pars;
     33 	} d [NR_DECLARATORS];
     34 };
     35 
     36 struct decl {
     37 	unsigned ns;
     38 	int sclass;
     39 	int qualifier;
     40 	Symbol *sym;
     41 	Type *type;
     42 	Type *parent;
     43 	Symbol **pars;
     44 	Symbol *bufpars[NR_DCL_SYM];
     45 	Type *buftpars[NR_DCL_TYP];
     46 };
     47 
     48 
     49 static void
     50 endfundcl(Type *tp, Symbol **pars)
     51 {
     52 	/*
     53 	 * If endfundcl is called from a type built from a typedef then
     54 	 * we do not have any parameters because in that case we only
     55 	 * care about the type.
     56 	 */
     57 	if (pars) {
     58 		if ((tp->prop&TK_R) != 0 && *pars)
     59 			warn("parameter names (without types) in function declaration");
     60 
     61 		/* avoid non used warnings in prototypes */
     62 		while (*pars)
     63 			(*pars++)->flags |= SUSED;
     64 		popctx();
     65 	}
     66 }
     67 
     68 static void
     69 push(struct declarators *dp, int op, ...)
     70 {
     71 	va_list va;
     72 	unsigned n;
     73 	struct declarator *p;
     74 
     75 	va_start(va, op);
     76 	if ((n = dp->nr++) == NR_DECLARATORS)
     77 		error("too many declarators");
     78 
     79 	p = &dp->d[n];
     80 	p->op = op;
     81 	p->tpars = NULL;
     82 
     83 	switch (op) {
     84 	case ARY:
     85 		p->nelem = va_arg(va, TINT);
     86 		break;
     87 	case KRFTN:
     88 	case FTN:
     89 		p->nelem = va_arg(va, unsigned);
     90 		p->tpars = va_arg(va, Type **);
     91 		p->pars = va_arg(va, Symbol **);
     92 		break;
     93 	case IDEN:
     94 		p->sym = va_arg(va, Symbol *);
     95 		break;
     96 	}
     97 	va_end(va);
     98 }
     99 
    100 static int
    101 pop(struct declarators *dp, struct decl *dcl)
    102 {
    103 	struct declarator *p;
    104 
    105 	if (dp->nr == 0)
    106 		return 0;
    107 
    108 	p = &dp->d[--dp->nr];
    109 	if (p->op == IDEN) {
    110 		dcl->sym = p->sym;
    111 		return 1;
    112 	}
    113 
    114 	/*
    115 	 * We have a type derived from a function type. We don't care
    116 	 * about the parameters because they were used only in the
    117 	 * process of building a final type. Prototype arguments are
    118 	 * discarded in funbody() because the final type of the decl
    119 	 * is an actual function.
    120 	 */
    121 	if (dcl->type->op == FTN)
    122 		endfundcl(dcl->type, dcl->pars);
    123 	dcl->pars = p->pars;
    124 
    125 	dcl->type = mktype(dcl->type, p->op, p->nelem, p->tpars);
    126 	return 1;
    127 }
    128 
    129 static void
    130 arydcl(struct declarators *dp)
    131 {
    132 	Node *np = NULL;
    133 	TINT n = 0;
    134 	int ns;
    135 
    136 	ns = namespace;
    137 	namespace = NS_IDEN;
    138 	expect('[');
    139 	if (yytoken != ']') {
    140 		if ((np = constexpr()) == NULL) {
    141 			errorp("invalid storage size");
    142 		} else {
    143 			if ((n = np->sym->u.i) <= 0) {
    144 				errorp("array size is not a positive number");
    145 				n = 1;
    146 			}
    147 			freetree(np);
    148 		}
    149 	}
    150 	namespace = ns;
    151 	expect(']');
    152 
    153 	push(dp, ARY, n);
    154 }
    155 
    156 static int
    157 empty(Symbol *sym, Type *tp, int param)
    158 {
    159 	if (!sym->name) {
    160 		sym->type = tp;
    161 		switch (tp->op) {
    162 		default:
    163 			 /* warn if it is not a parameter */
    164 			if (!param)
    165 				warn("empty declaration");
    166 		case STRUCT:
    167 		case UNION:
    168 		case ENUM:
    169 			return 1;
    170 		}
    171 	}
    172 	return 0;
    173 }
    174 
    175 static void
    176 bad_storage(Type *tp, char *name)
    177 {
    178 	if (tp->op != FTN)
    179 		errorp("incorrect storage class for file-scope declaration");
    180 	else
    181 		errorp("invalid storage class for function '%s'", name);
    182 }
    183 
    184 static Symbol *
    185 redcl(Symbol *sym, Type *tp, int sclass)
    186 {
    187 	int flags;
    188 	char *name = sym->name;
    189 
    190 	if (!eqtype(sym->type, tp, EQUIV)) {
    191 		errorp("conflicting types for '%s'", name);
    192 		return sym;
    193 	}
    194 
    195 	/* we prefere ansi types over k&r types */
    196 	if ((sym->type->prop & TK_R) == 0 && (tp->prop & TK_R) != 0)
    197 		sym->type = tp;
    198 
    199 	if (sym->token == TYPEIDEN && sclass != TYPEDEF ||
    200 	    sym->token != TYPEIDEN && sclass == TYPEDEF) {
    201 		goto redeclaration;
    202 	}
    203 	if (curctx != GLOBALCTX && tp->op != FTN) {
    204 		/* is it the redeclaration of a local variable? */
    205 		if ((sym->flags & SEXTERN) && sclass == EXTERN)
    206 			return sym;
    207 		goto redeclaration;
    208 	}
    209 
    210 	flags = sym->flags;
    211 	switch (sclass) {
    212 	case REGISTER:
    213 	case AUTO:
    214 		bad_storage(tp, name);
    215 		break;
    216 	case NOSCLASS:
    217 		if ((flags & SPRIVATE) == 0) {
    218 			if (flags & SEXTERN)
    219 				flags &= ~(SEXTERN|SEMITTED);
    220 			flags |= SGLOBAL;
    221 			break;
    222 		}
    223 		errorp("non-static declaration of '%s' follows static declaration",
    224 		       name);
    225 		break;
    226 	case TYPEDEF:
    227 		/* Only C11 allows multiple definitions of a typedef. */
    228 		goto redeclaration;
    229 	case EXTERN:
    230 		break;
    231 	case STATIC:
    232 		if ((flags & (SGLOBAL|SEXTERN)) == 0) {
    233 			flags |= SPRIVATE;
    234 			break;
    235 		}
    236 		errorp("static declaration of '%s' follows non-static declaration",
    237 		       name);
    238 		break;
    239 	}
    240 	sym->flags = flags;
    241 
    242 	return sym;
    243 
    244 redeclaration:
    245 	errorp("redeclaration of '%s'", name);
    246 	return sym;
    247 }
    248 
    249 static Symbol *
    250 identifier(struct decl *dcl)
    251 {
    252 	Symbol *sym = dcl->sym;
    253 	Type *tp = dcl->type;
    254 	int sclass = dcl->sclass;
    255 	char *name = sym->name;
    256 
    257 	if (empty(sym, tp, 0))
    258 		return sym;
    259 
    260 	/* TODO: Add warning about ANSI limits */
    261 	if (!(tp->prop & TDEFINED)                &&
    262 	    sclass != EXTERN && sclass != TYPEDEF &&
    263 	    !(tp->op == ARY && yytoken == '=')) {
    264 		errorp("declared variable '%s' of incomplete type", name);
    265 	}
    266 
    267 	if (tp->op == FTN) {
    268 		if (sclass == NOSCLASS)
    269 			sclass = EXTERN;
    270 		if (!strcmp(name, "main") && tp->type != inttype) {
    271 			errorp("main shall be defined with a return type of int");
    272 		}
    273 	}
    274 
    275 	if (strcmp(name, "__func__") == 0)
    276 		errorp("__func__ is a reserved variable name");
    277 
    278 	if (sym->flags & SDECLARED) {
    279 		sym = redcl(dcl->sym, tp, sclass);
    280 	} else {
    281 		int flags = sym->flags | SDECLARED;
    282 
    283 		sym->type = tp;
    284 
    285 		switch (sclass) {
    286 		case REGISTER:
    287 		case AUTO:
    288 			if (curctx != GLOBALCTX && tp->op != FTN) {
    289 				flags |= (sclass == REGISTER) ? SREGISTER : SAUTO;
    290 				break;
    291 			}
    292 			bad_storage(tp, name);
    293 		case NOSCLASS:
    294 			if (tp->op == FTN)
    295 				flags |= SEXTERN;
    296 			else
    297 				flags |= (curctx == GLOBALCTX) ? SGLOBAL : SAUTO;
    298 			break;
    299 		case EXTERN:
    300 			flags |= SEXTERN;
    301 			break;
    302 		case STATIC:
    303 			flags |= (curctx == GLOBALCTX) ? SPRIVATE : SLOCAL;
    304 			break;
    305 		case TYPEDEF:
    306 			flags |= STYPEDEF;
    307 			sym->u.token = sym->token = TYPEIDEN;
    308 			break;
    309 		}
    310 		sym->flags = flags;
    311 	}
    312 
    313 	if (accept('='))
    314 		initializer(sym, sym->type);
    315 	if (!(sym->flags & (SGLOBAL|SEXTERN)) && tp->op != FTN)
    316 		sym->flags |= SDEFINED;
    317 	if (sym->token == IDEN && tp->op != FTN)
    318 		emit(ODECL, sym);
    319 	return sym;
    320 }
    321 
    322 static Symbol *
    323 parameter(struct decl *dcl)
    324 {
    325 	Symbol *sym = dcl->sym;
    326 	Type *funtp = dcl->parent, *tp = dcl->type;
    327 	char *name = sym->name;
    328 	int flags;
    329 
    330 	flags = 0;
    331 	switch (dcl->sclass) {
    332 	case STATIC:
    333 	case EXTERN:
    334 	case AUTO:
    335 		errorp("bad storage class in function parameter");
    336 		break;
    337 	case REGISTER:
    338 		flags |= SREGISTER;
    339 		break;
    340 	case NOSCLASS:
    341 		flags |= SAUTO;
    342 		break;
    343 	}
    344 
    345 	switch (tp->op) {
    346 	case VOID:
    347 		funtp->n.elem = 1;
    348 		if (dcl->sclass)
    349 			errorp("void as unique parameter may not be qualified");
    350 		return NULL;
    351 	case ARY:
    352 		tp = mktype(tp->type, PTR, 0, NULL);
    353 		break;
    354 	case FTN:
    355 		errorp("incorrect function type for a function parameter");
    356 		return NULL;
    357 	}
    358 	if (!empty(sym, tp, 1)) {
    359 		int isdcl = sym->flags&SDECLARED, isk_r = funtp->prop & TK_R;
    360 		if (isdcl && !isk_r) {
    361 			errorp("redefinition of parameter '%s'", name);
    362 			return NULL;
    363 		}
    364 		if (!isdcl && isk_r) {
    365 			errorp("declaration for parameter '%s' but no such parameter",
    366 			       sym->name);
    367 			return NULL;
    368 		}
    369 		if (strcmp(name, "__func__") == 0)
    370 			errorp("__func__ is a reserved variable name");
    371 		sym->flags |= SDECLARED;
    372 	}
    373 
    374 	sym->type = tp;
    375 	sym->flags &= ~(SAUTO|SREGISTER);
    376 	sym->flags |= flags;
    377 	return sym;
    378 }
    379 
    380 static Symbol *dodcl(int rep,
    381                      Symbol *(*fun)(struct decl *),
    382                      unsigned ns,
    383                      Type *type);
    384 
    385 static int
    386 krpars(struct declarators *dp)
    387 {
    388 	Symbol *sym;
    389 	int toomany = 0;
    390 	unsigned npars = 0;
    391 
    392 	do {
    393 		sym = yylval.sym;
    394 		expect(IDEN);
    395 		sym->flags |= SAUTO;
    396 		if ((sym = install(NS_IDEN, sym)) == NULL) {
    397 			errorp("redefinition of parameter '%s'",
    398 			       yylval.sym->name);
    399 			continue;
    400 		}
    401 		if (npars < NR_FUNPARAM) {
    402 			++npars;
    403 			*dp->pars++ = sym;
    404 			continue;
    405 		}
    406 		toomany = 1;
    407 	} while (accept(','));
    408 
    409 	return toomany;
    410 }
    411 
    412 static unsigned
    413 krfun(struct declarators *dp)
    414 {
    415 	int toomany = 0;
    416 
    417 	if (yytoken != ')')
    418 		toomany = krpars(dp);
    419 
    420 	if (dp->nr_types == NR_DCL_TYP) {
    421 		toomany = 1;
    422 	} else {
    423 		++dp->nr_types;
    424 		*dp->tpars++ = ellipsistype;
    425 	}
    426 
    427 	if (toomany)
    428 		errorp("too many parameters in function definition");
    429 	return 1;
    430 }
    431 
    432 static unsigned
    433 ansifun(struct declarators *dp)
    434 {
    435 	Symbol *sym;
    436 	unsigned npars, ntype, toomany, distoomany, voidpar;
    437 	Type type, *tp;
    438 
    439 	type.n.elem = 0;
    440 	type.prop = 0;
    441 	npars = ntype = toomany = distoomany = voidpar = 0;
    442 
    443 	do {
    444 		if (accept(ELLIPSIS)) {
    445 			if (ntype < 1)
    446 				errorp("a named argument is requiered before '...'");
    447 			if (yytoken != ')')
    448 				errorp("... must be the last parameter");
    449 			sym = NULL;
    450 			tp = ellipsistype;
    451 		} else if ((sym = dodcl(NOREP, parameter, NS_IDEN, &type)) == NULL) {
    452 			voidpar = 1;
    453 			sym = NULL;
    454 			tp = NULL;
    455 		} else {
    456 			tp = sym->type;
    457 		}
    458 
    459 		if (sym) {
    460 			if (npars == NR_FUNPARAM) {
    461 				toomany = 1;
    462 			} else {
    463 				npars++;
    464 				*dp->pars++ = sym;
    465 			}
    466 		}
    467 
    468 		if (tp) {
    469 			if (dp->nr_types == NR_DCL_TYP) {
    470 				toomany = 1;
    471 			} else {
    472 				ntype++;
    473 				dp->nr_types++;
    474 				*dp->tpars++ = tp;
    475 			}
    476 		}
    477 
    478 	} while (accept(','));
    479 
    480 	if (toomany == 1)
    481 		errorp("too many parameters in function definition");
    482 	if (voidpar && ntype > 0)
    483 		errorp("'void' must be the only parameter");
    484 	return ntype;
    485 }
    486 
    487 static int
    488 isfunbody(int tok)
    489 {
    490 	switch (tok) {
    491 	case '{':
    492 	case TYPE:
    493 	case SCLASS:
    494 	case TYPEIDEN:
    495 		return 1;
    496 	default:
    497 		return 0;
    498 	}
    499 }
    500 
    501 static int
    502 funbody(Symbol *sym, Symbol *pars[])
    503 {
    504 	Type *tp;
    505 	Symbol **bp, *p;
    506 	Symbol *emptypars[] = {NULL};
    507 
    508 	if (!sym)
    509 		return 0;
    510 
    511 	tp = sym->type;
    512 	if (tp->op != FTN)
    513 		return 0;
    514 	if (!isfunbody(yytoken) || sym->ns != NS_IDEN) {
    515 		emit(ODECL, sym);
    516 		endfundcl(tp, pars);
    517 		return  0;
    518 	}
    519 
    520 	if (curctx < PARAMCTX) {
    521 		assert(!pars);
    522 		errorp("typedef'ed function type cannot be instantiated");
    523 		curctx = PARAMCTX;
    524 		pars = emptypars;
    525 	}
    526 
    527 	if (curctx != PARAMCTX)
    528 		error("nested function declaration");
    529 
    530 	tp->prop |= TFUNDEF;
    531 	curfun = sym;
    532 	if (tp->prop & TK_R) {
    533 		while (yytoken != '{') {
    534 			dodcl(REP, parameter, NS_IDEN, sym->type);
    535 			expect(';');
    536 		}
    537 		for (bp = pars; p = *bp; ++bp) {
    538 			if (p->type == NULL) {
    539 				warn("type of '%s' defaults to int", p->name);
    540 				p->type = inttype;
    541 			}
    542 		}
    543 	}
    544 	if (sym->flags & STYPEDEF)
    545 		errorp("function definition declared 'typedef'");
    546 	if (sym->flags & SDEFINED)
    547 		errorp("redefinition of '%s'", sym->name);
    548 	if (sym->flags & SEXTERN) {
    549 		sym->flags &= ~SEXTERN;
    550 		sym->flags |= SGLOBAL;
    551 	}
    552 	sym->flags |= SDEFINED;
    553 	sym->flags &= ~SEMITTED;
    554 	sym->u.pars = pars;
    555 	emit(OFUN, sym);
    556 	compound(NULL, NULL, NULL);
    557 	emit(OEFUN, NULL);
    558 	popctx();
    559 	flushtypes();
    560 	curfun = NULL;
    561 
    562 	/*
    563 	 * A function declaration without arguments is a k&r function,
    564 	 * but when it is a definition is a function with 0 arguments
    565 	 */
    566 	if ((tp->prop & TK_R) && *pars == NULL) {
    567 		tp = mktype(tp->type, FTN, 0, NULL);
    568 		tp->prop |= TFUNDEF;
    569 		sym->type = tp;
    570 	}
    571 
    572 	return 1;
    573 }
    574 
    575 static void
    576 fundcl(struct declarators *dp)
    577 {
    578 	Type **types = dp->tpars;
    579 	unsigned ntypes, typefun;
    580 	Symbol **pars = dp->pars;
    581 	unsigned (*fun)(struct declarators *);
    582 
    583 	pushctx();
    584 	expect('(');
    585 	if (yytoken == ')' || yytoken == IDEN) {
    586 		typefun = KRFTN;
    587 		fun = krfun;
    588 	} else {
    589 		typefun = FTN;
    590 		fun = ansifun;
    591 	}
    592 	ntypes = (*fun)(dp);
    593 	*dp->pars++= NULL;
    594 	expect(')');
    595 
    596 	push(dp, typefun, ntypes, types, pars);
    597 }
    598 
    599 static void declarator(struct declarators *dp);
    600 
    601 static void
    602 directdcl(struct declarators *dp)
    603 {
    604 	Symbol *p, *sym;
    605 	static int nested;
    606 
    607 	if (accept('(')) {
    608 		if (nested == NR_SUBTYPE)
    609 			error("too many declarators nested by parentheses");
    610 		++nested;
    611 		declarator(dp);
    612 		--nested;
    613 		expect(')');
    614 	} else {
    615 		if (yytoken == IDEN || yytoken == TYPEIDEN) {
    616 			sym = yylval.sym;
    617 			if (p = install(dp->ns, sym)) {
    618 				sym = p;
    619 				sym->flags &= ~SDECLARED;
    620 			}
    621 			next();
    622 		} else {
    623 			sym = newsym(dp->ns, NULL);
    624 		}
    625 		push(dp, IDEN, sym);
    626 	}
    627 
    628 	for (;;) {
    629 		switch (yytoken) {
    630 		case '(':  fundcl(dp); break;
    631 		case '[':  arydcl(dp); break;
    632 		default:   return;
    633 		}
    634 	}
    635 }
    636 
    637 static void
    638 declarator(struct declarators *dp)
    639 {
    640 	unsigned  n;
    641 
    642 	for (n = 0; accept('*'); ++n) {
    643 		while (accept(TQUALIFIER))
    644 			;
    645 	}
    646 
    647 	directdcl(dp);
    648 
    649 	while (n--)
    650 		push(dp, PTR);
    651 }
    652 
    653 static Type *structdcl(void), *enumdcl(void);
    654 
    655 static Type *
    656 specifier(int *sclass, int *qualifier)
    657 {
    658 	Type *tp = NULL;
    659 	unsigned spec, qlf, sign, type, cls, size;
    660 
    661 	spec = qlf = sign = type = cls = size = 0;
    662 
    663 	for (;;) {
    664 		unsigned *p = NULL;
    665 		Type *(*dcl)(void) = NULL;
    666 
    667 		switch (yytoken) {
    668 		case SCLASS:
    669 			p = &cls;
    670 			break;
    671 		case TQUALIFIER:
    672 			qlf |= yylval.token;
    673 			next();
    674 			continue;
    675 		case TYPEIDEN:
    676 			if (type)
    677 				goto return_type;
    678 			tp = yylval.sym->type;
    679 			p = &type;
    680 			break;
    681 		case TYPE:
    682 			switch (yylval.token) {
    683 			case ENUM:
    684 				dcl = enumdcl;
    685 				p = &type;
    686 				break;
    687 			case STRUCT:
    688 			case UNION:
    689 				dcl = structdcl;
    690 				p = &type;
    691 				break;
    692 			case VA_LIST:
    693 			case VOID:
    694 			case BOOL:
    695 			case CHAR:
    696 			case INT:
    697 			case FLOAT:
    698 			case DOUBLE:
    699 				p = &type;
    700 				break;
    701 			case SIGNED:
    702 			case UNSIGNED:
    703 				p = &sign;
    704 				break;
    705 			case LONG:
    706 				if (size == LONG) {
    707 					yylval.token = LLONG;
    708 					size = 0;
    709 				}
    710 			case SHORT:
    711 				p = &size;
    712 				break;
    713 			}
    714 			break;
    715 		default:
    716 			goto return_type;
    717 		}
    718 		if (*p)
    719 			errorp("invalid type specification");
    720 		*p = yylval.token;
    721 		if (dcl) {
    722 			if (size || sign)
    723 				errorp("invalid type specification");
    724 			tp = (*dcl)();
    725 			goto return_type;
    726 		} else {
    727 			next();
    728 		}
    729 		spec = 1;
    730 	}
    731 
    732 return_type:
    733 	*sclass = cls;
    734 	*qualifier = qlf;
    735 	if (!tp) {
    736 		if (spec) {
    737 			tp = ctype(type, sign, size);
    738 		} else {
    739 			if (curctx != GLOBALCTX)
    740 				unexpected();
    741 			warn("type defaults to 'int' in declaration");
    742 			tp = inttype;
    743 		}
    744 	}
    745 	return tp;
    746 }
    747 
    748 static Symbol *
    749 newtag(void)
    750 {
    751 	Symbol *sym;
    752 	int ns, op, tag = yylval.token;
    753 	static unsigned tpns = NS_STRUCTS;
    754 
    755 	ns = namespace;
    756 	namespace = NS_TAG;
    757 	next();
    758 	namespace = ns;
    759 
    760 	switch (yytoken) {
    761 	case IDEN:
    762 	case TYPEIDEN:
    763 		sym = yylval.sym;
    764 		if ((sym->flags & SDECLARED) == 0)
    765 			install(NS_TAG, yylval.sym);
    766 		next();
    767 		break;
    768 	default:
    769 		sym = newsym(NS_TAG, NULL);
    770 		break;
    771 	}
    772 	if (!sym->type) {
    773 		Type *tp;
    774 
    775 		if (tpns == NS_STRUCTS + NR_MAXSTRUCTS)
    776 			error("too many tags declared");
    777 		tp = mktype(NULL, tag, 0, NULL);
    778 		tp->ns = tpns++;
    779 		sym->type = tp;
    780 		tp->tag = sym;
    781 		DBG("DECL: declared tag '%s' with ns = %d\n",
    782 		    (sym->name) ? sym->name : "anonymous", tp->ns);
    783 	}
    784 
    785 	if ((op = sym->type->op) != tag &&  op != INT)
    786 		error("'%s' defined as wrong kind of tag", sym->name);
    787 	return sym;
    788 }
    789 
    790 static void fieldlist(Type *tp);
    791 
    792 static Type *
    793 structdcl(void)
    794 {
    795 	Symbol *sym;
    796 	Type *tp;
    797 	static int nested;
    798 	int ns;
    799 
    800 	sym = newtag();
    801 	tp = sym->type;
    802 
    803 	if (!accept('{'))
    804 		return tp;
    805 
    806 	ns = namespace;
    807 	namespace = tp->ns;
    808 
    809 	if (tp->prop & TDEFINED && sym->ctx == curctx)
    810 		error("redefinition of struct/union '%s'", sym->name);
    811 
    812 	if (nested == NR_STRUCT_LEVEL)
    813 		error("too many levels of nested structure or union definitions");
    814 
    815 	++nested;
    816 	do fieldlist(tp); while (yytoken != '}');
    817 	--nested;
    818 
    819 	deftype(tp);
    820 	namespace = ns;
    821 	expect('}');
    822 	return tp;
    823 }
    824 
    825 static Type *
    826 enumdcl(void)
    827 {
    828 	Type *tp;
    829 	Symbol *sym, *tagsym;
    830 	int ns, val, toomany;
    831 	unsigned nctes;
    832 
    833 	ns = namespace;
    834 	tagsym = newtag();
    835 	tp = tagsym->type;
    836 
    837 	namespace = NS_IDEN;
    838 	if (!accept('{')) {
    839 		namespace = ns;
    840 		return tp;
    841 	}
    842 	if (tp->prop & TDEFINED)
    843 		errorp("redefinition of enumeration '%s'", tagsym->name);
    844 	deftype(tp);
    845 
    846 	/* TODO: check incorrect values in val */
    847 	for (nctes = val = 0; yytoken != '}'; ++nctes, ++val) {
    848 		if (yytoken != IDEN)
    849 			unexpected();
    850 		sym = yylval.sym;
    851 		next();
    852 		if (nctes == NR_ENUM_CTES && !toomany) {
    853 			errorp("too many enum constants in a single enum");
    854 			toomany = 1;
    855 		}
    856 		if (accept('=')) {
    857 			Node *np = constexpr();
    858 
    859 			if (np == NULL)
    860 				errorp("invalid enumeration value");
    861 			else
    862 				val = np->sym->u.i;
    863 			freetree(np);
    864 		}
    865 		if ((sym = install(NS_IDEN, sym)) == NULL) {
    866 			errorp("'%s' redeclared as different kind of symbol",
    867 			       yytext);
    868 		} else {
    869 			sym->u.i = val;
    870 			sym->flags |= SCONSTANT;
    871 			sym->type = inttype;
    872 		}
    873 		if (!accept(','))
    874 			break;
    875 	}
    876 	namespace = ns;
    877 	expect('}');
    878 	return tp;
    879 }
    880 
    881 static Symbol *
    882 type(struct decl *dcl)
    883 {
    884 	Symbol *sym = dcl->sym;
    885 
    886 	if (dcl->sclass)
    887 		error("class storage in type name");
    888 	if (sym->name)
    889 		error("unexpected identifier in type name");
    890 	sym->type = dcl->type;
    891 
    892 	return sym;
    893 }
    894 
    895 static Symbol *
    896 field(struct decl *dcl)
    897 {
    898 	static char *anon = "<anonymous>";
    899 	Symbol *sym = dcl->sym;
    900 	char *name = (sym->name) ? sym->name : anon;
    901 	Type *structp = dcl->parent, *tp = dcl->type;
    902 	TINT n = structp->n.elem;
    903 
    904 	if (accept(':')) {
    905 		Node *np;
    906 		TINT n;
    907 
    908 		if ((np = constexpr()) == NULL) {
    909 			unexpected();
    910 			n = 0;
    911 		} else {
    912 			n = np->sym->u.i;
    913 			freetree(np);
    914 		}
    915 		if (n == 0 && name != anon)
    916 			errorp("zero width for bit-field '%s'", name);
    917 		if (tp != booltype && tp != inttype && tp != uinttype)
    918 			errorp("bit-field '%s' has invalid type", name);
    919 		if (n < 0)
    920 			errorp("negative width in bit-field '%s'", name);
    921 		else if (n > tp->size*8)
    922 			errorp("width of '%s' exceeds its type", name);
    923 	} else if (empty(sym, tp, 0)) {
    924 		return sym;
    925 	}
    926 
    927 	if (sym->flags & SDECLARED) {
    928 		errorp("duplicated member '%s'", name);
    929 		return sym;
    930 	}
    931 
    932 	if ((tp->prop & TDEFINED) == 0) {
    933 		if (tp->op == ARY && tp->n.elem == 0) {
    934 			if (n == 0)
    935 				errorp("flexible array member in a struct with no named members");
    936 			if (ahead() != '}')
    937 				errorp("flexible array member not at end of struct");
    938 		} else {
    939 			errorp("field '%s' has incomplete type", name);
    940 			tp = inttype;
    941 		}
    942 	}
    943 	if (tp->op == FTN) {
    944 		errorp("field '%s' declared as a function", name);
    945 		tp = inttype;
    946 	}
    947 	if (dcl->sclass)
    948 		errorp("storage class in struct/union field '%s'", name);
    949 
    950 	sym->type = tp;
    951 	sym->flags |= SFIELD|SDECLARED;
    952 
    953 	if (n == NR_FIELDS) {
    954 		errorp("too many fields in struct/union");
    955 		return sym;
    956 	}
    957 
    958 	DBG("DECL: New field '%s' in namespace %d\n", name, structp->ns);
    959 	structp->p.fields = xrealloc(structp->p.fields, ++n * sizeof(*sym));
    960 	structp->p.fields[n-1] = sym;
    961 	structp->n.elem = n;
    962 
    963 	return sym;
    964 }
    965 
    966 static Symbol *
    967 dodcl(int rep, Symbol *(*fun)(struct decl *), unsigned ns, Type *parent)
    968 {
    969 	Symbol *sym;
    970 	Type *base;
    971 	struct decl dcl;
    972 	struct declarators stack;
    973 
    974 	dcl.ns = ns;
    975 	dcl.parent = parent;
    976 	base = specifier(&dcl.sclass, &dcl.qualifier);
    977 
    978 	do {
    979 		dcl.type = base;
    980 		dcl.pars = NULL;
    981 		stack.nr_types = stack.nr = 0;
    982 		stack.tpars = dcl.buftpars;
    983 		stack.pars = dcl.bufpars;
    984 		stack.dcl = &dcl;
    985 		stack.ns = ns;
    986 
    987 		declarator(&stack);
    988 
    989 		while (pop(&stack, &dcl))
    990 			;
    991 		sym = (*fun)(&dcl);
    992 		if (funbody(sym, dcl.pars))
    993 			return sym;
    994 	} while (rep && accept(','));
    995 
    996 	return sym;
    997 }
    998 
    999 void
   1000 decl(void)
   1001 {
   1002 	Symbol *sym;
   1003 
   1004 	if (accept(';'))
   1005 		return;
   1006 
   1007 	sym = dodcl(REP, identifier, NS_IDEN, NULL);
   1008 	if ((sym->type->prop & TFUNDEF) == 0)
   1009 		expect(';');
   1010 }
   1011 
   1012 static void
   1013 fieldlist(Type *tp)
   1014 {
   1015 	if (yytoken != ';')
   1016 		dodcl(REP, field, tp->ns, tp);
   1017 	expect(';');
   1018 }
   1019 
   1020 Type *
   1021 typename(void)
   1022 {
   1023 	return dodcl(NOREP, type, NS_DUMMY, NULL)->type;
   1024 }