scc

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

decl.c (19255B)


      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 			if (type.n.elem == 1 && ntype > 1)
    453 				voidpar = 1;
    454 			sym = NULL;
    455 			tp = NULL;
    456 		} else {
    457 			tp = sym->type;
    458 		}
    459 
    460 		if (sym) {
    461 			if (npars == NR_FUNPARAM) {
    462 				toomany = 1;
    463 			} else {
    464 				npars++;
    465 				*dp->pars++ = sym;
    466 			}
    467 		}
    468 
    469 		if (tp) {
    470 			if (dp->nr_types == NR_DCL_TYP) {
    471 				toomany = 1;
    472 			} else {
    473 				ntype++;
    474 				dp->nr_types++;
    475 				*dp->tpars++ = tp;
    476 			}
    477 		}
    478 
    479 	} while (accept(','));
    480 
    481 	if (toomany == 1)
    482 		errorp("too many parameters in function definition");
    483 	if (voidpar && ntype > 1)
    484 		errorp("'void' must be the only parameter");
    485 	return ntype;
    486 }
    487 
    488 static int
    489 isfunbody(int tok)
    490 {
    491 	switch (tok) {
    492 	case '{':
    493 	case TYPE:
    494 	case SCLASS:
    495 	case TYPEIDEN:
    496 		return 1;
    497 	default:
    498 		return 0;
    499 	}
    500 }
    501 
    502 static int
    503 funbody(Symbol *sym, Symbol *pars[])
    504 {
    505 	Type *tp;
    506 	Symbol **bp, *p;
    507 	Symbol *emptypars[] = {NULL};
    508 
    509 	if (!sym)
    510 		return 0;
    511 
    512 	tp = sym->type;
    513 	if (tp->op != FTN)
    514 		return 0;
    515 	if (!isfunbody(yytoken) || sym->ns != NS_IDEN) {
    516 		emit(ODECL, sym);
    517 		endfundcl(tp, pars);
    518 		return  0;
    519 	}
    520 
    521 	if (curctx < PARAMCTX) {
    522 		assert(!pars);
    523 		errorp("typedef'ed function type cannot be instantiated");
    524 		curctx = PARAMCTX;
    525 		pars = emptypars;
    526 	}
    527 
    528 	if (curctx != PARAMCTX)
    529 		error("nested function declaration");
    530 
    531 	tp->prop |= TFUNDEF;
    532 	curfun = sym;
    533 	if (tp->prop & TK_R) {
    534 		while (yytoken != '{') {
    535 			dodcl(REP, parameter, NS_IDEN, sym->type);
    536 			expect(';');
    537 		}
    538 		for (bp = pars; p = *bp; ++bp) {
    539 			if (p->type == NULL) {
    540 				warn("type of '%s' defaults to int", p->name);
    541 				p->type = inttype;
    542 			}
    543 		}
    544 	}
    545 	if (sym->flags & STYPEDEF)
    546 		errorp("function definition declared 'typedef'");
    547 	if (sym->flags & SDEFINED)
    548 		errorp("redefinition of '%s'", sym->name);
    549 	if (sym->flags & SEXTERN) {
    550 		sym->flags &= ~SEXTERN;
    551 		sym->flags |= SGLOBAL;
    552 	}
    553 	sym->flags |= SDEFINED;
    554 	sym->flags &= ~SEMITTED;
    555 	sym->u.pars = pars;
    556 	emit(OFUN, sym);
    557 	compound(NULL, NULL, NULL);
    558 	emit(OEFUN, NULL);
    559 	popctx();
    560 	flushtypes();
    561 	curfun = NULL;
    562 
    563 	/*
    564 	 * A function declaration without arguments is a k&r function,
    565 	 * but when it is a definition is a function with 0 arguments
    566 	 */
    567 	if ((tp->prop & TK_R) && *pars == NULL) {
    568 		tp = mktype(tp->type, FTN, 0, NULL);
    569 		tp->prop |= TFUNDEF;
    570 		sym->type = tp;
    571 	}
    572 
    573 	return 1;
    574 }
    575 
    576 static void
    577 fundcl(struct declarators *dp)
    578 {
    579 	Type **types = dp->tpars;
    580 	unsigned ntypes, typefun;
    581 	Symbol **pars = dp->pars;
    582 	unsigned (*fun)(struct declarators *);
    583 
    584 	pushctx();
    585 	expect('(');
    586 	if (yytoken == ')' || yytoken == IDEN) {
    587 		typefun = KRFTN;
    588 		fun = krfun;
    589 	} else {
    590 		typefun = FTN;
    591 		fun = ansifun;
    592 	}
    593 	ntypes = (*fun)(dp);
    594 	*dp->pars++= NULL;
    595 	expect(')');
    596 
    597 	push(dp, typefun, ntypes, types, pars);
    598 }
    599 
    600 static void declarator(struct declarators *dp);
    601 
    602 static void
    603 directdcl(struct declarators *dp)
    604 {
    605 	Symbol *p, *sym;
    606 	static int nested;
    607 
    608 	if (accept('(')) {
    609 		if (nested == NR_SUBTYPE)
    610 			error("too many declarators nested by parentheses");
    611 		++nested;
    612 		declarator(dp);
    613 		--nested;
    614 		expect(')');
    615 	} else {
    616 		if (yytoken == IDEN || yytoken == TYPEIDEN) {
    617 			sym = yylval.sym;
    618 			if (p = install(dp->ns, sym)) {
    619 				sym = p;
    620 				sym->flags &= ~SDECLARED;
    621 			}
    622 			next();
    623 		} else {
    624 			sym = newsym(dp->ns, NULL);
    625 		}
    626 		push(dp, IDEN, sym);
    627 	}
    628 
    629 	for (;;) {
    630 		switch (yytoken) {
    631 		case '(':  fundcl(dp); break;
    632 		case '[':  arydcl(dp); break;
    633 		default:   return;
    634 		}
    635 	}
    636 }
    637 
    638 static void
    639 declarator(struct declarators *dp)
    640 {
    641 	unsigned  n;
    642 
    643 	for (n = 0; accept('*'); ++n) {
    644 		while (accept(TQUALIFIER))
    645 			;
    646 	}
    647 
    648 	directdcl(dp);
    649 
    650 	while (n--)
    651 		push(dp, PTR);
    652 }
    653 
    654 static Type *structdcl(void), *enumdcl(void);
    655 
    656 static Type *
    657 specifier(int *sclass, int *qualifier)
    658 {
    659 	Type *tp = NULL;
    660 	unsigned spec, qlf, sign, type, cls, size;
    661 
    662 	spec = qlf = sign = type = cls = size = 0;
    663 
    664 	for (;;) {
    665 		unsigned *p = NULL;
    666 		Type *(*dcl)(void) = NULL;
    667 
    668 		switch (yytoken) {
    669 		case SCLASS:
    670 			p = &cls;
    671 			break;
    672 		case TQUALIFIER:
    673 			qlf |= yylval.token;
    674 			next();
    675 			continue;
    676 		case TYPEIDEN:
    677 			if (type)
    678 				goto return_type;
    679 			tp = yylval.sym->type;
    680 			p = &type;
    681 			break;
    682 		case TYPE:
    683 			switch (yylval.token) {
    684 			case ENUM:
    685 				dcl = enumdcl;
    686 				p = &type;
    687 				break;
    688 			case STRUCT:
    689 			case UNION:
    690 				dcl = structdcl;
    691 				p = &type;
    692 				break;
    693 			case VA_LIST:
    694 			case VOID:
    695 			case BOOL:
    696 			case CHAR:
    697 			case INT:
    698 			case FLOAT:
    699 			case DOUBLE:
    700 				p = &type;
    701 				break;
    702 			case SIGNED:
    703 			case UNSIGNED:
    704 				p = &sign;
    705 				break;
    706 			case LONG:
    707 				if (size == LONG) {
    708 					yylval.token = LLONG;
    709 					size = 0;
    710 				}
    711 			case SHORT:
    712 				p = &size;
    713 				break;
    714 			}
    715 			break;
    716 		default:
    717 			goto return_type;
    718 		}
    719 		if (*p)
    720 			errorp("invalid type specification");
    721 		*p = yylval.token;
    722 		if (dcl) {
    723 			if (size || sign)
    724 				errorp("invalid type specification");
    725 			tp = (*dcl)();
    726 			goto return_type;
    727 		} else {
    728 			next();
    729 		}
    730 		spec = 1;
    731 	}
    732 
    733 return_type:
    734 	*sclass = cls;
    735 	*qualifier = qlf;
    736 	if (!tp) {
    737 		if (spec) {
    738 			tp = ctype(type, sign, size);
    739 		} else {
    740 			if (curctx != GLOBALCTX)
    741 				unexpected();
    742 			warn("type defaults to 'int' in declaration");
    743 			tp = inttype;
    744 		}
    745 	}
    746 	return tp;
    747 }
    748 
    749 static Symbol *
    750 newtag(void)
    751 {
    752 	Symbol *sym;
    753 	int ns, op, tag = yylval.token;
    754 	static unsigned tpns = NS_STRUCTS;
    755 
    756 	ns = namespace;
    757 	namespace = NS_TAG;
    758 	next();
    759 	namespace = ns;
    760 
    761 	switch (yytoken) {
    762 	case IDEN:
    763 	case TYPEIDEN:
    764 		sym = yylval.sym;
    765 		if ((sym->flags & SDECLARED) == 0)
    766 			install(NS_TAG, yylval.sym);
    767 		next();
    768 		break;
    769 	default:
    770 		sym = newsym(NS_TAG, NULL);
    771 		break;
    772 	}
    773 	if (!sym->type) {
    774 		Type *tp;
    775 
    776 		if (tpns == NS_STRUCTS + NR_MAXSTRUCTS)
    777 			error("too many tags declared");
    778 		tp = mktype(NULL, tag, 0, NULL);
    779 		tp->ns = tpns++;
    780 		sym->type = tp;
    781 		tp->tag = sym;
    782 		DBG("DECL: declared tag '%s' with ns = %d\n",
    783 		    (sym->name) ? sym->name : "anonymous", tp->ns);
    784 	}
    785 
    786 	if ((op = sym->type->op) != tag &&  op != INT)
    787 		error("'%s' defined as wrong kind of tag", sym->name);
    788 	return sym;
    789 }
    790 
    791 static void fieldlist(Type *tp);
    792 
    793 static Type *
    794 structdcl(void)
    795 {
    796 	Symbol *sym;
    797 	Type *tp;
    798 	static int nested;
    799 	int ns;
    800 
    801 	sym = newtag();
    802 	tp = sym->type;
    803 
    804 	if (!accept('{'))
    805 		return tp;
    806 
    807 	ns = namespace;
    808 	namespace = tp->ns;
    809 
    810 	if (tp->prop & TDEFINED && sym->ctx == curctx)
    811 		error("redefinition of struct/union '%s'", sym->name);
    812 
    813 	if (nested == NR_STRUCT_LEVEL)
    814 		error("too many levels of nested structure or union definitions");
    815 
    816 	++nested;
    817 	while (yytoken != '}')
    818 		fieldlist(tp);
    819 	--nested;
    820 
    821 	deftype(tp);
    822 	namespace = ns;
    823 	expect('}');
    824 	return tp;
    825 }
    826 
    827 static Type *
    828 enumdcl(void)
    829 {
    830 	Type *tp;
    831 	Symbol *sym, *tagsym;
    832 	int ns, val, toomany;
    833 	unsigned nctes;
    834 
    835 	ns = namespace;
    836 	tagsym = newtag();
    837 	tp = tagsym->type;
    838 
    839 	namespace = NS_IDEN;
    840 	if (!accept('{')) {
    841 		namespace = ns;
    842 		return tp;
    843 	}
    844 	if (tp->prop & TDEFINED)
    845 		errorp("redefinition of enumeration '%s'", tagsym->name);
    846 	deftype(tp);
    847 
    848 	/* TODO: check incorrect values in val */
    849 	for (nctes = val = 0; yytoken != '}'; ++nctes, ++val) {
    850 		if (yytoken != IDEN)
    851 			unexpected();
    852 		sym = yylval.sym;
    853 		next();
    854 		if (nctes == NR_ENUM_CTES && !toomany) {
    855 			errorp("too many enum constants in a single enum");
    856 			toomany = 1;
    857 		}
    858 		if (accept('=')) {
    859 			Node *np = constexpr();
    860 
    861 			if (np == NULL)
    862 				errorp("invalid enumeration value");
    863 			else
    864 				val = np->sym->u.i;
    865 			freetree(np);
    866 		}
    867 		if ((sym = install(NS_IDEN, sym)) == NULL) {
    868 			errorp("'%s' redeclared as different kind of symbol",
    869 			       yytext);
    870 		} else {
    871 			sym->u.i = val;
    872 			sym->flags |= SCONSTANT;
    873 			sym->type = inttype;
    874 		}
    875 		if (!accept(','))
    876 			break;
    877 	}
    878 	namespace = ns;
    879 	expect('}');
    880 	return tp;
    881 }
    882 
    883 static Symbol *
    884 type(struct decl *dcl)
    885 {
    886 	Symbol *sym = dcl->sym;
    887 
    888 	if (dcl->sclass)
    889 		error("class storage in type name");
    890 	if (sym->name)
    891 		error("unexpected identifier in type name");
    892 	sym->type = dcl->type;
    893 
    894 	return sym;
    895 }
    896 
    897 static Symbol *
    898 field(struct decl *dcl)
    899 {
    900 	static char *anon = "<anonymous>";
    901 	Symbol *sym = dcl->sym;
    902 	char *name = (sym->name) ? sym->name : anon;
    903 	Type *structp = dcl->parent, *tp = dcl->type;
    904 	TINT n = structp->n.elem;
    905 
    906 	if (accept(':')) {
    907 		Node *np;
    908 		TINT n;
    909 
    910 		if ((np = constexpr()) == NULL) {
    911 			unexpected();
    912 			n = 0;
    913 		} else {
    914 			n = np->sym->u.i;
    915 			freetree(np);
    916 		}
    917 		if (n == 0 && name != anon)
    918 			errorp("zero width for bit-field '%s'", name);
    919 		if (tp != booltype && tp != inttype && tp != uinttype)
    920 			errorp("bit-field '%s' has invalid type", name);
    921 		if (n < 0)
    922 			errorp("negative width in bit-field '%s'", name);
    923 		else if (n > tp->size*8)
    924 			errorp("width of '%s' exceeds its type", name);
    925 	} else if (empty(sym, tp, 0)) {
    926 		return sym;
    927 	}
    928 
    929 	if (sym->flags & SDECLARED) {
    930 		errorp("duplicated member '%s'", name);
    931 		return sym;
    932 	}
    933 
    934 	if ((tp->prop & TDEFINED) == 0) {
    935 		if (tp->op == ARY && tp->n.elem == 0) {
    936 			if (n == 0)
    937 				errorp("flexible array member in a struct with no named members");
    938 			if (ahead() != '}')
    939 				errorp("flexible array member not at end of struct");
    940 		} else {
    941 			errorp("field '%s' has incomplete type", name);
    942 			tp = inttype;
    943 		}
    944 	}
    945 	if (tp->op == FTN) {
    946 		errorp("field '%s' declared as a function", name);
    947 		tp = inttype;
    948 	}
    949 	if (dcl->sclass)
    950 		errorp("storage class in struct/union field '%s'", name);
    951 
    952 	sym->type = tp;
    953 	sym->flags |= SFIELD|SDECLARED;
    954 
    955 	if (n == NR_FIELDS) {
    956 		errorp("too many fields in struct/union");
    957 		return sym;
    958 	}
    959 
    960 	DBG("DECL: New field '%s' in namespace %d\n", name, structp->ns);
    961 	structp->p.fields = xrealloc(structp->p.fields, ++n * sizeof(*sym));
    962 	structp->p.fields[n-1] = sym;
    963 	structp->n.elem = n;
    964 
    965 	return sym;
    966 }
    967 
    968 static Symbol *
    969 dodcl(int rep, Symbol *(*fun)(struct decl *), unsigned ns, Type *parent)
    970 {
    971 	Symbol *sym;
    972 	Type *base;
    973 	struct decl dcl;
    974 	struct declarators stack;
    975 
    976 	dcl.ns = ns;
    977 	dcl.parent = parent;
    978 	base = specifier(&dcl.sclass, &dcl.qualifier);
    979 
    980 	do {
    981 		dcl.type = base;
    982 		dcl.pars = NULL;
    983 		stack.nr_types = stack.nr = 0;
    984 		stack.tpars = dcl.buftpars;
    985 		stack.pars = dcl.bufpars;
    986 		stack.dcl = &dcl;
    987 		stack.ns = ns;
    988 
    989 		declarator(&stack);
    990 
    991 		while (pop(&stack, &dcl))
    992 			;
    993 		sym = (*fun)(&dcl);
    994 		if (funbody(sym, dcl.pars))
    995 			return sym;
    996 	} while (rep && accept(','));
    997 
    998 	return sym;
    999 }
   1000 
   1001 void
   1002 decl(void)
   1003 {
   1004 	Symbol *sym;
   1005 
   1006 	if (accept(';'))
   1007 		return;
   1008 
   1009 	sym = dodcl(REP, identifier, NS_IDEN, NULL);
   1010 	if ((sym->type->prop & TFUNDEF) == 0)
   1011 		expect(';');
   1012 }
   1013 
   1014 static void
   1015 fieldlist(Type *tp)
   1016 {
   1017 	if (yytoken != ';')
   1018 		dodcl(REP, field, tp->ns, tp);
   1019 	expect(';');
   1020 }
   1021 
   1022 Type *
   1023 typename(void)
   1024 {
   1025 	return dodcl(NOREP, type, NS_DUMMY, NULL)->type;
   1026 }