diff options
author | Michael Forney <mforney@mforney.org> | 2019-04-05 19:42:44 -0700 |
---|---|---|
committer | Michael Forney <mforney@mforney.org> | 2019-04-06 12:01:51 -0700 |
commit | a8961c59fcc0c92806af1853b93c1bc69259ce5f (patch) | |
tree | 6b09b6a4ada1f153a02f82c1d6244b156e532f19 | |
parent | 952b5b29818a1f9c36736c7d04f03309a4e1b5a5 (diff) | |
download | cproc-a8961c59fcc0c92806af1853b93c1bc69259ce5f.tar.xz |
Track type qualifiers separately
Using a special qualified type kind has a number of problems:
- Important fields such as size, align, and incomplete may not be set,
since the qualified type was created before a struct was completed.
- When we don't care about type qualifiers (which is the usual case),
we have to explicitly unqualify the type which is annoying and
error-prone.
Instead, in derived types, keep track of the qualifiers of the base type
alongside the base type (similar to what is done for members, parameters,
declarations, and expressions in the past few commits).
-rw-r--r-- | cc.h | 15 | ||||
-rw-r--r-- | decl.c | 166 | ||||
-rw-r--r-- | expr.c | 44 | ||||
-rw-r--r-- | init.c | 5 | ||||
-rw-r--r-- | qbe.c | 2 | ||||
-rw-r--r-- | type.c | 52 |
6 files changed, 128 insertions, 156 deletions
@@ -132,7 +132,6 @@ enum typequal { enum typekind { TYPENONE, - TYPEQUALIFIED, TYPEVOID, TYPEBASIC, TYPEPOINTER, @@ -187,12 +186,11 @@ struct type { struct type *base; struct list link; /* used only during construction of type */ }; + /* qualifiers of the base type */ + enum typequal qual; _Bool incomplete; union { struct { - enum typequal kind; - } qualified; - struct { enum { BASICBOOL, BASICCHAR, @@ -389,9 +387,8 @@ _Bool consume(int); /* type */ struct type *mktype(enum typekind); -struct type *mkqualifiedtype(struct type *, enum typequal); -struct type *mkpointertype(struct type *); -struct type *mkarraytype(struct type *, uint64_t); +struct type *mkpointertype(struct type *, enum typequal); +struct type *mkarraytype(struct type *, enum typequal, uint64_t); _Bool typecompatible(struct type *, struct type *); _Bool typesame(struct type *, struct type *); @@ -403,7 +400,7 @@ struct type *typeintpromote(struct type *); enum typeprop typeprop(struct type *); struct member *typemember(struct type *, const char *, uint64_t *); -struct param *mkparam(char *, struct type *); +struct param *mkparam(char *, struct type *, enum typequal); extern struct type typevoid; extern struct type typebool; @@ -419,7 +416,7 @@ extern struct type typevalist, typevalistptr; struct decl *mkdecl(enum declkind, struct type *, enum typequal, enum linkage); _Bool decl(struct scope *, struct func *); -struct type *typename(struct scope *); +struct type *typename(struct scope *, enum typequal *); struct decl *stringdecl(struct expr *); @@ -12,6 +12,11 @@ static struct list tentativedefns = {&tentativedefns, &tentativedefns}; +struct qualtype { + struct type *type; + enum typequal qual; +}; + enum storageclass { SCNONE, @@ -60,7 +65,6 @@ mkdecl(enum declkind k, struct type *t, enum typequal tq, enum linkage linkage) { struct decl *d; - assert(t->kind != TYPEQUALIFIED); d = xmalloc(sizeof(*d)); d->kind = k; d->linkage = linkage; @@ -227,11 +231,12 @@ tagspec(struct scope *s) } /* 6.7 Declarations */ -static struct type * +static struct qualtype declspecs(struct scope *s, enum storageclass *sc, enum funcspec *fs, int *align) { struct type *t, *other; struct decl *d; + struct expr *e; enum typespec ts = SPECNONE; enum typequal tq = QUALNONE; int ntypes = 0; @@ -330,9 +335,13 @@ declspecs(struct scope *s, enum storageclass *sc, enum funcspec *fs, int *align) case T__TYPEOF__: next(); expect(TLPAREN, "after '__typeof__'"); - t = typename(s); - if (!t) - t = expr(s)->type; + t = typename(s, &tq); + if (!t) { + e = expr(s); + t = e->type; + tq |= e->qual; + delexpr(e); + } ++ntypes; expect(TRPAREN, "to close '__typeof__'"); break; @@ -343,7 +352,7 @@ declspecs(struct scope *s, enum storageclass *sc, enum funcspec *fs, int *align) error(&tok.loc, "alignment specifier not allowed in this declaration"); next(); expect(TLPAREN, "after '_Alignas'"); - other = typename(s); + other = typename(s, NULL); if (other) { *align = other->align; } else { @@ -399,7 +408,7 @@ done: if (!t && (tq || (sc && *sc) || (fs && *fs))) error(&tok.loc, "declaration has no type specifier"); - return mkqualifiedtype(t, tq); + return (struct qualtype){t, tq}; } /* 6.7.6 Declarators */ @@ -414,6 +423,12 @@ istypename(struct scope *s, const char *name) return d && d->kind == DECLTYPE; } +/* +When parsing a declarator, qualifiers for derived types are temporarily +stored in the `qual` field of the type itself (elsewhere this field +is used for the qualifiers of the base type). This is corrected in +declarator(). +*/ static void declaratortypes(struct scope *s, struct list *result, char **name, bool allowabstract) { @@ -424,15 +439,11 @@ declaratortypes(struct scope *s, struct list *result, char **name, bool allowabs enum typequal tq; while (consume(TMUL)) { - t = mkpointertype(NULL); - listinsert(result, &t->link); tq = QUALNONE; while (typequal(&tq)) ; - if (tq) { - t = mkqualifiedtype(NULL, tq); - listinsert(result, &t->link); - } + t = mkpointertype(NULL, tq); + listinsert(result, &t->link); } if (name) *name = NULL; @@ -461,6 +472,7 @@ declaratortypes(struct scope *s, struct list *result, char **name, bool allowabs next(); func: t = mktype(TYPEFUNC); + t->qual = QUALNONE; t->func.isprototype = false; t->func.isvararg = false; t->func.isnoreturn = false; @@ -471,7 +483,7 @@ declaratortypes(struct scope *s, struct list *result, char **name, bool allowabs if (!istypename(s, tok.lit)) { /* identifier-list (K&R declaration) */ do { - *p = mkparam(tok.lit, NULL); + *p = mkparam(tok.lit, NULL, QUALNONE); p = &(*p)->next; next(); if (!consume(TCOMMA)) @@ -520,11 +532,7 @@ declaratortypes(struct scope *s, struct list *result, char **name, bool allowabs i = intconstexpr(s, false); expect(TRBRACK, "after array length"); } - if (tq) { - t = mkqualifiedtype(NULL, tq); - listinsert(ptr->prev, &t->link); - } - t = mkarraytype(NULL, i); + t = mkarraytype(NULL, tq, i); listinsert(ptr->prev, &t->link); break; default: @@ -533,39 +541,38 @@ declaratortypes(struct scope *s, struct list *result, char **name, bool allowabs } } -static struct type * -declarator(struct scope *s, struct type *base, char **name, bool allowabstract) +static struct qualtype +declarator(struct scope *s, struct qualtype base, char **name, bool allowabstract) { struct type *t; + enum typequal tq; struct list result = {&result, &result}, *l, *prev; declaratortypes(s, &result, name, allowabstract); for (l = result.prev; l != &result; l = prev) { prev = l->prev; t = listelement(l, struct type, link); - t->base = base; + tq = t->qual; + t->base = base.type; + t->qual = base.qual; switch (t->kind) { case TYPEFUNC: - if (base->kind == TYPEFUNC) + if (base.type->kind == TYPEFUNC) error(&tok.loc, "function declarator specifies function return type"); - if (base->kind == TYPEARRAY) + if (base.type->kind == TYPEARRAY) error(&tok.loc, "function declarator specifies array return type"); break; case TYPEARRAY: - if (base->incomplete) + if (base.type->incomplete) error(&tok.loc, "array element has incomplete type"); - if (base->kind == TYPEFUNC) + if (base.type->kind == TYPEFUNC) error(&tok.loc, "array element has function type"); - t->align = base->align; - t->size = base->size * t->array.length; // XXX: overflow? - break; - case TYPEQUALIFIED: - t->align = base->align; - t->size = base->size; - t->repr = base->repr; + t->align = base.type->align; + t->size = base.type->size * t->array.length; // XXX: overflow? break; } - base = t; + base.type = t; + base.qual = tq; } return base; @@ -574,15 +581,12 @@ declarator(struct scope *s, struct type *base, char **name, bool allowabstract) static struct type * adjust(struct type *t) { - enum typequal tq = QUALNONE; - - t = typeunqual(t, &tq); switch (t->kind) { case TYPEARRAY: - t = mkqualifiedtype(mkpointertype(t->base), tq); + t = mkpointertype(t->base, t->qual); break; case TYPEFUNC: - t = mkpointertype(t); + t = mkpointertype(t, QUALNONE); break; } @@ -592,41 +596,38 @@ adjust(struct type *t) static struct param * parameter(struct scope *s) { - struct param *p; - struct type *t; + char *name; + struct qualtype t; enum storageclass sc; t = declspecs(s, &sc, NULL, NULL); - if (!t) + if (!t.type) error(&tok.loc, "no type in parameter declaration"); if (sc && sc != SCREGISTER) error(&tok.loc, "parameter declaration has invalid storage-class specifier"); - p = mkparam(NULL, t); - p->type = typeunqual(adjust(declarator(s, p->type, &p->name, true)), &p->qual); + t = declarator(s, t, &name, true); - return p; + return mkparam(name, adjust(t.type), t.qual); } static bool paramdecl(struct scope *s, struct param *params) { struct param *p; - struct type *t, *base; + struct qualtype t, base; char *name; base = declspecs(s, NULL, NULL, NULL); - if (!base) + if (!base.type) return false; for (;;) { - t = adjust(declarator(s, base, &name, false)); - for (p = params; p; p = p->next) { - if (strcmp(name, p->name) == 0) { - p->type = typeunqual(t, &p->qual); - break; - } - } + t = declarator(s, base, &name, false); + for (p = params; p && strcmp(name, p->name) != 0; p = p->next) + ; if (!p) error(&tok.loc, "old-style function declarator has no parameter named '%s'", name); + p->type = adjust(t.type); + p->qual = t.qual; if (tok.kind == TSEMICOLON) break; expect(TCOMMA, "or ';' after parameter declarator"); @@ -636,17 +637,17 @@ paramdecl(struct scope *s, struct param *params) } static void -addmember(struct structbuilder *b, struct type *mt, char *name, int align, uint64_t width) +addmember(struct structbuilder *b, struct qualtype mt, char *name, int align, uint64_t width) { struct type *t = b->type; struct member *m; size_t end; - assert(mt->align > 0); + assert(mt.type->align > 0); if (name || width == -1) { m = xmalloc(sizeof(*m)); - m->qual = QUALNONE; - m->type = typeunqual(mt, &m->qual); + m->type = mt.type; + m->qual = mt.qual; m->name = name; m->next = NULL; *b->last = m; @@ -655,41 +656,41 @@ addmember(struct structbuilder *b, struct type *mt, char *name, int align, uint6 if (width == -1) { m->bits.before = 0; m->bits.after = 0; - if (align < mt->align) - align = mt->align; + if (align < mt.type->align) + align = mt.type->align; t->size = ALIGNUP(t->size, align); if (t->kind == TYPESTRUCT) { m->offset = t->size; - t->size += mt->size; + t->size += mt.type->size; } else { m->offset = 0; - if (t->size < mt->size) - t->size = mt->size; + if (t->size < mt.type->size) + t->size = mt.type->size; } } else { /* bit-field */ - if (!(typeprop(mt) & PROPINT)) + if (!(typeprop(mt.type) & PROPINT)) error(&tok.loc, "bit-field has invalid type"); if (align) error(&tok.loc, "alignment specified for bit-field"); if (!width && name) error(&tok.loc, "bit-field with zero width must not have declarator"); - if (width > mt->size * 8) + if (width > mt.type->size * 8) error(&tok.loc, "bit-field exceeds width of underlying type"); /* calculate end of the storage-unit for this bit-field */ - end = ALIGNUP(t->size, mt->size); + end = ALIGNUP(t->size, mt.type->size); if (!width || width > (end - t->size) * 8 + b->bits) { /* no room, allocate a new storage-unit */ t->size = end; b->bits = 0; } if (width) { - m->offset = ALIGNDOWN(t->size - !!b->bits, mt->size); + m->offset = ALIGNDOWN(t->size - !!b->bits, mt.type->size); m->bits.before = (t->size - m->offset) * 8 - b->bits; - m->bits.after = mt->size * 8 - width - m->bits.before; + m->bits.after = mt.type->size * 8 - width - m->bits.before; t->size += (width - b->bits + 7) / 8; b->bits = m->bits.after % 8; } - align = mt->align; + align = mt.type->align; } if (t->align < align) t->align = align; @@ -698,16 +699,16 @@ addmember(struct structbuilder *b, struct type *mt, char *name, int align, uint6 static void structdecl(struct scope *s, struct structbuilder *b) { - struct type *base, *mt; + struct qualtype base, mt; char *name; uint64_t width; int align; base = declspecs(s, NULL, NULL, &align); - if (!base) + if (!base.type) error(&tok.loc, "no type in struct member declaration"); if (tok.kind == TSEMICOLON) { - if ((base->kind != TYPESTRUCT && base->kind != TYPEUNION) || base->structunion.tag) + if ((base.type->kind != TYPESTRUCT && base.type->kind != TYPEUNION) || base.type->structunion.tag) error(&tok.loc, "struct declaration must declare at least one member"); next(); addmember(b, base, NULL, align, -1); @@ -731,18 +732,24 @@ structdecl(struct scope *s, struct structbuilder *b) /* 6.7.7 Type names */ struct type * -typename(struct scope *s) +typename(struct scope *s, enum typequal *tq) { - struct type *t; + struct qualtype t; t = declspecs(s, NULL, NULL, NULL); - return t ? declarator(s, t, NULL, true) : NULL; + if (t.type) { + t = declarator(s, t, NULL, true); + if (tq) + *tq |= t.qual; + } + return t.type; } bool decl(struct scope *s, struct func *f) { - struct type *t, *base; + struct qualtype base, qt; + struct type *t; enum typequal tq; enum storageclass sc; enum funcspec fs; @@ -768,7 +775,7 @@ decl(struct scope *s, struct func *f) return true; } base = declspecs(s, &sc, &fs, &align); - if (!base) + if (!base.type) return false; if (!f) { /* 6.9p2 */ @@ -782,8 +789,9 @@ decl(struct scope *s, struct func *f) return true; } for (;;) { - tq = QUALNONE; - t = typeunqual(declarator(s, base, &name, false), &tq); + qt = declarator(s, base, &name, false); + t = qt.type; + tq = qt.qual; kind = sc & SCTYPEDEF ? DECLTYPE : t->kind == TYPEFUNC ? DECLFUNC : DECLOBJECT; d = scopegetdecl(s, name, false); if (d && d->kind != kind) @@ -17,7 +17,7 @@ mkexpr(enum exprkind k, struct type *t) e = xmalloc(sizeof(*e)); e->qual = QUALNONE; - e->type = t ? typeunqual(t, &e->qual) : NULL; + e->type = t; e->lvalue = false; e->decayed = false; e->kind = k; @@ -58,8 +58,7 @@ decay(struct expr *e) switch (t->kind) { case TYPEARRAY: e = mkunaryexpr(TBAND, e); - e->type = mkpointertype(t->base); - e->qual = tq; + e->type = mkpointertype(t->base, tq); e->decayed = true; break; case TYPEFUNC: @@ -82,7 +81,7 @@ mkunaryexpr(enum tokenkind op, struct expr *base) base->decayed = false; return base; } - expr = mkexpr(EXPRUNARY, mkpointertype(mkqualifiedtype(base->type, base->qual))); + expr = mkexpr(EXPRUNARY, mkpointertype(base->type, base->qual)); expr->unary.op = op; expr->unary.base = base; return expr; @@ -90,6 +89,7 @@ mkunaryexpr(enum tokenkind op, struct expr *base) if (base->type->kind != TYPEPOINTER) error(&tok.loc, "cannot dereference non-pointer"); expr = mkexpr(EXPRUNARY, base->type->base); + expr->qual = base->type->qual; expr->lvalue = true; expr->unary.op = op; expr->unary.base = base; @@ -176,7 +176,7 @@ mkbinaryexpr(struct location *loc, enum tokenkind op, struct expr *l, struct exp t = l->type; r = mkbinaryexpr(loc, TMUL, exprconvert(r, &typeulong), mkconstexpr(&typeulong, t->base->size)); } else { - if (!typecompatible(typeunqual(l->type->base, NULL), typeunqual(r->type->base, NULL))) + if (!typecompatible(l->type->base, r->type->base)) error(&tok.loc, "pointer operands to '-' are to incompatible types"); op = TDIV; t = &typelong; @@ -320,7 +320,7 @@ primaryexpr(struct scope *s) next(); break; case TSTRINGLIT: - e = mkexpr(EXPRSTRING, mkarraytype(&typechar, 0)); + e = mkexpr(EXPRSTRING, mkarraytype(&typechar, QUALNONE, 0)); e->lvalue = true; e->string.size = 0; e->string.data = NULL; @@ -402,7 +402,7 @@ builtinfunc(struct scope *s, enum builtinkind kind) switch (kind) { case BUILTINALLOCA: - e = mkexpr(EXPRBUILTIN, mkpointertype(&typevoid)); + e = mkexpr(EXPRBUILTIN, mkpointertype(&typevoid, QUALNONE)); e->builtin.kind = BUILTINALLOCA; e->builtin.arg = exprconvert(assignexpr(s), &typeulong); break; @@ -423,7 +423,7 @@ builtinfunc(struct scope *s, enum builtinkind kind) e->constant.f = strtod("nan", NULL); break; case BUILTINOFFSETOF: - t = typename(s); + t = typename(s, NULL); expect(TCOMMA, "after type name"); name = expect(TIDENT, "after ','"); if (t->kind != TYPESTRUCT && t->kind != TYPEUNION) @@ -439,8 +439,7 @@ builtinfunc(struct scope *s, enum builtinkind kind) e->builtin.kind = BUILTINVAARG; e->builtin.arg = exprconvert(assignexpr(s), &typevalistptr); expect(TCOMMA, "after va_list"); - e->type = typename(s); - typeunqual(e->type, &e->qual); + e->type = typename(s, &e->qual); break; case BUILTINVACOPY: e = mkexpr(EXPRASSIGN, typevalist.base); @@ -547,15 +546,15 @@ postfixexpr(struct scope *s, struct expr *r) op = tok.kind; if (r->type->kind != TYPEPOINTER) error(&tok.loc, "arrow operator must be applied to pointer to struct/union"); - tq = QUALNONE; - t = typeunqual(r->type->base, &tq); + t = r->type->base; + tq = r->type->qual; if (t->kind != TYPESTRUCT && t->kind != TYPEUNION) error(&tok.loc, "arrow operator must be applied to pointer to struct/union"); next(); if (tok.kind != TIDENT) error(&tok.loc, "expected identifier after '->' operator"); lvalue = op == TARROW || r->unary.base->lvalue; - r = exprconvert(r, mkpointertype(&typechar)); + r = exprconvert(r, mkpointertype(&typechar, QUALNONE)); offset = 0; m = typemember(t, tok.lit, &offset); if (!m) @@ -563,7 +562,7 @@ postfixexpr(struct scope *s, struct expr *r) if (m->bits.before || m->bits.after) error(&tok.loc, "bit-field access is not yet supported"); r = mkbinaryexpr(&tok.loc, TADD, r, mkconstexpr(&typeulong, offset)); - r = exprconvert(r, mkpointertype(mkqualifiedtype(m->type, tq | m->qual))); + r = exprconvert(r, mkpointertype(m->type, tq | m->qual)); e = mkunaryexpr(TMUL, r); e->lvalue = lvalue; next(); @@ -641,7 +640,7 @@ unaryexpr(struct scope *s) case T_ALIGNOF: next(); if (consume(TLPAREN)) { - t = typename(s); + t = typename(s, NULL); if (t) { expect(TRPAREN, "after type name"); /* might be part of a compound literal */ @@ -677,11 +676,13 @@ static struct expr * castexpr(struct scope *s) { struct type *t; + enum typequal tq; struct expr *r, *e, **end; end = &r; while (consume(TLPAREN)) { - t = typename(s); + tq = QUALNONE; + t = typename(s, &tq); if (!t) { e = expr(s); expect(TRPAREN, "after expression to match '('"); @@ -691,6 +692,7 @@ castexpr(struct scope *s) expect(TRPAREN, "after type name"); if (tok.kind == TLBRACE) { e = mkexpr(EXPRCOMPOUND, t); + e->qual = tq; e->lvalue = true; e->compound.init = parseinit(s, t); e = decay(e); @@ -796,9 +798,9 @@ condexpr(struct scope *s) } else if (nullpointer(e->cond.f) && t->kind == TYPEPOINTER) { e->type = t; } else if (t->kind == TYPEPOINTER && f->kind == TYPEPOINTER) { - tq = QUALNONE; - t = typeunqual(t->base, &tq); - f = typeunqual(f->base, &tq); + tq = t->qual | f->qual; + t = t->base; + f = f->base; if (t == &typevoid || f == &typevoid) { e->type = &typevoid; } else { @@ -806,7 +808,7 @@ condexpr(struct scope *s) error(&tok.loc, "operands of conditional operator must have compatible types"); e->type = typecomposite(t, f); } - e->type = mkpointertype(mkqualifiedtype(e->type, tq)); + e->type = mkpointertype(e->type, tq); } else { error(&tok.loc, "invalid operands to conditional operator"); } @@ -858,7 +860,7 @@ assignexpr(struct scope *s) r = assignexpr(s); if (op) { /* rewrite `E1 OP= E2` as `T = &E1, *T = *T OP E2`, where T is a temporary slot */ - tmp = mkexpr(EXPRTEMP, mkpointertype(l->type)); + tmp = mkexpr(EXPRTEMP, mkpointertype(l->type, l->qual)); tmp->lvalue = true; tmp->temp = NULL; e = mkexpr(EXPRCOMMA, l->type); @@ -78,7 +78,7 @@ subobj(struct initparser *p, struct type *t, uint64_t off) off += p->sub->offset; if (++p->sub == p->obj + LEN(p->obj)) fatal("internal error: too many designators"); - p->sub->type = typeunqual(t, NULL); + p->sub->type = t; p->sub->offset = off; p->sub->iscur = false; } @@ -206,7 +206,6 @@ parseinit(struct scope *s, struct type *t) struct expr *expr; struct type *base; - t = typeunqual(t, NULL); p.cur = NULL; p.sub = p.obj; p.sub->offset = 0; @@ -238,7 +237,7 @@ parseinit(struct scope *s, struct type *t) case TYPEARRAY: if (expr->decayed && expr->unary.base->kind == EXPRSTRING) { expr = expr->unary.base; - base = typeunqual(t->base, NULL); + base = t->base; /* XXX: wide string literals */ if (!(typeprop(base) & PROPCHAR)) error(&tok.loc, "array initializer is string literal with incompatible type"); @@ -378,7 +378,7 @@ mkfunc(char *name, struct type *t, struct scope *s) scopeputdecl(s, p->name, d); } - t = mkarraytype(mkqualifiedtype(&typechar, QUALCONST), strlen(name) + 1); + t = mkarraytype(&typechar, QUALCONST, strlen(name) + 1); d = mkdecl(DECLOBJECT, t, QUALNONE, LINKNONE); d->value = mkglobal("__func__", true); scopeputdecl(s, "__func__", d); @@ -46,31 +46,13 @@ mktype(enum typekind kind) } struct type * -mkqualifiedtype(struct type *base, enum typequal tq) -{ - struct type *t; - - if (!tq) - return base; - t = mktype(TYPEQUALIFIED); - t->base = base; - t->qualified.kind = tq; - if (base) { - t->size = base->size; - t->align = base->align; - t->repr = base->repr; - } - // XXX: incomplete? - return t; -} - -struct type * -mkpointertype(struct type *base) +mkpointertype(struct type *base, enum typequal qual) { struct type *t; t = mktype(TYPEPOINTER); t->base = base; + t->qual = qual; t->size = 8; t->align = 8; t->repr = &i64; @@ -79,12 +61,13 @@ mkpointertype(struct type *base) } struct type * -mkarraytype(struct type *base, uint64_t len) +mkarraytype(struct type *base, enum typequal qual, uint64_t len) { struct type *t; t = mktype(TYPEARRAY); t->base = base; + t->qual = qual; t->array.length = len; t->incomplete = !len; if (t->base) { @@ -176,20 +159,16 @@ typecompatible(struct type *t1, struct type *t2) each other (unless they are the same type) */ return t1->basic.kind == BASICENUM && t2->basic.kind == BASICINT || t1->basic.kind == BASICINT && t2->basic.kind == BASICENUM; - case TYPEQUALIFIED: - if (t1->qualified.kind != t2->qualified.kind) - return false; - return typecompatible(t1->base, t2->base); case TYPEVOID: return true; case TYPEPOINTER: - return typecompatible(t1->base, t2->base); + return t1->qual == t2->qual && typecompatible(t1->base, t2->base); case TYPEARRAY: if (t1->array.length && t2->array.length && t1->array.length != t2->array.length) return false; - return typecompatible(t1->base, t2->base); + return t1->qual == t2->qual && typecompatible(t1->base, t2->base); case TYPEFUNC: - if (!typecompatible(t1->base, t2->base)) + if (t1->qual != t2->qual || !typecompatible(t1->base, t2->base)) return false; if (!t1->func.isprototype) { if (!t2->func.isprototype) @@ -233,20 +212,8 @@ typecomposite(struct type *t1, struct type *t2) } struct type * -typeunqual(struct type *t, enum typequal *tq) -{ - while (t->kind == TYPEQUALIFIED) { - if (tq) - *tq |= t->qualified.kind; - t = t->base; - } - return t; -} - -struct type * typeintpromote(struct type *t) { - assert(t->kind != TYPEQUALIFIED); if (typeprop(t) & PROPINT && typerank(t) <= typerank(&typeint)) return t->size < typeint.size || t->basic.issigned ? &typeint : &typeuint; return t; @@ -255,7 +222,6 @@ typeintpromote(struct type *t) struct type * typeargpromote(struct type *t) { - assert(t->kind != TYPEQUALIFIED); if (t == &typefloat) return &typedouble; return typeintpromote(t); @@ -321,14 +287,14 @@ typemember(struct type *t, const char *name, uint64_t *offset) } struct param * -mkparam(char *name, struct type *t) +mkparam(char *name, struct type *t, enum typequal tq) { struct param *p; p = xmalloc(sizeof(*p)); p->name = name; p->type = t; - p->qual = QUALNONE; + p->qual = tq; p->next = NULL; return p; |