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