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