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