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