expr.c - scc - simple c99 compiler
 (HTM) git clone git://git.simple-cc.org/scc
 (DIR) Log
 (DIR) Files
 (DIR) Refs
 (DIR) Submodules
 (DIR) README
 (DIR) LICENSE
       ---
       expr.c (21695B)
       ---
            1 #include <assert.h>
            2 #include <stdlib.h>
            3 #include <string.h>
            4 
            5 #include <scc/cstd.h>
            6 #include <scc/scc.h>
            7 #include "cc1.h"
            8 
            9 #define XCHG(lp, rp, np) (np = lp, lp = rp, rp = np)
           10 
           11 int
           12 power2node(Node *np, int *log)
           13 {
           14         int n;
           15         TUINT u;
           16         Symbol *sym;
           17 
           18         if (!np || !(np->flags & NCONST) || !np->sym)
           19                 return 0;
           20 
           21         sym = np->sym;
           22         if (sym->type->op != INT)
           23                 return 0;
           24 
           25         n = 0;
           26         for (u = sym->u.u; u; u >>= 1) {
           27                 if (u & 1)
           28                         n++;
           29         }
           30 
           31         if (log)
           32                 *log = n;
           33 
           34         return n == 1;
           35 }
           36 
           37 int
           38 cmpnode(Node *np, TUINT val)
           39 {
           40         Symbol *sym;
           41         Type *tp;
           42         TUINT mask, nodeval;
           43 
           44         if (!np || !(np->flags & NCONST) || !np->sym)
           45                 return 0;
           46         sym = np->sym;
           47         tp = sym->type;
           48 
           49         switch (tp->op) {
           50         case PTR:
           51         case INT:
           52                 mask = (val > 1) ? ones(np->type->size) : -1;
           53                 nodeval = (tp->prop & TSIGNED) ? sym->u.i : sym->u.u;
           54                 return (nodeval & mask) == (val & mask);
           55         case FLOAT:
           56                 return sym->u.f == val;
           57         }
           58         return 0;
           59 }
           60 
           61 static Node *
           62 promote(Node *np)
           63 {
           64         Type *tp;
           65         Node *new;
           66         struct limits *lim, *ilim;
           67 
           68         tp = np->type;
           69 
           70         switch (tp->op) {
           71         case ENUM:
           72         case INT:
           73                 if (tp->n.rank >= inttype->n.rank)
           74                         return np;
           75                 lim = getlimits(tp);
           76                 ilim = getlimits(inttype);
           77                 tp = (lim->max.i <= ilim->max.i) ? inttype : uinttype;
           78                 break;
           79         case FLOAT:
           80                 /* TODO: Add support for C99 float math */
           81                 tp = doubletype;
           82                 break;
           83         default:
           84                 abort();
           85         }
           86         if ((new = convert(np, tp, 1)) != NULL)
           87                 return new;
           88         return np;
           89 }
           90 
           91 static void
           92 arithconv(Node **p1, Node **p2)
           93 {
           94         int to = 0, s1, s2;
           95         unsigned r1, r2;
           96         Type *tp1, *tp2;
           97         Node *np1, *np2;
           98         struct limits *lp1, *lp2;
           99 
          100         np1 = promote(*p1);
          101         np2 = promote(*p2);
          102 
          103         tp1 = np1->type;
          104         tp2 = np2->type;
          105 
          106         if (tp1 == tp2)
          107                 goto set_p1_p2;
          108 
          109         s1 = (tp1->prop & TSIGNED) != 0;
          110         r1 = tp1->n.rank;
          111         lp1 = getlimits(tp1);
          112 
          113         s2 = (tp2->prop & TSIGNED) != 0;
          114         r2 = tp2->n.rank;
          115         lp2 = getlimits(tp2);
          116 
          117         if (s1 == s2 || tp1->op == FLOAT || tp2->op == FLOAT) {
          118                 to = r1 - r2;
          119         } else if (!s1) {
          120                 if (r1 >= r2 || lp1->max.i >= lp2->max.i)
          121                         to = 1;
          122                 else
          123                         to = -1;
          124         } else {
          125                 if (r2 >= r1 || lp2->max.i >= lp1->max.i)
          126                         to = -1;
          127                 else
          128                         to = 1;
          129         }
          130 
          131         if (to > 0)
          132                 np2 = convert(np2, tp1, 1);
          133         else if (to < 0)
          134                 np1 = convert(np1, tp2, 1);
          135                 
          136 set_p1_p2:
          137         *p1 = np1;
          138         *p2 = np2;
          139 }
          140 
          141 static int
          142 null(Node *np)
          143 {
          144         if (np->type != pvoidtype)
          145                 return 0;
          146 
          147         switch (np->op) {
          148         case OCAST:
          149                 np = np->left;
          150                 if (np->type != inttype)
          151                         return 0;
          152         case OSYM:
          153                 return cmpnode(np, 0);
          154         default:
          155                 return 0;
          156         }
          157 }
          158 
          159 static Node *
          160 chkternary(Node *yes, Node *no)
          161 {
          162         /*
          163          * FIXME:
          164          * We are ignoring type qualifiers here,
          165          * but the standard has strong rules about this.
          166          * take a look to 6.5.15
          167          */
          168 
          169         if (!eqtype(yes->type, no->type, EQUIV)) {
          170                 if ((yes->type->prop & TARITH) && (no->type->prop & TARITH)) {
          171                         arithconv(&yes, &no);
          172                 } else if (yes->type->op != PTR && no->type->op != PTR) {
          173                         goto wrong_type;
          174                 } else {
          175                         /* convert integer 0 to NULL */
          176                         if ((yes->type->prop & TINTEGER) && cmpnode(yes, 0))
          177                                 yes = convert(yes, pvoidtype, 0);
          178                         if ((no->type->prop & TINTEGER) && cmpnode(no, 0))
          179                                 no = convert(no, pvoidtype, 0);
          180                         /*
          181                          * At this point the type of both should be
          182                          * a pointer to something, or we have don't
          183                          * compatible types
          184                          */
          185                         if (yes->type->op != PTR || no->type->op != PTR)
          186                                 goto wrong_type;
          187                         /*
          188                          * If we have a null pointer constant then
          189                          * convert to the another type
          190                          */
          191                         if (null(yes))
          192                                 yes = convert(yes, no->type, 0);
          193                         if (null(no))
          194                                 no = convert(no, yes->type, 0);
          195 
          196                         if (!eqtype(yes->type, no->type, EQUIV))
          197                                 goto wrong_type;
          198                 }
          199         }
          200         return node(OCOLON, yes->type, yes, no);
          201 
          202 wrong_type:
          203         errorp("type mismatch in conditional expression");
          204         freetree(yes);
          205         freetree(no);
          206         return constnode(zero);
          207 }
          208 
          209 static void
          210 chklvalue(Node *np)
          211 {
          212         if (!(np->flags & NLVAL))
          213                 errorp("lvalue required in operation");
          214         if (np->type == voidtype)
          215                 errorp("invalid use of void expression");
          216 }
          217 
          218 static Node *
          219 chkconstaddr(Node *var, Node *addr)
          220 {
          221         unsigned mask = SGLOBAL|SLOCAL|SPRIVATE|SEXTERN;
          222 
          223         if (var->sym && var->sym->flags & mask
          224         || var->op == OFIELD && var->left->op == OSYM
          225         || var->op == OFIELD && (var->left->flags & NCONST)) {
          226                 addr->flags |= NCONST;
          227         }
          228 
          229         return addr;
          230 }
          231 
          232 Node *
          233 decay(Node *np)
          234 {
          235         Node *new;
          236         Type *tp = np->type;
          237 
          238         switch (tp->op) {
          239         case ARY:
          240                 DBG("EXPR decay ary");
          241                 tp = tp->type;
          242                 if (np->op != OPTR)
          243                         goto new_node;
          244                 new = np->left;
          245                 free(np);
          246                 new->type = mktype(tp, PTR, 0, NULL);
          247                 return chkconstaddr(new, new);
          248         case FTN:
          249                 DBG("EXPR decay function");
          250         new_node:
          251                 new = node(OADDR, mktype(tp, PTR, 0, NULL), np, NULL);
          252                 new->flags |= NDECAY;
          253                 return chkconstaddr(np, new);
          254         default:
          255                 return np;
          256         }
          257 }
          258 
          259 static Node *
          260 integerop(int op, Node *lp, Node *rp)
          261 {
          262         if (!(lp->type->prop & TINTEGER) || !(rp->type->prop & TINTEGER))
          263                 error("operator requires integer operands");
          264 
          265 
          266         switch (op) {
          267         case OA_MOD:
          268         case OA_SHL:
          269         case OA_SHR:
          270         case OA_AND:
          271         case OA_XOR:
          272         case OA_OR:
          273                 rp = convert(rp, lp->type, 0);
          274                 break;
          275         default:
          276                 arithconv(&lp, &rp);
          277                 break;
          278         }
          279 
          280         return node(op, lp->type, lp, rp);
          281 }
          282 
          283 static Node *
          284 integeruop(int op, Node *np)
          285 {
          286         if (!(np->type->prop & TINTEGER))
          287                 error("unary operator requires integer operand");
          288         np = promote(np);
          289         return node(op, np->type, np, NULL);
          290 }
          291 
          292 static Node *
          293 numericaluop(int op, Node *np)
          294 {
          295         if (!(np->type->prop & TARITH))
          296                 error("unary operator requires numerical operand");
          297         np = promote(np);
          298         return node(op, np->type, np, NULL);
          299 }
          300 
          301 Node *
          302 convert(Node *np, Type *newtp, int iscast)
          303 {
          304         Type *oldtp = np->type;
          305         int op = newtp->op;
          306 
          307         if (eqtype(newtp, oldtp, EQUAL))
          308                 return np;
          309         if (iscast && op == VOID)
          310                 goto good_conv;
          311 
          312         switch (oldtp->op) {
          313         case ENUM:
          314         case INT:
          315                 if (op == PTR && (iscast || cmpnode(np, 0)))
          316                         goto good_conv;
          317         case FLOAT:
          318                 if (op == INT || op == FLOAT || op == ENUM)
          319                         goto good_conv;
          320                 return NULL;
          321         case PTR:
          322                 if (op == ENUM || op == INT) {
          323                         if (iscast)
          324                                 goto good_conv;
          325                 } else if (op == PTR) {
          326                         if (eqtype(newtp, oldtp, EQUIV))
          327                                 goto good_ptr_conv;
          328                         if (iscast)
          329                                 goto good_ptr_conv;
          330                         if (newtp == pvoidtype || oldtp == pvoidtype)
          331                                 goto good_ptr_conv;
          332                 }
          333         default:
          334                 return NULL;
          335         }
          336 
          337 good_ptr_conv:
          338         np->type = newtp;
          339         return np;
          340 
          341 good_conv:
          342         return node(OCAST, newtp, np, NULL);
          343 }
          344 
          345 static Node *
          346 parithmetic(int op, Node *lp, Node *rp)
          347 {
          348         Type *tp;
          349         Node *size, *np;
          350 
          351         if (lp->type->op != PTR)
          352                 XCHG(lp, rp, np);
          353 
          354         tp = rp->type;
          355         if (tp->op == PTR && !(tp->type->prop & TDEFINED))
          356                 goto incomplete;
          357         tp = lp->type;
          358         if (!(tp->type->prop & TDEFINED))
          359                 goto incomplete;
          360         size = sizeofnode(tp->type);
          361 
          362         if (op == OSUB && BTYPE(rp) == PTR) {
          363                 if ((rp = convert(rp, lp->type, 0)) == NULL)
          364                         goto incorrect;
          365                 lp = node(OSUB, pdifftype, lp, rp);
          366                 return node(ODIV, inttype, lp, size);
          367         }
          368         if (!(rp->type->prop & TINTEGER))
          369                 goto incorrect;
          370 
          371         rp = convert(promote(rp), sizettype, 0);
          372         rp = node(OMUL, sizettype, rp, size);
          373         rp = convert(rp, tp, 1);
          374 
          375         return node(op, tp, lp, rp);
          376 
          377 incomplete:
          378         errorp("invalid use of undefined type");
          379         return lp;
          380 incorrect:
          381         errorp("incorrect arithmetic operands");
          382         return lp;
          383 
          384 }
          385 
          386 static Node *
          387 arithmetic(int op, Node *lp, Node *rp)
          388 {
          389         Node *np;
          390         Type *ltp = lp->type, *rtp = rp->type;
          391 
          392         if ((ltp->prop & TARITH) && (rtp->prop & TARITH)) {
          393                 switch (op) {
          394                 case OA_ADD:
          395                 case OA_SUB:
          396                 case OA_MUL:
          397                 case OA_DIV:
          398                         rp = convert(rp, lp->type, 0);
          399                         break;
          400                 default:
          401                         arithconv(&lp, &rp);
          402                         break;
          403                 }
          404                 return node(op, lp->type, lp, rp);
          405         } else if ((ltp->op == PTR || rtp->op == PTR)) {
          406                 switch (op) {
          407                 case OADD:
          408                 case OSUB:
          409                 case OA_ADD:
          410                 case OA_SUB:
          411                 case OINC:
          412                 case ODEC:
          413                         np = parithmetic(op, lp, rp);
          414                         if ((lp->flags&NCONST) && (rp->flags&NCONST))
          415                                 np->flags |= NCONST;
          416                         return np;
          417                 }
          418         }
          419         errorp("incorrect arithmetic operands");
          420         return lp;
          421 }
          422 
          423 static Node *
          424 pcompare(int op, Node *lp, Node *rp)
          425 {
          426         Node *np;
          427 
          428         if (lp->type->prop&TINTEGER) {
          429                 if ((np = convert(lp, rp->type, 0)) == NULL)
          430                         errorp("incompatible types in comparison");
          431                 else
          432                         lp = np;
          433         }
          434         if (rp->type->prop&TINTEGER) {
          435                 if ((np = convert(rp, lp->type, 0)) == NULL)
          436                         errorp("incompatible types in comparison");
          437                 else
          438                         rp = np;
          439         }
          440 
          441         return convert(node(op, pvoidtype, lp, rp), inttype, 1);
          442 }
          443 
          444 static Node *
          445 compare(int op, Node *lp, Node *rp)
          446 {
          447         Type *ltp, *rtp;
          448 
          449         ltp = lp->type;
          450         rtp = rp->type;
          451 
          452         if (ltp->op == PTR || rtp->op == PTR) {
          453                 return pcompare(op, lp, rp);
          454         } else if ((ltp->prop & TARITH) && (rtp->prop & TARITH)) {
          455                 arithconv(&lp, &rp);
          456                 return convert(node(op, lp->type, lp, rp), inttype, 1);
          457         } else {
          458                 errorp("incompatible types in comparison");
          459                 freetree(lp);
          460                 freetree(rp);
          461                 return constnode(zero);
          462         }
          463 }
          464 
          465 int
          466 negop(int op)
          467 {
          468         switch (op) {
          469         case OEQ:  return ONE;
          470         case ONE:  return OEQ;
          471         case OLT:  return OGE;
          472         case OGE:  return OLT;
          473         case OLE:  return OGT;
          474         case OGT:  return OLE;
          475         default:   abort();
          476         }
          477         return op;
          478 }
          479 
          480 static Node *
          481 exp2cond(Node *np, int neg)
          482 {
          483         int op;
          484 
          485         if (np->type->prop & TAGGREG) {
          486                 errorp("used struct/union type value where scalar is required");
          487                 return constnode(zero);
          488         }
          489         switch (np->op) {
          490         case ONEG:
          491         case OOR:
          492         case OAND:
          493                 return (neg) ? node(ONEG, inttype, np, NULL) : np;
          494         case OEQ:
          495         case ONE:
          496         case OLT:
          497         case OGE:
          498         case OLE:
          499         case OGT:
          500                 if (neg)
          501                         np->op = negop(np->op);
          502                 return np;
          503         default:
          504                 op = (neg) ?  OEQ : ONE;
          505                 return compare(op, np, constnode(zero));
          506         }
          507 }
          508 
          509 static Node *
          510 logic(int op, Node *lp, Node *rp)
          511 {
          512         lp = exp2cond(lp, 0);
          513         rp = exp2cond(rp, 0);
          514         return node(op, inttype, lp, rp);
          515 }
          516 
          517 static Node *
          518 field(Node *np)
          519 {
          520         Symbol *sym;
          521 
          522         namespace = np->type->ns;
          523         next();
          524         namespace = NS_IDEN;
          525 
          526         sym = yylval.sym;
          527         if (yytoken != IDEN)
          528                 unexpected();
          529         next();
          530 
          531         if (!(np->type->prop & TAGGREG)) {
          532                 errorp("request for member '%s' in something not a structure or union",
          533                       yylval.sym->name);
          534                 goto free_np;
          535         }
          536         if ((sym->flags & SDECLARED) == 0) {
          537                 errorp("incorrect field in struct/union");
          538                 goto free_np;
          539         }
          540         np = node(OFIELD, sym->type, np, varnode(sym));
          541         np->flags |= NLVAL;
          542         return np;
          543 
          544 free_np:
          545         freetree(np);
          546         return constnode(zero);
          547 }
          548 
          549 static Node *
          550 content(int op, Node *np)
          551 {
          552         if (BTYPE(np) != PTR) {
          553                 errorp("invalid argument of memory indirection");
          554         } else {
          555                 np = node(op, np->type->type, np, NULL);
          556                 np->flags |= NLVAL;
          557         }
          558         return np;
          559 }
          560 
          561 static Node *
          562 array(Node *lp, Node *rp)
          563 {
          564         Type *tp;
          565         Node *np;
          566 
          567         if (!(lp->type->prop & TINTEGER) && !(rp->type->prop & TINTEGER))
          568                 error("array subscript is not an integer");
          569         np = arithmetic(OADD, lp, rp);
          570         tp = np->type;
          571         if (tp->op != PTR)
          572                 errorp("subscripted value is neither array nor pointer");
          573         return content(OPTR, np);
          574 }
          575 
          576 static Node *
          577 assignop(int op, Node *lp, Node *rp)
          578 {
          579         if ((rp = convert(rp, lp->type, 0)) == NULL) {
          580                 errorp("incompatible types when assigning");
          581                 return lp;
          582         }
          583 
          584         return node(op, lp->type, lp, rp);
          585 }
          586 
          587 static Node *
          588 incdec(Node *np, int op)
          589 {
          590         Type *tp = np->type;
          591         Node *inc;
          592 
          593         chklvalue(np);
          594         np->flags |= NEFFECT;
          595 
          596         if (!(tp->prop & TDEFINED)) {
          597                 errorp("invalid use of undefined type");
          598                 return np;
          599         } else if (tp->op == PTR && !(tp->type->prop & TDEFINED)) {
          600                 errorp("%s of pointer to an incomplete type",
          601                        (op == OINC || op == OA_ADD) ? "increment" : "decrement");
          602                 return np;
          603         } else if (tp->op == PTR || (tp->prop & TARITH)) {
          604                 inc = constnode(one);
          605         } else {
          606                 errorp("wrong type argument to increment or decrement");
          607                 return np;
          608         }
          609         return arithmetic(op, np, inc);
          610 }
          611 
          612 static Node *
          613 address(int op, Node *np)
          614 {
          615         Node *new;
          616         Type *tp;
          617         Symbol *sym = np->sym;
          618 
          619         if ((np->flags & NDECAY) != 0) {
          620                 new = np->left;
          621                 free(np);
          622                 np = new;
          623         }
          624         tp = np->type;
          625 
          626         /*
          627          * ansi c accepts & applied to a function name, and it generates
          628          * a function pointer
          629          */
          630         if (np->op == OSYM) {
          631                 if (tp->op == FTN)
          632                         return decay(np);
          633                 if (tp->op == ARY)
          634                         goto dont_check_lvalue;
          635         }
          636         chklvalue(np);
          637 
          638 dont_check_lvalue:
          639         if (sym && (sym->flags & SREGISTER))
          640                 errorp("address of register variable '%s' requested", yytext);
          641         new = node(op, mktype(tp, PTR, 0, NULL), np, NULL);
          642 
          643         return chkconstaddr(np, new);
          644 }
          645 
          646 static Node *
          647 negation(int op, Node *np)
          648 {
          649         if (!(np->type->prop & TARITH) && np->type->op != PTR) {
          650                 errorp("invalid argument of unary '!'");
          651                 return constnode(zero);
          652         }
          653         return exp2cond(np, 1);
          654 }
          655 
          656 static Symbol *
          657 adjstrings(Symbol *sym)
          658 {
          659         char *s, *t;
          660         size_t len, n;
          661         Type *tp;
          662 
          663         tp = sym->type;
          664         s = sym->u.s;
          665         for (len = tp->n.elem;; len += n) {
          666                 next();
          667                 if (yytoken != STRING)
          668                         break;
          669                 t = yylval.sym->u.s;
          670                 n = yylval.sym->type->n.elem - 1;
          671 
          672                 s = xrealloc(s, len + n);
          673                 memcpy(s + len - 1, t, n);
          674                 s[len + n - 1] = '\0';
          675         }
          676 
          677         if (tp->n.elem != len) {
          678                 sym->type = mktype(chartype, ARY, len, NULL);
          679                 sym->u.s = s;
          680         }
          681         return sym;
          682 }
          683 
          684 static Node *
          685 funcsym(Symbol *sym)
          686 {
          687         char *s;
          688         Node *np;
          689 
          690         sym = install(sym->ns, sym);
          691         s = curfun->name;
          692         np = constnode(newstring(s, strlen(s)+1));
          693         sym->type = np->type;
          694         sym->flags |= SHASINIT | SLOCAL | SUSED;
          695         emit(ODECL, sym);
          696         emit(OINIT, np);
          697 
          698         return varnode(sym);
          699 }
          700 
          701 /*************************************************************
          702  * grammar functions                                         *
          703  *************************************************************/
          704 static Node *
          705 primary(void)
          706 {
          707         Node *np;
          708         Symbol *sym;
          709         Node *(*fun)(Symbol *);
          710 
          711         sym = yylval.sym;
          712         switch (yytoken) {
          713         case STRING:
          714                 np = constnode(adjstrings(sym));
          715                 sym->flags |= SHASINIT;
          716                 emit(ODECL, sym);
          717                 emit(OINIT, np);
          718                 return varnode(sym);
          719         case BUILTIN:
          720                 fun = sym->u.fun;
          721                 next();
          722                 expect('(');
          723                 np = (*fun)(sym);
          724                 expect(')');
          725 
          726                 /* do not call to next */
          727                 return np;
          728         case CONSTANT:
          729                 np = constnode(sym);
          730                 break;
          731         case DEFINED:
          732                 np = defined();
          733                 break;
          734         case '(':
          735                 next();
          736                 np = expr();
          737                 expect(')');
          738 
          739                 /* do not call to next */
          740                 return np;
          741         case IDEN:
          742                 assert((sym->flags & SCONSTANT) == 0);
          743                 if ((sym->flags & SDECLARED) != 0) {
          744                         sym->flags |= SUSED;
          745                         np = varnode(sym);
          746                 } else if (namespace == NS_CPP) {
          747                         np = constnode(zero);
          748                 } else if (!strcmp(yytext, "__func__") && curctx > PARAMCTX) {
          749                         np = funcsym(sym);
          750                 } else {
          751                         errorp("'%s' undeclared", yytext);
          752                         sym->type = inttype;
          753                         sym = install(sym->ns, sym);
          754                         sym->flags |= SUSED;
          755                         np = varnode(sym);
          756                 }
          757                 break;
          758         default:
          759                 unexpected();
          760         }
          761         next();
          762 
          763         return np;
          764 }
          765 
          766 static Node *
          767 arguments(Node *np)
          768 {
          769         int toomany, n, op;
          770         Node *par = NULL, *arg;
          771         Type *argtype, *tp = np->type, *rettype;
          772         Type **targs = (Type *[]) {ellipsistype};
          773 
          774         if (tp->op == PTR && tp->type->op == FTN) {
          775                 np = content(OPTR, np);
          776                 tp = np->type;
          777         }
          778         if (tp->op != FTN) {
          779                 n = 1;
          780                 rettype = inttype;
          781                 errorp("function or function pointer expected");
          782         } else {
          783                 targs = tp->p.pars;
          784                 n = tp->n.elem;
          785                 rettype = tp->type;
          786         }
          787 
          788         expect('(');
          789         if (yytoken == ')')
          790                 goto no_pars;
          791         toomany = 0;
          792 
          793         do {
          794                 arg = assign();
          795                 argtype = *targs;
          796                 if (argtype == ellipsistype) {
          797                         n = 0;
          798                         switch (arg->type->op) {
          799                         case INT:
          800                                 arg = promote(arg);
          801                                 break;
          802                         case FLOAT:
          803                                 if (arg->type == floattype)
          804                                         arg = convert(arg, doubletype, 1);
          805                                 break;
          806                         }
          807                         par = node(OPAR, arg->type, par, arg);
          808                         continue;
          809                 }
          810                 if (--n < 0) {
          811                         if (!toomany)
          812                                 errorp("too many arguments in function call");
          813                         toomany = 1;
          814                         continue;
          815                 }
          816                 ++targs;
          817                 if ((arg = convert(arg, argtype, 0)) != NULL) {
          818                         par = node(OPAR, arg->type, par, arg);
          819                         continue;
          820                 }
          821                 errorp("incompatible type for argument %d in function call",
          822                        tp->n.elem - n);
          823         } while (accept(','));
          824 
          825 no_pars:
          826         expect(')');
          827         if (n > 0 && *targs != ellipsistype)
          828                 errorp("too few arguments in function call");
          829 
          830         op = (tp->prop&TELLIPSIS) ? OCALLE : OCALL;
          831         return node(op, rettype, np, par);
          832 }
          833 
          834 static Type *
          835 typeof(Node *np)
          836 {
          837         Node *new;
          838         Type *tp;
          839 
          840         if (np == NULL)
          841                 unexpected();
          842         if ((np->flags & NDECAY) != 0) {
          843                 new = np->left;
          844                 free(np);
          845                 np = new;
          846         }
          847         tp = np->type;
          848         freetree(np);
          849         return tp;
          850 }
          851 
          852 static Node *unary(void);
          853 
          854 static Type *
          855 sizeexp(void)
          856 {
          857         Type *tp;
          858 
          859         if (!accept('('))
          860                 return typeof(unary());
          861 
          862         switch (yytoken) {
          863         case TYPE:
          864         case TYPEIDEN:
          865                 tp = typename();
          866                 break;
          867         default:
          868                 tp = typeof(expr());
          869                 break;
          870         }
          871         expect(')');
          872 
          873         return tp;
          874 }
          875 
          876 static Node *
          877 postfix(Node *lp)
          878 {
          879         int op;
          880         Node *rp;
          881 
          882         for (;;) {
          883                 switch (yytoken) {
          884                 case '[':
          885                         next();
          886                         rp = expr();
          887                         expect(']');
          888                         lp = array(decay(lp), rp);
          889                         break;
          890                 case DEC:
          891                 case INC:
          892                         op = (yytoken == INC) ? OINC : ODEC;
          893                         lp = incdec(decay(lp), op);
          894                         next();
          895                         break;
          896 
          897                 case INDIR:
          898                         lp = content(OPTR, decay(lp));
          899                 case '.':
          900                         lp = field(decay(lp));
          901                         break;
          902                 case '(':
          903                         lp = arguments(decay(lp));
          904                         lp->flags |= NEFFECT;
          905                         break;
          906                 default:
          907                         return lp;
          908                 }
          909         }
          910 }
          911 
          912 static Node *cast(void);
          913 
          914 static Node *
          915 unary(void)
          916 {
          917         Node *(*fun)(int, Node *), *np;
          918         int op;
          919         Type *tp;
          920 
          921         switch (yytoken) {
          922         case '!': op = 0;     fun = negation;     break;
          923         case '+': op = OADD;  fun = numericaluop; break;
          924         case '-': op = OSNEG; fun = numericaluop; break;
          925         case '~': op = OCPL;  fun = integeruop;   break;
          926         case '&': op = OADDR; fun = address;      break;
          927         case '*': op = OPTR;  fun = content;      break;
          928         case SIZEOF:
          929                 next();
          930                 tp = sizeexp();
          931                 if (!(tp->prop & TDEFINED))
          932                         errorp("sizeof applied to an incomplete type");
          933                 return sizeofnode(tp);
          934         case INC:
          935         case DEC:
          936                 op = (yytoken == INC) ? OA_ADD : OA_SUB;
          937                 next();
          938                 np = incdec(unary(), op);
          939                 goto decay;
          940         case DEFINED:
          941                 return defined();
          942         default:
          943                 np = postfix(primary());
          944                 goto decay;
          945         }
          946 
          947         next();
          948         np = (*fun)(op, cast());
          949 
          950 decay:
          951         return decay(np);
          952 }
          953 
          954 static Node *
          955 cast(void)
          956 {
          957         Node *tmp, *np;
          958         Type *tp;
          959         static int nested;
          960 
          961         if (!accept('('))
          962                 return unary();
          963 
          964         switch (yytoken) {
          965         case TQUALIFIER:
          966         case TYPE:
          967         case TYPEIDEN:
          968                 tp = typename();
          969                 expect(')');
          970 
          971                 if (yytoken == '{')
          972                         return decay(initlist(tp));
          973 
          974                 switch (tp->op) {
          975                 case ARY:
          976                         error("cast specifies an array type");
          977                 default:
          978                         tmp = cast();
          979                         if ((np = convert(tmp,  tp, 1)) == NULL)
          980                                 error("bad type conversion requested");
          981                         np->flags &= ~NLVAL;
          982                 }
          983                 break;
          984         default:
          985                 if (nested == NR_SUBEXPR)
          986                         error("too many expressions nested by parentheses");
          987                 ++nested;
          988                 np = expr();
          989                 --nested;
          990                 expect(')');
          991                 np = postfix(np);
          992                 break;
          993         }
          994 
          995         return np;
          996 }
          997 
          998 static Node *
          999 mul(void)
         1000 {
         1001         Node *np, *(*fun)(int, Node *, Node *);
         1002         int op;
         1003 
         1004         np = cast();
         1005         for (;;) {
         1006                 switch (yytoken) {
         1007                 case '*': op = OMUL; fun = arithmetic; break;
         1008                 case '/': op = ODIV; fun = arithmetic; break;
         1009                 case '%': op = OMOD; fun = integerop;  break;
         1010                 default: return np;
         1011                 }
         1012                 next();
         1013                 np = (*fun)(op, np, cast());
         1014         }
         1015 }
         1016 
         1017 static Node *
         1018 add(void)
         1019 {
         1020         int op;
         1021         Node *np;
         1022 
         1023         np = mul();
         1024         for (;;) {
         1025                 switch (yytoken) {
         1026                 case '+': op = OADD; break;
         1027                 case '-': op = OSUB; break;
         1028                 default:  return np;
         1029                 }
         1030                 next();
         1031                 np = arithmetic(op, np, mul());
         1032         }
         1033 }
         1034 
         1035 static Node *
         1036 shift(void)
         1037 {
         1038         int op;
         1039         Node *np;
         1040 
         1041         np = add();
         1042         for (;;) {
         1043                 switch (yytoken) {
         1044                 case SHL: op = OSHL; break;
         1045                 case SHR: op = OSHR; break;
         1046                 default:  return np;
         1047                 }
         1048                 next();
         1049                 np = integerop(op, np, add());
         1050         }
         1051 }
         1052 
         1053 static Node *
         1054 relational(void)
         1055 {
         1056         int op;
         1057         Node *np;
         1058 
         1059         np = shift();
         1060         for (;;) {
         1061                 switch (yytoken) {
         1062                 case '<': op = OLT; break;
         1063                 case '>': op = OGT; break;
         1064                 case GE:  op = OGE; break;
         1065                 case LE:  op = OLE; break;
         1066                 default:  return np;
         1067                 }
         1068                 next();
         1069                 np = compare(op, np, shift());
         1070         }
         1071 }
         1072 
         1073 static Node *
         1074 eq(void)
         1075 {
         1076         int op;
         1077         Node *np;
         1078 
         1079         np = relational();
         1080         for (;;) {
         1081                 switch (yytoken) {
         1082                 case EQ: op = OEQ; break;
         1083                 case NE: op = ONE; break;
         1084                 default: return np;
         1085                 }
         1086                 next();
         1087                 np = compare(op, np, relational());
         1088         }
         1089 }
         1090 
         1091 static Node *
         1092 bit_and(void)
         1093 {
         1094         Node *np;
         1095 
         1096         np = eq();
         1097         while (accept('&'))
         1098                 np = integerop(OBAND, np, eq());
         1099         return np;
         1100 }
         1101 
         1102 static Node *
         1103 bit_xor(void)
         1104 {
         1105         Node *np;
         1106 
         1107         np = bit_and();
         1108         while (accept('^'))
         1109                 np = integerop(OBXOR,  np, bit_and());
         1110         return np;
         1111 }
         1112 
         1113 static Node *
         1114 bit_or(void)
         1115 {
         1116         Node *np;
         1117 
         1118         np = bit_xor();
         1119         while (accept('|'))
         1120                 np = integerop(OBOR, np, bit_xor());
         1121         return np;
         1122 }
         1123 
         1124 static Node *
         1125 and(void)
         1126 {
         1127         Node *np;
         1128 
         1129         np = bit_or();
         1130         while (accept(AND))
         1131                 np = logic(OAND, np, bit_or());
         1132         return np;
         1133 }
         1134 
         1135 static Node *
         1136 or(void)
         1137 {
         1138         Node *np;
         1139 
         1140         np = and();
         1141         while (accept(OR))
         1142                 np = logic(OOR, np, and());
         1143         return np;
         1144 }
         1145 
         1146 static Node *
         1147 ternary(void)
         1148 {
         1149         Node *cond;
         1150 
         1151         cond = or();
         1152         while (accept('?')) {
         1153                 Node *ifyes, *ifno, *np;
         1154 
         1155                 cond = exp2cond(cond, 0);
         1156                 ifyes = expr();
         1157                 expect(':');
         1158                 ifno = ternary();
         1159                 np = chkternary(ifyes, ifno);
         1160                 cond = node(OASK, np->type, cond, np);
         1161         }
         1162         return cond;
         1163 }
         1164 
         1165 Node *
         1166 assign(void)
         1167 {
         1168         Node *np, *(*fun)(int , Node *, Node *);
         1169         int op;
         1170 
         1171         np = ternary();
         1172         for (;;) {
         1173                 switch (yytoken) {
         1174                 case '=':    op = OASSIGN; fun = assignop;   break;
         1175                 case MUL_EQ: op = OA_MUL;  fun = arithmetic; break;
         1176                 case DIV_EQ: op = OA_DIV;  fun = arithmetic; break;
         1177                 case MOD_EQ: op = OA_MOD;  fun = integerop;  break;
         1178                 case ADD_EQ: op = OA_ADD;  fun = arithmetic; break;
         1179                 case SUB_EQ: op = OA_SUB;  fun = arithmetic; break;
         1180                 case SHL_EQ: op = OA_SHL;  fun = integerop;  break;
         1181                 case SHR_EQ: op = OA_SHR;  fun = integerop;  break;
         1182                 case AND_EQ: op = OA_AND;  fun = integerop;  break;
         1183                 case XOR_EQ: op = OA_XOR;  fun = integerop;  break;
         1184                 case OR_EQ:  op = OA_OR;   fun = integerop;  break;
         1185                 default: return np;
         1186                 }
         1187                 chklvalue(np);
         1188                 np->flags |= NEFFECT;
         1189                 next();
         1190                 np = (fun)(op, np, assign());
         1191         }
         1192 }
         1193 
         1194 Node *
         1195 expr(void)
         1196 {
         1197         Node *lp, *rp;
         1198 
         1199         lp = assign();
         1200         while (accept(',')) {
         1201                 rp = assign();
         1202                 lp = node(OCOMMA, rp->type, lp, rp);
         1203         }
         1204 
         1205         return lp;
         1206 }
         1207 
         1208 Node *
         1209 constexpr(void)
         1210 {
         1211         Node *np;
         1212 
         1213         np = ternary();
         1214         if (np && np->type->op == INT) {
         1215                 np = simplify(convert(np, inttype, 0));
         1216                 if (np->flags & NCONST)
         1217                         return np;
         1218         }
         1219         freetree(np);
         1220         return NULL;
         1221 }
         1222 
         1223 Node *
         1224 condexpr(int neg)
         1225 {
         1226         Node *np;
         1227 
         1228         np = exp2cond(expr(), neg);
         1229         if (np->flags & NCONST)
         1230                 warn("conditional expression is constant");
         1231         return simplify(np);
         1232 }