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