]> git.sur5r.net Git - cc65/blob - src/ld65/expr.c
efdff899e19a5404fa0f9004b6543174c4e9ac00
[cc65] / src / ld65 / expr.c
1 /*****************************************************************************/
2 /*                                                                           */
3 /*                                  expr.c                                   */
4 /*                                                                           */
5 /*                 Expression evaluation for the ld65 linker                 */
6 /*                                                                           */
7 /*                                                                           */
8 /*                                                                           */
9 /* (C) 1998-2012, Ullrich von Bassewitz                                      */
10 /*                Roemerstrasse 52                                           */
11 /*                D-70794 Filderstadt                                        */
12 /* EMail:         uz@cc65.org                                                */
13 /*                                                                           */
14 /*                                                                           */
15 /* This software is provided 'as-is', without any expressed or implied       */
16 /* warranty.  In no event will the authors be held liable for any damages    */
17 /* arising from the use of this software.                                    */
18 /*                                                                           */
19 /* Permission is granted to anyone to use this software for any purpose,     */
20 /* including commercial applications, and to alter it and redistribute it    */
21 /* freely, subject to the following restrictions:                            */
22 /*                                                                           */
23 /* 1. The origin of this software must not be misrepresented; you must not   */
24 /*    claim that you wrote the original software. If you use this software   */
25 /*    in a product, an acknowledgment in the product documentation would be  */
26 /*    appreciated but is not required.                                       */
27 /* 2. Altered source versions must be plainly marked as such, and must not   */
28 /*    be misrepresented as being the original software.                      */
29 /* 3. This notice may not be removed or altered from any source              */
30 /*    distribution.                                                          */
31 /*                                                                           */
32 /*****************************************************************************/
33
34
35
36 /* common */
37 #include "check.h"
38 #include "exprdefs.h"
39 #include "xmalloc.h"
40
41 /* ld65 */
42 #include "global.h"
43 #include "error.h"
44 #include "fileio.h"
45 #include "memarea.h"
46 #include "segments.h"
47 #include "expr.h"
48
49
50
51 /*****************************************************************************/
52 /*                                   Code                                    */
53 /*****************************************************************************/
54
55
56
57 ExprNode* NewExprNode (ObjData* O, unsigned char Op)
58 /* Create a new expression node */
59 {
60     /* Allocate fresh memory */
61     ExprNode* N = xmalloc (sizeof (ExprNode));
62     N->Op       = Op;
63     N->Left     = 0;
64     N->Right    = 0;
65     N->Obj      = O;
66     N->V.IVal   = 0;
67
68     return N;
69 }
70
71
72
73 static void FreeExprNode (ExprNode* E)
74 /* Free a node */
75 {
76     /* Free the memory */
77     xfree (E);
78 }
79
80
81
82 void FreeExpr (ExprNode* Root)
83 /* Free the expression, Root is pointing to. */
84 {
85     if (Root) {
86         FreeExpr (Root->Left);
87         FreeExpr (Root->Right);
88         FreeExprNode (Root);
89     }
90 }
91
92
93
94 int IsConstExpr (ExprNode* Root)
95 /* Return true if the given expression is a constant expression, that is, one
96 ** with no references to external symbols.
97 */
98 {
99     int         Const;
100     Export*     E;
101     Section*    S;
102     MemoryArea* M;
103
104     if (EXPR_IS_LEAF (Root->Op)) {
105         switch (Root->Op) {
106
107             case EXPR_LITERAL:
108                 return 1;
109
110             case EXPR_SYMBOL:
111                 /* Get the referenced export */
112                 E = GetExprExport (Root);
113                 /* If this export has a mark set, we've already encountered it.
114                 ** This means that the export is used to define it's own value,
115                 ** which in turn means, that we have a circular reference.
116                 */
117                 if (ExportHasMark (E)) {
118                     CircularRefError (E);
119                     Const = 0;
120                 } else {
121                     MarkExport (E);
122                     Const = IsConstExport (E);
123                     UnmarkExport (E);
124                 }
125                 return Const;
126
127             case EXPR_SECTION:
128                 /* A section expression is const if the segment it is in is
129                 ** not relocatable and already placed.
130                 */
131                 S = GetExprSection (Root);
132                 M = S->Seg->MemArea;
133                 return M != 0 && (M->Flags & MF_PLACED) != 0 && !M->Relocatable;
134
135             case EXPR_SEGMENT:
136                 /* A segment is const if it is not relocatable and placed */
137                 M = Root->V.Seg->MemArea;
138                 return M != 0 && (M->Flags & MF_PLACED) != 0 && !M->Relocatable;
139
140             case EXPR_MEMAREA:
141                 /* A memory area is const if it is not relocatable and placed */
142                 return !Root->V.Mem->Relocatable &&
143                        (Root->V.Mem->Flags & MF_PLACED);
144
145             default:
146                 /* Anything else is not const */
147                 return 0;
148
149         }
150
151     } else if (EXPR_IS_UNARY (Root->Op)) {
152
153         SegExprDesc D;
154
155         /* Special handling for the BANK pseudo function */
156         switch (Root->Op) {
157
158             case EXPR_BANK:
159                 /* Get segment references for the expression */
160                 GetSegExprVal (Root->Left, &D);
161
162                 /* The expression is const if the expression contains exactly
163                 ** one segment that is assigned to a memory area which has a
164                 ** bank attribute that is constant.
165                 */
166                 return (D.TooComplex              == 0  &&
167                         D.Seg                     != 0  &&
168                         D.Seg->MemArea            != 0  &&
169                         D.Seg->MemArea->BankExpr  != 0  &&
170                         IsConstExpr (D.Seg->MemArea->BankExpr));
171
172             default:
173                 /* All others handled normal */
174                 return IsConstExpr (Root->Left);
175
176         }
177
178     } else {
179
180         /* We must handle shortcut boolean expressions here */
181         switch (Root->Op) {
182
183             case EXPR_BOOLAND:
184                 if (IsConstExpr (Root->Left)) {
185                     /* lhs is const, if it is zero, don't eval right */
186                     if (GetExprVal (Root->Left) == 0) {
187                         return 1;
188                     } else {
189                         return IsConstExpr (Root->Right);
190                     }
191                 } else {
192                     /* lhs not const --> tree not const */
193                     return 0;
194                 }
195                 break;
196
197             case EXPR_BOOLOR:
198                 if (IsConstExpr (Root->Left)) {
199                     /* lhs is const, if it is not zero, don't eval right */
200                     if (GetExprVal (Root->Left) != 0) {
201                         return 1;
202                     } else {
203                         return IsConstExpr (Root->Right);
204                     }
205                 } else {
206                     /* lhs not const --> tree not const */
207                     return 0;
208                 }
209                 break;
210
211             default:
212                 /* All others are handled normal */
213                 return IsConstExpr (Root->Left) && IsConstExpr (Root->Right);
214         }
215     }
216 }
217
218
219
220 Import* GetExprImport (ExprNode* Expr)
221 /* Get the import data structure for a symbol expression node */
222 {
223     /* Check that this is really a symbol */
224     PRECONDITION (Expr->Op == EXPR_SYMBOL);
225
226     /* If we have an object file, get the import from it, otherwise
227     ** (internally generated expressions), get the import from the
228     ** import pointer.
229     */
230     if (Expr->Obj) {
231         /* Return the Import */
232         return GetObjImport (Expr->Obj, Expr->V.ImpNum);
233     } else {
234         return Expr->V.Imp;
235     }
236 }
237
238
239
240 Export* GetExprExport (ExprNode* Expr)
241 /* Get the exported symbol for a symbol expression node */
242 {
243     /* Check that this is really a symbol */
244     PRECONDITION (Expr->Op == EXPR_SYMBOL);
245
246     /* Return the export for an import*/
247     return GetExprImport (Expr)->Exp;
248 }
249
250
251
252 Section* GetExprSection (ExprNode* Expr)
253 /* Get the segment for a section expression node */
254 {
255     /* Check that this is really a section node */
256     PRECONDITION (Expr->Op == EXPR_SECTION);
257
258     /* If we have an object file, get the section from it, otherwise
259     ** (internally generated expressions), get the section from the
260     ** section pointer.
261     */
262     if (Expr->Obj) {
263         /* Return the export */
264         return CollAt (&Expr->Obj->Sections, Expr->V.SecNum);
265     } else {
266         return Expr->V.Sec;
267     }
268 }
269
270
271
272 long GetExprVal (ExprNode* Expr)
273 /* Get the value of a constant expression */
274 {
275     long        Right;
276     long        Left;
277     long        Val;
278     Section*    S;
279     Export*     E;
280     SegExprDesc D;
281
282     switch (Expr->Op) {
283
284         case EXPR_LITERAL:
285             return Expr->V.IVal;
286
287         case EXPR_SYMBOL:
288             /* Get the referenced export */
289             E = GetExprExport (Expr);
290             /* If this export has a mark set, we've already encountered it.
291             ** This means that the export is used to define it's own value,
292             ** which in turn means, that we have a circular reference.
293             */
294             if (ExportHasMark (E)) {
295                 CircularRefError (E);
296                 Val = 0;
297             } else {
298                 MarkExport (E);
299                 Val = GetExportVal (E);
300                 UnmarkExport (E);
301             }
302             return Val;
303
304         case EXPR_SECTION:
305             S = GetExprSection (Expr);
306             return S->Offs + S->Seg->PC;
307
308         case EXPR_SEGMENT:
309             return Expr->V.Seg->PC;
310
311         case EXPR_MEMAREA:
312             return Expr->V.Mem->Start;
313
314         case EXPR_PLUS:
315             return GetExprVal (Expr->Left) + GetExprVal (Expr->Right);
316
317         case EXPR_MINUS:
318             return GetExprVal (Expr->Left) - GetExprVal (Expr->Right);
319
320         case EXPR_MUL:
321             return GetExprVal (Expr->Left) * GetExprVal (Expr->Right);
322
323         case EXPR_DIV:
324             Left  = GetExprVal (Expr->Left);
325             Right = GetExprVal (Expr->Right);
326             if (Right == 0) {
327                 Error ("Division by zero");
328             }
329             return Left / Right;
330
331         case EXPR_MOD:
332             Left  = GetExprVal (Expr->Left);
333             Right = GetExprVal (Expr->Right);
334             if (Right == 0) {
335                 Error ("Modulo operation with zero");
336             }
337             return Left % Right;
338
339         case EXPR_OR:
340             return GetExprVal (Expr->Left) | GetExprVal (Expr->Right);
341
342         case EXPR_XOR:
343             return GetExprVal (Expr->Left) ^ GetExprVal (Expr->Right);
344
345         case EXPR_AND:
346             return GetExprVal (Expr->Left) & GetExprVal (Expr->Right);
347
348         case EXPR_SHL:
349             return GetExprVal (Expr->Left) << GetExprVal (Expr->Right);
350
351         case EXPR_SHR:
352             return GetExprVal (Expr->Left) >> GetExprVal (Expr->Right);
353
354         case EXPR_EQ:
355             return (GetExprVal (Expr->Left) == GetExprVal (Expr->Right));
356
357         case EXPR_NE:
358             return (GetExprVal (Expr->Left) != GetExprVal (Expr->Right));
359
360         case EXPR_LT:
361             return (GetExprVal (Expr->Left) < GetExprVal (Expr->Right));
362
363         case EXPR_GT:
364             return (GetExprVal (Expr->Left) > GetExprVal (Expr->Right));
365
366         case EXPR_LE:
367             return (GetExprVal (Expr->Left) <= GetExprVal (Expr->Right));
368
369         case EXPR_GE:
370             return (GetExprVal (Expr->Left) >= GetExprVal (Expr->Right));
371
372         case EXPR_BOOLAND:
373             return GetExprVal (Expr->Left) && GetExprVal (Expr->Right);
374
375         case EXPR_BOOLOR:
376             return GetExprVal (Expr->Left) || GetExprVal (Expr->Right);
377
378         case EXPR_BOOLXOR:
379             return (GetExprVal (Expr->Left) != 0) ^ (GetExprVal (Expr->Right) != 0);
380
381         case EXPR_MAX:
382             Left = GetExprVal (Expr->Left);
383             Right = GetExprVal (Expr->Right);
384             return (Left > Right)? Left : Right;
385
386         case EXPR_MIN:
387             Left = GetExprVal (Expr->Left);
388             Right = GetExprVal (Expr->Right);
389             return (Left < Right)? Left : Right;
390
391         case EXPR_UNARY_MINUS:
392             return -GetExprVal (Expr->Left);
393
394         case EXPR_NOT:
395             return ~GetExprVal (Expr->Left);
396
397         case EXPR_SWAP:
398             Left = GetExprVal (Expr->Left);
399             return ((Left >> 8) & 0x00FF) | ((Left << 8) & 0xFF00);
400
401         case EXPR_BOOLNOT:
402             return !GetExprVal (Expr->Left);
403
404         case EXPR_BANK:
405             GetSegExprVal (Expr->Left, &D);
406             if (D.TooComplex || D.Seg == 0) {
407                 Error ("Argument for .BANK is not segment relative or too complex");
408             }
409             if (D.Seg->MemArea == 0) {
410                 Error ("Segment `%s' is referenced by .BANK but "
411                        "not assigned to a memory area",
412                        GetString (D.Seg->Name));
413             }
414             if (D.Seg->MemArea->BankExpr == 0) {
415                 Error ("Memory area `%s' is referenced by .BANK but "
416                        "has no BANK attribute",
417                        GetString (D.Seg->MemArea->Name));
418             }
419             return GetExprVal (D.Seg->MemArea->BankExpr);
420
421         case EXPR_BYTE0:
422             return GetExprVal (Expr->Left) & 0xFF;
423
424         case EXPR_BYTE1:
425             return (GetExprVal (Expr->Left) >> 8) & 0xFF;
426
427         case EXPR_BYTE2:
428             return (GetExprVal (Expr->Left) >> 16) & 0xFF;
429
430         case EXPR_BYTE3:
431             return (GetExprVal (Expr->Left) >> 24) & 0xFF;
432
433         case EXPR_WORD0:
434             return GetExprVal (Expr->Left) & 0xFFFF;
435
436         case EXPR_WORD1:
437             return (GetExprVal (Expr->Left) >> 16) & 0xFFFF;
438
439         case EXPR_FARADDR:
440             return GetExprVal (Expr->Left) & 0xFFFFFF;
441
442         case EXPR_DWORD:
443             return GetExprVal (Expr->Left) & 0xFFFFFFFF;
444
445         default:
446             Internal ("Unknown expression Op type: %u", Expr->Op);
447             /* NOTREACHED */
448             return 0;
449     }
450 }
451
452
453
454 static void GetSegExprValInternal (ExprNode* Expr, SegExprDesc* D, int Sign)
455 /* Check if the given expression consists of a segment reference and only
456 ** constant values, additions and subtractions. If anything else is found,
457 ** set D->TooComplex to true.
458 ** Internal, recursive routine.
459 */
460 {
461     Export* E;
462
463     switch (Expr->Op) {
464
465         case EXPR_LITERAL:
466             D->Val += (Sign * Expr->V.IVal);
467             break;
468
469         case EXPR_SYMBOL:
470             /* Get the referenced export */
471             E = GetExprExport (Expr);
472             /* If this export has a mark set, we've already encountered it.
473             ** This means that the export is used to define it's own value,
474             ** which in turn means, that we have a circular reference.
475             */
476             if (ExportHasMark (E)) {
477                 CircularRefError (E);
478             } else {
479                 MarkExport (E);
480                 GetSegExprValInternal (E->Expr, D, Sign);
481                 UnmarkExport (E);
482             }
483             break;
484
485         case EXPR_SECTION:
486             if (D->Seg) {
487                 /* We cannot handle more than one segment reference in o65 */
488                 D->TooComplex = 1;
489             } else {
490                 /* Get the section from the expression */
491                 Section* S = GetExprSection (Expr);
492                 /* Remember the segment reference */
493                 D->Seg = S->Seg;
494                 /* Add the offset of the section to the constant value */
495                 D->Val += Sign * (S->Offs + D->Seg->PC);
496             }
497             break;
498
499         case EXPR_SEGMENT:
500             if (D->Seg) {
501                 /* We cannot handle more than one segment reference in o65 */
502                 D->TooComplex = 1;
503             } else {
504                 /* Remember the segment reference */
505                 D->Seg = Expr->V.Seg;
506                 /* Add the offset of the segment to the constant value */
507                 D->Val += (Sign * D->Seg->PC);
508             }
509             break;
510
511         case EXPR_PLUS:
512             GetSegExprValInternal (Expr->Left, D, Sign);
513             GetSegExprValInternal (Expr->Right, D, Sign);
514             break;
515
516         case EXPR_MINUS:
517             GetSegExprValInternal (Expr->Left, D, Sign);
518             GetSegExprValInternal (Expr->Right, D, -Sign);
519             break;
520
521         default:
522             /* Expression contains illegal operators */
523             D->TooComplex = 1;
524             break;
525
526     }
527 }
528
529
530
531 void GetSegExprVal (ExprNode* Expr, SegExprDesc* D)
532 /* Check if the given expression consists of a segment reference and only
533 ** constant values, additions and subtractions. If anything else is found,
534 ** set D->TooComplex to true. The function will initialize D.
535 */
536 {
537     /* Initialize the given structure */
538     D->Val        = 0;
539     D->TooComplex = 0;
540     D->Seg        = 0;
541
542     /* Call our recursive calculation routine */
543     GetSegExprValInternal (Expr, D, 1);
544 }
545
546
547
548 ExprNode* LiteralExpr (long Val, ObjData* O)
549 /* Return an expression tree that encodes the given literal value */
550 {
551     ExprNode* Expr = NewExprNode (O, EXPR_LITERAL);
552     Expr->V.IVal = Val;
553     return Expr;
554 }
555
556
557
558 ExprNode* MemoryExpr (MemoryArea* Mem, long Offs, ObjData* O)
559 /* Return an expression tree that encodes an offset into a memory area */
560 {
561     ExprNode* Root;
562
563     ExprNode* Expr = NewExprNode (O, EXPR_MEMAREA);
564     Expr->V.Mem = Mem;
565
566     if (Offs != 0) {
567         Root = NewExprNode (O, EXPR_PLUS);
568         Root->Left = Expr;
569         Root->Right = LiteralExpr (Offs, O);
570     } else {
571         Root = Expr;
572     }
573
574     return Root;
575 }
576
577
578
579 ExprNode* SegmentExpr (Segment* Seg, long Offs, ObjData* O)
580 /* Return an expression tree that encodes an offset into a segment */
581 {
582     ExprNode* Root;
583
584     ExprNode* Expr = NewExprNode (O, EXPR_SEGMENT);
585     Expr->V.Seg = Seg;
586
587     if (Offs != 0) {
588         Root = NewExprNode (O, EXPR_PLUS);
589         Root->Left = Expr;
590         Root->Right = LiteralExpr (Offs, O);
591     } else {
592         Root = Expr;
593     }
594
595     return Root;
596 }
597
598
599
600 ExprNode* SectionExpr (Section* Sec, long Offs, ObjData* O)
601 /* Return an expression tree that encodes an offset into a section */
602 {
603     ExprNode* Root;
604
605     ExprNode* Expr = NewExprNode (O, EXPR_SECTION);
606     Expr->V.Sec = Sec;
607
608     if (Offs != 0) {
609         Root = NewExprNode (O, EXPR_PLUS);
610         Root->Left = Expr;
611         Root->Right = LiteralExpr (Offs, O);
612     } else {
613         Root = Expr;
614     }
615
616     return Root;
617 }
618
619
620
621 ExprNode* ReadExpr (FILE* F, ObjData* O)
622 /* Read an expression from the given file */
623 {
624     ExprNode* Expr;
625
626     /* Read the node tag and handle NULL nodes */
627     unsigned char Op = Read8 (F);
628     if (Op == EXPR_NULL) {
629         return 0;
630     }
631
632     /* Create a new node */
633     Expr = NewExprNode (O, Op);
634
635     /* Check the tag and handle the different expression types */
636     if (EXPR_IS_LEAF (Op)) {
637         switch (Op) {
638
639             case EXPR_LITERAL:
640                 Expr->V.IVal = Read32Signed (F);
641                 break;
642
643             case EXPR_SYMBOL:
644                 /* Read the import number */
645                 Expr->V.ImpNum = ReadVar (F);
646                 break;
647
648             case EXPR_SECTION:
649                 /* Read the section number */
650                 Expr->V.SecNum = ReadVar (F);
651                 break;
652
653             default:
654                 Error ("Invalid expression op: %02X", Op);
655
656         }
657
658     } else {
659
660         /* Not a leaf node */
661         Expr->Left = ReadExpr (F, O);
662         Expr->Right = ReadExpr (F, O);
663
664     }
665
666     /* Return the tree */
667     return Expr;
668 }
669
670
671
672 int EqualExpr (ExprNode* E1, ExprNode* E2)
673 /* Check if two expressions are identical. */
674 {
675     /* If one pointer is NULL, both must be NULL */
676     if ((E1 == 0) ^ (E2 == 0)) {
677         return 0;
678     }
679     if (E1 == 0) {
680         return 1;
681     }
682
683     /* Both pointers not NULL, check OP */
684     if (E1->Op != E2->Op) {
685         return 0;
686     }
687
688     /* OPs are identical, check data for leafs, or subtrees */
689     switch (E1->Op) {
690
691         case EXPR_LITERAL:
692             /* Value must be identical */
693             return (E1->V.IVal == E2->V.IVal);
694
695         case EXPR_SYMBOL:
696             /* Import must be identical */
697             return (GetExprImport (E1) == GetExprImport (E2));
698
699         case EXPR_SECTION:
700             /* Section must be identical */
701             return (GetExprSection (E1) == GetExprSection (E2));
702
703         case EXPR_SEGMENT:
704             /* Segment must be identical */
705             return (E1->V.Seg == E2->V.Seg);
706
707         case EXPR_MEMAREA:
708             /* Memory area must be identical */
709             return (E1->V.Mem == E2->V.Mem);
710
711         default:
712             /* Not a leaf node */
713             return EqualExpr (E1->Left, E2->Left) && EqualExpr (E1->Right, E2->Right);
714     }
715
716 }