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