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