4 * Ullrich von Bassewitz, 21.06.1998
39 /*****************************************************************************/
41 /*****************************************************************************/
45 /* Generator attributes */
46 #define GEN_NOPUSH 0x01 /* Don't push lhs */
48 /* Map a generator function and its attributes to a token */
50 token_t Tok; /* Token to map to */
51 unsigned Flags; /* Flags for generator function */
52 void (*Func) (unsigned, unsigned long); /* Generator func */
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 };
83 /*****************************************************************************/
84 /* Function forwards */
85 /*****************************************************************************/
89 static int hie10 (ExprDesc* lval);
90 /* Handle ++, --, !, unary - etc. */
94 /*****************************************************************************/
95 /* Helper functions */
96 /*****************************************************************************/
100 static unsigned GlobalModeFlags (unsigned flags)
101 /* Return the addressing mode flags for the variable with the given flags */
104 if (flags == E_TGLAB) {
105 /* External linkage */
107 } else if (flags == E_TREGISTER) {
108 /* Register variable */
118 static int IsNullPtr (ExprDesc* lval)
119 /* Return true if this is the NULL pointer constant */
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? */
128 static type* promoteint (type* lhst, type* rhst)
129 /* In an expression with two ints, return the type of the result */
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.
136 if (IsTypeLong (lhst) || IsTypeLong (rhst)) {
137 if (IsSignUnsigned (lhst) || IsSignUnsigned (rhst)) {
143 if (IsSignUnsigned (lhst) || IsSignUnsigned (rhst)) {
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.
163 unsigned ltype, rtype;
166 /* Get the type strings */
167 type* lhst = lhs->Type;
168 type* rhst = rhs->Type;
170 /* Generate type adjustment code if needed */
171 ltype = TypeOf (lhst);
172 if (lhs->Flags == E_MCONST) {
176 /* Value is in primary register*/
179 rtype = TypeOf (rhst);
180 if (rhs->Flags == E_MCONST) {
183 flags = g_typeadjust (ltype, rtype);
185 /* Set the type of the result */
186 lhs->Type = promoteint (lhst, rhst);
188 /* Return the code generator flags */
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.
202 /* Get the type of the right hand side. Treat function types as
203 * pointer-to-function
205 type* rhst = rhs->Type;
206 if (IsTypeFunc (rhst)) {
207 rhst = PointerTo (rhst);
210 /* After calling this function, rhs will have the type of the lhs */
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
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");
226 /* Adjust the int types. To avoid manipulation of TOS mark lhs
229 unsigned flags = TypeOf (rhst);
230 if (rhs->Flags == E_MCONST) {
233 return g_typeadjust (TypeOf (lhst) | CF_CONST, flags);
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.
242 if (!IsTypeVoid (Indirect (lhst)) && !IsTypeVoid (Indirect (rhst))) {
243 /* Compare the types */
244 switch (TypeCmp (lhst, rhst)) {
246 case TC_INCOMPATIBLE:
247 Error ("Incompatible pointer types");
251 Error ("Pointer types differ in type qualifiers");
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");
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.
268 if (TypeCmp (Indirect (lhst), rhst) < TC_EQUAL) {
269 Error ("Incompatible types");
272 Error ("Incompatible types");
275 Error ("Incompatible types");
278 /* Return an int value in all cases where the operands are not both ints */
284 void DefineData (ExprDesc* Expr)
285 /* Output a data definition for the given expression */
287 unsigned Flags = Expr->Flags;
289 switch (Flags & E_MCTYPE) {
293 g_defdata (TypeOf (Expr->Type) | CF_CONST, Expr->ConstVal, 0);
297 /* Register variable. Taking the address is usually not
300 if (!AllowRegVarAddr) {
301 Error ("Cannot take the address of a register variable");
307 /* Local or global symbol */
308 g_defdata (GlobalModeFlags (Flags), Expr->Name, Expr->ConstVal);
312 /* a literal of some kind */
313 g_defdata (CF_STATIC, LiteralPoolLabel, Expr->ConstVal);
317 Internal ("Unknown constant type: %04X", Flags);
323 static void lconst (unsigned Flags, ExprDesc* Expr)
324 /* Load the primary register with some constant value. */
326 switch (Expr->Flags & E_MCTYPE) {
329 g_leasp (Expr->ConstVal);
333 /* Number constant */
334 g_getimmed (Flags | TypeOf (Expr->Type) | CF_CONST, Expr->ConstVal, 0);
338 /* Register variable. Taking the address is usually not
341 if (!AllowRegVarAddr) {
342 Error ("Cannot take the address of a register variable");
348 /* Local or global symbol, load address */
349 Flags |= GlobalModeFlags (Expr->Flags);
351 g_getimmed (Flags, Expr->Name, Expr->ConstVal);
356 g_getimmed (CF_STATIC, LiteralPoolLabel, Expr->ConstVal);
360 Internal ("Unknown constant type: %04X", Expr->Flags);
366 static int kcalc (int tok, long val1, long val2)
367 /* Calculate an operation with left and right operand constant. */
371 return (val1 == val2);
373 return (val1 != val2);
375 return (val1 < val2);
377 return (val1 <= val2);
379 return (val1 >= val2);
381 return (val1 > val2);
383 return (val1 | val2);
385 return (val1 ^ val2);
387 return (val1 & val2);
389 return (val1 >> val2);
391 return (val1 << val2);
393 return (val1 * val2);
396 Error ("Division by zero");
399 return (val1 / val2);
402 Error ("Modulo operation with zero");
405 return (val1 % val2);
407 Internal ("kcalc: got token 0x%X\n", tok);
414 static const GenDesc* FindGen (token_t Tok, const GenDesc** Table)
415 /* Find a token in a generator table */
418 while ((G = *Table) != 0) {
429 static int istypeexpr (void)
430 /* Return true if some sort of variable or type is waiting (helper for cast
431 * and sizeof() in hie10).
436 return CurTok.Tok == TOK_LPAREN && (
437 (NextTok.Tok >= TOK_FIRSTTYPE && NextTok.Tok <= TOK_LASTTYPE) ||
438 (NextTok.Tok == TOK_CONST) ||
439 (NextTok.Tok == TOK_IDENT &&
440 (Entry = FindSym (NextTok.Ident)) != 0 &&
446 static void PushAddr (ExprDesc* lval)
447 /* If the expression contains an address that was somehow evaluated,
448 * push this address on the stack. This is a helper function for all
449 * sorts of implicit or explicit assignment functions where the lvalue
450 * must be saved if it's not constant, before evaluating the rhs.
453 /* Get the address on stack if needed */
454 if (lval->Flags != E_MREG && (lval->Flags & E_MEXPR)) {
455 /* Push the address (always a pointer) */
462 static void MakeConstIntExpr (ExprDesc* Expr, long Value)
463 /* Make Expr a constant integer expression with the given value */
465 Expr->Flags = E_MCONST;
466 Expr->Type = type_int;
467 Expr->ConstVal = Value;
472 void ConstSubExpr (int (*F) (ExprDesc*), ExprDesc* Expr)
473 /* Will evaluate an expression via the given function. If the result is not
474 * a constant, a diagnostic will be printed, and the value is replaced by
475 * a constant one to make sure there are no internal errors that result
476 * from this input error.
479 memset (Expr, 0, sizeof (*Expr));
480 if (F (Expr) != 0 || Expr->Flags != E_MCONST) {
481 Error ("Constant expression expected");
482 /* To avoid any compiler errors, make the expression a valid const */
483 MakeConstIntExpr (Expr, 1);
489 /*****************************************************************************/
491 /*****************************************************************************/
495 void exprhs (unsigned flags, int k, ExprDesc *lval)
496 /* Put the result of an expression into the primary register */
502 /* Dereferenced lvalue */
503 flags |= TypeOf (lval->Type);
504 if (lval->Test & E_FORCETEST) {
506 lval->Test &= ~E_FORCETEST;
508 if (f & E_MGLOBAL) { /* ref to globalvar */
510 flags |= GlobalModeFlags (f);
511 g_getstatic (flags, lval->Name, lval->ConstVal);
512 } else if (f & E_MLOCAL) {
513 /* ref to localvar */
514 g_getlocal (flags, lval->ConstVal);
515 } else if (f & E_MCONST) {
516 /* ref to absolute address */
517 g_getstatic (flags | CF_ABSOLUTE, lval->ConstVal, 0);
518 } else if (f == E_MEOFFS) {
519 g_getind (flags, lval->ConstVal);
520 } else if (f != E_MREG) {
523 } else if (f == E_MEOFFS) {
524 /* reference not storable */
525 flags |= TypeOf (lval->Type);
526 g_inc (flags | CF_CONST, lval->ConstVal);
527 } else if ((f & E_MEXPR) == 0) {
528 /* Constant of some sort, load it into the primary */
529 lconst (flags, lval);
531 if (lval->Test & E_FORCETEST) { /* we testing this value? */
533 flags |= TypeOf (lval->Type);
534 g_test (flags); /* yes, force a test */
535 lval->Test &= ~E_FORCETEST;
541 static unsigned FunctionParamList (FuncDesc* Func)
542 /* Parse a function parameter list and pass the parameters to the called
543 * function. Depending on several criteria this may be done by just pushing
544 * each parameter separately, or creating the parameter frame once and then
545 * storing into this frame.
546 * The function returns the size of the parameters pushed.
551 /* Initialize variables */
552 SymEntry* Param = 0; /* Keep gcc silent */
553 unsigned ParamSize = 0; /* Size of parameters pushed */
554 unsigned ParamCount = 0; /* Number of parameters pushed */
555 unsigned FrameSize = 0; /* Size of parameter frame */
556 unsigned FrameParams = 0; /* Number of params in frame */
557 int FrameOffs = 0; /* Offset into parameter frame */
558 int Ellipsis = 0; /* Function is variadic */
560 /* As an optimization, we may allocate the complete parameter frame at
561 * once instead of pushing each parameter as it comes. We may do that,
564 * - optimizations that increase code size are enabled (allocating the
565 * stack frame at once gives usually larger code).
566 * - we have more than one parameter to push (don't count the last param
567 * for __fastcall__ functions).
569 if (CodeSizeFactor >= 200) {
571 /* Calculate the number and size of the parameters */
572 FrameParams = Func->ParamCount;
573 FrameSize = Func->ParamSize;
574 if (FrameParams > 0 && (Func->Flags & FD_FASTCALL) != 0) {
575 /* Last parameter is not pushed */
576 const SymEntry* LastParam = Func->SymTab->SymTail;
577 FrameSize -= CheckedSizeOf (LastParam->Type);
581 /* Do we have more than one parameter in the frame? */
582 if (FrameParams > 1) {
583 /* Okeydokey, setup the frame */
588 /* Don't use a preallocated frame */
593 /* Parse the actual parameter list */
594 while (CurTok.Tok != TOK_RPAREN) {
599 /* Count arguments */
602 /* Fetch the pointer to the next argument, check for too many args */
603 if (ParamCount <= Func->ParamCount) {
604 /* Beware: If there are parameters with identical names, they
605 * cannot go into the same symbol table, which means that in this
606 * case of errorneous input, the number of nodes in the symbol
607 * table and ParamCount are NOT equal. We have to handle this case
608 * below to avoid segmentation violations. Since we know that this
609 * problem can only occur if there is more than one parameter,
610 * we will just use the last one.
612 if (ParamCount == 1) {
614 Param = Func->SymTab->SymHead;
615 } else if (Param->NextSym != 0) {
617 Param = Param->NextSym;
618 CHECK ((Param->Flags & SC_PARAM) != 0);
620 } else if (!Ellipsis) {
621 /* Too many arguments. Do we have an open param list? */
622 if ((Func->Flags & FD_VARIADIC) == 0) {
623 /* End of param list reached, no ellipsis */
624 Error ("Too many arguments in function call");
626 /* Assume an ellipsis even in case of errors to avoid an error
627 * message for each other argument.
632 /* Do some optimization: If we have a constant value to push,
633 * use a special function that may optimize.
636 if (!Ellipsis && CheckedSizeOf (Param->Type) == 1) {
637 CFlags = CF_FORCECHAR;
640 if (evalexpr (CFlags, hie1, &lval) == 0) {
641 /* A constant value */
645 /* If we don't have an argument spec, accept anything, otherwise
646 * convert the actual argument to the type needed.
649 /* Promote the argument if needed */
650 assignadjust (Param->Type, &lval);
652 /* If we have a prototype, chars may be pushed as chars */
653 Flags |= CF_FORCECHAR;
656 /* Use the type of the argument for the push */
657 Flags |= TypeOf (lval.Type);
659 /* If this is a fastcall function, don't push the last argument */
660 if (ParamCount == Func->ParamCount && (Func->Flags & FD_FASTCALL) != 0) {
661 /* Just load the argument into the primary. This is only needed if
662 * we have a constant argument, otherwise the value is already in
665 if (Flags & CF_CONST) {
666 exprhs (CF_FORCECHAR, 0, &lval);
669 unsigned ArgSize = sizeofarg (Flags);
671 /* We have the space already allocated, store in the frame */
672 CHECK (FrameSize >= ArgSize);
673 FrameSize -= ArgSize;
674 FrameOffs -= ArgSize;
676 g_putlocal (Flags | CF_NOKEEP, FrameOffs, lval.ConstVal);
678 /* Push the argument */
679 g_push (Flags, lval.ConstVal);
682 /* Calculate total parameter size */
683 ParamSize += ArgSize;
686 /* Check for end of argument list */
687 if (CurTok.Tok != TOK_COMMA) {
693 /* Check if we had enough parameters */
694 if (ParamCount < Func->ParamCount) {
695 Error ("Too few arguments in function call");
698 /* The function returns the size of all parameters pushed onto the stack.
699 * However, if there are parameters missing (which is an error and was
700 * flagged by the compiler) AND a stack frame was preallocated above,
701 * we would loose track of the stackpointer and generate an internal error
702 * later. So we correct the value by the parameters that should have been
703 * pushed to avoid an internal compiler error. Since an error was
704 * generated before, no code will be output anyway.
706 return ParamSize + FrameSize;
711 static void FunctionCall (int k, ExprDesc* lval)
712 /* Perform a function call. */
714 FuncDesc* Func; /* Function descriptor */
715 int IsFuncPtr; /* Flag */
716 unsigned ParamSize; /* Number of parameter bytes */
717 CodeMark Mark = 0; /* Initialize to keep gcc silent */
718 int PtrOffs = 0; /* Offset of function pointer on stack */
719 int IsFastCall = 0; /* True if it's a fast call function */
720 int PtrOnStack = 0; /* True if a pointer copy is on stack */
722 /* Get a pointer to the function descriptor from the type string */
723 Func = GetFuncDesc (lval->Type);
725 /* Handle function pointers transparently */
726 IsFuncPtr = IsTypeFuncPtr (lval->Type);
729 /* Check wether it's a fastcall function that has parameters */
730 IsFastCall = IsFastCallFunc (lval->Type + 1) && (Func->ParamCount > 0);
732 /* Things may be difficult, depending on where the function pointer
733 * resides. If the function pointer is an expression of some sort
734 * (not a local or global variable), we have to evaluate this
735 * expression now and save the result for later. Since calls to
736 * function pointers may be nested, we must save it onto the stack.
737 * For fastcall functions we do also need to place a copy of the
738 * pointer on stack, since we cannot use a/x.
740 PtrOnStack = IsFastCall || ((lval->Flags & (E_MGLOBAL | E_MLOCAL)) == 0);
743 /* Not a global or local variable, or a fastcall function. Load
744 * the pointer into the primary and mark it as an expression.
746 exprhs (CF_NONE, k, lval);
747 lval->Flags |= E_MEXPR;
749 /* Remember the code position */
750 Mark = GetCodePos ();
752 /* Push the pointer onto the stack and remember the offset */
757 /* Check for known standard functions and inline them if requested */
758 } else if (InlineStdFuncs && IsStdFunc ((const char*) lval->Name)) {
760 /* Inline this function */
761 HandleStdFunc (lval);
766 /* Parse the parameter list */
767 ParamSize = FunctionParamList (Func);
769 /* We need the closing paren here */
772 /* Special handling for function pointers */
775 /* If the function is not a fastcall function, load the pointer to
776 * the function into the primary.
780 /* Not a fastcall function - we may use the primary */
782 /* If we have no parameters, the pointer is still in the
783 * primary. Remove the code to push it and correct the
786 if (ParamSize == 0) {
791 /* Load from the saved copy */
792 g_getlocal (CF_PTR, PtrOffs);
795 /* Load from original location */
796 exprhs (CF_NONE, k, lval);
799 /* Call the function */
800 g_callind (TypeOf (lval->Type+1), ParamSize, PtrOffs);
804 /* Fastcall function. We cannot use the primary for the function
805 * pointer and must therefore use an offset to the stack location.
806 * Since fastcall functions may never be variadic, we can use the
807 * index register for this purpose.
809 g_callind (CF_LOCAL, ParamSize, PtrOffs);
812 /* If we have a pointer on stack, remove it */
814 g_space (- (int) sizeofarg (CF_PTR));
823 /* Normal function */
824 g_call (TypeOf (lval->Type), (const char*) lval->Name, ParamSize);
831 static int primary (ExprDesc* lval)
832 /* This is the lowest level of the expression parser. */
836 /* Initialize fields in the expression stucture */
837 lval->Test = 0; /* No test */
838 lval->Sym = 0; /* Symbol unknown */
840 /* Character and integer constants. */
841 if (CurTok.Tok == TOK_ICONST || CurTok.Tok == TOK_CCONST) {
842 lval->Flags = E_MCONST | E_TCONST;
843 lval->Type = CurTok.Type;
844 lval->ConstVal = CurTok.IVal;
849 /* Process parenthesized subexpression by calling the whole parser
852 if (CurTok.Tok == TOK_LPAREN) {
854 memset (lval, 0, sizeof (*lval)); /* Remove any attributes */
860 /* All others may only be used if the expression evaluation is not called
861 * recursively by the preprocessor.
864 /* Illegal expression in PP mode */
865 Error ("Preprocessor expression expected");
866 MakeConstIntExpr (lval, 1);
871 if (CurTok.Tok == TOK_IDENT) {
876 /* Get a pointer to the symbol table entry */
877 Sym = lval->Sym = FindSym (CurTok.Ident);
879 /* Is the symbol known? */
882 /* We found the symbol - skip the name token */
885 /* The expression type is the symbol type */
886 lval->Type = Sym->Type;
888 /* Check for illegal symbol types */
889 CHECK ((Sym->Flags & SC_LABEL) != SC_LABEL);
890 if (Sym->Flags & SC_TYPE) {
891 /* Cannot use type symbols */
892 Error ("Variable identifier expected");
893 /* Assume an int type to make lval valid */
894 lval->Flags = E_MLOCAL | E_TLOFFS;
895 lval->Type = type_int;
900 /* Check for legal symbol types */
901 if ((Sym->Flags & SC_CONST) == SC_CONST) {
902 /* Enum or some other numeric constant */
903 lval->Flags = E_MCONST;
904 lval->ConstVal = Sym->V.ConstVal;
906 } else if ((Sym->Flags & SC_FUNC) == SC_FUNC) {
908 lval->Flags = E_MGLOBAL | E_MCONST | E_TGLAB;
909 lval->Name = (unsigned long) Sym->Name;
911 } else if ((Sym->Flags & SC_AUTO) == SC_AUTO) {
912 /* Local variable. If this is a parameter for a variadic
913 * function, we have to add some address calculations, and the
914 * address is not const.
916 if ((Sym->Flags & SC_PARAM) == SC_PARAM && F_IsVariadic (CurrentFunc)) {
917 /* Variadic parameter */
918 g_leavariadic (Sym->V.Offs - F_GetParamSize (CurrentFunc));
919 lval->Flags = E_MEXPR;
922 /* Normal parameter */
923 lval->Flags = E_MLOCAL | E_TLOFFS;
924 lval->ConstVal = Sym->V.Offs;
926 } else if ((Sym->Flags & SC_STATIC) == SC_STATIC) {
927 /* Static variable */
928 if (Sym->Flags & (SC_EXTERN | SC_STORAGE)) {
929 lval->Flags = E_MGLOBAL | E_MCONST | E_TGLAB;
930 lval->Name = (unsigned long) Sym->Name;
932 lval->Flags = E_MGLOBAL | E_MCONST | E_TLLAB;
933 lval->Name = Sym->V.Label;
936 } else if ((Sym->Flags & SC_REGISTER) == SC_REGISTER) {
937 /* Register variable, zero page based */
938 lval->Flags = E_MGLOBAL | E_MCONST | E_TREGISTER;
939 lval->Name = Sym->V.Offs;
942 /* Local static variable */
943 lval->Flags = E_MGLOBAL | E_MCONST | E_TLLAB;
944 lval->Name = Sym->V.Offs;
948 /* The symbol is referenced now */
949 Sym->Flags |= SC_REF;
950 if (IsTypeFunc (lval->Type) || IsTypeArray (lval->Type)) {
956 /* We did not find the symbol. Remember the name, then skip it */
957 strcpy (Ident, CurTok.Ident);
960 /* IDENT is either an auto-declared function or an undefined variable. */
961 if (CurTok.Tok == TOK_LPAREN) {
962 /* Declare a function returning int. For that purpose, prepare a
963 * function signature for a function having an empty param list
966 Warning ("Function call without a prototype");
967 Sym = AddGlobalSym (Ident, GetImplicitFuncType(), SC_EXTERN | SC_REF | SC_FUNC);
968 lval->Type = Sym->Type;
969 lval->Flags = E_MGLOBAL | E_MCONST | E_TGLAB;
970 lval->Name = (unsigned long) Sym->Name;
976 /* Undeclared Variable */
977 Sym = AddLocalSym (Ident, type_int, SC_AUTO | SC_REF, 0);
978 lval->Flags = E_MLOCAL | E_TLOFFS;
979 lval->Type = type_int;
981 Error ("Undefined symbol: `%s'", Ident);
987 /* String literal? */
988 if (CurTok.Tok == TOK_SCONST) {
989 lval->Flags = E_MCONST | E_TLIT;
990 lval->ConstVal = CurTok.IVal;
991 lval->Type = GetCharArrayType (GetLiteralPoolOffs () - CurTok.IVal);
997 if (CurTok.Tok == TOK_ASM) {
999 lval->Type = type_void;
1000 lval->Flags = E_MEXPR;
1005 /* __AX__ and __EAX__ pseudo values? */
1006 if (CurTok.Tok == TOK_AX || CurTok.Tok == TOK_EAX) {
1007 lval->Type = (CurTok.Tok == TOK_AX)? type_uint : type_ulong;
1008 lval->Flags = E_MREG;
1009 lval->Test &= ~E_CC;
1012 return 1; /* May be used as lvalue */
1015 /* Illegal primary. */
1016 Error ("Expression expected");
1017 MakeConstIntExpr (lval, 1);
1023 static int arrayref (int k, ExprDesc* lval)
1024 /* Handle an array reference */
1038 /* Skip the bracket */
1041 /* Get the type of left side */
1044 /* We can apply a special treatment for arrays that have a const base
1045 * address. This is true for most arrays and will produce a lot better
1046 * code. Check if this is a const base address.
1048 lflags = lval->Flags & ~E_MCTYPE;
1049 ConstBaseAddr = (lflags == E_MCONST) || /* Constant numeric address */
1050 (lflags & E_MGLOBAL) != 0 || /* Static array, or ... */
1051 lflags == E_MLOCAL; /* Local array */
1053 /* If we have a constant base, we delay the address fetch */
1054 Mark1 = GetCodePos ();
1055 Mark2 = 0; /* Silence gcc */
1056 if (!ConstBaseAddr) {
1057 /* Get a pointer to the array into the primary */
1058 exprhs (CF_NONE, k, lval);
1060 /* Get the array pointer on stack. Do not push more than 16
1061 * bit, even if this value is greater, since we cannot handle
1062 * other than 16bit stuff when doing indexing.
1064 Mark2 = GetCodePos ();
1068 /* TOS now contains ptr to array elements. Get the subscript. */
1070 if (l == 0 && lval2.Flags == E_MCONST) {
1072 /* The array subscript is a constant - remove value from stack */
1073 if (!ConstBaseAddr) {
1077 /* Get an array pointer into the primary */
1078 exprhs (CF_NONE, k, lval);
1081 if (IsClassPtr (tptr1)) {
1083 /* Scale the subscript value according to element size */
1084 lval2.ConstVal *= CheckedPSizeOf (tptr1);
1086 /* Remove code for lhs load */
1089 /* Handle constant base array on stack. Be sure NOT to
1090 * handle pointers the same way, this won't work.
1092 if (IsTypeArray (tptr1) &&
1093 ((lval->Flags & ~E_MCTYPE) == E_MCONST ||
1094 (lval->Flags & ~E_MCTYPE) == E_MLOCAL ||
1095 (lval->Flags & E_MGLOBAL) != 0 ||
1096 (lval->Flags == E_MEOFFS))) {
1097 lval->ConstVal += lval2.ConstVal;
1100 /* Pointer - load into primary and remember offset */
1101 if ((lval->Flags & E_MEXPR) == 0 || k != 0) {
1102 exprhs (CF_NONE, k, lval);
1104 lval->ConstVal = lval2.ConstVal;
1105 lval->Flags = E_MEOFFS;
1108 /* Result is of element type */
1109 lval->Type = Indirect (tptr1);
1114 } else if (IsClassPtr (tptr2 = lval2.Type)) {
1115 /* Subscript is pointer, get element type */
1116 lval2.Type = Indirect (tptr2);
1118 /* Scale the rhs value in the primary register */
1119 g_scale (TypeOf (tptr1), CheckedSizeOf (lval2.Type));
1121 lval->Type = lval2.Type;
1123 Error ("Cannot subscript");
1126 /* Add the subscript. Since arrays are indexed by integers,
1127 * we will ignore the true type of the subscript here and
1128 * use always an int.
1130 g_inc (CF_INT | CF_CONST, lval2.ConstVal);
1134 /* Array subscript is not constant. Load it into the primary */
1135 Mark2 = GetCodePos ();
1136 exprhs (CF_NONE, l, &lval2);
1139 if (IsClassPtr (tptr1)) {
1141 /* Get the element type */
1142 lval->Type = Indirect (tptr1);
1144 /* Indexing is based on int's, so we will just use the integer
1145 * portion of the index (which is in (e)ax, so there's no further
1148 g_scale (CF_INT, CheckedSizeOf (lval->Type));
1150 } else if (IsClassPtr (tptr2)) {
1152 /* Get the element type */
1153 lval2.Type = Indirect (tptr2);
1155 /* Get the int value on top. If we go here, we're sure,
1156 * both values are 16 bit (the first one was truncated
1157 * if necessary and the second one is a pointer).
1158 * Note: If ConstBaseAddr is true, we don't have a value on
1159 * stack, so to "swap" both, just push the subscript.
1161 if (ConstBaseAddr) {
1163 exprhs (CF_NONE, k, lval);
1170 g_scale (TypeOf (tptr1), CheckedSizeOf (lval2.Type));
1171 lval->Type = lval2.Type;
1173 Error ("Cannot subscript");
1176 /* The offset is now in the primary register. It didn't have a
1177 * constant base address for the lhs, the lhs address is already
1178 * on stack, and we must add the offset. If the base address was
1179 * constant, we call special functions to add the address to the
1182 if (!ConstBaseAddr) {
1183 /* Add the subscript. Both values are int sized. */
1187 /* If the subscript has itself a constant address, it is often
1188 * a better idea to reverse again the order of the evaluation.
1189 * This will generate better code if the subscript is a byte
1190 * sized variable. But beware: This is only possible if the
1191 * subscript was not scaled, that is, if this was a byte array
1194 rflags = lval2.Flags & ~E_MCTYPE;
1195 ConstSubAddr = (rflags == E_MCONST) || /* Constant numeric address */
1196 (rflags & E_MGLOBAL) != 0 || /* Static array, or ... */
1197 rflags == E_MLOCAL; /* Local array */
1199 if (ConstSubAddr && CheckedSizeOf (lval->Type) == 1) {
1203 /* Reverse the order of evaluation */
1204 unsigned flags = (CheckedSizeOf (lval2.Type) == 1)? CF_CHAR : CF_INT;
1207 /* Get a pointer to the array into the primary. We have changed
1208 * Type above but we need the original type to load the
1209 * address, so restore it temporarily.
1211 SavedType = lval->Type;
1213 exprhs (CF_NONE, k, lval);
1214 lval->Type = SavedType;
1216 /* Add the variable */
1217 if (rflags == E_MLOCAL) {
1218 g_addlocal (flags, lval2.ConstVal);
1220 flags |= GlobalModeFlags (lval2.Flags);
1221 g_addstatic (flags, lval2.Name, lval2.ConstVal);
1224 if (lflags == E_MCONST) {
1225 /* Constant numeric address. Just add it */
1226 g_inc (CF_INT | CF_UNSIGNED, lval->ConstVal);
1227 } else if (lflags == E_MLOCAL) {
1228 /* Base address is a local variable address */
1229 if (IsTypeArray (tptr1)) {
1230 g_addaddr_local (CF_INT, lval->ConstVal);
1232 g_addlocal (CF_PTR, lval->ConstVal);
1235 /* Base address is a static variable address */
1236 unsigned flags = CF_INT;
1237 flags |= GlobalModeFlags (lval->Flags);
1238 if (IsTypeArray (tptr1)) {
1239 g_addaddr_static (flags, lval->Name, lval->ConstVal);
1241 g_addstatic (flags, lval->Name, lval->ConstVal);
1247 lval->Flags = E_MEXPR;
1250 return !IsTypeArray (lval->Type);
1256 static int structref (int k, ExprDesc* lval)
1257 /* Process struct field after . or ->. */
1263 /* Skip the token and check for an identifier */
1265 if (CurTok.Tok != TOK_IDENT) {
1266 Error ("Identifier expected");
1267 lval->Type = type_int;
1271 /* Get the symbol table entry and check for a struct field */
1272 strcpy (Ident, CurTok.Ident);
1274 Field = FindStructField (lval->Type, Ident);
1276 Error ("Struct/union has no field named `%s'", Ident);
1277 lval->Type = type_int;
1281 /* If we have constant input data, the result is also constant */
1282 flags = lval->Flags & ~E_MCTYPE;
1283 if (flags == E_MCONST ||
1284 (k == 0 && (flags == E_MLOCAL ||
1285 (flags & E_MGLOBAL) != 0 ||
1286 lval->Flags == E_MEOFFS))) {
1287 lval->ConstVal += Field->V.Offs;
1289 if ((flags & E_MEXPR) == 0 || k != 0) {
1290 exprhs (CF_NONE, k, lval);
1292 lval->ConstVal = Field->V.Offs;
1293 lval->Flags = E_MEOFFS;
1295 lval->Type = Field->Type;
1296 return !IsTypeArray (Field->Type);
1301 static int hie11 (ExprDesc *lval)
1302 /* Handle compound types (structs and arrays) */
1309 if (CurTok.Tok < TOK_LBRACK || CurTok.Tok > TOK_PTR_REF) {
1316 if (CurTok.Tok == TOK_LBRACK) {
1318 /* Array reference */
1319 k = arrayref (k, lval);
1321 } else if (CurTok.Tok == TOK_LPAREN) {
1323 /* Function call. Skip the opening parenthesis */
1326 if (IsTypeFunc (lval->Type) || IsTypeFuncPtr (lval->Type)) {
1328 /* Call the function */
1329 FunctionCall (k, lval);
1331 /* Result is in the primary register */
1332 lval->Flags = E_MEXPR;
1335 lval->Type = GetFuncReturn (lval->Type);
1338 Error ("Illegal function call");
1342 } else if (CurTok.Tok == TOK_DOT) {
1344 if (!IsClassStruct (lval->Type)) {
1345 Error ("Struct expected");
1347 k = structref (0, lval);
1349 } else if (CurTok.Tok == TOK_PTR_REF) {
1352 if (tptr[0] != T_PTR || (tptr[1] & T_STRUCT) == 0) {
1353 Error ("Struct pointer expected");
1355 k = structref (k, lval);
1365 static void store (ExprDesc* lval)
1366 /* Store primary reg into this reference */
1372 flags = TypeOf (lval->Type);
1373 if (f & E_MGLOBAL) {
1374 flags |= GlobalModeFlags (f);
1381 g_putstatic (flags, lval->Name, lval->ConstVal);
1383 } else if (f & E_MLOCAL) {
1384 g_putlocal (flags, lval->ConstVal, 0);
1385 } else if (f == E_MEOFFS) {
1386 g_putind (flags, lval->ConstVal);
1387 } else if (f != E_MREG) {
1389 g_putind (flags, 0);
1391 /* Store into absolute address */
1392 g_putstatic (flags | CF_ABSOLUTE, lval->ConstVal, 0);
1396 /* Assume that each one of the stores will invalidate CC */
1397 lval->Test &= ~E_CC;
1402 static void pre_incdec (ExprDesc* lval, void (*inc) (unsigned, unsigned long))
1403 /* Handle --i and ++i */
1410 if ((k = hie10 (lval)) == 0) {
1411 Error ("Invalid lvalue");
1415 /* Get the data type */
1416 flags = TypeOf (lval->Type) | CF_FORCECHAR | CF_CONST;
1418 /* Get the increment value in bytes */
1419 val = (lval->Type [0] == T_PTR)? CheckedPSizeOf (lval->Type) : 1;
1421 /* We're currently only able to handle some adressing modes */
1422 if ((lval->Flags & E_MGLOBAL) == 0 && /* Global address? */
1423 (lval->Flags & E_MLOCAL) == 0 && /* Local address? */
1424 (lval->Flags & E_MCONST) == 0 && /* Constant address? */
1425 (lval->Flags & E_MEXPR) == 0) { /* Address in a/x? */
1427 /* Use generic code. Push the address if needed */
1430 /* Fetch the value */
1431 exprhs (CF_NONE, k, lval);
1433 /* Increment value in primary */
1436 /* Store the result back */
1441 /* Special code for some addressing modes - use the special += ops */
1442 if (lval->Flags & E_MGLOBAL) {
1443 flags |= GlobalModeFlags (lval->Flags);
1445 g_addeqstatic (flags, lval->Name, lval->ConstVal, val);
1447 g_subeqstatic (flags, lval->Name, lval->ConstVal, val);
1449 } else if (lval->Flags & E_MLOCAL) {
1450 /* ref to localvar */
1452 g_addeqlocal (flags, lval->ConstVal, val);
1454 g_subeqlocal (flags, lval->ConstVal, val);
1456 } else if (lval->Flags & E_MCONST) {
1457 /* ref to absolute address */
1458 flags |= CF_ABSOLUTE;
1460 g_addeqstatic (flags, lval->ConstVal, 0, val);
1462 g_subeqstatic (flags, lval->ConstVal, 0, val);
1464 } else if (lval->Flags & E_MEXPR) {
1465 /* Address in a/x, check if we have an offset */
1466 unsigned Offs = (lval->Flags == E_MEOFFS)? lval->ConstVal : 0;
1468 g_addeqind (flags, Offs, val);
1470 g_subeqind (flags, Offs, val);
1473 Internal ("Invalid addressing mode");
1478 /* Result is an expression */
1479 lval->Flags = E_MEXPR;
1484 static void post_incdec (ExprDesc *lval, int k, void (*inc) (unsigned, unsigned long))
1485 /* Handle i-- and i++ */
1491 Error ("Invalid lvalue");
1495 /* Get the data type */
1496 flags = TypeOf (lval->Type);
1498 /* Push the address if needed */
1501 /* Fetch the value and save it (since it's the result of the expression) */
1502 exprhs (CF_NONE, 1, lval);
1503 g_save (flags | CF_FORCECHAR);
1505 /* If we have a pointer expression, increment by the size of the type */
1506 if (lval->Type[0] == T_PTR) {
1507 inc (flags | CF_CONST | CF_FORCECHAR, CheckedSizeOf (lval->Type + 1));
1509 inc (flags | CF_CONST | CF_FORCECHAR, 1);
1512 /* Store the result back */
1515 /* Restore the original value */
1516 g_restore (flags | CF_FORCECHAR);
1517 lval->Flags = E_MEXPR;
1522 static void unaryop (int tok, ExprDesc* lval)
1523 /* Handle unary -/+ and ~ */
1530 if (k == 0 && (lval->Flags & E_MCONST) != 0) {
1531 /* Value is constant */
1533 case TOK_MINUS: lval->ConstVal = -lval->ConstVal; break;
1534 case TOK_PLUS: break;
1535 case TOK_COMP: lval->ConstVal = ~lval->ConstVal; break;
1536 default: Internal ("Unexpected token: %d", tok);
1539 /* Value is not constant */
1540 exprhs (CF_NONE, k, lval);
1542 /* Get the type of the expression */
1543 flags = TypeOf (lval->Type);
1545 /* Handle the operation */
1547 case TOK_MINUS: g_neg (flags); break;
1548 case TOK_PLUS: break;
1549 case TOK_COMP: g_com (flags); break;
1550 default: Internal ("Unexpected token: %d", tok);
1552 lval->Flags = E_MEXPR;
1558 static int typecast (ExprDesc* lval)
1559 /* Handle an explicit cast */
1562 type Type[MAXTYPELEN];
1564 /* Skip the left paren */
1573 /* Read the expression we have to cast */
1576 /* If the expression is a function, treat it as pointer-to-function */
1577 if (IsTypeFunc (lval->Type)) {
1578 lval->Type = PointerTo (lval->Type);
1581 /* Check for a constant on the right side */
1582 if (k == 0 && lval->Flags == E_MCONST) {
1584 /* A cast of a constant to something else. If the new type is an int,
1585 * be sure to handle the size extension correctly. If the new type is
1586 * not an int, the cast is implementation specific anyway, so leave
1589 if (IsClassInt (Type)) {
1591 /* Get the current and new size of the value */
1592 unsigned OldSize = CheckedSizeOf (lval->Type);
1593 unsigned NewSize = CheckedSizeOf (Type);
1594 unsigned OldBits = OldSize * 8;
1595 unsigned NewBits = NewSize * 8;
1597 /* Check if the new datatype will have a smaller range */
1598 if (NewSize < OldSize) {
1600 /* Cut the value to the new size */
1601 lval->ConstVal &= (0xFFFFFFFFUL >> (32 - NewBits));
1603 /* If the new value is signed, sign extend the value */
1604 if (!IsSignUnsigned (Type)) {
1605 lval->ConstVal |= ((~0L) << NewBits);
1608 } else if (NewSize > OldSize) {
1610 /* Sign extend the value if needed */
1611 if (!IsSignUnsigned (Type) && !IsSignUnsigned (lval->Type)) {
1612 if (lval->ConstVal & (0x01UL << (OldBits-1))) {
1613 lval->ConstVal |= ((~0L) << OldBits);
1621 /* Not a constant. Be sure to ignore casts to void */
1622 if (!IsTypeVoid (Type)) {
1624 /* If the size does not change, leave the value alone. Otherwise,
1625 * we have to load the value into the primary and generate code to
1626 * cast the value in the primary register.
1628 if (SizeOf (Type) != SizeOf (lval->Type)) {
1630 /* Load the value into the primary */
1631 exprhs (CF_NONE, k, lval);
1633 /* Mark the lhs as const to avoid a manipulation of TOS */
1634 g_typecast (TypeOf (Type) | CF_CONST, TypeOf (lval->Type));
1636 /* Value is now in primary */
1637 lval->Flags = E_MEXPR;
1643 /* In any case, use the new type */
1644 lval->Type = TypeDup (Type);
1652 static int hie10 (ExprDesc* lval)
1653 /* Handle ++, --, !, unary - etc. */
1658 switch (CurTok.Tok) {
1661 pre_incdec (lval, g_inc);
1665 pre_incdec (lval, g_dec);
1671 unaryop (CurTok.Tok, lval);
1676 if (evalexpr (CF_NONE, hie10, lval) == 0) {
1677 /* Constant expression */
1678 lval->ConstVal = !lval->ConstVal;
1680 g_bneg (TypeOf (lval->Type));
1681 lval->Test |= E_CC; /* bneg will set cc */
1682 lval->Flags = E_MEXPR; /* say it's an expr */
1684 return 0; /* expr not storable */
1688 if (evalexpr (CF_NONE, hie10, lval) != 0) {
1689 /* Expression is not const, indirect value loaded into primary */
1690 lval->Flags = E_MEXPR;
1691 lval->ConstVal = 0; /* Offset is zero now */
1694 if (IsClassPtr (t)) {
1695 lval->Type = Indirect (t);
1697 Error ("Illegal indirection");
1704 /* The & operator may be applied to any lvalue, and it may be
1705 * applied to functions, even if they're no lvalues.
1707 if (k == 0 && !IsTypeFunc (lval->Type)) {
1708 /* Allow the & operator with an array */
1709 if (!IsTypeArray (lval->Type)) {
1710 Error ("Illegal address");
1713 t = TypeAlloc (TypeLen (lval->Type) + 2);
1715 TypeCpy (t + 1, lval->Type);
1722 if (istypeexpr ()) {
1723 type Type[MAXTYPELEN];
1725 lval->ConstVal = CheckedSizeOf (ParseType (Type));
1728 /* Remember the output queue pointer */
1729 CodeMark Mark = GetCodePos ();
1731 lval->ConstVal = CheckedSizeOf (lval->Type);
1732 /* Remove any generated code */
1735 lval->Flags = E_MCONST | E_TCONST;
1736 lval->Type = type_uint;
1737 lval->Test &= ~E_CC;
1741 if (istypeexpr ()) {
1743 return typecast (lval);
1748 switch (CurTok.Tok) {
1750 post_incdec (lval, k, g_inc);
1754 post_incdec (lval, k, g_dec);
1764 static int hie_internal (const GenDesc** ops, /* List of generators */
1765 ExprDesc* lval, /* parent expr's lval */
1766 int (*hienext) (ExprDesc*),
1767 int* UsedGen) /* next higher level */
1768 /* Helper function */
1775 token_t tok; /* The operator token */
1776 unsigned ltype, type;
1777 int rconst; /* Operand is a constant */
1783 while ((Gen = FindGen (CurTok.Tok, ops)) != 0) {
1785 /* Tell the caller that we handled it's ops */
1788 /* All operators that call this function expect an int on the lhs */
1789 if (!IsClassInt (lval->Type)) {
1790 Error ("Integer expression expected");
1793 /* Remember the operator token, then skip it */
1797 /* Get the lhs on stack */
1798 Mark1 = GetCodePos ();
1799 ltype = TypeOf (lval->Type);
1800 if (k == 0 && lval->Flags == E_MCONST) {
1801 /* Constant value */
1802 Mark2 = GetCodePos ();
1803 g_push (ltype | CF_CONST, lval->ConstVal);
1805 /* Value not constant */
1806 exprhs (CF_NONE, k, lval);
1807 Mark2 = GetCodePos ();
1811 /* Get the right hand side */
1812 rconst = (evalexpr (CF_NONE, hienext, &lval2) == 0);
1814 /* Check the type of the rhs */
1815 if (!IsClassInt (lval2.Type)) {
1816 Error ("Integer expression expected");
1819 /* Check for const operands */
1820 if (k == 0 && lval->Flags == E_MCONST && rconst) {
1822 /* Both operands are constant, remove the generated code */
1826 /* Evaluate the result */
1827 lval->ConstVal = kcalc (tok, lval->ConstVal, lval2.ConstVal);
1829 /* Get the type of the result */
1830 lval->Type = promoteint (lval->Type, lval2.Type);
1834 /* If the right hand side is constant, and the generator function
1835 * expects the lhs in the primary, remove the push of the primary
1838 unsigned rtype = TypeOf (lval2.Type);
1841 /* Second value is constant - check for div */
1844 if (tok == TOK_DIV && lval2.ConstVal == 0) {
1845 Error ("Division by zero");
1846 } else if (tok == TOK_MOD && lval2.ConstVal == 0) {
1847 Error ("Modulo operation with zero");
1849 if ((Gen->Flags & GEN_NOPUSH) != 0) {
1852 ltype |= CF_REG; /* Value is in register */
1856 /* Determine the type of the operation result. */
1857 type |= g_typeadjust (ltype, rtype);
1858 lval->Type = promoteint (lval->Type, lval2.Type);
1861 Gen->Func (type, lval2.ConstVal);
1862 lval->Flags = E_MEXPR;
1865 /* We have a rvalue now */
1874 static int hie_compare (const GenDesc** ops, /* List of generators */
1875 ExprDesc* lval, /* parent expr's lval */
1876 int (*hienext) (ExprDesc*))
1877 /* Helper function for the compare operators */
1884 token_t tok; /* The operator token */
1886 int rconst; /* Operand is a constant */
1891 while ((Gen = FindGen (CurTok.Tok, ops)) != 0) {
1893 /* Remember the operator token, then skip it */
1897 /* Get the lhs on stack */
1898 Mark1 = GetCodePos ();
1899 ltype = TypeOf (lval->Type);
1900 if (k == 0 && lval->Flags == E_MCONST) {
1901 /* Constant value */
1902 Mark2 = GetCodePos ();
1903 g_push (ltype | CF_CONST, lval->ConstVal);
1905 /* Value not constant */
1906 exprhs (CF_NONE, k, lval);
1907 Mark2 = GetCodePos ();
1911 /* Get the right hand side */
1912 rconst = (evalexpr (CF_NONE, hienext, &lval2) == 0);
1914 /* Make sure, the types are compatible */
1915 if (IsClassInt (lval->Type)) {
1916 if (!IsClassInt (lval2.Type) && !(IsClassPtr(lval2.Type) && IsNullPtr(lval))) {
1917 Error ("Incompatible types");
1919 } else if (IsClassPtr (lval->Type)) {
1920 if (IsClassPtr (lval2.Type)) {
1921 /* Both pointers are allowed in comparison if they point to
1922 * the same type, or if one of them is a void pointer.
1924 type* left = Indirect (lval->Type);
1925 type* right = Indirect (lval2.Type);
1926 if (TypeCmp (left, right) < TC_EQUAL && *left != T_VOID && *right != T_VOID) {
1927 /* Incomatible pointers */
1928 Error ("Incompatible types");
1930 } else if (!IsNullPtr (&lval2)) {
1931 Error ("Incompatible types");
1935 /* Check for const operands */
1936 if (k == 0 && lval->Flags == E_MCONST && rconst) {
1938 /* Both operands are constant, remove the generated code */
1942 /* Evaluate the result */
1943 lval->ConstVal = kcalc (tok, lval->ConstVal, lval2.ConstVal);
1947 /* If the right hand side is constant, and the generator function
1948 * expects the lhs in the primary, remove the push of the primary
1954 if ((Gen->Flags & GEN_NOPUSH) != 0) {
1957 ltype |= CF_REG; /* Value is in register */
1961 /* Determine the type of the operation result. If the left
1962 * operand is of type char and the right is a constant, or
1963 * if both operands are of type char, we will encode the
1964 * operation as char operation. Otherwise the default
1965 * promotions are used.
1967 if (IsTypeChar (lval->Type) && (IsTypeChar (lval2.Type) || rconst)) {
1969 if (IsSignUnsigned (lval->Type) || IsSignUnsigned (lval2.Type)) {
1970 flags |= CF_UNSIGNED;
1973 flags |= CF_FORCECHAR;
1976 unsigned rtype = TypeOf (lval2.Type) | (flags & CF_CONST);
1977 flags |= g_typeadjust (ltype, rtype);
1981 Gen->Func (flags, lval2.ConstVal);
1982 lval->Flags = E_MEXPR;
1985 /* Result type is always int */
1986 lval->Type = type_int;
1988 /* We have a rvalue now, condition codes are set */
1998 static int hie9 (ExprDesc *lval)
1999 /* Process * and / operators. */
2001 static const GenDesc* hie9_ops [] = {
2002 &GenMUL, &GenDIV, &GenMOD, 0
2006 return hie_internal (hie9_ops, lval, hie10, &UsedGen);
2011 static void parseadd (int k, ExprDesc* lval)
2012 /* Parse an expression with the binary plus operator. lval contains the
2013 * unprocessed left hand side of the expression and will contain the
2014 * result of the expression on return.
2018 unsigned flags; /* Operation flags */
2019 CodeMark Mark; /* Remember code position */
2020 type* lhst; /* Type of left hand side */
2021 type* rhst; /* Type of right hand side */
2024 /* Skip the PLUS token */
2027 /* Get the left hand side type, initialize operation flags */
2031 /* Check for constness on both sides */
2032 if (k == 0 && (lval->Flags & E_MCONST) != 0) {
2034 /* The left hand side is a constant. Good. Get rhs */
2036 if (k == 0 && lval2.Flags == E_MCONST) {
2038 /* Right hand side is also constant. Get the rhs type */
2041 /* Both expressions are constants. Check for pointer arithmetic */
2042 if (IsClassPtr (lhst) && IsClassInt (rhst)) {
2043 /* Left is pointer, right is int, must scale rhs */
2044 lval->ConstVal += lval2.ConstVal * CheckedPSizeOf (lhst);
2045 /* Result type is a pointer */
2046 } else if (IsClassInt (lhst) && IsClassPtr (rhst)) {
2047 /* Left is int, right is pointer, must scale lhs */
2048 lval->ConstVal = lval->ConstVal * CheckedPSizeOf (rhst) + lval2.ConstVal;
2049 /* Result type is a pointer */
2050 lval->Type = lval2.Type;
2051 } else if (IsClassInt (lhst) && IsClassInt (rhst)) {
2052 /* Integer addition */
2053 lval->ConstVal += lval2.ConstVal;
2054 typeadjust (lval, &lval2, 1);
2057 Error ("Invalid operands for binary operator `+'");
2060 /* Result is constant, condition codes not set */
2061 lval->Test &= ~E_CC;
2065 /* lhs is a constant and rhs is not constant. Load rhs into
2068 exprhs (CF_NONE, k, &lval2);
2070 /* Beware: The check above (for lhs) lets not only pass numeric
2071 * constants, but also constant addresses (labels), maybe even
2072 * with an offset. We have to check for that here.
2075 /* First, get the rhs type. */
2079 if (lval->Flags == E_MCONST) {
2080 /* A numerical constant */
2083 /* Constant address label */
2084 flags |= GlobalModeFlags (lval->Flags) | CF_CONSTADDR;
2087 /* Check for pointer arithmetic */
2088 if (IsClassPtr (lhst) && IsClassInt (rhst)) {
2089 /* Left is pointer, right is int, must scale rhs */
2090 g_scale (CF_INT, CheckedPSizeOf (lhst));
2091 /* Operate on pointers, result type is a pointer */
2093 /* Generate the code for the add */
2094 if (lval->Flags == E_MCONST) {
2095 /* Numeric constant */
2096 g_inc (flags, lval->ConstVal);
2098 /* Constant address */
2099 g_addaddr_static (flags, lval->Name, lval->ConstVal);
2101 } else if (IsClassInt (lhst) && IsClassPtr (rhst)) {
2103 /* Left is int, right is pointer, must scale lhs. */
2104 unsigned ScaleFactor = CheckedPSizeOf (rhst);
2106 /* Operate on pointers, result type is a pointer */
2108 lval->Type = lval2.Type;
2110 /* Since we do already have rhs in the primary, if lhs is
2111 * not a numeric constant, and the scale factor is not one
2112 * (no scaling), we must take the long way over the stack.
2114 if (lval->Flags == E_MCONST) {
2115 /* Numeric constant, scale lhs */
2116 lval->ConstVal *= ScaleFactor;
2117 /* Generate the code for the add */
2118 g_inc (flags, lval->ConstVal);
2119 } else if (ScaleFactor == 1) {
2120 /* Constant address but no need to scale */
2121 g_addaddr_static (flags, lval->Name, lval->ConstVal);
2123 /* Constant address that must be scaled */
2124 g_push (TypeOf (lval2.Type), 0); /* rhs --> stack */
2125 g_getimmed (flags, lval->Name, lval->ConstVal);
2126 g_scale (CF_PTR, ScaleFactor);
2129 } else if (IsClassInt (lhst) && IsClassInt (rhst)) {
2130 /* Integer addition */
2131 flags |= typeadjust (lval, &lval2, 1);
2132 /* Generate the code for the add */
2133 if (lval->Flags == E_MCONST) {
2134 /* Numeric constant */
2135 g_inc (flags, lval->ConstVal);
2137 /* Constant address */
2138 g_addaddr_static (flags, lval->Name, lval->ConstVal);
2142 Error ("Invalid operands for binary operator `+'");
2145 /* Result is in primary register */
2146 lval->Flags = E_MEXPR;
2147 lval->Test &= ~E_CC;
2153 /* Left hand side is not constant. Get the value onto the stack. */
2154 exprhs (CF_NONE, k, lval); /* --> primary register */
2155 Mark = GetCodePos ();
2156 g_push (TypeOf (lval->Type), 0); /* --> stack */
2158 /* Evaluate the rhs */
2159 if (evalexpr (CF_NONE, hie9, &lval2) == 0) {
2161 /* Right hand side is a constant. Get the rhs type */
2164 /* Remove pushed value from stack */
2166 pop (TypeOf (lval->Type));
2168 /* Check for pointer arithmetic */
2169 if (IsClassPtr (lhst) && IsClassInt (rhst)) {
2170 /* Left is pointer, right is int, must scale rhs */
2171 lval2.ConstVal *= CheckedPSizeOf (lhst);
2172 /* Operate on pointers, result type is a pointer */
2174 } else if (IsClassInt (lhst) && IsClassPtr (rhst)) {
2175 /* Left is int, right is pointer, must scale lhs (ptr only) */
2176 g_scale (CF_INT | CF_CONST, CheckedPSizeOf (rhst));
2177 /* Operate on pointers, result type is a pointer */
2179 lval->Type = lval2.Type;
2180 } else if (IsClassInt (lhst) && IsClassInt (rhst)) {
2181 /* Integer addition */
2182 flags = typeadjust (lval, &lval2, 1);
2185 Error ("Invalid operands for binary operator `+'");
2188 /* Generate code for the add */
2189 g_inc (flags | CF_CONST, lval2.ConstVal);
2191 /* Result is in primary register */
2192 lval->Flags = E_MEXPR;
2193 lval->Test &= ~E_CC;
2197 /* lhs and rhs are not constant. Get the rhs type. */
2200 /* Check for pointer arithmetic */
2201 if (IsClassPtr (lhst) && IsClassInt (rhst)) {
2202 /* Left is pointer, right is int, must scale rhs */
2203 g_scale (CF_INT, CheckedPSizeOf (lhst));
2204 /* Operate on pointers, result type is a pointer */
2206 } else if (IsClassInt (lhst) && IsClassPtr (rhst)) {
2207 /* Left is int, right is pointer, must scale lhs */
2208 g_tosint (TypeOf (rhst)); /* Make sure, TOS is int */
2209 g_swap (CF_INT); /* Swap TOS and primary */
2210 g_scale (CF_INT, CheckedPSizeOf (rhst));
2211 /* Operate on pointers, result type is a pointer */
2213 lval->Type = lval2.Type;
2214 } else if (IsClassInt (lhst) && IsClassInt (rhst)) {
2215 /* Integer addition */
2216 flags = typeadjust (lval, &lval2, 0);
2219 Error ("Invalid operands for binary operator `+'");
2222 /* Generate code for the add */
2225 /* Result is in primary register */
2226 lval->Flags = E_MEXPR;
2227 lval->Test &= ~E_CC;
2236 static void parsesub (int k, ExprDesc* lval)
2237 /* Parse an expression with the binary minus operator. lval contains the
2238 * unprocessed left hand side of the expression and will contain the
2239 * result of the expression on return.
2243 unsigned flags; /* Operation flags */
2244 type* lhst; /* Type of left hand side */
2245 type* rhst; /* Type of right hand side */
2246 CodeMark Mark1; /* Save position of output queue */
2247 CodeMark Mark2; /* Another position in the queue */
2248 int rscale; /* Scale factor for the result */
2251 /* Skip the MINUS token */
2254 /* Get the left hand side type, initialize operation flags */
2257 rscale = 1; /* Scale by 1, that is, don't scale */
2259 /* Remember the output queue position, then bring the value onto the stack */
2260 Mark1 = GetCodePos ();
2261 exprhs (CF_NONE, k, lval); /* --> primary register */
2262 Mark2 = GetCodePos ();
2263 g_push (TypeOf (lhst), 0); /* --> stack */
2265 /* Parse the right hand side */
2266 if (evalexpr (CF_NONE, hie9, &lval2) == 0) {
2268 /* The right hand side is constant. Get the rhs type. */
2271 /* Check left hand side */
2272 if (k == 0 && (lval->Flags & E_MCONST) != 0) {
2274 /* Both sides are constant, remove generated code */
2276 pop (TypeOf (lhst)); /* Clean up the stack */
2278 /* Check for pointer arithmetic */
2279 if (IsClassPtr (lhst) && IsClassInt (rhst)) {
2280 /* Left is pointer, right is int, must scale rhs */
2281 lval->ConstVal -= lval2.ConstVal * CheckedPSizeOf (lhst);
2282 /* Operate on pointers, result type is a pointer */
2283 } else if (IsClassPtr (lhst) && IsClassPtr (rhst)) {
2284 /* Left is pointer, right is pointer, must scale result */
2285 if (TypeCmp (Indirect (lhst), Indirect (rhst)) < TC_QUAL_DIFF) {
2286 Error ("Incompatible pointer types");
2288 lval->ConstVal = (lval->ConstVal - lval2.ConstVal) /
2289 CheckedPSizeOf (lhst);
2291 /* Operate on pointers, result type is an integer */
2292 lval->Type = type_int;
2293 } else if (IsClassInt (lhst) && IsClassInt (rhst)) {
2294 /* Integer subtraction */
2295 typeadjust (lval, &lval2, 1);
2296 lval->ConstVal -= lval2.ConstVal;
2299 Error ("Invalid operands for binary operator `-'");
2302 /* Result is constant, condition codes not set */
2303 /* lval->Flags = E_MCONST; ### */
2304 lval->Test &= ~E_CC;
2308 /* Left hand side is not constant, right hand side is.
2309 * Remove pushed value from stack.
2312 pop (TypeOf (lhst));
2314 if (IsClassPtr (lhst) && IsClassInt (rhst)) {
2315 /* Left is pointer, right is int, must scale rhs */
2316 lval2.ConstVal *= CheckedPSizeOf (lhst);
2317 /* Operate on pointers, result type is a pointer */
2319 } else if (IsClassPtr (lhst) && IsClassPtr (rhst)) {
2320 /* Left is pointer, right is pointer, must scale result */
2321 if (TypeCmp (Indirect (lhst), Indirect (rhst)) < TC_QUAL_DIFF) {
2322 Error ("Incompatible pointer types");
2324 rscale = CheckedPSizeOf (lhst);
2326 /* Operate on pointers, result type is an integer */
2328 lval->Type = type_int;
2329 } else if (IsClassInt (lhst) && IsClassInt (rhst)) {
2330 /* Integer subtraction */
2331 flags = typeadjust (lval, &lval2, 1);
2334 Error ("Invalid operands for binary operator `-'");
2337 /* Do the subtraction */
2338 g_dec (flags | CF_CONST, lval2.ConstVal);
2340 /* If this was a pointer subtraction, we must scale the result */
2342 g_scale (flags, -rscale);
2345 /* Result is in primary register */
2346 lval->Flags = E_MEXPR;
2347 lval->Test &= ~E_CC;
2353 /* Right hand side is not constant. Get the rhs type. */
2356 /* Check for pointer arithmetic */
2357 if (IsClassPtr (lhst) && IsClassInt (rhst)) {
2358 /* Left is pointer, right is int, must scale rhs */
2359 g_scale (CF_INT, CheckedPSizeOf (lhst));
2360 /* Operate on pointers, result type is a pointer */
2362 } else if (IsClassPtr (lhst) && IsClassPtr (rhst)) {
2363 /* Left is pointer, right is pointer, must scale result */
2364 if (TypeCmp (Indirect (lhst), Indirect (rhst)) < TC_QUAL_DIFF) {
2365 Error ("Incompatible pointer types");
2367 rscale = CheckedPSizeOf (lhst);
2369 /* Operate on pointers, result type is an integer */
2371 lval->Type = type_int;
2372 } else if (IsClassInt (lhst) && IsClassInt (rhst)) {
2373 /* Integer subtraction. If the left hand side descriptor says that
2374 * the lhs is const, we have to remove this mark, since this is no
2375 * longer true, lhs is on stack instead.
2377 if (lval->Flags == E_MCONST) {
2378 lval->Flags = E_MEXPR;
2380 /* Adjust operand types */
2381 flags = typeadjust (lval, &lval2, 0);
2384 Error ("Invalid operands for binary operator `-'");
2387 /* Generate code for the sub (the & is a hack here) */
2388 g_sub (flags & ~CF_CONST, 0);
2390 /* If this was a pointer subtraction, we must scale the result */
2392 g_scale (flags, -rscale);
2395 /* Result is in primary register */
2396 lval->Flags = E_MEXPR;
2397 lval->Test &= ~E_CC;
2403 static int hie8 (ExprDesc* lval)
2404 /* Process + and - binary operators. */
2406 int k = hie9 (lval);
2407 while (CurTok.Tok == TOK_PLUS || CurTok.Tok == TOK_MINUS) {
2409 if (CurTok.Tok == TOK_PLUS) {
2422 static int hie7 (ExprDesc *lval)
2423 /* Parse << and >>. */
2425 static const GenDesc* hie7_ops [] = {
2430 return hie_internal (hie7_ops, lval, hie8, &UsedGen);
2435 static int hie6 (ExprDesc *lval)
2436 /* process greater-than type comparators */
2438 static const GenDesc* hie6_ops [] = {
2439 &GenLT, &GenLE, &GenGE, &GenGT, 0
2441 return hie_compare (hie6_ops, lval, hie7);
2446 static int hie5 (ExprDesc *lval)
2448 static const GenDesc* hie5_ops[] = {
2451 return hie_compare (hie5_ops, lval, hie6);
2456 static int hie4 (ExprDesc* lval)
2457 /* Handle & (bitwise and) */
2459 static const GenDesc* hie4_ops [] = {
2464 return hie_internal (hie4_ops, lval, hie5, &UsedGen);
2469 static int hie3 (ExprDesc *lval)
2470 /* Handle ^ (bitwise exclusive or) */
2472 static const GenDesc* hie3_ops [] = {
2477 return hie_internal (hie3_ops, lval, hie4, &UsedGen);
2482 static int hie2 (ExprDesc *lval)
2483 /* Handle | (bitwise or) */
2485 static const GenDesc* hie2_ops [] = {
2490 return hie_internal (hie2_ops, lval, hie3, &UsedGen);
2495 static int hieAndPP (ExprDesc* lval)
2496 /* Process "exp && exp" in preprocessor mode (that is, when the parser is
2497 * called recursively from the preprocessor.
2502 ConstSubExpr (hie2, lval);
2503 while (CurTok.Tok == TOK_BOOL_AND) {
2505 /* Left hand side must be an int */
2506 if (!IsClassInt (lval->Type)) {
2507 Error ("Left hand side must be of integer type");
2508 MakeConstIntExpr (lval, 1);
2515 ConstSubExpr (hie2, &lval2);
2517 /* Since we are in PP mode, all we know about is integers */
2518 if (!IsClassInt (lval2.Type)) {
2519 Error ("Right hand side must be of integer type");
2520 MakeConstIntExpr (&lval2, 1);
2523 /* Combine the two */
2524 lval->ConstVal = (lval->ConstVal && lval2.ConstVal);
2527 /* Always a rvalue */
2533 static int hieOrPP (ExprDesc *lval)
2534 /* Process "exp || exp" in preprocessor mode (that is, when the parser is
2535 * called recursively from the preprocessor.
2540 ConstSubExpr (hieAndPP, lval);
2541 while (CurTok.Tok == TOK_BOOL_OR) {
2543 /* Left hand side must be an int */
2544 if (!IsClassInt (lval->Type)) {
2545 Error ("Left hand side must be of integer type");
2546 MakeConstIntExpr (lval, 1);
2553 ConstSubExpr (hieAndPP, &lval2);
2555 /* Since we are in PP mode, all we know about is integers */
2556 if (!IsClassInt (lval2.Type)) {
2557 Error ("Right hand side must be of integer type");
2558 MakeConstIntExpr (&lval2, 1);
2561 /* Combine the two */
2562 lval->ConstVal = (lval->ConstVal || lval2.ConstVal);
2565 /* Always a rvalue */
2571 static int hieAnd (ExprDesc* lval, unsigned TrueLab, int* BoolOp)
2572 /* Process "exp && exp" */
2579 if (CurTok.Tok == TOK_BOOL_AND) {
2581 /* Tell our caller that we're evaluating a boolean */
2584 /* Get a label that we will use for false expressions */
2585 lab = GetLocalLabel ();
2587 /* If the expr hasn't set condition codes, set the force-test flag */
2588 if ((lval->Test & E_CC) == 0) {
2589 lval->Test |= E_FORCETEST;
2592 /* Load the value */
2593 exprhs (CF_FORCECHAR, k, lval);
2595 /* Generate the jump */
2596 g_falsejump (CF_NONE, lab);
2598 /* Parse more boolean and's */
2599 while (CurTok.Tok == TOK_BOOL_AND) {
2606 if ((lval2.Test & E_CC) == 0) {
2607 lval2.Test |= E_FORCETEST;
2609 exprhs (CF_FORCECHAR, k, &lval2);
2611 /* Do short circuit evaluation */
2612 if (CurTok.Tok == TOK_BOOL_AND) {
2613 g_falsejump (CF_NONE, lab);
2615 /* Last expression - will evaluate to true */
2616 g_truejump (CF_NONE, TrueLab);
2620 /* Define the false jump label here */
2621 g_defcodelabel (lab);
2623 /* Define the label */
2624 lval->Flags = E_MEXPR;
2625 lval->Test |= E_CC; /* Condition codes are set */
2633 static int hieOr (ExprDesc *lval)
2634 /* Process "exp || exp". */
2638 int BoolOp = 0; /* Did we have a boolean op? */
2639 int AndOp; /* Did we have a && operation? */
2640 unsigned TrueLab; /* Jump to this label if true */
2644 TrueLab = GetLocalLabel ();
2646 /* Call the next level parser */
2647 k = hieAnd (lval, TrueLab, &BoolOp);
2649 /* Any boolean or's? */
2650 if (CurTok.Tok == TOK_BOOL_OR) {
2652 /* If the expr hasn't set condition codes, set the force-test flag */
2653 if ((lval->Test & E_CC) == 0) {
2654 lval->Test |= E_FORCETEST;
2657 /* Get first expr */
2658 exprhs (CF_FORCECHAR, k, lval);
2660 /* For each expression jump to TrueLab if true. Beware: If we
2661 * had && operators, the jump is already in place!
2664 g_truejump (CF_NONE, TrueLab);
2667 /* Remember that we had a boolean op */
2670 /* while there's more expr */
2671 while (CurTok.Tok == TOK_BOOL_OR) {
2678 k = hieAnd (&lval2, TrueLab, &AndOp);
2679 if ((lval2.Test & E_CC) == 0) {
2680 lval2.Test |= E_FORCETEST;
2682 exprhs (CF_FORCECHAR, k, &lval2);
2684 /* If there is more to come, add shortcut boolean eval. */
2685 g_truejump (CF_NONE, TrueLab);
2688 lval->Flags = E_MEXPR;
2689 lval->Test |= E_CC; /* Condition codes are set */
2693 /* If we really had boolean ops, generate the end sequence */
2695 DoneLab = GetLocalLabel ();
2696 g_getimmed (CF_INT | CF_CONST, 0, 0); /* Load FALSE */
2697 g_falsejump (CF_NONE, DoneLab);
2698 g_defcodelabel (TrueLab);
2699 g_getimmed (CF_INT | CF_CONST, 1, 0); /* Load TRUE */
2700 g_defcodelabel (DoneLab);
2707 static int hieQuest (ExprDesc *lval)
2708 /* Parse "lvalue ? exp : exp" */
2713 ExprDesc lval2; /* Expression 2 */
2714 ExprDesc lval3; /* Expression 3 */
2715 type* type2; /* Type of expression 2 */
2716 type* type3; /* Type of expression 3 */
2717 type* rtype; /* Type of result */
2718 CodeMark Mark1; /* Save position in output code */
2719 CodeMark Mark2; /* Save position in output code */
2723 k = Preprocessing? hieOrPP (lval) : hieOr (lval);
2724 if (CurTok.Tok == TOK_QUEST) {
2726 if ((lval->Test & E_CC) == 0) {
2727 /* Condition codes not set, force a test */
2728 lval->Test |= E_FORCETEST;
2730 exprhs (CF_NONE, k, lval);
2731 labf = GetLocalLabel ();
2732 g_falsejump (CF_NONE, labf);
2734 /* Parse second and third expression */
2735 expression1 (&lval2);
2736 labt = GetLocalLabel ();
2739 g_defcodelabel (labf);
2740 expression1 (&lval3);
2742 /* Check if any conversions are needed, if so, do them.
2743 * Conversion rules for ?: expression are:
2744 * - if both expressions are int expressions, default promotion
2745 * rules for ints apply.
2746 * - if both expressions are pointers of the same type, the
2747 * result of the expression is of this type.
2748 * - if one of the expressions is a pointer and the other is
2749 * a zero constant, the resulting type is that of the pointer
2751 * - all other cases are flagged by an error.
2755 if (IsClassInt (type2) && IsClassInt (type3)) {
2757 /* Get common type */
2758 rtype = promoteint (type2, type3);
2760 /* Convert the third expression to this type if needed */
2761 g_typecast (TypeOf (rtype), TypeOf (type3));
2763 /* Setup a new label so that the expr3 code will jump around
2764 * the type cast code for expr2.
2766 labf = GetLocalLabel (); /* Get new label */
2767 Mark1 = GetCodePos (); /* Remember current position */
2768 g_jump (labf); /* Jump around code */
2770 /* The jump for expr2 goes here */
2771 g_defcodelabel (labt);
2773 /* Create the typecast code for expr2 */
2774 Mark2 = GetCodePos (); /* Remember position */
2775 g_typecast (TypeOf (rtype), TypeOf (type2));
2777 /* Jump here around the typecase code. */
2778 g_defcodelabel (labf);
2779 labt = 0; /* Mark other label as invalid */
2781 } else if (IsClassPtr (type2) && IsClassPtr (type3)) {
2782 /* Must point to same type */
2783 if (TypeCmp (Indirect (type2), Indirect (type3)) < TC_EQUAL) {
2784 Error ("Incompatible pointer types");
2786 /* Result has the common type */
2788 } else if (IsClassPtr (type2) && IsNullPtr (&lval3)) {
2789 /* Result type is pointer, no cast needed */
2791 } else if (IsNullPtr (&lval2) && IsClassPtr (type3)) {
2792 /* Result type is pointer, no cast needed */
2795 Error ("Incompatible types");
2796 rtype = lval2.Type; /* Doesn't matter here */
2799 /* If we don't have the label defined until now, do it */
2801 g_defcodelabel (labt);
2804 /* Setup the target expression */
2805 lval->Flags = E_MEXPR;
2814 static void opeq (const GenDesc* Gen, ExprDesc *lval, int k)
2815 /* Process "op=" operators. */
2824 Error ("Invalid lvalue in assignment");
2828 /* Determine the type of the lhs */
2829 flags = TypeOf (lval->Type);
2830 MustScale = (Gen->Func == g_add || Gen->Func == g_sub) &&
2831 lval->Type [0] == T_PTR;
2833 /* Get the lhs address on stack (if needed) */
2836 /* Fetch the lhs into the primary register if needed */
2837 exprhs (CF_NONE, k, lval);
2839 /* Bring the lhs on stack */
2840 Mark = GetCodePos ();
2843 /* Evaluate the rhs */
2844 if (evalexpr (CF_NONE, hie1, &lval2) == 0) {
2845 /* The resulting value is a constant. If the generator has the NOPUSH
2846 * flag set, don't push the lhs.
2848 if (Gen->Flags & GEN_NOPUSH) {
2853 /* lhs is a pointer, scale rhs */
2854 lval2.ConstVal *= CheckedSizeOf (lval->Type+1);
2857 /* If the lhs is character sized, the operation may be later done
2860 if (CheckedSizeOf (lval->Type) == 1) {
2861 flags |= CF_FORCECHAR;
2864 /* Special handling for add and sub - some sort of a hack, but short code */
2865 if (Gen->Func == g_add) {
2866 g_inc (flags | CF_CONST, lval2.ConstVal);
2867 } else if (Gen->Func == g_sub) {
2868 g_dec (flags | CF_CONST, lval2.ConstVal);
2870 Gen->Func (flags | CF_CONST, lval2.ConstVal);
2873 /* rhs is not constant and already in the primary register */
2875 /* lhs is a pointer, scale rhs */
2876 g_scale (TypeOf (lval2.Type), CheckedSizeOf (lval->Type+1));
2879 /* If the lhs is character sized, the operation may be later done
2882 if (CheckedSizeOf (lval->Type) == 1) {
2883 flags |= CF_FORCECHAR;
2886 /* Adjust the types of the operands if needed */
2887 Gen->Func (g_typeadjust (flags, TypeOf (lval2.Type)), 0);
2890 lval->Flags = E_MEXPR;
2895 static void addsubeq (const GenDesc* Gen, ExprDesc *lval, int k)
2896 /* Process the += and -= operators */
2904 /* We must have an lvalue */
2906 Error ("Invalid lvalue in assignment");
2910 /* We're currently only able to handle some adressing modes */
2911 if ((lval->Flags & E_MGLOBAL) == 0 && /* Global address? */
2912 (lval->Flags & E_MLOCAL) == 0 && /* Local address? */
2913 (lval->Flags & E_MCONST) == 0) { /* Constant address? */
2914 /* Use generic routine */
2915 opeq (Gen, lval, k);
2919 /* Skip the operator */
2922 /* Check if we have a pointer expression and must scale rhs */
2923 MustScale = (lval->Type [0] == T_PTR);
2925 /* Initialize the code generator flags */
2929 /* Evaluate the rhs */
2930 if (evalexpr (CF_NONE, hie1, &lval2) == 0) {
2931 /* The resulting value is a constant. */
2933 /* lhs is a pointer, scale rhs */
2934 lval2.ConstVal *= CheckedSizeOf (lval->Type+1);
2939 /* rhs is not constant and already in the primary register */
2941 /* lhs is a pointer, scale rhs */
2942 g_scale (TypeOf (lval2.Type), CheckedSizeOf (lval->Type+1));
2946 /* Setup the code generator flags */
2947 lflags |= TypeOf (lval->Type) | CF_FORCECHAR;
2948 rflags |= TypeOf (lval2.Type);
2950 /* Adjust the rhs to the lhs. To avoid manipulation of the TOS, mark
2953 g_typeadjust (lflags | CF_CONST, rflags);
2955 /* Output apropriate code */
2956 if (lval->Flags & E_MGLOBAL) {
2957 /* Static variable */
2958 lflags |= GlobalModeFlags (lval->Flags);
2959 if (Gen->Tok == TOK_PLUS_ASSIGN) {
2960 g_addeqstatic (lflags, lval->Name, lval->ConstVal, lval2.ConstVal);
2962 g_subeqstatic (lflags, lval->Name, lval->ConstVal, lval2.ConstVal);
2964 } else if (lval->Flags & E_MLOCAL) {
2965 /* ref to localvar */
2966 if (Gen->Tok == TOK_PLUS_ASSIGN) {
2967 g_addeqlocal (lflags, lval->ConstVal, lval2.ConstVal);
2969 g_subeqlocal (lflags, lval->ConstVal, lval2.ConstVal);
2971 } else if (lval->Flags & E_MCONST) {
2972 /* ref to absolute address */
2973 lflags |= CF_ABSOLUTE;
2974 if (Gen->Tok == TOK_PLUS_ASSIGN) {
2975 g_addeqstatic (lflags, lval->ConstVal, 0, lval2.ConstVal);
2977 g_subeqstatic (lflags, lval->ConstVal, 0, lval2.ConstVal);
2979 } else if (lval->Flags & E_MEXPR) {
2980 /* Address in a/x. */
2981 if (Gen->Tok == TOK_PLUS_ASSIGN) {
2982 g_addeqind (lflags, lval->ConstVal, lval2.ConstVal);
2984 g_subeqind (lflags, lval->ConstVal, lval2.ConstVal);
2987 Internal ("Invalid addressing mode");
2990 /* Expression is in the primary now */
2991 lval->Flags = E_MEXPR;
2996 static void Assignment (ExprDesc* lval)
2997 /* Parse an assignment */
3002 type* ltype = lval->Type;
3004 /* Check for assignment to const */
3005 if (IsQualConst (ltype)) {
3006 Error ("Assignment to const");
3009 /* cc65 does not have full support for handling structs by value. Since
3010 * assigning structs is one of the more useful operations from this
3011 * family, allow it here.
3013 if (IsClassStruct (ltype)) {
3015 /* Bring the address of the lhs into the primary and push it */
3016 exprhs (0, 0, lval);
3017 g_push (CF_PTR | CF_UNSIGNED, 0);
3019 /* Get the expression on the right of the '=' into the primary */
3022 /* Get the address */
3023 exprhs (0, 0, &lval2);
3026 /* Push the address (or whatever is in ax in case of errors) */
3027 g_push (CF_PTR | CF_UNSIGNED, 0);
3029 /* Check for equality of the structs */
3030 if (TypeCmp (ltype, lval2.Type) < TC_STRICT_COMPATIBLE) {
3031 Error ("Incompatible types");
3034 /* Load the size of the struct into the primary */
3035 g_getimmed (CF_INT | CF_UNSIGNED | CF_CONST, CheckedSizeOf (ltype), 0);
3037 /* Call the memcpy function */
3038 g_call (CF_FIXARGC, "memcpy", 4);
3042 /* Get the address on stack if needed */
3045 /* No struct, setup flags for the load */
3046 flags = CheckedSizeOf (ltype) == 1? CF_FORCECHAR : CF_NONE;
3048 /* Get the expression on the right of the '=' into the primary */
3049 if (evalexpr (flags, hie1, &lval2) == 0) {
3050 /* Constant expression. Adjust the types */
3051 assignadjust (ltype, &lval2);
3052 /* Put the value into the primary register */
3053 lconst (flags, &lval2);
3055 /* Expression is not constant and already in the primary */
3056 assignadjust (ltype, &lval2);
3059 /* Generate a store instruction */
3064 /* Value is still in primary */
3065 lval->Flags = E_MEXPR;
3070 int hie1 (ExprDesc* lval)
3071 /* Parse first level of expression hierarchy. */
3075 k = hieQuest (lval);
3076 switch (CurTok.Tok) {
3085 Error ("Invalid lvalue in assignment");
3091 case TOK_PLUS_ASSIGN:
3092 addsubeq (&GenPASGN, lval, k);
3095 case TOK_MINUS_ASSIGN:
3096 addsubeq (&GenSASGN, lval, k);
3099 case TOK_MUL_ASSIGN:
3100 opeq (&GenMASGN, lval, k);
3103 case TOK_DIV_ASSIGN:
3104 opeq (&GenDASGN, lval, k);
3107 case TOK_MOD_ASSIGN:
3108 opeq (&GenMOASGN, lval, k);
3111 case TOK_SHL_ASSIGN:
3112 opeq (&GenSLASGN, lval, k);
3115 case TOK_SHR_ASSIGN:
3116 opeq (&GenSRASGN, lval, k);
3119 case TOK_AND_ASSIGN:
3120 opeq (&GenAASGN, lval, k);
3123 case TOK_XOR_ASSIGN:
3124 opeq (&GenXOASGN, lval, k);
3128 opeq (&GenOASGN, lval, k);
3139 int hie0 (ExprDesc *lval)
3140 /* Parse comma operator. */
3145 while (CurTok.Tok == TOK_COMMA) {
3154 int evalexpr (unsigned flags, int (*f) (ExprDesc*), ExprDesc* lval)
3155 /* Will evaluate an expression via the given function. If the result is a
3156 * constant, 0 is returned and the value is put in the lval struct. If the
3157 * result is not constant, exprhs is called to bring the value into the
3158 * primary register and 1 is returned.
3165 if (k == 0 && lval->Flags == E_MCONST) {
3166 /* Constant expression */
3169 /* Not constant, load into the primary */
3170 exprhs (flags, k, lval);
3177 int expr (int (*func) (ExprDesc*), ExprDesc *lval)
3178 /* Expression parser; func is either hie0 or hie1. */
3187 /* Do some checks if code generation is still constistent */
3188 if (savsp != oursp) {
3190 fprintf (stderr, "oursp != savesp (%d != %d)\n", oursp, savsp);
3192 Internal ("oursp != savsp (%d != %d)", oursp, savsp);
3200 void expression1 (ExprDesc* lval)
3201 /* Evaluate an expression on level 1 (no comma operator) and put it into
3202 * the primary register
3205 memset (lval, 0, sizeof (*lval));
3206 exprhs (CF_NONE, expr (hie1, lval), lval);
3211 void expression (ExprDesc* lval)
3212 /* Evaluate an expression and put it into the primary register */
3214 memset (lval, 0, sizeof (*lval));
3215 exprhs (CF_NONE, expr (hie0, lval), lval);
3220 void ConstExpr (ExprDesc* lval)
3221 /* Get a constant value */
3223 memset (lval, 0, sizeof (*lval));
3224 if (expr (hie1, lval) != 0 || (lval->Flags & E_MCONST) == 0) {
3225 Error ("Constant expression expected");
3226 /* To avoid any compiler errors, make the expression a valid const */
3227 MakeConstIntExpr (lval, 1);
3233 void ConstIntExpr (ExprDesc* Val)
3234 /* Get a constant int value */
3236 memset (Val, 0, sizeof (*Val));
3237 if (expr (hie1, Val) != 0 ||
3238 (Val->Flags & E_MCONST) == 0 ||
3239 !IsClassInt (Val->Type)) {
3240 Error ("Constant integer expression expected");
3241 /* To avoid any compiler errors, make the expression a valid const */
3242 MakeConstIntExpr (Val, 1);
3248 void intexpr (ExprDesc* lval)
3249 /* Get an integer expression */
3252 if (!IsClassInt (lval->Type)) {
3253 Error ("Integer expression expected");
3254 /* To avoid any compiler errors, make the expression a valid int */
3255 MakeConstIntExpr (lval, 1);
3261 void boolexpr (ExprDesc* lval)
3262 /* Get a boolean expression */
3264 /* Read an expression */
3267 /* If it's an integer, it's ok. If it's not an integer, but a pointer,
3268 * the pointer used in a boolean context is also ok
3270 if (!IsClassInt (lval->Type) && !IsClassPtr (lval->Type)) {
3271 Error ("Boolean expression expected");
3272 /* To avoid any compiler errors, make the expression a valid int */
3273 MakeConstIntExpr (lval, 1);
3279 void test (unsigned label, int cond)
3280 /* Generate code to perform test and jump if false. */
3285 /* Eat the parenthesis */
3288 /* Prepare the expression, setup labels */
3289 memset (&lval, 0, sizeof (lval));
3291 /* Generate code to eval the expr */
3292 k = expr (hie0, &lval);
3293 if (k == 0 && lval.Flags == E_MCONST) {
3294 /* Constant rvalue */
3295 if (cond == 0 && lval.ConstVal == 0) {
3297 Warning ("Unreachable code");
3298 } else if (cond && lval.ConstVal) {
3305 /* If the expr hasn't set condition codes, set the force-test flag */
3306 if ((lval.Test & E_CC) == 0) {
3307 lval.Test |= E_FORCETEST;
3310 /* Load the value into the primary register */
3311 exprhs (CF_FORCECHAR, k, &lval);
3313 /* Generate the jump */
3315 g_truejump (CF_NONE, label);
3317 /* Special case (putting this here is a small hack - but hey, the
3318 * compiler itself is one big hack...): If a semicolon follows, we
3319 * don't have a statement and may omit the jump.
3321 if (CurTok.Tok != TOK_SEMI) {
3322 g_falsejump (CF_NONE, label);
3326 /* Check for the closing brace */