]> git.sur5r.net Git - cc65/blob - src/cc65/expr.c
4e5cc2791ad881f76cb8c856c9a26c5ead6f41d0
[cc65] / src / cc65 / expr.c
1 /*
2  * expr.c
3  *
4  * Ullrich von Bassewitz, 21.06.1998
5  */
6
7
8
9 #include <stdio.h>
10 #include <stdlib.h>
11 #include <string.h>
12
13 /* common */
14 #include "check.h"
15 #include "xmalloc.h"
16
17 /* cc65 */
18 #include "asmcode.h"
19 #include "asmlabel.h"
20 #include "codegen.h"
21 #include "datatype.h"
22 #include "declare.h"
23 #include "error.h"
24 #include "funcdesc.h"
25 #include "function.h"
26 #include "global.h"
27 #include "litpool.h"
28 #include "macrotab.h"
29 #include "preproc.h"
30 #include "scanner.h"
31 #include "stdfunc.h"
32 #include "symtab.h"
33 #include "typecmp.h"
34 #include "expr.h"
35
36
37
38 /*****************************************************************************/
39 /*                                   Data                                    */
40 /*****************************************************************************/
41
42
43
44 /* Generator attributes */
45 #define GEN_NOPUSH      0x01            /* Don't push lhs */
46
47 /* Map a generator function and its attributes to a token */
48 typedef struct {
49     unsigned char Tok;                  /* Token to map to */
50     unsigned char Flags;                /* Flags for generator function */
51     void          (*Func) (unsigned, unsigned long);    /* Generator func */
52 } GenDesc;
53
54 /* Descriptors for the operations */
55 static GenDesc GenMUL    = { TOK_STAR,          GEN_NOPUSH,     g_mul };
56 static GenDesc GenDIV    = { TOK_DIV,           GEN_NOPUSH,     g_div };
57 static GenDesc GenMOD    = { TOK_MOD,           GEN_NOPUSH,     g_mod };
58 static GenDesc GenASL    = { TOK_SHL,           GEN_NOPUSH,     g_asl };
59 static GenDesc GenASR    = { TOK_SHR,           GEN_NOPUSH,     g_asr };
60 static GenDesc GenLT     = { TOK_LT,            GEN_NOPUSH,     g_lt  };
61 static GenDesc GenLE     = { TOK_LE,            GEN_NOPUSH,     g_le  };
62 static GenDesc GenGE     = { TOK_GE,            GEN_NOPUSH,     g_ge  };
63 static GenDesc GenGT     = { TOK_GT,            GEN_NOPUSH,     g_gt  };
64 static GenDesc GenEQ     = { TOK_EQ,            GEN_NOPUSH,     g_eq  };
65 static GenDesc GenNE     = { TOK_NE,            GEN_NOPUSH,     g_ne  };
66 static GenDesc GenAND    = { TOK_AND,           GEN_NOPUSH,     g_and };
67 static GenDesc GenXOR    = { TOK_XOR,           GEN_NOPUSH,     g_xor };
68 static GenDesc GenOR     = { TOK_OR,            GEN_NOPUSH,     g_or  };
69 static GenDesc GenPASGN  = { TOK_PLUS_ASSIGN,   GEN_NOPUSH,     g_add };
70 static GenDesc GenSASGN  = { TOK_MINUS_ASSIGN,  GEN_NOPUSH,     g_sub };
71 static GenDesc GenMASGN  = { TOK_MUL_ASSIGN,    GEN_NOPUSH,     g_mul };
72 static GenDesc GenDASGN  = { TOK_DIV_ASSIGN,    GEN_NOPUSH,     g_div };
73 static GenDesc GenMOASGN = { TOK_MOD_ASSIGN,    GEN_NOPUSH,     g_mod };
74 static GenDesc GenSLASGN = { TOK_SHL_ASSIGN,    GEN_NOPUSH,     g_asl };
75 static GenDesc GenSRASGN = { TOK_SHR_ASSIGN,    GEN_NOPUSH,     g_asr };
76 static GenDesc GenAASGN  = { TOK_AND_ASSIGN,    GEN_NOPUSH,     g_and };
77 static GenDesc GenXOASGN = { TOK_XOR_ASSIGN,    GEN_NOPUSH,     g_xor };
78 static GenDesc GenOASGN  = { TOK_OR_ASSIGN,     GEN_NOPUSH,     g_or  };
79
80
81
82 /*****************************************************************************/
83 /*                             Function forwards                             */
84 /*****************************************************************************/
85
86
87
88 static int hie10 (struct expent* lval);
89 /* Handle ++, --, !, unary - etc. */
90
91
92
93 /*****************************************************************************/
94 /*                             Helper functions                              */
95 /*****************************************************************************/
96
97
98
99 static unsigned GlobalModeFlags (unsigned flags)
100 /* Return the addressing mode flags for the variable with the given flags */
101 {
102     flags &= E_MCTYPE;
103     if (flags == E_TGLAB) {
104         /* External linkage */
105         return CF_EXTERNAL;
106     } else if (flags == E_TREGISTER) {
107         /* Register variable */
108         return CF_REGVAR;
109     } else {
110         /* Static */
111         return CF_STATIC;
112     }
113 }
114
115
116
117 static int IsNullPtr (struct expent* lval)
118 /* Return true if this is the NULL pointer constant */
119 {
120     return (IsClassInt (lval->e_tptr) &&        /* Is it an int? */
121             lval->e_flags == E_MCONST &&        /* Is it constant? */
122             lval->e_const == 0);                /* And is it's value zero? */
123 }
124
125
126
127 static type* promoteint (type* lhst, type* rhst)
128 /* In an expression with two ints, return the type of the result */
129 {
130     /* Rules for integer types:
131      *   - If one of the values is a long, the result is long.
132      *   - If one of the values is unsigned, the result is also unsigned.
133      *   - Otherwise the result is an int.
134      */
135     if (IsTypeLong (lhst) || IsTypeLong (rhst)) {
136         if (IsSignUnsigned (lhst) || IsSignUnsigned (rhst)) {
137             return type_ulong;
138         } else {
139             return type_long;
140         }
141     } else {
142         if (IsSignUnsigned (lhst) || IsSignUnsigned (rhst)) {
143             return type_uint;
144         } else {
145             return type_int;
146         }
147     }
148 }
149
150
151
152 static unsigned typeadjust (struct expent* lhs, struct expent* rhs, int NoPush)
153 /* Adjust the two values for a binary operation. lhs is expected on stack or
154  * to be constant, rhs is expected to be in the primary register or constant.
155  * The function will put the type of the result into lhs and return the
156  * code generator flags for the operation.
157  * If NoPush is given, it is assumed that the operation does not expect the lhs
158  * to be on stack, and that lhs is in a register instead.
159  * Beware: The function does only accept int types.
160  */
161 {
162     unsigned ltype, rtype;
163     unsigned flags;
164
165     /* Get the type strings */
166     type* lhst = lhs->e_tptr;
167     type* rhst = rhs->e_tptr;
168
169     /* Generate type adjustment code if needed */
170     ltype = TypeOf (lhst);
171     if (lhs->e_flags == E_MCONST) {
172         ltype |= CF_CONST;
173     }
174     if (NoPush) {
175         /* Value is in primary register*/
176         ltype |= CF_REG;
177     }
178     rtype = TypeOf (rhst);
179     if (rhs->e_flags == E_MCONST) {
180         rtype |= CF_CONST;
181     }
182     flags = g_typeadjust (ltype, rtype);
183
184     /* Set the type of the result */
185     lhs->e_tptr = promoteint (lhst, rhst);
186
187     /* Return the code generator flags */
188     return flags;
189 }
190
191
192
193 unsigned assignadjust (type* lhst, struct expent* rhs)
194 /* Adjust the type of the right hand expression so that it can be assigned to
195  * the type on the left hand side. This function is used for assignment and
196  * for converting parameters in a function call. It returns the code generator
197  * flags for the operation. The type string of the right hand side will be
198  * set to the type of the left hand side.
199  */
200 {
201     /* Get the type of the right hand side */
202     type* rhst = rhs->e_tptr;
203
204     /* After calling this function, rhs will have the type of the lhs */
205     rhs->e_tptr = lhst;
206
207     /* First, do some type checking */
208     if (IsTypeVoid (lhst) || IsTypeVoid (rhst)) {
209         /* If one of the sides are of type void, output a more apropriate
210          * error message.
211          */
212         Error ("Illegal type");
213     } else if (IsClassInt (lhst)) {
214         if (IsClassPtr (rhst)) {
215             /* Pointer -> int conversion */
216             Warning ("Converting pointer to integer without a cast");
217         } else if (!IsClassInt (rhst)) {
218             Error ("Incompatible types");
219         } else {
220             /* Adjust the int types. To avoid manipulation of TOS mark lhs
221              * as const.
222              */
223             unsigned flags = TypeOf (rhst);
224             if (rhs->e_flags & E_MCONST) {
225                 flags |= CF_CONST;
226             }
227             return g_typeadjust (TypeOf (lhst) | CF_CONST, flags);
228         }
229     } else if (IsClassPtr (lhst)) {
230         if (IsClassPtr (rhst)) {
231             /* Pointer to pointer assignment is valid, if:
232              *   - both point to the same types, or
233              *   - the rhs pointer is a void pointer, or
234              *   - the lhs pointer is a void pointer.
235              */
236             if (!IsTypeVoid (Indirect (lhst)) && !IsTypeVoid (Indirect (rhst))) {
237                 /* Compare the types */
238                 switch (TypeCmp (lhst, rhst)) {
239
240                     case TC_INCOMPATIBLE:
241                         Error ("Incompatible pointer types");
242                         break;
243
244                     case TC_QUAL_DIFF:
245                         Error ("Pointer types differ in type qualifiers");
246                         break;
247
248                     default:
249                         /* Ok */
250                         break;
251                 }
252             }
253         } else if (IsClassInt (rhst)) {
254             /* Int to pointer assignment is valid only for constant zero */
255             if ((rhs->e_flags & E_MCONST) == 0 || rhs->e_const != 0) {
256                 Warning ("Converting integer to pointer without a cast");
257             }
258         } else if (IsTypeFuncPtr (lhst) && IsTypeFunc(rhst)) {
259             /* Assignment of function to function pointer is allowed, provided
260              * that both functions have the same parameter list.
261              */
262             if (TypeCmp (Indirect (lhst), rhst) < TC_EQUAL) {
263                 Error ("Incompatible types");
264             }
265         } else {
266             Error ("Incompatible types");
267         }
268     } else {
269         Error ("Incompatible types");
270     }
271
272     /* Return an int value in all cases where the operands are not both ints */
273     return CF_INT;
274 }
275
276
277
278 void DefineData (struct expent* lval)
279 /* Output a data definition for the given expression */
280 {
281     unsigned flags = lval->e_flags;
282
283     switch (flags & E_MCTYPE) {
284
285         case E_TCONST:
286             /* Number */
287             g_defdata (TypeOf (lval->e_tptr) | CF_CONST, lval->e_const, 0);
288             break;
289
290         case E_TREGISTER:
291             /* Register variable. Taking the address is usually not
292              * allowed.
293              */
294             if (!AllowRegVarAddr) {
295                 Error ("Cannot take the address of a register variable");
296             }
297             /* FALLTHROUGH */
298
299         case E_TGLAB:
300         case E_TLLAB:
301             /* Local or global symbol */
302             g_defdata (GlobalModeFlags (flags), lval->e_name, lval->e_const);
303             break;
304
305         case E_TLIT:
306             /* a literal of some kind */
307             g_defdata (CF_STATIC, LiteralLabel, lval->e_const);
308             break;
309
310         default:
311             Internal ("Unknown constant type: %04X", flags);
312     }
313 }
314
315
316
317 static void lconst (unsigned flags, struct expent* lval)
318 /* Load primary reg with some constant value. */
319 {
320     switch (lval->e_flags & E_MCTYPE) {
321
322         case E_TLOFFS:
323             g_leasp (lval->e_const);
324             break;
325
326         case E_TCONST:
327             /* Number constant */
328             g_getimmed (flags | TypeOf (lval->e_tptr) | CF_CONST, lval->e_const, 0);
329             break;
330
331         case E_TREGISTER:
332             /* Register variable. Taking the address is usually not
333              * allowed.
334              */
335             if (!AllowRegVarAddr) {
336                 Error ("Cannot take the address of a register variable");
337             }
338             /* FALLTHROUGH */
339
340         case E_TGLAB:
341         case E_TLLAB:
342             /* Local or global symbol, load address */
343             flags |= GlobalModeFlags (lval->e_flags);
344             flags &= ~CF_CONST;
345             g_getimmed (flags, lval->e_name, lval->e_const);
346             break;
347
348         case E_TLIT:
349             /* Literal string */
350             g_getimmed (CF_STATIC, LiteralLabel, lval->e_const);
351             break;
352
353         default:
354             Internal ("Unknown constant type: %04X", lval->e_flags);
355     }
356 }
357
358
359
360 static int kcalc (int tok, long val1, long val2)
361 /* Calculate an operation with left and right operand constant. */
362 {
363     switch (tok) {
364         case TOK_EQ:
365             return (val1 == val2);
366         case TOK_NE:
367             return (val1 != val2);
368         case TOK_LT:
369             return (val1 < val2);
370         case TOK_LE:
371             return (val1 <= val2);
372         case TOK_GE:
373             return (val1 >= val2);
374         case TOK_GT:
375             return (val1 > val2);
376         case TOK_OR:
377             return (val1 | val2);
378         case TOK_XOR:
379             return (val1 ^ val2);
380         case TOK_AND:
381             return (val1 & val2);
382         case TOK_SHR:
383             return (val1 >> val2);
384         case TOK_SHL:
385             return (val1 << val2);
386         case TOK_STAR:
387             return (val1 * val2);
388         case TOK_DIV:
389             if (val2 == 0) {
390                 Error ("Division by zero");
391                 return 0x7FFFFFFF;
392             }
393             return (val1 / val2);
394         case TOK_MOD:
395             if (val2 == 0) {
396                 Error ("Modulo operation with zero");
397                 return 0;
398             }
399             return (val1 % val2);
400         default:
401             Internal ("kcalc: got token 0x%X\n", tok);
402             return 0;
403     }
404 }
405
406
407
408 static GenDesc* FindGen (int Tok, GenDesc** Table)
409 {
410     GenDesc* G;
411     while ((G = *Table) != 0) {
412         if (G->Tok == Tok) {
413             return G;
414         }
415         ++Table;
416     }
417     return 0;
418 }
419
420
421
422 static int istypeexpr (void)
423 /* Return true if some sort of variable or type is waiting (helper for cast
424  * and sizeof() in hie10).
425  */
426 {
427     SymEntry* Entry;
428
429     return curtok == TOK_LPAREN && (
430             (nxttok >= TOK_FIRSTTYPE && nxttok <= TOK_LASTTYPE) ||
431             (nxttok == TOK_CONST)                               ||
432             (nxttok  == TOK_IDENT                               &&
433             (Entry = FindSym (NextTok.Ident)) != 0              &&
434             IsTypeDef (Entry))
435            );
436 }
437
438
439
440 static void PushAddr (struct expent* lval)
441 /* If the expression contains an address that was somehow evaluated,
442  * push this address on the stack. This is a helper function for all
443  * sorts of implicit or explicit assignment functions where the lvalue
444  * must be saved if it's not constant, before evaluating the rhs.
445  */
446 {
447     /* Get the address on stack if needed */
448     if (lval->e_flags != E_MREG && (lval->e_flags & E_MEXPR)) {
449         /* Push the address (always a pointer) */
450         g_push (CF_PTR, 0);
451     }
452 }
453
454
455
456 /*****************************************************************************/
457 /*                                   code                                    */
458 /*****************************************************************************/
459
460
461
462 void exprhs (unsigned flags, int k, struct expent *lval)
463 /* Put the result of an expression into the primary register */
464 {
465     int f;
466
467     f = lval->e_flags;
468     if (k) {
469         /* Dereferenced lvalue */
470         flags |= TypeOf (lval->e_tptr);
471         if (lval->e_test & E_FORCETEST) {
472             flags |= CF_TEST;
473             lval->e_test &= ~E_FORCETEST;
474         }
475         if (f & E_MGLOBAL) {    /* ref to globalvar */
476             /* Generate code */
477             flags |= GlobalModeFlags (f);
478             g_getstatic (flags, lval->e_name, lval->e_const);
479         } else if (f & E_MLOCAL) {
480             /* ref to localvar */
481             g_getlocal (flags, lval->e_const);
482         } else if (f & E_MCONST) {
483             /* ref to absolute address */
484             g_getstatic (flags | CF_ABSOLUTE, lval->e_const, 0);
485         } else if (f == E_MEOFFS) {
486             g_getind (flags, lval->e_const);
487         } else if (f != E_MREG) {
488             g_getind (flags, 0);
489         }
490     } else if (f == E_MEOFFS) {
491         /* reference not storable */
492         flags |= TypeOf (lval->e_tptr);
493         g_inc (flags | CF_CONST, lval->e_const);
494     } else if ((f & E_MEXPR) == 0) {
495         /* Constant of some sort, load it into the primary */
496         lconst (flags, lval);
497     }
498     if (lval->e_test & E_FORCETEST) {   /* we testing this value? */
499         /* debug... */
500         AddCodeHint ("forcetest");
501         flags |= TypeOf (lval->e_tptr);
502         g_test (flags);                 /* yes, force a test */
503         lval->e_test &= ~E_FORCETEST;
504     }
505 }
506
507
508 static void callfunction (struct expent* lval)
509 /* Perform a function call.  Called from hie11, this routine will
510  * either call the named function, or if the supplied ptr is zero,
511  * will call the contents of P.
512  */
513 {
514     struct expent lval2;
515     FuncDesc*     Func;         /* Function descriptor */
516     int           Ellipsis;     /* True if we have an open param list */
517     SymEntry*     Param;        /* Current formal parameter */
518     unsigned      ParamCount;   /* Actual parameter count */
519     unsigned      ParamSize;    /* Number of parameter bytes */
520     unsigned      Flags;
521     unsigned      CFlags;
522     CodeMark      Mark;
523
524
525     /* Get a pointer to the function descriptor from the type string */
526     Func = GetFuncDesc (lval->e_tptr);
527
528     /* Initialize vars to keep gcc silent */
529     Param = 0;
530     Mark  = 0;
531
532     /* Check if this is a function pointer. If so, save it. If not, check for
533      * special known library functions that may be inlined.
534      */
535     if (lval->e_flags & E_MEXPR) {
536         /* Function pointer is in primary register, save it */
537         Mark = GetCodePos ();
538         g_save (CF_PTR);
539     } else if (InlineStdFuncs && IsStdFunc ((const char*) lval->e_name)) {
540         /* Inline this function */
541         HandleStdFunc (lval);
542         return;
543     }
544
545     /* Parse the actual parameter list */
546     ParamSize  = 0;
547     ParamCount = 0;
548     Ellipsis   = 0;
549     while (curtok != TOK_RPAREN) {
550
551         /* Add a hint for the optimizer */
552         AddCodeHint ("param:start");
553
554         /* Count arguments */
555         ++ParamCount;
556
557         /* Fetch the pointer to the next argument, check for too many args */
558         if (ParamCount <= Func->ParamCount) {
559             if (ParamCount == 1) {
560                 /* First argument */
561                 Param = Func->SymTab->SymHead;
562             } else {
563                 /* Next argument */
564                 Param = Param->NextSym;
565                 CHECK ((Param->Flags & SC_PARAM) != 0);
566             }
567         } else if (!Ellipsis) {
568             /* Too many arguments. Do we have an open param list? */
569             if ((Func->Flags & FD_ELLIPSIS) == 0) {
570                 /* End of param list reached, no ellipsis */
571                 Error ("Too many arguments in function call");
572             }
573             /* Assume an ellipsis even in case of errors to avoid an error
574              * message for each other argument.
575              */
576             Ellipsis = 1;
577         }
578
579         /* Do some optimization: If we have a constant value to push,
580          * use a special function that may optimize.
581          */
582         CFlags = CF_NONE;
583         if (!Ellipsis && SizeOf (Param->Type) == 1) {
584             CFlags = CF_FORCECHAR;
585         }
586         Flags = 0;
587         if (evalexpr (CFlags, hie1, &lval2) == 0) {
588             /* A constant value */
589             Flags |= CF_CONST;
590         }
591
592         /* If we don't have an argument spec, accept anything, otherwise
593          * convert the actual argument to the type needed.
594          */
595         if (!Ellipsis) {
596             /* Promote the argument if needed */
597             assignadjust (Param->Type, &lval2);
598
599             /* If we have a prototype, chars may be pushed as chars */
600             Flags |= CF_FORCECHAR;
601         }
602
603         /* Use the type of the argument for the push */
604         Flags |= TypeOf (lval2.e_tptr);
605
606         /* If this is a fastcall function, don't push the last argument */
607         if (ParamCount == Func->ParamCount && (Func->Flags & FD_FASTCALL) != 0) {
608             /* Just load the argument into the primary. This is only needed if
609              * we have a constant argument, otherwise the value is already in
610              * the primary.
611              */
612             if (Flags & CF_CONST) {
613                 exprhs (CF_FORCECHAR, 0, &lval2);
614             }
615         } else {
616             /* Push the argument, count the argument size */
617             g_push (Flags, lval2.e_const);
618             ParamSize += sizeofarg (Flags);
619         }
620
621         /* Add an optimizer hint */
622         AddCodeHint ("param:end");
623
624         /* Check for end of argument list */
625         if (curtok != TOK_COMMA) {
626             break;
627         }
628         NextToken ();
629     }
630
631     /* We need the closing bracket here */
632     ConsumeRParen ();
633
634     /* Check if we had enough parameters */
635     if (ParamCount < Func->ParamCount) {
636         Error ("Too few arguments in function call");
637     }
638
639     /* */
640     if (lval->e_flags & E_MEXPR) {
641         /* Function called via pointer: Restore it and call function */
642         if (ParamSize != 0) {
643             g_restore (CF_PTR);
644         } else {
645             /* We had no parameters - remove save code */
646             RemoveCode (Mark);
647         }
648         g_callind (TypeOf (lval->e_tptr), ParamSize);
649     } else {
650         g_call (TypeOf (lval->e_tptr), (char*) lval->e_name, ParamSize);
651     }
652 }
653
654
655
656 void doasm (void)
657 /* This function parses ASM statements. The syntax of the ASM directive
658  * looks like the one defined for C++ (C has no ASM directive), that is,
659  * a string literal in parenthesis.
660  */
661 {
662     /* Skip the ASM */
663     NextToken ();
664
665     /* Need left parenthesis */
666     ConsumeLParen ();
667
668     /* String literal */
669     if (curtok != TOK_SCONST) {
670         Error ("String literal expected");
671     } else {
672         /* Write the string directly into the output, followed by a newline */
673         AddCodeLine (GetLiteral (curval));
674
675         /* Reset the string pointer, effectivly clearing the string from the
676          * string table. Since we're working with one token lookahead, this
677          * will fail if the next token is also a string token, but that's a
678          * syntax error anyway, because we expect a right paren.
679          */
680         ResetLiteralOffs (curval);
681     }
682
683     /* Skip the string token */
684     NextToken ();
685
686     /* Closing paren needed */
687     ConsumeRParen ();
688 }
689
690
691
692 static int primary (struct expent* lval)
693 /* This is the lowest level of the expression parser. */
694 {
695     int k;
696
697     /* not a test at all, yet */
698     lval->e_test = 0;
699
700     /* Character and integer constants. */
701     if (curtok == TOK_ICONST || curtok == TOK_CCONST) {
702         lval->e_flags = E_MCONST | E_TCONST;
703         lval->e_tptr  = curtype;
704         lval->e_const = curval;
705         NextToken ();
706         return 0;
707     }
708
709     /* Process parenthesized subexpression by calling the whole parser
710      * recursively.
711      */
712     if (curtok == TOK_LPAREN) {
713         NextToken ();
714         memset (lval, 0, sizeof (*lval));       /* Remove any attributes */
715         k = hie0 (lval);
716         ConsumeRParen ();
717         return k;
718     }
719
720     /* All others may only be used if the expression evaluation is not called
721      * recursively by the preprocessor.
722      */
723     if (Preprocessing) {
724         /* Illegal expression in PP mode */
725         Error ("Preprocessor expression expected");
726         lval->e_flags = E_MCONST;
727         lval->e_tptr = type_int;
728         return 0;
729     }
730
731     /* Identifier? */
732     if (curtok == TOK_IDENT) {
733
734         SymEntry* Sym;
735         ident Ident;
736
737         /* Get a pointer to the symbol table entry */
738         Sym = FindSym (CurTok.Ident);
739
740         /* Is the symbol known? */
741         if (Sym) {
742
743             /* We found the symbol - skip the name token */
744             NextToken ();
745
746             /* The expression type is the symbol type */
747             lval->e_tptr = Sym->Type;
748
749             /* Check for illegal symbol types */
750             CHECK ((Sym->Flags & SC_LABEL) != SC_LABEL);
751             if (Sym->Flags & SC_TYPE) {
752                 /* Cannot use type symbols */
753                 Error ("Variable identifier expected");
754                 /* Assume an int type to make lval valid */
755                 lval->e_flags = E_MLOCAL | E_TLOFFS;
756                 lval->e_tptr = type_int;
757                 lval->e_const = 0;
758                 return 0;
759             }
760
761             /* Check for legal symbol types */
762             if ((Sym->Flags & SC_ENUM) == SC_ENUM) {
763                 lval->e_flags = E_MCONST;
764                 lval->e_const = Sym->V.EnumVal;
765                 return 0;
766             } else if ((Sym->Flags & SC_FUNC) == SC_FUNC) {
767                 /* Function */
768                 lval->e_flags = E_MGLOBAL | E_MCONST | E_TGLAB;
769                 lval->e_name = (unsigned long) Sym->Name;
770                 lval->e_const = 0;
771             } else if ((Sym->Flags & SC_AUTO) == SC_AUTO) {
772                 /* Local variable */
773                 lval->e_flags = E_MLOCAL | E_TLOFFS;
774                 lval->e_const = Sym->V.Offs;
775             } else if ((Sym->Flags & SC_STATIC) == SC_STATIC) {
776                 /* Static variable */
777                 if (Sym->Flags & (SC_EXTERN | SC_STORAGE)) {
778                     lval->e_flags = E_MGLOBAL | E_MCONST | E_TGLAB;
779                     lval->e_name = (unsigned long) Sym->Name;
780                 } else {
781                     lval->e_flags = E_MGLOBAL | E_MCONST | E_TLLAB;
782                     lval->e_name = Sym->V.Label;
783                 }
784                 lval->e_const = 0;
785             } else if ((Sym->Flags & SC_REGISTER) == SC_REGISTER) {
786                 /* Register variable, zero page based */
787                 lval->e_flags = E_MGLOBAL | E_MCONST | E_TREGISTER;
788                 lval->e_name  = Sym->V.Offs;
789                 lval->e_const = 0;
790             } else {
791                 /* Local static variable */
792                 lval->e_flags = E_MGLOBAL | E_MCONST | E_TLLAB;
793                 lval->e_name  = Sym->V.Offs;
794                 lval->e_const = 0;
795             }
796
797             /* The symbol is referenced now */
798             Sym->Flags |= SC_REF;
799             if (IsTypeFunc (lval->e_tptr) || IsTypeArray (lval->e_tptr)) {
800                 return 0;
801             }
802             return 1;
803         }
804
805         /* We did not find the symbol. Remember the name, then skip it */
806         strcpy (Ident, CurTok.Ident);
807         NextToken ();
808
809         /* IDENT is either an auto-declared function or an undefined variable. */
810         if (curtok == TOK_LPAREN) {
811             /* Declare a function returning int. For that purpose, prepare a
812              * function signature for a function having an empty param list
813              * and returning int.
814              */
815             Warning ("Function call without a prototype");
816             Sym = AddGlobalSym (Ident, GetImplicitFuncType(), SC_EXTERN | SC_REF | SC_FUNC);
817             lval->e_tptr  = Sym->Type;
818             lval->e_flags = E_MGLOBAL | E_MCONST | E_TGLAB;
819             lval->e_name  = (unsigned long) Sym->Name;
820             lval->e_const = 0;
821             return 0;
822
823         } else {
824
825             /* Undeclared Variable */
826             Sym = AddLocalSym (Ident, type_int, SC_AUTO | SC_REF, 0);
827             lval->e_flags = E_MLOCAL | E_TLOFFS;
828             lval->e_tptr = type_int;
829             lval->e_const = 0;
830             Error ("Undefined symbol: `%s'", Ident);
831             return 1;
832
833         }
834     }
835
836     /* String literal? */
837     if (curtok == TOK_SCONST) {
838         lval->e_flags = E_MCONST | E_TLIT;
839         lval->e_const = curval;
840         lval->e_tptr  = GetCharArrayType (strlen (GetLiteral (curval)));
841         NextToken ();
842         return 0;
843     }
844
845     /* ASM statement? */
846     if (curtok == TOK_ASM) {
847         doasm ();
848         lval->e_tptr  = type_void;
849         lval->e_flags = E_MEXPR;
850         lval->e_const = 0;
851         return 0;
852     }
853
854     /* __AX__ and __EAX__ pseudo values? */
855     if (curtok == TOK_AX || curtok == TOK_EAX) {
856         lval->e_tptr  = (curtok == TOK_AX)? type_uint : type_ulong;
857         lval->e_flags = E_MREG;
858         lval->e_test &= ~E_CC;
859         lval->e_const = 0;
860         NextToken ();
861         return 1;               /* May be used as lvalue */
862     }
863
864     /* Illegal primary. */
865     Error ("Expression expected");
866     lval->e_flags = E_MCONST;
867     lval->e_tptr = type_int;
868     return 0;
869 }
870
871
872
873 static int arrayref (int k, struct expent* lval)
874 /* Handle an array reference */
875 {
876     unsigned lflags;
877     unsigned rflags;
878     int ConstBaseAddr;
879     int ConstSubAddr;
880     int l;
881     struct expent lval2;
882     CodeMark Mark1;
883     CodeMark Mark2;
884     type* tptr1;
885     type* tptr2;
886
887
888     /* Skip the bracket */
889     NextToken ();
890
891     /* Get the type of left side */
892     tptr1 = lval->e_tptr;
893
894     /* We can apply a special treatment for arrays that have a const base
895      * address. This is true for most arrays and will produce a lot better
896      * code. Check if this is a const base address.
897      */
898     lflags = lval->e_flags & ~E_MCTYPE;
899     ConstBaseAddr = (lflags == E_MCONST)       || /* Constant numeric address */
900                      (lflags & E_MGLOBAL) != 0 || /* Static array, or ... */
901                      lflags == E_MLOCAL;          /* Local array */
902
903     /* If we have a constant base, we delay the address fetch */
904     Mark1 = GetCodePos ();
905     Mark2 = 0;          /* Silence gcc */
906     if (!ConstBaseAddr) {
907         /* Get a pointer to the array into the primary */
908         exprhs (CF_NONE, k, lval);
909
910         /* Get the array pointer on stack. Do not push more than 16
911          * bit, even if this value is greater, since we cannot handle
912          * other than 16bit stuff when doing indexing.
913          */
914         Mark2 = GetCodePos ();
915         g_push (CF_PTR, 0);
916     }
917
918     /* TOS now contains ptr to array elements. Get the subscript. */
919     l = hie0 (&lval2);
920     if (l == 0 && lval2.e_flags == E_MCONST) {
921
922         /* The array subscript is a constant - remove value from stack */
923         if (!ConstBaseAddr) {
924             RemoveCode (Mark2);
925             pop (CF_PTR);
926         } else {
927             /* Get an array pointer into the primary */
928             exprhs (CF_NONE, k, lval);
929         }
930
931         if (IsClassPtr (tptr1)) {
932
933             /* Scale the subscript value according to element size */
934             lval2.e_const *= PSizeOf (tptr1);
935
936             /* Remove code for lhs load */
937             RemoveCode (Mark1);
938
939             /* Handle constant base array on stack. Be sure NOT to
940              * handle pointers the same way, this won't work.
941              */
942             if (IsTypeArray (tptr1) &&
943                 ((lval->e_flags & ~E_MCTYPE) == E_MCONST ||
944                 (lval->e_flags & ~E_MCTYPE) == E_MLOCAL ||
945                 (lval->e_flags & E_MGLOBAL) != 0 ||
946                 (lval->e_flags == E_MEOFFS))) {
947                 lval->e_const += lval2.e_const;
948
949             } else {
950                 /* Pointer - load into primary and remember offset */
951                 if ((lval->e_flags & E_MEXPR) == 0 || k != 0) {
952                     exprhs (CF_NONE, k, lval);
953                 }
954                 lval->e_const = lval2.e_const;
955                 lval->e_flags = E_MEOFFS;
956             }
957
958             /* Result is of element type */
959             lval->e_tptr = Indirect (tptr1);
960
961             /* Done */
962             goto end_array;
963
964         } else if (IsClassPtr (tptr2 = lval2.e_tptr)) {
965             /* Subscript is pointer, get element type */
966             lval2.e_tptr = Indirect (tptr2);
967
968             /* Scale the rhs value in the primary register */
969             g_scale (TypeOf (tptr1), SizeOf (lval2.e_tptr));
970             /* */
971             lval->e_tptr = lval2.e_tptr;
972         } else {
973             Error ("Cannot subscript");
974         }
975
976         /* Add the subscript. Since arrays are indexed by integers,
977          * we will ignore the true type of the subscript here and
978          * use always an int.
979          */
980         g_inc (CF_INT | CF_CONST, lval2.e_const);
981
982     } else {
983
984         /* Array subscript is not constant. Load it into the primary */
985         Mark2 = GetCodePos ();
986         exprhs (CF_NONE, l, &lval2);
987
988         tptr2 = lval2.e_tptr;
989         if (IsClassPtr (tptr1)) {
990
991             /* Get the element type */
992             lval->e_tptr = Indirect (tptr1);
993
994             /* Indexing is based on int's, so we will just use the integer
995              * portion of the index (which is in (e)ax, so there's no further
996              * action required).
997              */
998             g_scale (CF_INT, SizeOf (lval->e_tptr));
999
1000         } else if (IsClassPtr (tptr2)) {
1001
1002             /* Get the element type */
1003             lval2.e_tptr = Indirect (tptr2);
1004
1005             /* Get the int value on top. If we go here, we're sure,
1006              * both values are 16 bit (the first one was truncated
1007              * if necessary and the second one is a pointer).
1008              * Note: If ConstBaseAddr is true, we don't have a value on
1009              * stack, so to "swap" both, just push the subscript.
1010              */
1011             if (ConstBaseAddr) {
1012                 g_push (CF_INT, 0);
1013                 exprhs (CF_NONE, k, lval);
1014                 ConstBaseAddr = 0;
1015             } else {
1016                 g_swap (CF_INT);
1017             }
1018
1019             /* Scale it */
1020             g_scale (TypeOf (tptr1), SizeOf (lval2.e_tptr));
1021             lval->e_tptr = lval2.e_tptr;
1022         } else {
1023             Error ("Cannot subscript");
1024         }
1025
1026         /* The offset is now in the primary register. It didn't have a
1027          * constant base address for the lhs, the lhs address is already
1028          * on stack, and we must add the offset. If the base address was
1029          * constant, we call special functions to add the address to the
1030          * offset value.
1031          */
1032         if (!ConstBaseAddr) {
1033             /* Add the subscript. Both values are int sized. */
1034             g_add (CF_INT, 0);
1035         } else {
1036
1037             /* If the subscript has itself a constant address, it is often
1038              * a better idea to reverse again the order of the evaluation.
1039              * This will generate better code if the subscript is a byte
1040              * sized variable. But beware: This is only possible if the
1041              * subscript was not scaled, that is, if this was a byte array
1042              * or pointer.
1043              */
1044             rflags = lval2.e_flags & ~E_MCTYPE;
1045             ConstSubAddr = (rflags == E_MCONST)       || /* Constant numeric address */
1046                             (rflags & E_MGLOBAL) != 0 || /* Static array, or ... */
1047                             rflags == E_MLOCAL;          /* Local array */
1048
1049             if (ConstSubAddr && SizeOf (lval->e_tptr) == 1) {
1050
1051                 type* SavedType;
1052
1053                 /* Reverse the order of evaluation */
1054                 unsigned flags = (SizeOf (lval2.e_tptr) == 1)? CF_CHAR : CF_INT;
1055                 RemoveCode (Mark2);
1056
1057                 /* Get a pointer to the array into the primary. We have changed
1058                  * e_tptr above but we need the original type to load the
1059                  * address, so restore it temporarily.
1060                  */
1061                 SavedType = lval->e_tptr;
1062                 lval->e_tptr = tptr1;
1063                 exprhs (CF_NONE, k, lval);
1064                 lval->e_tptr = SavedType;
1065
1066                 /* Add the variable */
1067                 if (rflags == E_MLOCAL) {
1068                     g_addlocal (flags, lval2.e_const);
1069                 } else {
1070                     flags |= GlobalModeFlags (lval2.e_flags);
1071                     g_addstatic (flags, lval2.e_name, lval2.e_const);
1072                 }
1073             } else {
1074                 if (lflags == E_MCONST) {
1075                     /* Constant numeric address. Just add it */
1076                     g_inc (CF_INT | CF_UNSIGNED, lval->e_const);
1077                 } else if (lflags == E_MLOCAL) {
1078                     /* Base address is a local variable address */
1079                     if (IsTypeArray (tptr1)) {
1080                         g_addaddr_local (CF_INT, lval->e_const);
1081                     } else {
1082                         g_addlocal (CF_PTR, lval->e_const);
1083                     }
1084                 } else {
1085                     /* Base address is a static variable address */
1086                     unsigned flags = CF_INT;
1087                     flags |= GlobalModeFlags (lval->e_flags);
1088                     if (IsTypeArray (tptr1)) {
1089                         g_addaddr_static (flags, lval->e_name, lval->e_const);
1090                     } else {
1091                         g_addstatic (flags, lval->e_name, lval->e_const);
1092                     }
1093                 }
1094             }
1095         }
1096     }
1097     lval->e_flags = E_MEXPR;
1098 end_array:
1099     ConsumeRBrack ();
1100     return !IsTypeArray (lval->e_tptr);
1101
1102 }
1103
1104
1105
1106 static int structref (int k, struct expent* lval)
1107 /* Process struct field after . or ->. */
1108 {
1109     ident Ident;
1110     SymEntry* Field;
1111     int flags;
1112
1113     /* Skip the token and check for an identifier */
1114     NextToken ();
1115     if (curtok != TOK_IDENT) {
1116         Error ("Identifier expected");
1117         lval->e_tptr = type_int;
1118         return 0;
1119     }
1120
1121     /* Get the symbol table entry and check for a struct field */
1122     strcpy (Ident, CurTok.Ident);
1123     NextToken ();
1124     Field = FindStructField (lval->e_tptr, Ident);
1125     if (Field == 0) {
1126         Error ("Struct/union has no field named `%s'", Ident);
1127         lval->e_tptr = type_int;
1128         return 0;
1129     }
1130
1131     /* If we have constant input data, the result is also constant */
1132     flags = lval->e_flags & ~E_MCTYPE;
1133     if (flags == E_MCONST ||
1134         (k == 0 && (flags == E_MLOCAL ||
1135                     (flags & E_MGLOBAL) != 0 ||
1136                     lval->e_flags  == E_MEOFFS))) {
1137         lval->e_const += Field->V.Offs;
1138     } else {
1139         if ((flags & E_MEXPR) == 0 || k != 0) {
1140             exprhs (CF_NONE, k, lval);
1141         }
1142         lval->e_const = Field->V.Offs;
1143         lval->e_flags = E_MEOFFS;
1144     }
1145     lval->e_tptr = Field->Type;
1146     return !IsTypeArray (Field->Type);
1147 }
1148
1149
1150
1151 static int hie11 (struct expent *lval)
1152 /* Handle compound types (structs and arrays) */
1153 {
1154     int k;
1155     type* tptr;
1156
1157
1158     k = primary (lval);
1159     if (curtok < TOK_LBRACK || curtok > TOK_PTR_REF) {
1160         /* Not for us */
1161         return k;
1162     }
1163
1164     while (1) {
1165
1166         if (curtok == TOK_LBRACK) {
1167
1168             /* Array reference */
1169             k = arrayref (k, lval);
1170
1171         } else if (curtok == TOK_LPAREN) {
1172
1173             /* Function call. Skip the opening parenthesis */
1174             NextToken ();
1175             tptr = lval->e_tptr;
1176             if (IsTypeFunc (tptr) || IsTypeFuncPtr (tptr)) {
1177                 if (IsTypeFuncPtr (tptr)) {
1178                     /* Pointer to function. Handle transparently */
1179                     exprhs (CF_NONE, k, lval);  /* Function pointer to A/X */
1180                     ++lval->e_tptr;             /* Skip T_PTR */
1181                     lval->e_flags |= E_MEXPR;
1182                 }
1183                 callfunction (lval);
1184                 lval->e_flags = E_MEXPR;
1185                 lval->e_tptr += DECODE_SIZE + 1;        /* Set to result */
1186             } else {
1187                 Error ("Illegal function call");
1188             }
1189             k = 0;
1190
1191         } else if (curtok == TOK_DOT) {
1192
1193             if (!IsClassStruct (lval->e_tptr)) {
1194                 Error ("Struct expected");
1195             }
1196             k = structref (0, lval);
1197
1198         } else if (curtok == TOK_PTR_REF) {
1199
1200             tptr = lval->e_tptr;
1201             if (tptr[0] != T_PTR || (tptr[1] & T_STRUCT) == 0) {
1202                 Error ("Struct pointer expected");
1203             }
1204             k = structref (k, lval);
1205
1206         } else {
1207             return k;
1208         }
1209     }
1210 }
1211
1212
1213
1214 static void store (struct expent* lval)
1215 /* Store primary reg into this reference */
1216 {
1217     int f;
1218     unsigned flags;
1219
1220     f = lval->e_flags;
1221     flags = TypeOf (lval->e_tptr);
1222     if (f & E_MGLOBAL) {
1223         flags |= GlobalModeFlags (f);
1224         if (lval->e_test) {
1225             /* Just testing */
1226             flags |= CF_TEST;
1227         }
1228
1229         /* Generate code */
1230         g_putstatic (flags, lval->e_name, lval->e_const);
1231
1232     } else if (f & E_MLOCAL) {
1233         g_putlocal (flags, lval->e_const);
1234     } else if (f == E_MEOFFS) {
1235         g_putind (flags, lval->e_const);
1236     } else if (f != E_MREG) {
1237         if (f & E_MEXPR) {
1238             g_putind (flags, 0);
1239         } else {
1240             /* Store into absolute address */
1241             g_putstatic (flags | CF_ABSOLUTE, lval->e_const, 0);
1242         }
1243     }
1244
1245     /* Assume that each one of the stores will invalidate CC */
1246     lval->e_test &= ~E_CC;
1247 }
1248
1249
1250
1251 static void pre_incdec (struct expent* lval, void (*inc) (unsigned, unsigned long))
1252 /* Handle --i and ++i */
1253 {
1254     int k;
1255     unsigned flags;
1256     unsigned long val;
1257
1258     NextToken ();
1259     if ((k = hie10 (lval)) == 0) {
1260         Error ("Invalid lvalue");
1261         return;
1262     }
1263
1264     /* Get the data type */
1265     flags = TypeOf (lval->e_tptr) | CF_FORCECHAR | CF_CONST;
1266
1267     /* Get the increment value in bytes */
1268     val = (lval->e_tptr [0] == T_PTR)? PSizeOf (lval->e_tptr) : 1;
1269
1270     /* We're currently only able to handle some adressing modes */
1271     if ((lval->e_flags & E_MGLOBAL) == 0 &&     /* Global address? */
1272         (lval->e_flags & E_MLOCAL) == 0  &&     /* Local address? */
1273         (lval->e_flags & E_MCONST) == 0  &&     /* Constant address? */
1274         (lval->e_flags & E_MEXPR) == 0) {       /* Address in a/x? */
1275
1276         /* Use generic code. Push the address if needed */
1277         PushAddr (lval);
1278
1279         /* Fetch the value */
1280         exprhs (CF_NONE, k, lval);
1281
1282         /* Increment value in primary */
1283         inc (flags, val);
1284
1285         /* Store the result back */
1286         store (lval);
1287
1288     } else {
1289
1290         /* Special code for some addressing modes - use the special += ops */
1291         if (lval->e_flags & E_MGLOBAL) {
1292             flags |= GlobalModeFlags (lval->e_flags);
1293             if (inc == g_inc) {
1294                 g_addeqstatic (flags, lval->e_name, lval->e_const, val);
1295             } else {
1296                 g_subeqstatic (flags, lval->e_name, lval->e_const, val);
1297             }
1298         } else if (lval->e_flags & E_MLOCAL) {
1299             /* ref to localvar */
1300             if (inc == g_inc) {
1301                 g_addeqlocal (flags, lval->e_const, val);
1302             } else {
1303                 g_subeqlocal (flags, lval->e_const, val);
1304             }
1305         } else if (lval->e_flags & E_MCONST) {
1306             /* ref to absolute address */
1307             flags |= CF_ABSOLUTE;
1308             if (inc == g_inc) {
1309                 g_addeqstatic (flags, lval->e_const, 0, val);
1310             } else {
1311                 g_subeqstatic (flags, lval->e_const, 0, val);
1312             }
1313         } else if (lval->e_flags & E_MEXPR) {
1314             /* Address in a/x. */
1315             if (inc == g_inc) {
1316                 g_addeqind (flags, lval->e_const, val);
1317             } else {
1318                 g_subeqind (flags, lval->e_const, val);
1319             }
1320         } else {
1321             Internal ("Invalid addressing mode");
1322         }
1323
1324     }
1325
1326     /* Result is an expression */
1327     lval->e_flags = E_MEXPR;
1328 }
1329
1330
1331
1332 static void post_incdec (struct expent *lval, int k, void (*inc) (unsigned, unsigned long))
1333 /* Handle i-- and i++ */
1334 {
1335     unsigned flags;
1336
1337     NextToken ();
1338     if (k == 0) {
1339         Error ("Invalid lvalue");
1340         return;
1341     }
1342
1343     /* Get the data type */
1344     flags = TypeOf (lval->e_tptr);
1345
1346     /* Push the address if needed */
1347     PushAddr (lval);
1348
1349     /* Fetch the value and save it (since it's the result of the expression) */
1350     exprhs (CF_NONE, 1, lval);
1351     g_save (flags | CF_FORCECHAR);
1352
1353     /* If we have a pointer expression, increment by the size of the type */
1354     if (lval->e_tptr[0] == T_PTR) {
1355         inc (flags | CF_CONST | CF_FORCECHAR, SizeOf (lval->e_tptr + 1));
1356     } else {
1357         inc (flags | CF_CONST | CF_FORCECHAR, 1);
1358     }
1359
1360     /* Store the result back */
1361     store (lval);
1362
1363     /* Restore the original value */
1364     g_restore (flags | CF_FORCECHAR);
1365     lval->e_flags = E_MEXPR;
1366 }
1367
1368
1369
1370 static void unaryop (int tok, struct expent* lval)
1371 /* Handle unary -/+ and ~ */
1372 {
1373     int k;
1374     unsigned flags;
1375
1376     NextToken ();
1377     k = hie10 (lval);
1378     if (k == 0 && lval->e_flags & E_MCONST) {
1379         /* Value is constant */
1380         switch (tok) {
1381             case TOK_MINUS: lval->e_const =     -lval->e_const; break;
1382             case TOK_PLUS:                                      break;
1383             case TOK_COMP:  lval->e_const = ~lval->e_const;     break;
1384             default:        Internal ("Unexpected token: %d", tok);
1385         }
1386     } else {
1387         /* Value is not constant */
1388         exprhs (CF_NONE, k, lval);
1389
1390         /* Get the type of the expression */
1391         flags = TypeOf (lval->e_tptr);
1392
1393         /* Handle the operation */
1394         switch (tok) {
1395             case TOK_MINUS: g_neg (flags);  break;
1396             case TOK_PLUS:                  break;
1397             case TOK_COMP:  g_com (flags);  break;
1398             default:    Internal ("Unexpected token: %d", tok);
1399         }
1400         lval->e_flags = E_MEXPR;
1401     }
1402 }
1403
1404
1405
1406 static int typecast (struct expent* lval)
1407 /* Handle an explicit cast */
1408 {
1409     int k;
1410     type Type[MAXTYPELEN];
1411
1412     /* Skip the left paren */
1413     NextToken ();
1414
1415     /* Read the type */
1416     ParseType (Type);
1417
1418     /* Closing paren */
1419     ConsumeRParen ();
1420
1421     /* Read the expression we have to cast */
1422     k = hie10 (lval);
1423
1424     /* Check for a const expression */
1425     if (k == 0 && lval->e_flags == E_MCONST) {
1426
1427         /* A cast of a constant to something else. If the new type is an int,
1428          * be sure to handle the size extension correctly. If the new type is
1429          * not an int, the cast is implementation specific anyway, so leave
1430          * the value alone.
1431          */
1432         if (IsClassInt (Type)) {
1433
1434             /* Get the current and new size of the value */
1435             unsigned OldSize = SizeOf (lval->e_tptr);
1436             unsigned NewSize = SizeOf (Type);
1437             unsigned OldBits = OldSize * 8;
1438             unsigned NewBits = NewSize * 8;
1439
1440             /* Check if the new datatype will have a smaller range */
1441             if (NewSize < OldSize) {
1442
1443                 /* Cut the value to the new size */
1444                 lval->e_const &= (0xFFFFFFFFUL >> (32 - NewBits));
1445
1446                 /* If the new value is signed, sign extend the value */
1447                 if (!IsSignUnsigned (Type)) {
1448                     lval->e_const |= ((~0L) << NewBits);
1449                 }
1450
1451             } else if (NewSize > OldSize) {
1452
1453                 /* Sign extend the value if needed */
1454                 if (!IsSignUnsigned (Type) && !IsSignUnsigned (lval->e_tptr)) {
1455                     if (lval->e_const & (0x01UL << (OldBits-1))) {
1456                         lval->e_const |= ((~0L) << OldBits);
1457                     }
1458                 }
1459             }
1460         }
1461
1462     } else {
1463
1464         /* Not a constant. Be sure to ignore casts to void */
1465         if (!IsTypeVoid (Type)) {
1466
1467             /* If the size does not change, leave the value alone. Otherwise,
1468              * we have to load the value into the primary and generate code to
1469              * cast teh value in the primary register.
1470              */
1471             if (SizeOf (Type) != SizeOf (lval->e_tptr)) {
1472
1473                 /* Load the value into the primary */
1474                 exprhs (CF_NONE, k, lval);
1475
1476                 /* Mark the lhs as const to avoid a manipulation of TOS */
1477                 g_typecast (TypeOf (Type) | CF_CONST, TypeOf (lval->e_tptr));
1478
1479                 /* Value is now in primary */
1480                 lval->e_flags = E_MEXPR;
1481                 k = 0;
1482             }
1483         }
1484     }
1485
1486     /* In any case, use the new type */
1487     lval->e_tptr = TypeDup (Type);
1488
1489     /* Done */
1490     return k;
1491 }
1492
1493
1494
1495 static int hie10 (struct expent* lval)
1496 /* Handle ++, --, !, unary - etc. */
1497 {
1498     int k;
1499     type* t;
1500
1501     switch (curtok) {
1502
1503         case TOK_INC:
1504             pre_incdec (lval, g_inc);
1505             return 0;
1506
1507         case TOK_DEC:
1508             pre_incdec (lval, g_dec);
1509             return 0;
1510
1511         case TOK_PLUS:
1512         case TOK_MINUS:
1513         case TOK_COMP:
1514             unaryop (curtok, lval);
1515             return 0;
1516
1517         case TOK_BOOL_NOT:
1518             NextToken ();
1519             if (evalexpr (CF_NONE, hie10, lval) == 0) {
1520                 /* Constant expression */
1521                 lval->e_const = !lval->e_const;
1522             } else {
1523                 g_bneg (TypeOf (lval->e_tptr));
1524                 lval->e_test |= E_CC;                   /* bneg will set cc */
1525                 lval->e_flags = E_MEXPR;                /* say it's an expr */
1526             }
1527             return 0;                           /* expr not storable */
1528
1529         case TOK_STAR:
1530             NextToken ();
1531             if (evalexpr (CF_NONE, hie10, lval) != 0) {
1532                 /* Expression is not const, indirect value loaded into primary */
1533                 lval->e_flags = E_MEXPR;
1534                 lval->e_const = 0;              /* Offset is zero now */
1535             }
1536             t = lval->e_tptr;
1537             if (IsClassPtr (t)) {
1538                 lval->e_tptr = Indirect (t);
1539             } else {
1540                 Error ("Illegal indirection");
1541             }
1542             return 1;
1543
1544         case TOK_AND:
1545             NextToken ();
1546             k = hie10 (lval);
1547             if (k == 0) {
1548                 /* Allow the & operator with an array */
1549                 if (!IsTypeArray (lval->e_tptr)) {
1550                     Error ("Illegal address");
1551                 }
1552             } else {
1553                 t = TypeAlloc (TypeLen (lval->e_tptr) + 2);
1554                 t [0] = T_PTR;
1555                 TypeCpy (t + 1, lval->e_tptr);
1556                 lval->e_tptr = t;
1557             }
1558             return 0;
1559
1560         case TOK_SIZEOF:
1561             NextToken ();
1562             if (istypeexpr ()) {
1563                 type Type[MAXTYPELEN];
1564                 NextToken ();
1565                 lval->e_const = SizeOf (ParseType (Type));
1566                 ConsumeRParen ();
1567             } else {
1568                 /* Remember the output queue pointer */
1569                 CodeMark Mark = GetCodePos ();
1570                 hie10 (lval);
1571                 lval->e_const = SizeOf (lval->e_tptr);
1572                 /* Remove any generated code */
1573                 RemoveCode (Mark);
1574             }
1575             lval->e_flags = E_MCONST | E_TCONST;
1576             lval->e_tptr = type_uint;
1577             lval->e_test &= ~E_CC;
1578             return 0;
1579
1580         default:
1581             if (istypeexpr ()) {
1582                 /* A cast */
1583                 return typecast (lval);
1584             }
1585     }
1586
1587     k = hie11 (lval);
1588     switch (curtok) {
1589         case TOK_INC:
1590             post_incdec (lval, k, g_inc);
1591             return 0;
1592
1593         case TOK_DEC:
1594             post_incdec (lval, k, g_dec);
1595             return 0;
1596
1597         default:
1598             return k;
1599     }
1600 }
1601
1602
1603
1604 static int hie_internal (GenDesc** ops,         /* List of generators */
1605                          struct expent* lval,   /* parent expr's lval */
1606                          int (*hienext) (struct expent*),
1607                          int* UsedGen)          /* next higher level */
1608 /* Helper function */
1609 {
1610     int k;
1611     struct expent lval2;
1612     CodeMark Mark1;
1613     CodeMark Mark2;
1614     GenDesc* Gen;
1615     token_t tok;                        /* The operator token */
1616     unsigned ltype, type;
1617     int rconst;                         /* Operand is a constant */
1618
1619
1620     k = hienext (lval);
1621
1622     *UsedGen = 0;
1623     while ((Gen = FindGen (curtok, ops)) != 0) {
1624
1625         /* Tell the caller that we handled it's ops */
1626         *UsedGen = 1;
1627
1628         /* All operators that call this function expect an int on the lhs */
1629         if (!IsClassInt (lval->e_tptr)) {
1630             Error ("Integer expression expected");
1631         }
1632
1633         /* Remember the operator token, then skip it */
1634         tok = curtok;
1635         NextToken ();
1636
1637         /* Get the lhs on stack */
1638         Mark1 = GetCodePos ();
1639         ltype = TypeOf (lval->e_tptr);
1640         if (k == 0 && lval->e_flags == E_MCONST) {
1641             /* Constant value */
1642             Mark2 = GetCodePos ();
1643             g_push (ltype | CF_CONST, lval->e_const);
1644         } else {
1645             /* Value not constant */
1646             exprhs (CF_NONE, k, lval);
1647             Mark2 = GetCodePos ();
1648             g_push (ltype, 0);
1649         }
1650
1651         /* Get the right hand side */
1652         rconst = (evalexpr (CF_NONE, hienext, &lval2) == 0);
1653
1654         /* Check the type of the rhs */
1655         if (!IsClassInt (lval2.e_tptr)) {
1656             Error ("Integer expression expected");
1657         }
1658
1659         /* Check for const operands */
1660         if (k == 0 && lval->e_flags == E_MCONST && rconst) {
1661
1662             /* Both operands are constant, remove the generated code */
1663             RemoveCode (Mark1);
1664             pop (ltype);
1665
1666             /* Evaluate the result */
1667             lval->e_const = kcalc (tok, lval->e_const, lval2.e_const);
1668
1669             /* Get the type of the result */
1670             lval->e_tptr = promoteint (lval->e_tptr, lval2.e_tptr);
1671
1672         } else {
1673
1674             /* If the right hand side is constant, and the generator function
1675              * expects the lhs in the primary, remove the push of the primary
1676              * now.
1677              */
1678             unsigned rtype = TypeOf (lval2.e_tptr);
1679             type = 0;
1680             if (rconst) {
1681                 /* Second value is constant - check for div */
1682                 type |= CF_CONST;
1683                 rtype |= CF_CONST;
1684                 if (tok == TOK_DIV && lval2.e_const == 0) {
1685                     Error ("Division by zero");
1686                 } else if (tok == TOK_MOD && lval2.e_const == 0) {
1687                     Error ("Modulo operation with zero");
1688                 }
1689                 if ((Gen->Flags & GEN_NOPUSH) != 0) {
1690                     RemoveCode (Mark2);
1691                     pop (ltype);
1692                     ltype |= CF_REG;    /* Value is in register */
1693                 }
1694             }
1695
1696             /* Determine the type of the operation result. */
1697             type |= g_typeadjust (ltype, rtype);
1698             lval->e_tptr = promoteint (lval->e_tptr, lval2.e_tptr);
1699
1700             /* Generate code */
1701             Gen->Func (type, lval2.e_const);
1702             lval->e_flags = E_MEXPR;
1703         }
1704
1705         /* We have a rvalue now */
1706         k = 0;
1707     }
1708
1709     return k;
1710 }
1711
1712
1713
1714 static int hie_compare (GenDesc** ops,          /* List of generators */
1715                         struct expent* lval,    /* parent expr's lval */
1716                         int (*hienext) (struct expent*))
1717 /* Helper function for the compare operators */
1718 {
1719     int k;
1720     struct expent lval2;
1721     CodeMark Mark1;
1722     CodeMark Mark2;
1723     GenDesc* Gen;
1724     token_t tok;                        /* The operator token */
1725     unsigned ltype;
1726     int rconst;                         /* Operand is a constant */
1727
1728
1729     k = hienext (lval);
1730
1731     while ((Gen = FindGen (curtok, ops)) != 0) {
1732
1733         /* Remember the operator token, then skip it */
1734         tok = curtok;
1735         NextToken ();
1736
1737         /* Get the lhs on stack */
1738         Mark1 = GetCodePos ();
1739         ltype = TypeOf (lval->e_tptr);
1740         if (k == 0 && lval->e_flags == E_MCONST) {
1741             /* Constant value */
1742             Mark2 = GetCodePos ();
1743             g_push (ltype | CF_CONST, lval->e_const);
1744         } else {
1745             /* Value not constant */
1746             exprhs (CF_NONE, k, lval);
1747             Mark2 = GetCodePos ();
1748             g_push (ltype, 0);
1749         }
1750
1751         /* Get the right hand side */
1752         rconst = (evalexpr (CF_NONE, hienext, &lval2) == 0);
1753
1754         /* Make sure, the types are compatible */
1755         if (IsClassInt (lval->e_tptr)) {
1756             if (!IsClassInt (lval2.e_tptr) && !(IsClassPtr(lval2.e_tptr) && IsNullPtr(lval))) {
1757                 Error ("Incompatible types");
1758             }
1759         } else if (IsClassPtr (lval->e_tptr)) {
1760             if (IsClassPtr (lval2.e_tptr)) {
1761                 /* Both pointers are allowed in comparison if they point to
1762                  * the same type, or if one of them is a void pointer.
1763                  */
1764                 type* left  = Indirect (lval->e_tptr);
1765                 type* right = Indirect (lval2.e_tptr);
1766                 if (TypeCmp (left, right) < TC_EQUAL && *left != T_VOID && *right != T_VOID) {
1767                     /* Incomatible pointers */
1768                     Error ("Incompatible types");
1769                 }
1770             } else if (!IsNullPtr (&lval2)) {
1771                 Error ("Incompatible types");
1772             }
1773         }
1774
1775         /* Check for const operands */
1776         if (k == 0 && lval->e_flags == E_MCONST && rconst) {
1777
1778             /* Both operands are constant, remove the generated code */
1779             RemoveCode (Mark1);
1780             pop (ltype);
1781
1782             /* Evaluate the result */
1783             lval->e_const = kcalc (tok, lval->e_const, lval2.e_const);
1784
1785         } else {
1786
1787             /* If the right hand side is constant, and the generator function
1788              * expects the lhs in the primary, remove the push of the primary
1789              * now.
1790              */
1791             unsigned flags = 0;
1792             if (rconst) {
1793                 flags |= CF_CONST;
1794                 if ((Gen->Flags & GEN_NOPUSH) != 0) {
1795                     RemoveCode (Mark2);
1796                     pop (ltype);
1797                     ltype |= CF_REG;    /* Value is in register */
1798                 }
1799             }
1800
1801             /* Determine the type of the operation result. If the left
1802              * operand is of type char and the right is a constant, or
1803              * if both operands are of type char, we will encode the
1804              * operation as char operation. Otherwise the default
1805              * promotions are used.
1806              */
1807             if (IsTypeChar (lval->e_tptr) && (IsTypeChar (lval2.e_tptr) || rconst)) {
1808                 flags |= CF_CHAR;
1809                 if (IsSignUnsigned (lval->e_tptr) || IsSignUnsigned (lval2.e_tptr)) {
1810                     flags |= CF_UNSIGNED;
1811                 }
1812                 if (rconst) {
1813                     flags |= CF_FORCECHAR;
1814                 }
1815             } else {
1816                 unsigned rtype = TypeOf (lval2.e_tptr) | (flags & CF_CONST);
1817                 flags |= g_typeadjust (ltype, rtype);
1818             }
1819
1820             /* Generate code */
1821             Gen->Func (flags, lval2.e_const);
1822             lval->e_flags = E_MEXPR;
1823         }
1824
1825         /* Result type is always int */
1826         lval->e_tptr = type_int;
1827
1828         /* We have a rvalue now, condition codes are set */
1829         k = 0;
1830         lval->e_test |= E_CC;
1831     }
1832
1833     return k;
1834 }
1835
1836
1837
1838 static int hie9 (struct expent *lval)
1839 /* Process * and / operators. */
1840 {
1841     static GenDesc* hie9_ops [] = {
1842         &GenMUL, &GenDIV, &GenMOD, 0
1843     };
1844     int UsedGen;
1845
1846     return hie_internal (hie9_ops, lval, hie10, &UsedGen);
1847 }
1848
1849
1850
1851 static void parseadd (int k, struct expent* lval)
1852 /* Parse an expression with the binary plus operator. lval contains the
1853  * unprocessed left hand side of the expression and will contain the
1854  * result of the expression on return.
1855  */
1856 {
1857     struct expent lval2;
1858     unsigned flags;             /* Operation flags */
1859     CodeMark Mark;              /* Remember code position */
1860     type* lhst;                 /* Type of left hand side */
1861     type* rhst;                 /* Type of right hand side */
1862
1863
1864     /* Skip the PLUS token */
1865     NextToken ();
1866
1867     /* Get the left hand side type, initialize operation flags */
1868     lhst = lval->e_tptr;
1869     flags = 0;
1870
1871     /* Check for constness on both sides */
1872     if (k == 0 && lval->e_flags == E_MCONST) {
1873
1874         /* The left hand side is a constant. Good. Get rhs */
1875         if (evalexpr (CF_NONE, hie9, &lval2) == 0) {
1876
1877             /* Right hand side is also constant. Get the rhs type */
1878             rhst = lval2.e_tptr;
1879
1880             /* Both expressions are constants. Check for pointer arithmetic */
1881             if (IsClassPtr (lhst) && IsClassInt (rhst)) {
1882                 /* Left is pointer, right is int, must scale rhs */
1883                 lval->e_const = lval->e_const + lval2.e_const * PSizeOf (lhst);
1884                 /* Result type is a pointer */
1885             } else if (IsClassInt (lhst) && IsClassPtr (rhst)) {
1886                 /* Left is int, right is pointer, must scale lhs */
1887                 lval->e_const = lval->e_const * PSizeOf (rhst) + lval2.e_const;
1888                 /* Result type is a pointer */
1889                 lval->e_tptr = lval2.e_tptr;
1890             } else if (IsClassInt (lhst) && IsClassInt (rhst)) {
1891                 /* Integer addition */
1892                 lval->e_const += lval2.e_const;
1893                 typeadjust (lval, &lval2, 1);
1894             } else {
1895                 /* OOPS */
1896                 Error ("Invalid operands for binary operator `+'");
1897             }
1898
1899             /* Result is constant, condition codes not set */
1900             lval->e_test = E_MCONST;
1901
1902         } else {
1903
1904             /* lhs is constant, rhs is not. Get the rhs type. */
1905             rhst = lval2.e_tptr;
1906
1907             /* Check for pointer arithmetic */
1908             if (IsClassPtr (lhst) && IsClassInt (rhst)) {
1909                 /* Left is pointer, right is int, must scale rhs */
1910                 g_scale (CF_INT, PSizeOf (lhst));
1911                 /* Operate on pointers, result type is a pointer */
1912                 flags = CF_PTR;
1913             } else if (IsClassInt (lhst) && IsClassPtr (rhst)) {
1914                 /* Left is int, right is pointer, must scale lhs */
1915                 lval->e_const *= PSizeOf (rhst);
1916                 /* Operate on pointers, result type is a pointer */
1917                 flags = CF_PTR;
1918                 lval->e_tptr = lval2.e_tptr;
1919             } else if (IsClassInt (lhst) && IsClassInt (rhst)) {
1920                 /* Integer addition */
1921                 flags = typeadjust (lval, &lval2, 1);
1922             } else {
1923                 /* OOPS */
1924                 Error ("Invalid operands for binary operator `+'");
1925             }
1926
1927             /* Generate code for the add */
1928             g_inc (flags | CF_CONST, lval->e_const);
1929
1930             /* Result is in primary register */
1931             lval->e_flags = E_MEXPR;
1932             lval->e_test &= ~E_CC;
1933
1934         }
1935
1936     } else {
1937
1938         /* Left hand side is not constant. Get the value onto the stack. */
1939         exprhs (CF_NONE, k, lval);              /* --> primary register */
1940         Mark = GetCodePos ();
1941         g_push (TypeOf (lval->e_tptr), 0);      /* --> stack */
1942
1943         /* Evaluate the rhs */
1944         if (evalexpr (CF_NONE, hie9, &lval2) == 0) {
1945
1946             /* Right hand side is a constant. Get the rhs type */
1947             rhst = lval2.e_tptr;
1948
1949             /* Remove pushed value from stack */
1950             RemoveCode (Mark);
1951             pop (TypeOf (lval->e_tptr));
1952
1953             /* Check for pointer arithmetic */
1954             if (IsClassPtr (lhst) && IsClassInt (rhst)) {
1955                 /* Left is pointer, right is int, must scale rhs */
1956                 lval2.e_const *= PSizeOf (lhst);
1957                 /* Operate on pointers, result type is a pointer */
1958                 flags = CF_PTR;
1959             } else if (IsClassInt (lhst) && IsClassPtr (rhst)) {
1960                 /* Left is int, right is pointer, must scale lhs (ptr only) */
1961                 g_scale (CF_INT | CF_CONST, PSizeOf (rhst));
1962                 /* Operate on pointers, result type is a pointer */
1963                 flags = CF_PTR;
1964                 lval->e_tptr = lval2.e_tptr;
1965             } else if (IsClassInt (lhst) && IsClassInt (rhst)) {
1966                 /* Integer addition */
1967                 flags = typeadjust (lval, &lval2, 1);
1968             } else {
1969                 /* OOPS */
1970                 Error ("Invalid operands for binary operator `+'");
1971             }
1972
1973             /* Generate code for the add */
1974             g_inc (flags | CF_CONST, lval2.e_const);
1975
1976             /* Result is in primary register */
1977             lval->e_flags = E_MEXPR;
1978             lval->e_test &= ~E_CC;
1979
1980         } else {
1981
1982             /* lhs and rhs are not constant. Get the rhs type. */
1983             rhst = lval2.e_tptr;
1984
1985             /* Check for pointer arithmetic */
1986             if (IsClassPtr (lhst) && IsClassInt (rhst)) {
1987                 /* Left is pointer, right is int, must scale rhs */
1988                 g_scale (CF_INT, PSizeOf (lhst));
1989                 /* Operate on pointers, result type is a pointer */
1990                 flags = CF_PTR;
1991             } else if (IsClassInt (lhst) && IsClassPtr (rhst)) {
1992                 /* Left is int, right is pointer, must scale lhs */
1993                 g_tosint (TypeOf (rhst));       /* Make sure, TOS is int */
1994                 g_swap (CF_INT);                /* Swap TOS and primary */
1995                 g_scale (CF_INT, PSizeOf (rhst));
1996                 /* Operate on pointers, result type is a pointer */
1997                 flags = CF_PTR;
1998                 lval->e_tptr = lval2.e_tptr;
1999             } else if (IsClassInt (lhst) && IsClassInt (rhst)) {
2000                 /* Integer addition */
2001                 flags = typeadjust (lval, &lval2, 0);
2002             } else {
2003                 /* OOPS */
2004                 Error ("Invalid operands for binary operator `+'");
2005             }
2006
2007             /* Generate code for the add */
2008             g_add (flags, 0);
2009
2010             /* Result is in primary register */
2011             lval->e_flags = E_MEXPR;
2012             lval->e_test &= ~E_CC;
2013
2014         }
2015
2016     }
2017 }
2018
2019
2020
2021 static void parsesub (int k, struct expent* lval)
2022 /* Parse an expression with the binary minus operator. lval contains the
2023  * unprocessed left hand side of the expression and will contain the
2024  * result of the expression on return.
2025  */
2026 {
2027     struct expent lval2;
2028     unsigned flags;             /* Operation flags */
2029     type* lhst;                 /* Type of left hand side */
2030     type* rhst;                 /* Type of right hand side */
2031     CodeMark Mark1;             /* Save position of output queue */
2032     CodeMark Mark2;             /* Another position in the queue */
2033     int rscale;                 /* Scale factor for the result */
2034
2035
2036     /* Skip the MINUS token */
2037     NextToken ();
2038
2039     /* Get the left hand side type, initialize operation flags */
2040     lhst = lval->e_tptr;
2041     flags = 0;
2042     rscale = 1;                 /* Scale by 1, that is, don't scale */
2043
2044     /* Remember the output queue position, then bring the value onto the stack */
2045     Mark1 = GetCodePos ();
2046     exprhs (CF_NONE, k, lval);  /* --> primary register */
2047     Mark2 = GetCodePos ();
2048     g_push (TypeOf (lhst), 0);  /* --> stack */
2049
2050     /* Parse the right hand side */
2051     if (evalexpr (CF_NONE, hie9, &lval2) == 0) {
2052
2053         /* The right hand side is constant. Get the rhs type. */
2054         rhst = lval2.e_tptr;
2055
2056         /* Check left hand side */
2057         if (k == 0 && lval->e_flags & E_MCONST) {
2058
2059             /* Both sides are constant, remove generated code */
2060             RemoveCode (Mark1);
2061             pop (TypeOf (lhst));        /* Clean up the stack */
2062
2063             /* Check for pointer arithmetic */
2064             if (IsClassPtr (lhst) && IsClassInt (rhst)) {
2065                 /* Left is pointer, right is int, must scale rhs */
2066                 lval->e_const -= lval2.e_const * PSizeOf (lhst);
2067                 /* Operate on pointers, result type is a pointer */
2068             } else if (IsClassPtr (lhst) && IsClassPtr (rhst)) {
2069                 /* Left is pointer, right is pointer, must scale result */
2070                 if (TypeCmp (Indirect (lhst), Indirect (rhst)) < TC_EQUAL) {
2071                     Error ("Incompatible pointer types");
2072                 } else {
2073                     lval->e_const = (lval->e_const - lval2.e_const) / PSizeOf (lhst);
2074                 }
2075                 /* Operate on pointers, result type is an integer */
2076                 lval->e_tptr = type_int;
2077             } else if (IsClassInt (lhst) && IsClassInt (rhst)) {
2078                 /* Integer subtraction */
2079                 typeadjust (lval, &lval2, 1);
2080                 lval->e_const -= lval2.e_const;
2081             } else {
2082                 /* OOPS */
2083                 Error ("Invalid operands for binary operator `-'");
2084             }
2085
2086             /* Result is constant, condition codes not set */
2087             lval->e_flags = E_MCONST;
2088             lval->e_test &= ~E_CC;
2089
2090         } else {
2091
2092             /* Left hand side is not constant, right hand side is.
2093              * Remove pushed value from stack.
2094              */
2095             RemoveCode (Mark2);
2096             pop (TypeOf (lhst));
2097
2098             if (IsClassPtr (lhst) && IsClassInt (rhst)) {
2099                 /* Left is pointer, right is int, must scale rhs */
2100                 lval2.e_const *= PSizeOf (lhst);
2101                 /* Operate on pointers, result type is a pointer */
2102                 flags = CF_PTR;
2103             } else if (IsClassPtr (lhst) && IsClassPtr (rhst)) {
2104                 /* Left is pointer, right is pointer, must scale result */
2105                 if (TypeCmp (Indirect (lhst), Indirect (rhst)) < TC_EQUAL) {
2106                     Error ("Incompatible pointer types");
2107                 } else {
2108                     rscale = PSizeOf (lhst);
2109                 }
2110                 /* Operate on pointers, result type is an integer */
2111                 flags = CF_PTR;
2112                 lval->e_tptr = type_int;
2113             } else if (IsClassInt (lhst) && IsClassInt (rhst)) {
2114                 /* Integer subtraction */
2115                 flags = typeadjust (lval, &lval2, 1);
2116             } else {
2117                 /* OOPS */
2118                 Error ("Invalid operands for binary operator `-'");
2119             }
2120
2121             /* Do the subtraction */
2122             g_dec (flags | CF_CONST, lval2.e_const);
2123
2124             /* If this was a pointer subtraction, we must scale the result */
2125             if (rscale != 1) {
2126                 g_scale (flags, -rscale);
2127             }
2128
2129             /* Result is in primary register */
2130             lval->e_flags = E_MEXPR;
2131             lval->e_test &= ~E_CC;
2132
2133         }
2134
2135     } else {
2136
2137         /* Right hand side is not constant. Get the rhs type. */
2138         rhst = lval2.e_tptr;
2139
2140         /* Check for pointer arithmetic */
2141         if (IsClassPtr (lhst) && IsClassInt (rhst)) {
2142             /* Left is pointer, right is int, must scale rhs */
2143             g_scale (CF_INT, PSizeOf (lhst));
2144             /* Operate on pointers, result type is a pointer */
2145             flags = CF_PTR;
2146         } else if (IsClassPtr (lhst) && IsClassPtr (rhst)) {
2147             /* Left is pointer, right is pointer, must scale result */
2148             if (TypeCmp (Indirect (lhst), Indirect (rhst)) < TC_EQUAL) {
2149                 Error ("Incompatible pointer types");
2150             } else {
2151                 rscale = PSizeOf (lhst);
2152             }
2153             /* Operate on pointers, result type is an integer */
2154             flags = CF_PTR;
2155             lval->e_tptr = type_int;
2156         } else if (IsClassInt (lhst) && IsClassInt (rhst)) {
2157             /* Integer subtraction. If the left hand side descriptor says that
2158              * the lhs is const, we have to remove this mark, since this is no
2159              * longer true, lhs is on stack instead.
2160              */
2161             if (lval->e_flags == E_MCONST) {
2162                 lval->e_flags = E_MEXPR;
2163             }
2164             /* Adjust operand types */
2165             flags = typeadjust (lval, &lval2, 0);
2166         } else {
2167             /* OOPS */
2168             Error ("Invalid operands for binary operator `-'");
2169         }
2170
2171         /* Generate code for the sub (the & is a hack here) */
2172         g_sub (flags & ~CF_CONST, 0);
2173
2174         /* If this was a pointer subtraction, we must scale the result */
2175         if (rscale != 1) {
2176             g_scale (flags, -rscale);
2177         }
2178
2179         /* Result is in primary register */
2180         lval->e_flags = E_MEXPR;
2181         lval->e_test &= ~E_CC;
2182     }
2183 }
2184
2185
2186
2187 static int hie8 (struct expent* lval)
2188 /* Process + and - binary operators. */
2189 {
2190     int k = hie9 (lval);
2191     while (curtok == TOK_PLUS || curtok == TOK_MINUS) {
2192
2193         if (curtok == TOK_PLUS) {
2194             parseadd (k, lval);
2195         } else {
2196             parsesub (k, lval);
2197         }
2198         k = 0;
2199     }
2200     return k;
2201 }
2202
2203
2204
2205
2206 static int hie7 (struct expent *lval)
2207 /* Parse << and >>. */
2208 {
2209     static GenDesc* hie7_ops [] = {
2210         &GenASL, &GenASR, 0
2211     };
2212     int UsedGen;
2213
2214     return hie_internal (hie7_ops, lval, hie8, &UsedGen);
2215 }
2216
2217
2218
2219 static int hie6 (struct expent *lval)
2220 /* process greater-than type comparators */
2221 {
2222     static GenDesc* hie6_ops [] = {
2223         &GenLT, &GenLE, &GenGE, &GenGT, 0
2224     };
2225     return hie_compare (hie6_ops, lval, hie7);
2226 }
2227
2228
2229
2230 static int hie5 (struct expent *lval)
2231 {
2232     static GenDesc* hie5_ops[] = {
2233         &GenEQ, &GenNE, 0
2234     };
2235     return hie_compare (hie5_ops, lval, hie6);
2236 }
2237
2238
2239
2240 static int hie4 (struct expent* lval)
2241 /* Handle & (bitwise and) */
2242 {
2243     static GenDesc* hie4_ops [] = {
2244         &GenAND, 0
2245     };
2246     int UsedGen;
2247
2248     return hie_internal (hie4_ops, lval, hie5, &UsedGen);
2249 }
2250
2251
2252
2253 static int hie3 (struct expent *lval)
2254 /* Handle ^ (bitwise exclusive or) */
2255 {
2256     static GenDesc* hie3_ops [] = {
2257         &GenXOR, 0
2258     };
2259     int UsedGen;
2260
2261     return hie_internal (hie3_ops, lval, hie4, &UsedGen);
2262 }
2263
2264
2265
2266 static int hie2 (struct expent *lval)
2267 /* Handle | (bitwise or) */
2268 {
2269     static GenDesc* hie2_ops [] = {
2270         &GenOR, 0
2271     };
2272     int UsedGen;
2273
2274     return hie_internal (hie2_ops, lval, hie3, &UsedGen);
2275 }
2276
2277
2278
2279 static int hieAnd (struct expent* lval, unsigned TrueLab, int* BoolOp)
2280 /* Process "exp && exp" */
2281 {
2282     int k;
2283     int lab;
2284     struct expent lval2;
2285
2286     k = hie2 (lval);
2287     if (curtok == TOK_BOOL_AND) {
2288
2289         /* Tell our caller that we're evaluating a boolean */
2290         *BoolOp = 1;
2291
2292         /* Get a label that we will use for false expressions */
2293         lab = GetLabel ();
2294
2295         /* If the expr hasn't set condition codes, set the force-test flag */
2296         if ((lval->e_test & E_CC) == 0) {
2297             lval->e_test |= E_FORCETEST;
2298         }
2299
2300         /* Load the value */
2301         exprhs (CF_FORCECHAR, k, lval);
2302
2303         /* Generate the jump */
2304         g_falsejump (CF_NONE, lab);
2305
2306         /* Parse more boolean and's */
2307         while (curtok == TOK_BOOL_AND) {
2308
2309             /* Skip the && */
2310             NextToken ();
2311
2312             /* Get rhs */
2313             k = hie2 (&lval2);
2314             if ((lval2.e_test & E_CC) == 0) {
2315                 lval2.e_test |= E_FORCETEST;
2316             }
2317             exprhs (CF_FORCECHAR, k, &lval2);
2318
2319             /* Do short circuit evaluation */
2320             if (curtok == TOK_BOOL_AND) {
2321                 g_falsejump (CF_NONE, lab);
2322             } else {
2323                 /* Last expression - will evaluate to true */
2324                 g_truejump (CF_NONE, TrueLab);
2325             }
2326         }
2327
2328         /* Define the false jump label here */
2329         g_defloclabel (lab);
2330
2331         /* Define the label */
2332         lval->e_flags = E_MEXPR;
2333         lval->e_test |= E_CC;   /* Condition codes are set */
2334         k = 0;
2335     }
2336     return k;
2337 }
2338
2339
2340
2341 static int hieOr (struct expent *lval)
2342 /* Process "exp || exp". */
2343 {
2344     int k;
2345     struct expent lval2;
2346     int BoolOp = 0;             /* Did we have a boolean op? */
2347     int AndOp;                  /* Did we have a && operation? */
2348     unsigned TrueLab;           /* Jump to this label if true */
2349     unsigned DoneLab;
2350
2351     /* Get a label */
2352     TrueLab = GetLabel ();
2353
2354     /* Call the next level parser */
2355     k = hieAnd (lval, TrueLab, &BoolOp);
2356
2357     /* Any boolean or's? */
2358     if (curtok == TOK_BOOL_OR) {
2359
2360         /* If the expr hasn't set condition codes, set the force-test flag */
2361         if ((lval->e_test & E_CC) == 0) {
2362             lval->e_test |= E_FORCETEST;
2363         }
2364
2365         /* Get first expr */
2366         exprhs (CF_FORCECHAR, k, lval);
2367
2368         /* For each expression jump to TrueLab if true. Beware: If we
2369          * had && operators, the jump is already in place!
2370          */
2371         if (!BoolOp) {
2372             g_truejump (CF_NONE, TrueLab);
2373         }
2374
2375         /* Remember that we had a boolean op */
2376         BoolOp = 1;
2377
2378         /* while there's more expr */
2379         while (curtok == TOK_BOOL_OR) {
2380
2381             /* skip the || */
2382             NextToken ();
2383
2384             /* Get a subexpr */
2385             AndOp = 0;
2386             k = hieAnd (&lval2, TrueLab, &AndOp);
2387             if ((lval2.e_test & E_CC) == 0) {
2388                 lval2.e_test |= E_FORCETEST;
2389             }
2390             exprhs (CF_FORCECHAR, k, &lval2);
2391
2392             /* If there is more to come, add shortcut boolean eval.
2393              * Beware: If we had && operators, the jump is already
2394              * in place!
2395              */
2396 #if     0
2397 /* Seems this sometimes generates wrong code */
2398             if (curtok == TOK_BOOL_OR && !AndOp) {
2399                 g_truejump (CF_NONE, TrueLab);
2400             }
2401 #else
2402             g_truejump (CF_NONE, TrueLab);
2403 #endif
2404         }
2405         lval->e_flags = E_MEXPR;
2406         lval->e_test |= E_CC;                   /* Condition codes are set */
2407         k = 0;
2408     }
2409
2410     /* If we really had boolean ops, generate the end sequence */
2411     if (BoolOp) {
2412         DoneLab = GetLabel ();
2413         g_getimmed (CF_INT | CF_CONST, 0, 0);   /* Load FALSE */
2414         g_falsejump (CF_NONE, DoneLab);
2415         g_defloclabel (TrueLab);
2416         g_getimmed (CF_INT | CF_CONST, 1, 0);   /* Load TRUE */
2417         g_defloclabel (DoneLab);
2418     }
2419     return k;
2420 }
2421
2422
2423
2424 static int hieQuest (struct expent *lval)
2425 /* Parse "lvalue ? exp : exp" */
2426 {
2427     int k;
2428     int labf;
2429     int labt;
2430     struct expent lval2;        /* Expression 2 */
2431     struct expent lval3;        /* Expression 3 */
2432     type* type2;                /* Type of expression 2 */
2433     type* type3;                /* Type of expression 3 */
2434     type* rtype;                /* Type of result */
2435     CodeMark Mark1;             /* Save position in output code */
2436     CodeMark Mark2;             /* Save position in output code */
2437
2438
2439
2440     k = hieOr (lval);
2441     if (curtok == TOK_QUEST) {
2442         NextToken ();
2443         if ((lval->e_test & E_CC) == 0) {
2444             /* Condition codes not set, force a test */
2445             lval->e_test |= E_FORCETEST;
2446         }
2447         exprhs (CF_NONE, k, lval);
2448         labf = GetLabel ();
2449         g_falsejump (CF_NONE, labf);
2450
2451         /* Parse second and third expression */
2452         expression1 (&lval2);
2453         labt = GetLabel ();
2454         ConsumeColon ();
2455         g_jump (labt);
2456         g_defloclabel (labf);
2457         expression1 (&lval3);
2458
2459         /* Check if any conversions are needed, if so, do them.
2460          * Conversion rules for ?: expression are:
2461          *   - if both expressions are int expressions, default promotion
2462          *     rules for ints apply.
2463          *   - if both expressions are pointers of the same type, the
2464          *     result of the expression is of this type.
2465          *   - if one of the expressions is a pointer and the other is
2466          *     a zero constant, the resulting type is that of the pointer
2467          *     type.
2468          *   - all other cases are flagged by an error.
2469          */
2470         type2 = lval2.e_tptr;
2471         type3 = lval3.e_tptr;
2472         if (IsClassInt (type2) && IsClassInt (type3)) {
2473
2474             /* Get common type */
2475             rtype = promoteint (type2, type3);
2476
2477             /* Convert the third expression to this type if needed */
2478             g_typecast (TypeOf (rtype), TypeOf (type3));
2479
2480             /* Setup a new label so that the expr3 code will jump around
2481              * the type cast code for expr2.
2482              */
2483             labf = GetLabel ();         /* Get new label */
2484             Mark1 = GetCodePos ();      /* Remember current position */
2485             g_jump (labf);              /* Jump around code */
2486
2487             /* The jump for expr2 goes here */
2488             g_defloclabel (labt);
2489
2490             /* Create the typecast code for expr2 */
2491             Mark2 = GetCodePos ();      /* Remember position */
2492             g_typecast (TypeOf (rtype), TypeOf (type2));
2493
2494             /* If the typecast did not produce code, remove the jump,
2495              * otherwise output the label.
2496              */
2497             if (GetCodePos() == Mark2) {
2498                 RemoveCode (Mark1);     /* Remove code */
2499             } else {
2500                 /* We have typecast code, output label */
2501                 g_defloclabel (labf);
2502                 labt = 0;               /* Mark other label as invalid */
2503             }
2504
2505         } else if (IsClassPtr (type2) && IsClassPtr (type3)) {
2506             /* Must point to same type */
2507             if (TypeCmp (Indirect (type2), Indirect (type3)) < TC_EQUAL) {
2508                 Error ("Incompatible pointer types");
2509             }
2510             /* Result has the common type */
2511             rtype = lval2.e_tptr;
2512         } else if (IsClassPtr (type2) && IsNullPtr (&lval3)) {
2513             /* Result type is pointer, no cast needed */
2514             rtype = lval2.e_tptr;
2515         } else if (IsNullPtr (&lval2) && IsClassPtr (type3)) {
2516             /* Result type is pointer, no cast needed */
2517             rtype = lval3.e_tptr;
2518         } else {
2519             Error ("Incompatible types");
2520             rtype = lval2.e_tptr;               /* Doesn't matter here */
2521         }
2522
2523         /* If we don't have the label defined until now, do it */
2524         if (labt) {
2525             g_defloclabel (labt);
2526         }
2527
2528         /* Setup the target expression */
2529         lval->e_flags = E_MEXPR;
2530         lval->e_tptr = rtype;
2531         k = 0;
2532     }
2533     return k;
2534 }
2535
2536
2537
2538 static void opeq (GenDesc* Gen, struct expent *lval, int k)
2539 /* Process "op=" operators. */
2540 {
2541     struct expent lval2;
2542     unsigned flags;
2543     CodeMark Mark;
2544     int MustScale;
2545
2546     NextToken ();
2547     if (k == 0) {
2548         Error ("Invalid lvalue in assignment");
2549         return;
2550     }
2551
2552     /* Determine the type of the lhs */
2553     flags = TypeOf (lval->e_tptr);
2554     MustScale = (Gen->Func == g_add || Gen->Func == g_sub) &&
2555                 lval->e_tptr [0] == T_PTR;
2556
2557     /* Get the lhs address on stack (if needed) */
2558     PushAddr (lval);
2559
2560     /* Fetch the lhs into the primary register if needed */
2561     exprhs (CF_NONE, k, lval);
2562
2563     /* Bring the lhs on stack */
2564     Mark = GetCodePos ();
2565     g_push (flags, 0);
2566
2567     /* Evaluate the rhs */
2568     if (evalexpr (CF_NONE, hie1, &lval2) == 0) {
2569         /* The resulting value is a constant. If the generator has the NOPUSH
2570          * flag set, don't push the lhs.
2571          */
2572         if (Gen->Flags & GEN_NOPUSH) {
2573             RemoveCode (Mark);
2574             pop (flags);
2575         }
2576         if (MustScale) {
2577             /* lhs is a pointer, scale rhs */
2578             lval2.e_const *= SizeOf (lval->e_tptr+1);
2579         }
2580
2581         /* If the lhs is character sized, the operation may be later done
2582          * with characters.
2583          */
2584         if (SizeOf (lval->e_tptr) == 1) {
2585             flags |= CF_FORCECHAR;
2586         }
2587
2588         /* Special handling for add and sub - some sort of a hack, but short code */
2589         if (Gen->Func == g_add) {
2590             g_inc (flags | CF_CONST, lval2.e_const);
2591         } else if (Gen->Func == g_sub) {
2592             g_dec (flags | CF_CONST, lval2.e_const);
2593         } else {
2594             Gen->Func (flags | CF_CONST, lval2.e_const);
2595         }
2596     } else {
2597         /* rhs is not constant and already in the primary register */
2598         if (MustScale) {
2599             /* lhs is a pointer, scale rhs */
2600             g_scale (TypeOf (lval2.e_tptr), SizeOf (lval->e_tptr+1));
2601         }
2602
2603         /* If the lhs is character sized, the operation may be later done
2604          * with characters.
2605          */
2606         if (SizeOf (lval->e_tptr) == 1) {
2607             flags |= CF_FORCECHAR;
2608         }
2609
2610         /* Adjust the types of the operands if needed */
2611         Gen->Func (g_typeadjust (flags, TypeOf (lval2.e_tptr)), 0);
2612     }
2613     store (lval);
2614     lval->e_flags = E_MEXPR;
2615 }
2616
2617
2618
2619 static void addsubeq (GenDesc* Gen, struct expent *lval, int k)
2620 /* Process the += and -= operators */
2621 {
2622     struct expent lval2;
2623     unsigned flags;
2624     int MustScale;
2625
2626
2627     if (k == 0) {
2628         Error ("Invalid lvalue in assignment");
2629         return;
2630     }
2631
2632
2633     /* We're currently only able to handle some adressing modes */
2634     if ((lval->e_flags & E_MGLOBAL) == 0 &&     /* Global address? */
2635         (lval->e_flags & E_MLOCAL) == 0  &&     /* Local address? */
2636         (lval->e_flags & E_MCONST) == 0) {      /* Constant address? */
2637         /* Use generic routine */
2638         opeq (Gen, lval, k);
2639         return;
2640     }
2641
2642     /* Skip the operator */
2643     NextToken ();
2644
2645     /* Check if we have a pointer expression and must scale rhs */
2646     MustScale = (lval->e_tptr [0] == T_PTR);
2647
2648     /* Determine the code generator flags */
2649     flags = TypeOf (lval->e_tptr) | CF_FORCECHAR;
2650
2651     /* Evaluate the rhs */
2652     if (evalexpr (CF_NONE, hie1, &lval2) == 0) {
2653         /* The resulting value is a constant. */
2654         if (MustScale) {
2655             /* lhs is a pointer, scale rhs */
2656             lval2.e_const *= SizeOf (lval->e_tptr+1);
2657         }
2658         flags |= CF_CONST;
2659     } else {
2660         /* rhs is not constant and already in the primary register */
2661         if (MustScale) {
2662             /* lhs is a pointer, scale rhs */
2663             g_scale (TypeOf (lval2.e_tptr), SizeOf (lval->e_tptr+1));
2664         }
2665     }
2666
2667     /* Adjust the rhs to the lhs */
2668     g_typeadjust (flags, TypeOf (lval2.e_tptr));
2669
2670     /* Output apropriate code */
2671     if (lval->e_flags & E_MGLOBAL) {
2672         /* Static variable */
2673         flags |= GlobalModeFlags (lval->e_flags);
2674         if (Gen->Tok == TOK_PLUS_ASSIGN) {
2675             g_addeqstatic (flags, lval->e_name, lval->e_const, lval2.e_const);
2676         } else {
2677             g_subeqstatic (flags, lval->e_name, lval->e_const, lval2.e_const);
2678         }
2679     } else if (lval->e_flags & E_MLOCAL) {
2680         /* ref to localvar */
2681         if (Gen->Tok == TOK_PLUS_ASSIGN) {
2682             g_addeqlocal (flags, lval->e_const, lval2.e_const);
2683         } else {
2684             g_subeqlocal (flags, lval->e_const, lval2.e_const);
2685         }
2686     } else if (lval->e_flags & E_MCONST) {
2687         /* ref to absolute address */
2688         flags |= CF_ABSOLUTE;
2689         if (Gen->Tok == TOK_PLUS_ASSIGN) {
2690             g_addeqstatic (flags, lval->e_const, 0, lval2.e_const);
2691         } else {
2692             g_subeqstatic (flags, lval->e_const, 0, lval2.e_const);
2693         }
2694     } else if (lval->e_flags & E_MEXPR) {
2695         /* Address in a/x. */
2696         if (Gen->Tok == TOK_PLUS_ASSIGN) {
2697             g_addeqind (flags, lval->e_const, lval2.e_const);
2698         } else {
2699             g_subeqind (flags, lval->e_const, lval2.e_const);
2700         }
2701     } else {
2702         Internal ("Invalid addressing mode");
2703     }
2704
2705     /* Expression is in the primary now */
2706     lval->e_flags = E_MEXPR;
2707 }
2708
2709
2710
2711 static void Assignment (struct expent* lval)
2712 /* Parse an assignment */
2713 {
2714     int k;
2715     struct expent lval2;
2716     unsigned flags;
2717     type* ltype = lval->e_tptr;
2718
2719     /* Check for assignment to const */
2720     if (IsQualConst (ltype)) {
2721         Error ("Assignment to const");
2722     }
2723
2724     /* cc65 does not have full support for handling structs by value. Since
2725      * assigning structs is one of the more useful operations from this
2726      * familiy, allow it here.
2727      */
2728     if (IsClassStruct (ltype)) {
2729
2730         /* Bring the address of the lhs into the primary and push it */
2731         exprhs (0, 0, lval);
2732         g_push (CF_PTR | CF_UNSIGNED, 0);
2733
2734         /* Get the expression on the right of the '=' into the primary */
2735         k = hie1 (&lval2);
2736         if (k) {
2737             /* Get the address */
2738             exprhs (0, 0, &lval2);
2739         } else {
2740             /* We need an lvalue */
2741             Error ("Invalid lvalue in assignment");
2742         }
2743
2744         /* Push the address (or whatever is in ax in case of errors) */
2745         g_push (CF_PTR | CF_UNSIGNED, 0);
2746
2747         /* Check for equality of the structs */
2748         if (TypeCmp (ltype, lval2.e_tptr) < TC_EQUAL) {
2749             Error ("Incompatible types");
2750         }
2751
2752         /* Load the size of the struct into the primary */
2753         g_getimmed (CF_INT | CF_UNSIGNED | CF_CONST, SizeOf (ltype), 0);
2754
2755         /* Call the memcpy function */
2756         g_call (CF_FIXARGC, "memcpy", 4);
2757
2758     } else {
2759
2760         /* Get the address on stack if needed */
2761         PushAddr (lval);
2762
2763         /* No struct, setup flags for the load */
2764         flags = SizeOf (ltype) == 1? CF_FORCECHAR : CF_NONE;
2765
2766         /* Get the expression on the right of the '=' into the primary */
2767         if (evalexpr (flags, hie1, &lval2) == 0) {
2768             /* Constant expression. Adjust the types */
2769             assignadjust (ltype, &lval2);
2770             /* Put the value into the primary register */
2771             lconst (flags, &lval2);
2772         } else {
2773             /* Expression is not constant and already in the primary */
2774             assignadjust (ltype, &lval2);
2775         }
2776
2777         /* Generate a store instruction */
2778         store (lval);
2779
2780     }
2781
2782     /* Value is still in primary */
2783     lval->e_flags = E_MEXPR;
2784 }
2785
2786
2787
2788 int hie1 (struct expent* lval)
2789 /* Parse first level of expression hierarchy. */
2790 {
2791     int k;
2792
2793     k = hieQuest (lval);
2794     switch (curtok) {
2795
2796         case TOK_RPAREN:
2797         case TOK_SEMI:
2798             return k;
2799
2800         case TOK_ASSIGN:
2801             NextToken ();
2802             if (k == 0) {
2803                 Error ("Invalid lvalue in assignment");
2804             } else {
2805                 Assignment (lval);
2806             }
2807             break;
2808
2809         case TOK_PLUS_ASSIGN:
2810             addsubeq (&GenPASGN, lval, k);
2811             break;
2812
2813         case TOK_MINUS_ASSIGN:
2814             addsubeq (&GenSASGN, lval, k);
2815             break;
2816
2817         case TOK_MUL_ASSIGN:
2818             opeq (&GenMASGN, lval, k);
2819             break;
2820
2821         case TOK_DIV_ASSIGN:
2822             opeq (&GenDASGN, lval, k);
2823             break;
2824
2825         case TOK_MOD_ASSIGN:
2826             opeq (&GenMOASGN, lval, k);
2827             break;
2828
2829         case TOK_SHL_ASSIGN:
2830             opeq (&GenSLASGN, lval, k);
2831             break;
2832
2833         case TOK_SHR_ASSIGN:
2834             opeq (&GenSRASGN, lval, k);
2835             break;
2836
2837         case TOK_AND_ASSIGN:
2838             opeq (&GenAASGN, lval, k);
2839             break;
2840
2841         case TOK_XOR_ASSIGN:
2842             opeq (&GenXOASGN, lval, k);
2843             break;
2844
2845         case TOK_OR_ASSIGN:
2846             opeq (&GenOASGN, lval, k);
2847             break;
2848
2849         default:
2850             return k;
2851     }
2852     return 0;
2853 }
2854
2855
2856
2857 int hie0 (struct expent *lval)
2858 /* Parse comma operator. */
2859 {
2860     int k;
2861
2862     k = hie1 (lval);
2863     while (curtok == TOK_COMMA) {
2864         NextToken ();
2865         k = hie1 (lval);
2866     }
2867     return k;
2868 }
2869
2870
2871
2872 int evalexpr (unsigned flags, int (*f) (struct expent*), struct expent* lval)
2873 /* Will evaluate an expression via the given function. If the result is a
2874  * constant, 0 is returned and the value is put in the lval struct. If the
2875  * result is not constant, exprhs is called to bring the value into the
2876  * primary register and 1 is returned.
2877  */
2878 {
2879     int k;
2880
2881     /* Evaluate */
2882     k = f (lval);
2883     if (k == 0 && lval->e_flags == E_MCONST) {
2884         /* Constant expression */
2885         return 0;
2886     } else {
2887         /* Not constant, load into the primary */
2888         exprhs (flags, k, lval);
2889         return 1;
2890     }
2891 }
2892
2893
2894
2895 int expr (int (*func) (), struct expent *lval)
2896 /* Expression parser; func is either hie0 or hie1. */
2897 {
2898     int k;
2899     int savsp;
2900
2901     savsp = oursp;
2902
2903     k = (*func) (lval);
2904
2905     /* Do some checks if code generation is still constistent */
2906     if (savsp != oursp) {
2907         if (Debug) {
2908             fprintf (stderr, "oursp != savesp (%d != %d)\n", oursp, savsp);
2909         } else {
2910             Internal ("oursp != savsp (%d != %d)", oursp, savsp);
2911         }
2912     }
2913     return k;
2914 }
2915
2916
2917
2918 void expression1 (struct expent* lval)
2919 /* Evaluate an expression on level 1 (no comma operator) and put it into
2920  * the primary register
2921  */
2922 {
2923     memset (lval, 0, sizeof (*lval));
2924     exprhs (CF_NONE, expr (hie1, lval), lval);
2925 }
2926
2927
2928
2929 void expression (struct expent* lval)
2930 /* Evaluate an expression and put it into the primary register */
2931 {
2932     memset (lval, 0, sizeof (*lval));
2933     exprhs (CF_NONE, expr (hie0, lval), lval);
2934 }
2935
2936
2937
2938 void constexpr (struct expent* lval)
2939 /* Get a constant value */
2940 {
2941     memset (lval, 0, sizeof (*lval));
2942     if (expr (hie1, lval) != 0 || (lval->e_flags & E_MCONST) == 0) {
2943         Error ("Constant expression expected");
2944         /* To avoid any compiler errors, make the expression a valid const */
2945         lval->e_flags = E_MCONST;
2946         lval->e_tptr = type_int;
2947         lval->e_const = 0;
2948     }
2949 }
2950
2951
2952
2953 void intexpr (struct expent* lval)
2954 /* Get an integer expression */
2955 {
2956     expression (lval);
2957     if (!IsClassInt (lval->e_tptr)) {
2958         Error ("Integer expression expected");
2959         /* To avoid any compiler errors, make the expression a valid int */
2960         lval->e_flags = E_MCONST;
2961         lval->e_tptr = type_int;
2962         lval->e_const = 0;
2963     }
2964 }
2965
2966
2967
2968 void boolexpr (struct expent* lval)
2969 /* Get a boolean expression */
2970 {
2971     /* Read an expression */
2972     expression (lval);
2973
2974     /* If it's an integer, it's ok. If it's not an integer, but a pointer,
2975      * the pointer used in a boolean context is also ok
2976      */
2977     if (!IsClassInt (lval->e_tptr) && !IsClassPtr (lval->e_tptr)) {
2978         Error ("Boolean expression expected");
2979         /* To avoid any compiler errors, make the expression a valid int */
2980         lval->e_flags = E_MCONST;
2981         lval->e_tptr = type_int;
2982         lval->e_const = 0;
2983     }
2984 }
2985
2986
2987
2988 void test (unsigned label, int cond)
2989 /* Generate code to perform test and jump if false. */
2990 {
2991     int k;
2992     struct expent lval;
2993
2994     /* Eat the parenthesis */
2995     ConsumeLParen ();
2996
2997     /* Prepare the expression, setup labels */
2998     memset (&lval, 0, sizeof (lval));
2999     lval.e_test = E_TEST;
3000
3001     /* Generate code to eval the expr */
3002     k = expr (hie0, &lval);
3003     if (k == 0 && lval.e_flags == E_MCONST) {
3004         /* Constant rvalue */
3005         if (cond == 0 && lval.e_const == 0) {
3006             g_jump (label);
3007             Warning ("Unreachable code");
3008         } else if (cond && lval.e_const) {
3009             g_jump (label);
3010         }
3011         ConsumeRParen ();
3012         return;
3013     }
3014
3015     /* If the expr hasn't set condition codes, set the force-test flag */
3016     if ((lval.e_test & E_CC) == 0) {
3017         lval.e_test |= E_FORCETEST;
3018     }
3019
3020     /* Load the value into the primary register */
3021     exprhs (CF_FORCECHAR, k, &lval);
3022
3023     /* Check for the closing brace */
3024     ConsumeRParen ();
3025
3026     /* Generate the jump */
3027     if (cond) {
3028         g_truejump (CF_NONE, label);
3029     } else {
3030         /* Special case (putting this here is a small hack - but hey, the
3031          * compiler itself is one big hack...): If a semicolon follows, we
3032          * don't have a statement and may omit the jump.
3033          */
3034         if (curtok != TOK_SEMI) {
3035             g_falsejump (CF_NONE, label);
3036         }
3037     }
3038 }
3039
3040
3041
3042