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