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