* src/SDCCast.c (decorateType): removed buggy fix for bug #979599
[fw/sdcc] / src / SDCCast.c
1 /*-------------------------------------------------------------------------
2   SDCCast.c - source file for parser support & all ast related routines
3
4              Written By -  Sandeep Dutta . sandeep.dutta@usa.net (1998)
5
6    This program is free software; you can redistribute it and/or modify it
7    under the terms of the GNU General Public License as published by the
8    Free Software Foundation; either version 2, or (at your option) any
9    later version.
10
11    This program is distributed in the hope that it will be useful,
12    but WITHOUT ANY WARRANTY; without even the implied warranty of
13    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14    GNU General Public License for more details.
15
16    You should have received a copy of the GNU General Public License
17    along with this program; if not, write to the Free Software
18    Foundation, 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
19
20    In other words, you are welcome to use, share and improve this program.
21    You are forbidden to forbid anyone else to use, share and improve
22    what you give them.   Help stamp out software-hoarding!
23 -------------------------------------------------------------------------*/
24
25 #define DEBUG_CF(x) /* puts(x); */
26
27 #include "common.h"
28
29 int currLineno = 0;
30 set *astList = NULL;
31 set *operKeyReset = NULL;
32 ast *staticAutos = NULL;
33 int labelKey = 1;
34
35 #define LRVAL(x) x->left->rvalue
36 #define RRVAL(x) x->right->rvalue
37 #define TRVAL(x) x->rvalue
38 #define LLVAL(x) x->left->lvalue
39 #define RLVAL(x) x->right->lvalue
40 #define TLVAL(x) x->lvalue
41 #define RTYPE(x) x->right->ftype
42 #define RETYPE(x) x->right->etype
43 #define LTYPE(x) x->left->ftype
44 #define LETYPE(x) x->left->etype
45 #define TTYPE(x) x->ftype
46 #define TETYPE(x) x->etype
47 #define ALLOCATE 1
48 #define DEALLOCATE 2
49
50 int noLineno = 0;
51 int noAlloc = 0;
52 symbol *currFunc=NULL;
53 static ast *createIval (ast *, sym_link *, initList *, ast *);
54 static ast *createIvalCharPtr (ast *, sym_link *, ast *);
55 static ast *optimizeCompare (ast *);
56 ast *optimizeRRCRLC (ast *);
57 ast *optimizeSWAP (ast *);
58 ast *optimizeGetHbit (ast *);
59 ast *backPatchLabels (ast *, symbol *, symbol *);
60 void PA(ast *t);
61 int inInitMode = 0;
62 memmap *GcurMemmap=NULL;  /* points to the memmap that's currently active */
63 FILE *codeOutFile;
64 int 
65 ptt (ast * tree)
66 {
67   printTypeChain (tree->ftype, stdout);
68   return 0;
69 }
70
71
72 /*-----------------------------------------------------------------*/
73 /* newAst - creates a fresh node for an expression tree            */
74 /*-----------------------------------------------------------------*/
75 static ast *
76 newAst_ (unsigned type)
77 {
78   ast *ex;
79   static int oldLineno = 0;
80
81   ex = Safe_alloc ( sizeof (ast));
82
83   ex->type = type;
84   ex->lineno = (noLineno ? oldLineno : mylineno);
85   ex->filename = currFname;
86   ex->level = NestLevel;
87   ex->block = currBlockno;
88   ex->initMode = inInitMode;
89   ex->seqPoint = seqPointNo;
90   return ex;
91 }
92
93 ast *
94 newAst_VALUE (value * val)
95 {
96   ast *ex = newAst_ (EX_VALUE);
97   ex->opval.val = val;
98   return ex;
99 }
100
101 ast *
102 newAst_OP (unsigned op)
103 {
104   ast *ex = newAst_ (EX_OP);
105   ex->opval.op = op;
106   return ex;
107 }
108
109 ast *
110 newAst_LINK (sym_link * val)
111 {
112   ast *ex = newAst_ (EX_LINK);
113   ex->opval.lnk = val;
114   return ex;
115 }
116
117 /*-----------------------------------------------------------------*/
118 /* newNode - creates a new node                                    */
119 /*-----------------------------------------------------------------*/
120 ast *
121 newNode (long op, ast * left, ast * right)
122 {
123   ast *ex;
124
125   ex = newAst_OP (op);
126   ex->left = left;
127   ex->right = right;
128
129   return ex;
130 }
131
132 /*-----------------------------------------------------------------*/
133 /* newIfxNode - creates a new Ifx Node                             */
134 /*-----------------------------------------------------------------*/
135 ast *
136 newIfxNode (ast * condAst, symbol * trueLabel, symbol * falseLabel)
137 {
138   ast *ifxNode;
139
140   /* if this is a literal then we already know the result */
141   if (condAst->etype && IS_LITERAL (condAst->etype))
142     {
143       /* then depending on the expression value */
144       if (floatFromVal (condAst->opval.val))
145         ifxNode = newNode (GOTO,
146                            newAst_VALUE (symbolVal (trueLabel)),
147                            NULL);
148       else
149         ifxNode = newNode (GOTO,
150                            newAst_VALUE (symbolVal (falseLabel)),
151                            NULL);
152     }
153   else
154     {
155       ifxNode = newNode (IFX, condAst, NULL);
156       ifxNode->trueLabel = trueLabel;
157       ifxNode->falseLabel = falseLabel;
158     }
159
160   return ifxNode;
161 }
162
163 /*-----------------------------------------------------------------*/
164 /* copyAstValues - copies value portion of ast if needed     */
165 /*-----------------------------------------------------------------*/
166 void
167 copyAstValues (ast * dest, ast * src)
168 {
169   switch (src->opval.op)
170     {
171     case BLOCK:
172       dest->values.sym = copySymbolChain (src->values.sym);
173       break;
174
175     case SWITCH:
176       dest->values.switchVals.swVals =
177         copyValue (src->values.switchVals.swVals);
178       dest->values.switchVals.swDefault =
179         src->values.switchVals.swDefault;
180       dest->values.switchVals.swNum =
181         src->values.switchVals.swNum;
182       break;
183
184     case INLINEASM:
185       dest->values.inlineasm =  Safe_strdup(src->values.inlineasm);
186       break;
187
188     case ARRAYINIT:
189         dest->values.constlist = copyLiteralList(src->values.constlist);
190         break;
191
192     case FOR:
193       AST_FOR (dest, trueLabel) = copySymbol (AST_FOR (src, trueLabel));
194       AST_FOR (dest, continueLabel) = copySymbol (AST_FOR (src, continueLabel));
195       AST_FOR (dest, falseLabel) = copySymbol (AST_FOR (src, falseLabel));
196       AST_FOR (dest, condLabel) = copySymbol (AST_FOR (src, condLabel));
197       AST_FOR (dest, initExpr) = copyAst (AST_FOR (src, initExpr));
198       AST_FOR (dest, condExpr) = copyAst (AST_FOR (src, condExpr));
199       AST_FOR (dest, loopExpr) = copyAst (AST_FOR (src, loopExpr));
200     }
201
202 }
203
204 /*-----------------------------------------------------------------*/
205 /* copyAst - makes a copy of a given astession                     */
206 /*-----------------------------------------------------------------*/
207 ast *
208 copyAst (ast * src)
209 {
210   ast *dest;
211
212   if (!src)
213     return NULL;
214
215   dest = Safe_alloc ( sizeof (ast));
216
217   dest->type = src->type;
218   dest->lineno = src->lineno;
219   dest->level = src->level;
220   dest->funcName = src->funcName;
221
222   if (src->ftype)
223     dest->etype = getSpec (dest->ftype = copyLinkChain (src->ftype));
224
225   /* if this is a leaf */
226   /* if value */
227   if (src->type == EX_VALUE)
228     {
229       dest->opval.val = copyValue (src->opval.val);
230       goto exit;
231     }
232
233   /* if link */
234   if (src->type == EX_LINK)
235     {
236       dest->opval.lnk = copyLinkChain (src->opval.lnk);
237       goto exit;
238     }
239
240   dest->opval.op = src->opval.op;
241
242   /* if this is a node that has special values */
243   copyAstValues (dest, src);
244
245   dest->trueLabel = copySymbol (src->trueLabel);
246   dest->falseLabel = copySymbol (src->falseLabel);
247   dest->left = copyAst (src->left);
248   dest->right = copyAst (src->right);
249 exit:
250   return dest;
251
252 }
253
254 /*-----------------------------------------------------------------*/
255 /* removeIncDecOps: remove for side effects in *_ASSIGN's          */
256 /*                  "*s++ += 3" -> "*s++ = *s++ + 3"               */
257 /*-----------------------------------------------------------------*/
258 ast *removeIncDecOps (ast * tree) {
259
260   // traverse the tree and remove inc/dec ops
261
262   if (!tree)
263     return NULL;
264
265   if (tree->type == EX_OP &&
266       (tree->opval.op == INC_OP || tree->opval.op == DEC_OP)) {
267     if (tree->left)
268       tree=tree->left;
269     else
270       tree=tree->right;
271   }
272
273   tree->left=removeIncDecOps(tree->left);
274   tree->right=removeIncDecOps(tree->right);
275
276  return tree;
277 }
278
279 /*-----------------------------------------------------------------*/
280 /* removePreIncDecOps: remove for side effects in *_ASSIGN's       */
281 /*                  "*++s += 3" -> "*++s = *++s + 3"               */
282 /*-----------------------------------------------------------------*/
283 ast *removePreIncDecOps (ast * tree) {
284
285   // traverse the tree and remove pre-inc/dec ops
286
287   if (!tree)
288     return NULL;
289
290   if (tree->type == EX_OP &&
291       (tree->opval.op == INC_OP || tree->opval.op == DEC_OP)) {
292     if (tree->right)
293       tree=tree->right;
294   }
295
296   tree->left=removePreIncDecOps(tree->left);
297   tree->right=removePreIncDecOps(tree->right);
298
299  return tree;
300 }
301
302 /*-----------------------------------------------------------------*/
303 /* removePostIncDecOps: remove for side effects in *_ASSIGN's      */
304 /*                  "*s++ += 3" -> "*s++ = *s++ + 3"               */
305 /*-----------------------------------------------------------------*/
306 ast *removePostIncDecOps (ast * tree) {
307
308   // traverse the tree and remove pre-inc/dec ops
309
310   if (!tree)
311     return NULL;
312
313   if (tree->type == EX_OP &&
314       (tree->opval.op == INC_OP || tree->opval.op == DEC_OP)) {
315     if (tree->left)
316       tree=tree->left;
317   }
318
319   tree->left=removePostIncDecOps(tree->left);
320   tree->right=removePostIncDecOps(tree->right);
321
322  return tree;
323 }
324
325 /*-----------------------------------------------------------------*/
326 /* hasSEFcalls - returns TRUE if tree has a function call          */
327 /*-----------------------------------------------------------------*/
328 bool
329 hasSEFcalls (ast * tree)
330 {
331   if (!tree)
332     return FALSE;
333
334   if (tree->type == EX_OP &&
335       (tree->opval.op == CALL ||
336        tree->opval.op == PCALL ||
337        tree->opval.op == '=' ||
338        tree->opval.op == INC_OP ||
339        tree->opval.op == DEC_OP))
340     return TRUE;
341
342   return (hasSEFcalls (tree->left) |
343           hasSEFcalls (tree->right));
344 }
345
346 /*-----------------------------------------------------------------*/
347 /* isAstEqual - compares two asts & returns 1 if they are equal    */
348 /*-----------------------------------------------------------------*/
349 static int
350 isAstEqual (ast * t1, ast * t2)
351 {
352   if (!t1 && !t2)
353     return 1;
354
355   if (!t1 || !t2)
356     return 0;
357
358   /* match type */
359   if (t1->type != t2->type)
360     return 0;
361
362   switch (t1->type)
363     {
364     case EX_OP:
365       if (t1->opval.op != t2->opval.op)
366         return 0;
367       return (isAstEqual (t1->left, t2->left) &&
368               isAstEqual (t1->right, t2->right));
369       break;
370
371     case EX_VALUE:
372       if (t1->opval.val->sym)
373         {
374           if (!t2->opval.val->sym)
375             return 0;
376           else
377             return isSymbolEqual (t1->opval.val->sym,
378                                   t2->opval.val->sym);
379         }
380       else
381         {
382           if (t2->opval.val->sym)
383             return 0;
384           else
385             return (floatFromVal (t1->opval.val) ==
386                     floatFromVal (t2->opval.val));
387         }
388       break;
389
390       /* only compare these two types */
391     default:
392       return 0;
393     }
394
395   return 0;
396 }
397
398 /*-----------------------------------------------------------------*/
399 /* resolveSymbols - resolve symbols from the symbol table          */
400 /*-----------------------------------------------------------------*/
401 ast *
402 resolveSymbols (ast * tree)
403 {
404   /* walk the entire tree and check for values */
405   /* with symbols if we find one then replace  */
406   /* symbol with that from the symbol table    */
407
408   if (tree == NULL)
409     return tree;
410
411 #if 0
412   /* print the line          */
413   /* if not block & function */
414   if (tree->type == EX_OP &&
415       (tree->opval.op != FUNCTION &&
416        tree->opval.op != BLOCK &&
417        tree->opval.op != NULLOP))
418     {
419       filename = tree->filename;
420       lineno = tree->lineno;
421     }
422 #endif
423
424   /* make sure we resolve the true & false labels for ifx */
425   if (tree->type == EX_OP && tree->opval.op == IFX)
426     {
427       symbol *csym;
428
429       if (tree->trueLabel)
430         {
431           if ((csym = findSym (LabelTab, tree->trueLabel,
432                                tree->trueLabel->name)))
433             tree->trueLabel = csym;
434           else
435             werrorfl (tree->filename, tree->lineno, E_LABEL_UNDEF,
436                       tree->trueLabel->name);
437         }
438
439       if (tree->falseLabel)
440         {
441           if ((csym = findSym (LabelTab,
442                                tree->falseLabel,
443                                tree->falseLabel->name)))
444             tree->falseLabel = csym;
445           else
446             werrorfl (tree->filename, tree->lineno, E_LABEL_UNDEF,
447                       tree->falseLabel->name);
448         }
449
450     }
451
452   /* if this is a label resolve it from the labelTab */
453   if (IS_AST_VALUE (tree) &&
454       tree->opval.val->sym &&
455       tree->opval.val->sym->islbl)
456     {
457
458       symbol *csym = findSym (LabelTab, tree->opval.val->sym,
459                               tree->opval.val->sym->name);
460
461       if (!csym)
462         werrorfl (tree->filename, tree->lineno, E_LABEL_UNDEF,
463                   tree->opval.val->sym->name);
464       else
465         tree->opval.val->sym = csym;
466
467       goto resolveChildren;
468     }
469
470   /* do only for leafs */
471   if (IS_AST_VALUE (tree) &&
472       tree->opval.val->sym &&
473       !tree->opval.val->sym->implicit)
474     {
475
476       symbol *csym = findSymWithLevel (SymbolTab, tree->opval.val->sym);
477
478       /* if found in the symbol table & they r not the same */
479       if (csym && tree->opval.val->sym != csym)
480         {
481           tree->opval.val->sym = csym;
482           tree->opval.val->type = csym->type;
483           tree->opval.val->etype = csym->etype;
484         }
485
486       /* if not found in the symbol table */
487       /* mark it as undefined assume it is */
488       /* an integer in data space         */
489       if (!csym && !tree->opval.val->sym->implicit)
490         {
491
492           /* if this is a function name then */
493           /* mark it as returning an int     */
494           if (tree->funcName)
495             {
496               tree->opval.val->sym->type = newLink (DECLARATOR);
497               DCL_TYPE (tree->opval.val->sym->type) = FUNCTION;
498               tree->opval.val->sym->type->next =
499                 tree->opval.val->sym->etype = newIntLink ();
500               tree->opval.val->etype = tree->opval.val->etype;
501               tree->opval.val->type = tree->opval.val->sym->type;
502               werrorfl (tree->filename, tree->lineno, W_IMPLICIT_FUNC,
503                         tree->opval.val->sym->name);
504               //tree->opval.val->sym->undefined = 1;
505               allocVariables (tree->opval.val->sym);
506             }
507           else
508             {
509               tree->opval.val->sym->undefined = 1;
510               tree->opval.val->type =
511                 tree->opval.val->etype = newIntLink ();
512               tree->opval.val->sym->type =
513                 tree->opval.val->sym->etype = newIntLink ();
514             }
515         }
516     }
517
518 resolveChildren:
519   resolveSymbols (tree->left);
520   resolveSymbols (tree->right);
521
522   return tree;
523 }
524
525 /*-----------------------------------------------------------------*/
526 /* setAstLineno - walks a ast tree & sets the line number          */
527 /*-----------------------------------------------------------------*/
528 int setAstLineno (ast * tree, int lineno)
529 {
530   if (!tree)
531     return 0;
532
533   tree->lineno = lineno;
534   setAstLineno (tree->left, lineno);
535   setAstLineno (tree->right, lineno);
536   return 0;
537 }
538
539 /*-----------------------------------------------------------------*/
540 /* funcOfType :- function of type with name                        */
541 /*-----------------------------------------------------------------*/
542 symbol *
543 funcOfType (char *name, sym_link * type, sym_link * argType,
544             int nArgs, int rent)
545 {
546   symbol *sym;
547   /* create the symbol */
548   sym = newSymbol (name, 0);
549
550   /* setup return value */
551   sym->type = newLink (DECLARATOR);
552   DCL_TYPE (sym->type) = FUNCTION;
553   sym->type->next = copyLinkChain (type);
554   sym->etype = getSpec (sym->type);
555   FUNC_ISREENT(sym->type) = rent ? 1 : 0;
556
557   /* if arguments required */
558   if (nArgs)
559     {
560       value *args;
561       args = FUNC_ARGS(sym->type) = newValue ();
562
563       while (nArgs--)
564         {
565           args->type = copyLinkChain (argType);
566           args->etype = getSpec (args->type);
567           SPEC_EXTR(args->etype)=1;
568           if (!nArgs)
569             break;
570           args = args->next = newValue ();
571         }
572     }
573
574   /* save it */
575   addSymChain (sym);
576   sym->cdef = 1;
577   allocVariables (sym);
578   return sym;
579
580 }
581
582 /*-----------------------------------------------------------------*/
583 /* funcOfTypeVarg :- function of type with name and argtype        */
584 /*-----------------------------------------------------------------*/
585 symbol *
586 funcOfTypeVarg (char *name, char * rtype, int nArgs , char **atypes)
587 {
588   
589     symbol *sym;
590     int i ;
591     /* create the symbol */
592     sym = newSymbol (name, 0);
593     
594     /* setup return value */
595     sym->type = newLink (DECLARATOR);
596     DCL_TYPE (sym->type) = FUNCTION;
597     sym->type->next = typeFromStr(rtype);
598     sym->etype = getSpec (sym->type);
599     
600     /* if arguments required */
601     if (nArgs) {
602         value *args;
603         args = FUNC_ARGS(sym->type) = newValue ();
604         
605         for ( i = 0 ; i < nArgs ; i++ ) {
606             args->type = typeFromStr(atypes[i]);
607             args->etype = getSpec (args->type);
608             SPEC_EXTR(args->etype)=1;
609             if ((i + 1) == nArgs) break;
610             args = args->next = newValue ();
611         }
612     }
613
614     /* save it */
615     addSymChain (sym);
616     sym->cdef = 1;
617     allocVariables (sym);
618     return sym;
619
620 }
621
622 /*-----------------------------------------------------------------*/
623 /* reverseParms - will reverse a parameter tree                    */
624 /*-----------------------------------------------------------------*/
625 static void
626 reverseParms (ast * ptree)
627 {
628   ast *ttree;
629   if (!ptree)
630     return;
631
632   /* top down if we find a nonParm tree then quit */
633   if (ptree->type == EX_OP && ptree->opval.op == PARAM)
634     {
635       ttree = ptree->left;
636       ptree->left = ptree->right;
637       ptree->right = ttree;
638       reverseParms (ptree->left);
639       reverseParms (ptree->right);
640     }
641
642   return;
643 }
644
645 /*-----------------------------------------------------------------*/
646 /* processParms  - makes sure the parameters are okay and do some  */
647 /*                 processing with them                            */
648 /*-----------------------------------------------------------------*/
649 static int
650 processParms (ast *func,
651               value *defParm,
652               ast **actParm,
653               int *parmNumber, /* unused, although updated */
654               bool rightmost)
655 {
656   RESULT_TYPE resultType;
657   sym_link *functype;
658   
659   /* if none of them exist */
660   if (!defParm && !*actParm)
661     return 0;
662
663   if (defParm)
664     {
665       if (getenv("DEBUG_SANITY"))
666         {
667           fprintf (stderr, "processParms: %s ", defParm->name);
668         }
669       /* make sure the type is complete and sane */
670       checkTypeSanity(defParm->etype, defParm->name);
671     }
672
673   if (IS_CODEPTR (func->ftype))
674     functype = func->ftype->next;
675   else
676     functype = func->ftype;
677     
678   /* if the function is being called via a pointer &   */
679   /* it has not been defined a reentrant then we cannot */
680   /* have parameters                                   */
681   if (func->type != EX_VALUE && !IFFUNC_ISREENT (functype) && !options.stackAuto)
682     {
683       werror (W_NONRENT_ARGS);
684       fatalError++;
685       return 1;
686     }
687
688   /* if defined parameters ended but actual parameters */
689   /* exist and this is not defined as a variable arg   */
690   if (!defParm && *actParm && !IFFUNC_HASVARARGS(functype))
691     {
692       werror (E_TOO_MANY_PARMS);
693       return 1;
694     }
695
696   /* if defined parameters present but no actual parameters */
697   if (defParm && !*actParm)
698     {
699       werror (E_TOO_FEW_PARMS);
700       return 1;
701     }
702
703   /* if this is a PARAM node then match left & right */
704   if ((*actParm)->type == EX_OP && (*actParm)->opval.op == PARAM)
705     {
706       (*actParm)->decorated = 1;
707       return (processParms (func, defParm,
708                             &(*actParm)->left,  parmNumber, FALSE) ||
709               processParms (func, defParm ? defParm->next : NULL,
710                             &(*actParm)->right, parmNumber, rightmost));
711     }
712   else if (defParm) /* not vararg */
713     {
714       /* If we have found a value node by following only right-hand links,
715        * then we know that there are no more values after us.
716        *
717        * Therefore, if there are more defined parameters, the caller didn't
718        * supply enough.
719        */
720       if (rightmost && defParm->next)
721         {
722           werror (E_TOO_FEW_PARMS);
723           return 1;
724         }
725     }
726
727   /* decorate parameter */
728   resultType = defParm ? getResultTypeFromType (defParm->etype) :
729                          RESULT_TYPE_NONE;
730   *actParm = decorateType (*actParm, resultType);
731
732   if (IS_VOID((*actParm)->ftype))
733     {
734       werror (E_VOID_VALUE_USED);
735       return 1;
736     }
737
738   /* If this is a varargs function... */
739   if (!defParm && *actParm && IFFUNC_HASVARARGS(functype))
740     {
741       ast *newType = NULL;
742       sym_link *ftype;
743
744       if (IS_CAST_OP (*actParm)
745           || (IS_AST_LIT_VALUE (*actParm) && (*actParm)->values.literalFromCast))
746         {
747           /* Parameter was explicitly typecast; don't touch it. */
748           return 0;
749         }
750
751       ftype = (*actParm)->ftype;
752
753       /* If it's a char, upcast to int. */
754       if (IS_INTEGRAL (ftype)
755           && (getSize (ftype) < (unsigned) INTSIZE))
756         {
757           newType = newAst_LINK(INTTYPE);  
758         }
759
760       if (IS_PTR(ftype) && !IS_GENPTR(ftype))
761         {
762           newType = newAst_LINK (copyLinkChain(ftype));
763           DCL_TYPE (newType->opval.lnk) = port->unqualified_pointer;
764         }
765
766       if (IS_AGGREGATE (ftype))
767         {
768           newType = newAst_LINK (copyLinkChain (ftype));
769           DCL_TYPE (newType->opval.lnk) = port->unqualified_pointer;
770         }
771       
772       if (newType)
773         {
774           /* cast required; change this op to a cast. */
775           (*actParm)->decorated = 0;
776            *actParm = newNode (CAST, newType, *actParm);
777           (*actParm)->lineno = (*actParm)->right->lineno;
778           
779           decorateType (*actParm, RESULT_TYPE_NONE);
780         }
781       return 0;
782     } /* vararg */
783
784   /* if defined parameters ended but actual has not & */
785   /* reentrant */
786   if (!defParm && *actParm &&
787       (options.stackAuto || IFFUNC_ISREENT (functype)))
788     return 0;
789
790   resolveSymbols (*actParm);
791   
792   /* the parameter type must be at least castable */
793   if (compareType (defParm->type, (*actParm)->ftype) == 0)
794     {
795       werror (E_INCOMPAT_TYPES);
796       printFromToType ((*actParm)->ftype, defParm->type);
797       return 1;
798     }
799
800   /* if the parameter is castable then add the cast */
801   if (compareType (defParm->type, (*actParm)->ftype) < 0)
802     {
803       ast *pTree;
804
805       resultType = getResultTypeFromType (defParm->etype);
806       pTree = resolveSymbols (copyAst (*actParm));
807       
808       /* now change the current one to a cast */
809       (*actParm)->type = EX_OP;
810       (*actParm)->opval.op = CAST;
811       (*actParm)->left = newAst_LINK (defParm->type);
812       (*actParm)->right = pTree;
813       (*actParm)->decorated = 0; /* force typechecking */
814       decorateType (*actParm, resultType);
815     }
816
817   /* make a copy and change the regparm type to the defined parm */
818   (*actParm)->etype = getSpec ((*actParm)->ftype = copyLinkChain ((*actParm)->ftype));
819   SPEC_REGPARM ((*actParm)->etype) = SPEC_REGPARM (defParm->etype);
820   SPEC_ARGREG  ((*actParm)->etype) = SPEC_ARGREG (defParm->etype);
821   (*parmNumber)++;
822   return 0;
823 }
824
825 /*-----------------------------------------------------------------*/
826 /* createIvalType - generates ival for basic types                 */
827 /*-----------------------------------------------------------------*/
828 static ast *
829 createIvalType (ast * sym, sym_link * type, initList * ilist)
830 {
831   ast *iExpr;
832
833   /* if initList is deep */
834   if (ilist->type == INIT_DEEP)
835     ilist = ilist->init.deep;
836
837   iExpr = decorateType (resolveSymbols (list2expr (ilist)), RESULT_CHECK);
838   return decorateType (newNode ('=', sym, iExpr), RESULT_CHECK);
839 }
840
841 /*-----------------------------------------------------------------*/
842 /* createIvalStruct - generates initial value for structures       */
843 /*-----------------------------------------------------------------*/
844 static ast *
845 createIvalStruct (ast * sym, sym_link * type, initList * ilist)
846 {
847   ast *rast = NULL;
848   ast *lAst;
849   symbol *sflds;
850   initList *iloop;
851
852   sflds = SPEC_STRUCT (type)->fields;
853   if (ilist->type != INIT_DEEP)
854     {
855       werror (E_INIT_STRUCT, "");
856       return NULL;
857     }
858
859   iloop = ilist->init.deep;
860
861   for (; sflds; sflds = sflds->next, iloop = (iloop ? iloop->next : NULL))
862     {
863       /* if we have come to end */
864       if (!iloop)
865         break;
866       sflds->implicit = 1;
867       lAst = newNode (PTR_OP, newNode ('&', sym, NULL), newAst_VALUE (symbolVal (sflds)));
868       lAst = decorateType (resolveSymbols (lAst), RESULT_CHECK);
869       rast = decorateType (resolveSymbols (createIval (lAst, sflds->type, iloop, rast)), RESULT_CHECK);
870     }
871
872   if (iloop) {
873     werrorfl (sym->opval.val->sym->fileDef, sym->opval.val->sym->lineDef,
874               W_EXCESS_INITIALIZERS, "struct", 
875               sym->opval.val->sym->name);
876   }
877
878   return rast;
879 }
880
881
882 /*-----------------------------------------------------------------*/
883 /* createIvalArray - generates code for array initialization       */
884 /*-----------------------------------------------------------------*/
885 static ast *
886 createIvalArray (ast * sym, sym_link * type, initList * ilist)
887 {
888   ast *rast = NULL;
889   initList *iloop;
890   int lcnt = 0, size = 0;
891   literalList *literalL;
892
893   /* take care of the special   case  */
894   /* array of characters can be init  */
895   /* by a string                      */
896   if (IS_CHAR (type->next))
897     if ((rast = createIvalCharPtr (sym,
898                                    type,
899                         decorateType (resolveSymbols (list2expr (ilist)), RESULT_CHECK))))
900
901       return decorateType (resolveSymbols (rast), RESULT_CHECK);
902
903     /* not the special case             */
904     if (ilist->type != INIT_DEEP)
905     {
906         werror (E_INIT_STRUCT, "");
907         return NULL;
908     }
909
910     iloop = ilist->init.deep;
911     lcnt = DCL_ELEM (type);
912
913     if (port->arrayInitializerSuppported && convertIListToConstList(ilist, &literalL))
914     {
915         ast *aSym;
916
917         aSym = decorateType (resolveSymbols(sym), RESULT_CHECK);
918         
919         rast = newNode(ARRAYINIT, aSym, NULL);
920         rast->values.constlist = literalL;
921         
922         // Make sure size is set to length of initializer list.
923         while (iloop)
924         {
925             size++;
926             iloop = iloop->next;
927         }
928         
929         if (lcnt && size > lcnt)
930         {
931             // Array size was specified, and we have more initializers than needed.
932             char *name=sym->opval.val->sym->name;
933             int lineno=sym->opval.val->sym->lineDef;
934             char *filename=sym->opval.val->sym->fileDef;
935             
936             werrorfl (filename, lineno, W_EXCESS_INITIALIZERS, "array", name);
937         }
938     }
939     else
940     {
941         for (;;)
942         {
943             ast *aSym;
944             
945             aSym = newNode ('[', sym, newAst_VALUE (valueFromLit ((float) (size++))));
946             aSym = decorateType (resolveSymbols (aSym), RESULT_CHECK);
947             rast = createIval (aSym, type->next, iloop, rast);
948             iloop = (iloop ? iloop->next : NULL);
949             if (!iloop)
950             {
951                 break;
952             }
953             
954             /* no of elements given and we    */
955             /* have generated for all of them */
956             if (!--lcnt) 
957             {
958                 // is this a better way? at least it won't crash
959                 char *name = (IS_AST_SYM_VALUE(sym)) ? AST_SYMBOL(sym)->name : "";
960                 int lineno = iloop->lineno;
961                 char *filename = iloop->filename;
962                 werrorfl (filename, lineno, W_EXCESS_INITIALIZERS, "array", name);
963                 
964                 break;
965             }
966         }
967     }
968
969     /* if we have not been given a size  */
970     if (!DCL_ELEM (type))
971     {
972         /* but this still updates the typedef instead of the instance ! see bug 770487 */
973         DCL_ELEM (type) = size;
974     }
975
976     return decorateType (resolveSymbols (rast), RESULT_CHECK);
977 }
978
979
980 /*-----------------------------------------------------------------*/
981 /* createIvalCharPtr - generates initial values for char pointers  */
982 /*-----------------------------------------------------------------*/
983 static ast *
984 createIvalCharPtr (ast * sym, sym_link * type, ast * iexpr)
985 {
986   ast *rast = NULL;
987
988   /* if this is a pointer & right is a literal array then */
989   /* just assignment will do                              */
990   if (IS_PTR (type) && ((IS_LITERAL (iexpr->etype) ||
991                          SPEC_SCLS (iexpr->etype) == S_CODE)
992                         && IS_ARRAY (iexpr->ftype)))
993     return newNode ('=', sym, iexpr);
994
995   /* left side is an array so we have to assign each */
996   /* element                                         */
997   if ((IS_LITERAL (iexpr->etype) ||
998        SPEC_SCLS (iexpr->etype) == S_CODE)
999       && IS_ARRAY (iexpr->ftype))
1000     {
1001       /* for each character generate an assignment */
1002       /* to the array element */
1003       char *s = SPEC_CVAL (iexpr->etype).v_char;
1004       int i = 0;
1005       int size = getSize (iexpr->ftype);
1006       int symsize = getSize (type);
1007       
1008       if (size>symsize)
1009         {
1010           if (size>(symsize+1))
1011             werrorfl (iexpr->filename, iexpr->lineno, W_EXCESS_INITIALIZERS,
1012                       "string", sym->opval.val->sym->name);
1013           size = symsize;
1014         }
1015
1016       for (i=0;i<size;i++)
1017         {
1018           rast = newNode (NULLOP,
1019                           rast,
1020                           newNode ('=',
1021                                    newNode ('[', sym,
1022                                    newAst_VALUE (valueFromLit ((float) i))),
1023                                    newAst_VALUE (valueFromLit (*s))));
1024           s++;
1025         }
1026
1027       // now WE don't need iexpr's symbol anymore
1028       freeStringSymbol(AST_SYMBOL(iexpr));
1029
1030       return decorateType (resolveSymbols (rast), RESULT_CHECK);
1031     }
1032
1033   return NULL;
1034 }
1035
1036 /*-----------------------------------------------------------------*/
1037 /* createIvalPtr - generates initial value for pointers            */
1038 /*-----------------------------------------------------------------*/
1039 static ast *
1040 createIvalPtr (ast * sym, sym_link * type, initList * ilist)
1041 {
1042   ast *rast;
1043   ast *iexpr;
1044
1045   /* if deep then   */
1046   if (ilist->type == INIT_DEEP)
1047     ilist = ilist->init.deep;
1048
1049   iexpr = decorateType (resolveSymbols (list2expr (ilist)), RESULT_CHECK);
1050
1051   /* if character pointer */
1052   if (IS_CHAR (type->next))
1053     if ((rast = createIvalCharPtr (sym, type, iexpr)))
1054       return rast;
1055
1056   return newNode ('=', sym, iexpr);
1057 }
1058
1059 /*-----------------------------------------------------------------*/
1060 /* createIval - generates code for initial value                   */
1061 /*-----------------------------------------------------------------*/
1062 static ast *
1063 createIval (ast * sym, sym_link * type, initList * ilist, ast * wid)
1064 {
1065   ast *rast = NULL;
1066
1067   if (!ilist)
1068     return NULL;
1069
1070   /* if structure then    */
1071   if (IS_STRUCT (type))
1072     rast = createIvalStruct (sym, type, ilist);
1073   else
1074     /* if this is a pointer */
1075   if (IS_PTR (type))
1076     rast = createIvalPtr (sym, type, ilist);
1077   else
1078     /* if this is an array   */
1079   if (IS_ARRAY (type))
1080     rast = createIvalArray (sym, type, ilist);
1081   else
1082     /* if type is SPECIFIER */
1083   if (IS_SPEC (type))
1084     rast = createIvalType (sym, type, ilist);
1085
1086   if (wid)
1087     return decorateType (resolveSymbols (newNode (NULLOP, wid, rast)), RESULT_CHECK);
1088   else
1089     return decorateType (resolveSymbols (rast), RESULT_CHECK);
1090 }
1091
1092 /*-----------------------------------------------------------------*/
1093 /* initAggregates - initialises aggregate variables with initv     */
1094 /*-----------------------------------------------------------------*/
1095 ast * initAggregates (symbol * sym, initList * ival, ast * wid) {
1096   return createIval (newAst_VALUE (symbolVal (sym)), sym->type, ival, wid);
1097 }
1098
1099 /*-----------------------------------------------------------------*/
1100 /* gatherAutoInit - creates assignment expressions for initial     */
1101 /*    values                 */
1102 /*-----------------------------------------------------------------*/
1103 static ast *
1104 gatherAutoInit (symbol * autoChain)
1105 {
1106   ast *init = NULL;
1107   ast *work;
1108   symbol *sym;
1109
1110   inInitMode = 1;
1111   for (sym = autoChain; sym; sym = sym->next)
1112     {
1113
1114       /* resolve the symbols in the ival */
1115       if (sym->ival)
1116         resolveIvalSym (sym->ival, sym->type);
1117
1118       /* if this is a static variable & has an */
1119       /* initial value the code needs to be lifted */
1120       /* here to the main portion since they can be */
1121       /* initialised only once at the start    */
1122       if (IS_STATIC (sym->etype) && sym->ival &&
1123           SPEC_SCLS (sym->etype) != S_CODE)
1124         {
1125           symbol *newSym;
1126           
1127           /* insert the symbol into the symbol table */
1128           /* with level = 0 & name = rname       */
1129           newSym = copySymbol (sym);
1130           addSym (SymbolTab, newSym, newSym->rname, 0, 0, 1);
1131
1132           /* now lift the code to main */
1133           if (IS_AGGREGATE (sym->type)) {
1134             work = initAggregates (sym, sym->ival, NULL);
1135           } else {
1136             if (getNelements(sym->type, sym->ival)>1) {
1137               werrorfl (sym->fileDef, sym->lineDef,
1138                         W_EXCESS_INITIALIZERS, "scalar", 
1139                         sym->name);
1140             }
1141             work = newNode ('=', newAst_VALUE (symbolVal (newSym)),
1142                             list2expr (sym->ival));
1143           }
1144
1145           setAstLineno (work, sym->lineDef);
1146
1147           sym->ival = NULL;
1148           if (staticAutos)
1149             staticAutos = newNode (NULLOP, staticAutos, work);
1150           else
1151             staticAutos = work;
1152
1153           continue;
1154         }
1155
1156       /* if there is an initial value */
1157       if (sym->ival && SPEC_SCLS (sym->etype) != S_CODE)
1158         {
1159           initList *ilist=sym->ival;
1160           
1161           while (ilist->type == INIT_DEEP) {
1162             ilist = ilist->init.deep;
1163           }
1164
1165           /* update lineno for error msg */
1166           lineno=sym->lineDef;
1167           setAstLineno (ilist->init.node, lineno);
1168           
1169           if (IS_AGGREGATE (sym->type)) {
1170             work = initAggregates (sym, sym->ival, NULL);
1171           } else {
1172             if (getNelements(sym->type, sym->ival)>1) {
1173               werrorfl (sym->fileDef, sym->lineDef,
1174                         W_EXCESS_INITIALIZERS, "scalar", 
1175                         sym->name);
1176             }
1177             work = newNode ('=', newAst_VALUE (symbolVal (sym)),
1178                             list2expr (sym->ival));
1179           }
1180           
1181           // just to be sure
1182           setAstLineno (work, sym->lineDef);
1183
1184           sym->ival = NULL;
1185           if (init)
1186             init = newNode (NULLOP, init, work);
1187           else
1188             init = work;
1189         }
1190     }
1191   inInitMode = 0;
1192   return init;
1193 }
1194
1195 /*-----------------------------------------------------------------*/
1196 /* freeStringSymbol - delete a literal string if no more usage     */
1197 /*-----------------------------------------------------------------*/
1198 void freeStringSymbol(symbol *sym) {
1199   /* make sure this is a literal string */
1200   assert (sym->isstrlit);
1201   if (--sym->isstrlit == 0) { // lower the usage count
1202     memmap *segment=SPEC_OCLS(sym->etype);
1203     if (segment) {
1204       deleteSetItem(&segment->syms, sym);
1205     }
1206   }
1207 }
1208   
1209 /*-----------------------------------------------------------------*/
1210 /* stringToSymbol - creates a symbol from a literal string         */
1211 /*-----------------------------------------------------------------*/
1212 static value *
1213 stringToSymbol (value * val)
1214 {
1215   char name[SDCC_NAME_MAX + 1];
1216   static int charLbl = 0;
1217   symbol *sym;
1218   set *sp;
1219   unsigned int size;
1220
1221   // have we heard this before?
1222   for (sp=statsg->syms; sp; sp=sp->next) {
1223     sym=sp->item;
1224     size = getSize (sym->type);
1225     if (sym->isstrlit && size == getSize (val->type) &&
1226         !memcmp(SPEC_CVAL(sym->etype).v_char, SPEC_CVAL(val->etype).v_char, size)) {
1227       // yes, this is old news. Don't publish it again.
1228       sym->isstrlit++; // but raise the usage count
1229       return symbolVal(sym);
1230     }
1231   }
1232
1233   SNPRINTF (name, sizeof(name), "_str_%d", charLbl++);
1234   sym = newSymbol (name, 0);    /* make it @ level 0 */
1235   strncpyz (sym->rname, name, SDCC_NAME_MAX);
1236
1237   /* copy the type from the value passed */
1238   sym->type = copyLinkChain (val->type);
1239   sym->etype = getSpec (sym->type);
1240   /* change to storage class & output class */
1241   SPEC_SCLS (sym->etype) = S_CODE;
1242   SPEC_CVAL (sym->etype).v_char = SPEC_CVAL (val->etype).v_char;
1243   SPEC_STAT (sym->etype) = 1;
1244   /* make the level & block = 0 */
1245   sym->block = sym->level = 0;
1246   sym->isstrlit = 1;
1247   /* create an ival */
1248   sym->ival = newiList (INIT_NODE, newAst_VALUE (val));
1249   if (noAlloc == 0)
1250     {
1251       /* allocate it */
1252       addSymChain (sym);
1253       allocVariables (sym);
1254     }
1255   sym->ival = NULL;
1256   return symbolVal (sym);
1257
1258 }
1259
1260 /*-----------------------------------------------------------------*/
1261 /* processBlockVars - will go thru the ast looking for block if    */
1262 /*                    a block is found then will allocate the syms */
1263 /*                    will also gather the auto inits present      */
1264 /*-----------------------------------------------------------------*/
1265 ast *
1266 processBlockVars (ast * tree, int *stack, int action)
1267 {
1268   if (!tree)
1269     return NULL;
1270
1271   /* if this is a block */
1272   if (tree->type == EX_OP && tree->opval.op == BLOCK)
1273     {
1274       ast *autoInit;
1275
1276       if (action == ALLOCATE)
1277         {
1278           *stack += allocVariables (tree->values.sym);
1279           autoInit = gatherAutoInit (tree->values.sym);
1280         
1281           /* if there are auto inits then do them */
1282           if (autoInit)
1283             tree->left = newNode (NULLOP, autoInit, tree->left);
1284         }
1285       else                      /* action is deallocate */
1286         deallocLocal (tree->values.sym);
1287     }
1288
1289   processBlockVars (tree->left, stack, action);
1290   processBlockVars (tree->right, stack, action);
1291   return tree;
1292 }
1293
1294
1295 /*-------------------------------------------------------------*/
1296 /* constExprTree - returns TRUE if this tree is a constant     */
1297 /*                 expression                                  */
1298 /*-------------------------------------------------------------*/
1299 bool constExprTree (ast *cexpr) {
1300
1301   if (!cexpr) {
1302     return TRUE;
1303   }
1304
1305   cexpr = decorateType (resolveSymbols (cexpr), RESULT_CHECK);
1306
1307   switch (cexpr->type) 
1308     {
1309     case EX_VALUE:
1310       if (IS_AST_LIT_VALUE(cexpr)) {
1311         // this is a literal
1312         return TRUE;
1313       }
1314       if (IS_AST_SYM_VALUE(cexpr) && IS_FUNC(AST_SYMBOL(cexpr)->type)) {
1315         // a function's address will never change
1316         return TRUE;
1317       }
1318       if (IS_AST_SYM_VALUE(cexpr) && IS_ARRAY(AST_SYMBOL(cexpr)->type)) {
1319         // an array's address will never change
1320         return TRUE;
1321       }
1322       if (IS_AST_SYM_VALUE(cexpr) && 
1323           IN_CODESPACE(SPEC_OCLS(AST_SYMBOL(cexpr)->etype))) {
1324         // a symbol in code space will never change
1325         // This is only for the 'char *s="hallo"' case and will have to leave
1326         //printf(" code space symbol");
1327         return TRUE;
1328       }
1329       return FALSE;
1330     case EX_LINK:
1331       werror (E_INTERNAL_ERROR, __FILE__, __LINE__,
1332               "unexpected link in expression tree\n");
1333       return FALSE;
1334     case EX_OP:
1335       if (cexpr->opval.op==ARRAYINIT) {
1336         // this is a list of literals
1337         return TRUE;
1338       }
1339       if (cexpr->opval.op=='=') {
1340         return constExprTree(cexpr->right);
1341       }
1342       if (cexpr->opval.op==CAST) {
1343         // cast ignored, maybe we should throw a warning here?
1344         return constExprTree(cexpr->right);
1345       }
1346       if (cexpr->opval.op=='&') { 
1347         return TRUE;
1348       }
1349       if (cexpr->opval.op==CALL || cexpr->opval.op==PCALL) {
1350         return FALSE;
1351       }
1352       if (constExprTree(cexpr->left) && constExprTree(cexpr->right)) {
1353         return TRUE;
1354       }
1355       return FALSE;
1356     case EX_OPERAND:
1357       return IS_CONSTANT(operandType(cexpr->opval.oprnd));
1358     }
1359   return FALSE;
1360 }
1361     
1362 /*-----------------------------------------------------------------*/
1363 /* constExprValue - returns the value of a constant expression     */
1364 /*                  or NULL if it is not a constant expression     */
1365 /*-----------------------------------------------------------------*/
1366 value *
1367 constExprValue (ast * cexpr, int check)
1368 {
1369   cexpr = decorateType (resolveSymbols (cexpr), RESULT_CHECK);
1370
1371   /* if this is not a constant then */
1372   if (!IS_LITERAL (cexpr->ftype))
1373     {
1374       /* then check if this is a literal array
1375          in code segment */
1376       if (SPEC_SCLS (cexpr->etype) == S_CODE &&
1377           SPEC_CVAL (cexpr->etype).v_char &&
1378           IS_ARRAY (cexpr->ftype))
1379         {
1380           value *val = valFromType (cexpr->ftype);
1381           SPEC_SCLS (val->etype) = S_LITERAL;
1382           val->sym = cexpr->opval.val->sym;
1383           val->sym->type = copyLinkChain (cexpr->ftype);
1384           val->sym->etype = getSpec (val->sym->type);
1385           strncpyz (val->name, cexpr->opval.val->sym->rname, SDCC_NAME_MAX);
1386           return val;
1387         }
1388
1389       /* if we are casting a literal value then */
1390       if (IS_AST_OP (cexpr) &&
1391           cexpr->opval.op == CAST &&
1392           IS_LITERAL (cexpr->right->ftype))
1393         {
1394         return valCastLiteral (cexpr->ftype,
1395                                floatFromVal (cexpr->right->opval.val));
1396         }
1397
1398       if (IS_AST_VALUE (cexpr))
1399         {
1400         return cexpr->opval.val;
1401         }
1402
1403       if (check)
1404         werror (E_CONST_EXPECTED, "found expression");
1405
1406       return NULL;
1407     }
1408
1409   /* return the value */
1410   return cexpr->opval.val;
1411
1412 }
1413
1414 /*-----------------------------------------------------------------*/
1415 /* isLabelInAst - will return true if a given label is found       */
1416 /*-----------------------------------------------------------------*/
1417 bool 
1418 isLabelInAst (symbol * label, ast * tree)
1419 {
1420   if (!tree || IS_AST_VALUE (tree) || IS_AST_LINK (tree))
1421     return FALSE;
1422
1423   if (IS_AST_OP (tree) &&
1424       tree->opval.op == LABEL &&
1425       isSymbolEqual (AST_SYMBOL (tree->left), label))
1426     return TRUE;
1427
1428   return isLabelInAst (label, tree->right) &&
1429     isLabelInAst (label, tree->left);
1430
1431 }
1432
1433 /*-----------------------------------------------------------------*/
1434 /* isLoopCountable - return true if the loop count can be determi- */
1435 /* -ned at compile time .                                          */
1436 /*-----------------------------------------------------------------*/
1437 bool 
1438 isLoopCountable (ast * initExpr, ast * condExpr, ast * loopExpr,
1439                  symbol ** sym, ast ** init, ast ** end)
1440 {
1441
1442   /* the loop is considered countable if the following
1443      conditions are true :-
1444
1445      a) initExpr :- <sym> = <const>
1446      b) condExpr :- <sym> < <const1>
1447      c) loopExpr :- <sym> ++
1448    */
1449
1450   /* first check the initExpr */
1451   if (IS_AST_OP (initExpr) &&
1452       initExpr->opval.op == '=' &&      /* is assignment */
1453       IS_AST_SYM_VALUE (initExpr->left))
1454     {                           /* left is a symbol */
1455
1456       *sym = AST_SYMBOL (initExpr->left);
1457       *init = initExpr->right;
1458     }
1459   else
1460     return FALSE;
1461
1462   /* for now the symbol has to be of
1463      integral type */
1464   if (!IS_INTEGRAL ((*sym)->type))
1465     return FALSE;
1466
1467   /* now check condExpr */
1468   if (IS_AST_OP (condExpr))
1469     {
1470
1471       switch (condExpr->opval.op)
1472         {
1473         case '<':
1474           if (IS_AST_SYM_VALUE (condExpr->left) &&
1475               isSymbolEqual (*sym, AST_SYMBOL (condExpr->left)) &&
1476               IS_AST_LIT_VALUE (condExpr->right))
1477             {
1478               *end = condExpr->right;
1479               break;
1480             }
1481           return FALSE;
1482
1483         case '!':
1484           if (IS_AST_OP (condExpr->left) &&
1485               condExpr->left->opval.op == '>' &&
1486               IS_AST_LIT_VALUE (condExpr->left->right) &&
1487               IS_AST_SYM_VALUE (condExpr->left->left) &&
1488               isSymbolEqual (*sym, AST_SYMBOL (condExpr->left->left)))
1489             {
1490
1491               *end = newNode ('+', condExpr->left->right,
1492                               newAst_VALUE (constVal ("1")));
1493               break;
1494             }
1495           return FALSE;
1496
1497         default:
1498           return FALSE;
1499         }
1500
1501     }
1502
1503   /* check loop expression is of the form <sym>++ */
1504   if (!IS_AST_OP (loopExpr))
1505     return FALSE;
1506
1507   /* check if <sym> ++ */
1508   if (loopExpr->opval.op == INC_OP)
1509     {
1510
1511       if (loopExpr->left)
1512         {
1513           /* pre */
1514           if (IS_AST_SYM_VALUE (loopExpr->left) &&
1515               isSymbolEqual (*sym, AST_SYMBOL (loopExpr->left)))
1516             return TRUE;
1517
1518         }
1519       else
1520         {
1521           /* post */
1522           if (IS_AST_SYM_VALUE (loopExpr->right) &&
1523               isSymbolEqual (*sym, AST_SYMBOL (loopExpr->right)))
1524             return TRUE;
1525         }
1526
1527     }
1528   else
1529     {
1530       /* check for += */
1531       if (loopExpr->opval.op == ADD_ASSIGN)
1532         {
1533
1534           if (IS_AST_SYM_VALUE (loopExpr->left) &&
1535               isSymbolEqual (*sym, AST_SYMBOL (loopExpr->left)) &&
1536               IS_AST_LIT_VALUE (loopExpr->right) &&
1537               (int) AST_LIT_VALUE (loopExpr->right) != 1)
1538             return TRUE;
1539         }
1540     }
1541
1542   return FALSE;
1543 }
1544
1545 /*-----------------------------------------------------------------*/
1546 /* astHasVolatile - returns true if ast contains any volatile      */
1547 /*-----------------------------------------------------------------*/
1548 bool 
1549 astHasVolatile (ast * tree)
1550 {
1551   if (!tree)
1552     return FALSE;
1553
1554   if (TETYPE (tree) && IS_VOLATILE (TETYPE (tree)))
1555     return TRUE;
1556
1557   if (IS_AST_OP (tree))
1558     return astHasVolatile (tree->left) ||
1559       astHasVolatile (tree->right);
1560   else
1561     return FALSE;
1562 }
1563
1564 /*-----------------------------------------------------------------*/
1565 /* astHasPointer - return true if the ast contains any ptr variable */
1566 /*-----------------------------------------------------------------*/
1567 bool 
1568 astHasPointer (ast * tree)
1569 {
1570   if (!tree)
1571     return FALSE;
1572
1573   if (IS_AST_LINK (tree))
1574     return TRUE;
1575
1576   /* if we hit an array expression then check
1577      only the left side */
1578   if (IS_AST_OP (tree) && tree->opval.op == '[')
1579     return astHasPointer (tree->left);
1580
1581   if (IS_AST_VALUE (tree))
1582     return IS_PTR (tree->ftype) || IS_ARRAY (tree->ftype);
1583
1584   return astHasPointer (tree->left) ||
1585     astHasPointer (tree->right);
1586
1587 }
1588
1589 /*-----------------------------------------------------------------*/
1590 /* astHasSymbol - return true if the ast has the given symbol      */
1591 /*-----------------------------------------------------------------*/
1592 bool 
1593 astHasSymbol (ast * tree, symbol * sym)
1594 {
1595   if (!tree || IS_AST_LINK (tree))
1596     return FALSE;
1597
1598   if (IS_AST_VALUE (tree))
1599     {
1600       if (IS_AST_SYM_VALUE (tree))
1601         return isSymbolEqual (AST_SYMBOL (tree), sym);
1602       else
1603         return FALSE;
1604     }
1605
1606   return astHasSymbol (tree->left, sym) ||
1607     astHasSymbol (tree->right, sym);
1608 }
1609
1610 /*-----------------------------------------------------------------*/
1611 /* astHasDeref - return true if the ast has an indirect access     */
1612 /*-----------------------------------------------------------------*/
1613 static bool 
1614 astHasDeref (ast * tree)
1615 {
1616   if (!tree || IS_AST_LINK (tree) || IS_AST_VALUE(tree))
1617     return FALSE;
1618
1619   if (tree->opval.op == '*' && tree->right == NULL) return TRUE;
1620   
1621   return astHasDeref (tree->left) || astHasDeref (tree->right);
1622 }
1623
1624 /*-----------------------------------------------------------------*/
1625 /* isConformingBody - the loop body has to conform to a set of rules */
1626 /* for the loop to be considered reversible read on for rules      */
1627 /*-----------------------------------------------------------------*/
1628 bool 
1629 isConformingBody (ast * pbody, symbol * sym, ast * body)
1630 {
1631
1632   /* we are going to do a pre-order traversal of the
1633      tree && check for the following conditions. (essentially
1634      a set of very shallow tests )
1635      a) the sym passed does not participate in
1636      any arithmetic operation
1637      b) There are no function calls
1638      c) all jumps are within the body
1639      d) address of loop control variable not taken
1640      e) if an assignment has a pointer on the
1641      left hand side make sure right does not have
1642      loop control variable */
1643
1644   /* if we reach the end or a leaf then true */
1645   if (!pbody || IS_AST_LINK (pbody) || IS_AST_VALUE (pbody))
1646     return TRUE;
1647   
1648   /* if anything else is "volatile" */
1649   if (IS_VOLATILE (TETYPE (pbody)))
1650     return FALSE;
1651
1652   /* we will walk the body in a pre-order traversal for
1653      efficiency sake */
1654   switch (pbody->opval.op)
1655     {
1656 /*------------------------------------------------------------------*/
1657     case '[':
1658       // if the loopvar is used as an index
1659       /* array op is commutative -- must check both left & right */
1660       if (astHasSymbol(pbody->right, sym) || astHasSymbol(pbody->left, sym)) {
1661         return FALSE;
1662       }
1663       return isConformingBody (pbody->right, sym, body)
1664               && isConformingBody (pbody->left, sym, body);
1665
1666 /*------------------------------------------------------------------*/
1667     case PTR_OP:
1668     case '.':
1669       return TRUE;
1670
1671 /*------------------------------------------------------------------*/
1672     case INC_OP:
1673     case DEC_OP:
1674
1675       /* sure we are not sym is not modified */
1676       if (pbody->left &&
1677           IS_AST_SYM_VALUE (pbody->left) &&
1678           isSymbolEqual (AST_SYMBOL (pbody->left), sym))
1679         return FALSE;
1680
1681       if (pbody->right &&
1682           IS_AST_SYM_VALUE (pbody->right) &&
1683           isSymbolEqual (AST_SYMBOL (pbody->right), sym))
1684         return FALSE;
1685
1686       return TRUE;
1687
1688 /*------------------------------------------------------------------*/
1689
1690     case '*':                   /* can be unary  : if right is null then unary operation */
1691     case '+':
1692     case '-':
1693     case '&':
1694
1695       /* if right is NULL then unary operation  */
1696 /*------------------------------------------------------------------*/
1697 /*----------------------------*/
1698       /*  address of                */
1699 /*----------------------------*/
1700       if (!pbody->right)
1701         {
1702           if (IS_AST_SYM_VALUE (pbody->left) &&
1703               isSymbolEqual (AST_SYMBOL (pbody->left), sym))
1704             return FALSE;
1705           else
1706             return isConformingBody (pbody->left, sym, body);
1707         }
1708       else
1709         {
1710           if (astHasSymbol (pbody->left, sym) ||
1711               astHasSymbol (pbody->right, sym))
1712             return FALSE;
1713         }
1714
1715
1716 /*------------------------------------------------------------------*/
1717     case '|':
1718     case '^':
1719     case '/':
1720     case '%':
1721     case LEFT_OP:
1722     case RIGHT_OP:
1723
1724       if (IS_AST_SYM_VALUE (pbody->left) &&
1725           isSymbolEqual (AST_SYMBOL (pbody->left), sym))
1726         return FALSE;
1727
1728       if (IS_AST_SYM_VALUE (pbody->right) &&
1729           isSymbolEqual (AST_SYMBOL (pbody->right), sym))
1730         return FALSE;
1731
1732       return isConformingBody (pbody->left, sym, body) &&
1733         isConformingBody (pbody->right, sym, body);
1734
1735     case '~':
1736     case '!':
1737     case RRC:
1738     case RLC:
1739     case GETHBIT:
1740     case SWAP:
1741       if (IS_AST_SYM_VALUE (pbody->left) &&
1742           isSymbolEqual (AST_SYMBOL (pbody->left), sym))
1743         return FALSE;
1744       return isConformingBody (pbody->left, sym, body);
1745
1746 /*------------------------------------------------------------------*/
1747
1748     case AND_OP:
1749     case OR_OP:
1750     case '>':
1751     case '<':
1752     case LE_OP:
1753     case GE_OP:
1754     case EQ_OP:
1755     case NE_OP:
1756     case '?':
1757     case ':':
1758     case SIZEOF:                /* evaluate wihout code generation */
1759
1760       if (IS_AST_SYM_VALUE (pbody->left) &&
1761           isSymbolEqual (AST_SYMBOL (pbody->left), sym))
1762         return FALSE;
1763
1764       if (IS_AST_SYM_VALUE (pbody->right) &&
1765           isSymbolEqual (AST_SYMBOL (pbody->right), sym))
1766         return FALSE;
1767
1768       return isConformingBody (pbody->left, sym, body) &&
1769         isConformingBody (pbody->right, sym, body);
1770
1771 /*------------------------------------------------------------------*/
1772     case '=':
1773
1774       /* if left has a pointer & right has loop
1775          control variable then we cannot */
1776       if (astHasPointer (pbody->left) &&
1777           astHasSymbol (pbody->right, sym))
1778         return FALSE;
1779       if (astHasVolatile (pbody->left))
1780         return FALSE;
1781
1782       if (IS_AST_SYM_VALUE (pbody->left)) {
1783         // if the loopvar has an assignment
1784         if (isSymbolEqual (AST_SYMBOL (pbody->left), sym))
1785           return FALSE;
1786         // if the loopvar is used in another (maybe conditional) block
1787         if (astHasSymbol (pbody->right, sym) &&
1788             (pbody->level >= body->level)) {
1789           return FALSE;
1790         }
1791       }
1792
1793       if (astHasVolatile (pbody->left))
1794         return FALSE;
1795
1796       if (astHasDeref(pbody->right)) return FALSE;
1797
1798       return isConformingBody (pbody->left, sym, body) &&
1799         isConformingBody (pbody->right, sym, body);
1800
1801     case MUL_ASSIGN:
1802     case DIV_ASSIGN:
1803     case AND_ASSIGN:
1804     case OR_ASSIGN:
1805     case XOR_ASSIGN:
1806     case RIGHT_ASSIGN:
1807     case LEFT_ASSIGN:
1808     case SUB_ASSIGN:
1809     case ADD_ASSIGN:
1810       assert ("Parser should not have generated this\n");
1811
1812 /*------------------------------------------------------------------*/
1813 /*----------------------------*/
1814       /*      comma operator        */
1815 /*----------------------------*/
1816     case ',':
1817       return isConformingBody (pbody->left, sym, body) &&
1818         isConformingBody (pbody->right, sym, body);
1819
1820 /*------------------------------------------------------------------*/
1821 /*----------------------------*/
1822       /*       function call        */
1823 /*----------------------------*/
1824     case CALL:
1825         /* if local & not passed as paramater then ok */
1826         if (sym->level && !astHasSymbol(pbody->right,sym)) 
1827             return TRUE;
1828       return FALSE;
1829
1830 /*------------------------------------------------------------------*/
1831 /*----------------------------*/
1832       /*     return statement       */
1833 /*----------------------------*/
1834     case RETURN:
1835       return FALSE;
1836
1837     case GOTO:
1838       if (isLabelInAst (AST_SYMBOL (pbody->left), body))
1839         return TRUE;
1840       else
1841         return FALSE;
1842     case SWITCH:
1843       if (astHasSymbol (pbody->left, sym))
1844         return FALSE;
1845
1846     default:
1847       break;
1848     }
1849
1850   return isConformingBody (pbody->left, sym, body) &&
1851     isConformingBody (pbody->right, sym, body);
1852
1853
1854
1855 }
1856
1857 /*-----------------------------------------------------------------*/
1858 /* isLoopReversible - takes a for loop as input && returns true    */
1859 /* if the for loop is reversible. If yes will set the value of     */
1860 /* the loop control var & init value & termination value           */
1861 /*-----------------------------------------------------------------*/
1862 bool
1863 isLoopReversible (ast * loop, symbol ** loopCntrl,
1864                   ast ** init, ast ** end)
1865 {
1866   /* if option says don't do it then don't */
1867   if (optimize.noLoopReverse)
1868     return 0;
1869   /* there are several tests to determine this */
1870
1871   /* for loop has to be of the form
1872      for ( <sym> = <const1> ;
1873      [<sym> < <const2>]  ;
1874      [<sym>++] | [<sym> += 1] | [<sym> = <sym> + 1] )
1875      forBody */
1876   if (!isLoopCountable (AST_FOR (loop, initExpr),
1877                         AST_FOR (loop, condExpr),
1878                         AST_FOR (loop, loopExpr),
1879                         loopCntrl, init, end))
1880     return 0;
1881
1882   /* now do some serious checking on the body of the loop
1883    */
1884
1885   return isConformingBody (loop->left, *loopCntrl, loop->left);
1886
1887 }
1888
1889 /*-----------------------------------------------------------------*/
1890 /* replLoopSym - replace the loop sym by loop sym -1               */
1891 /*-----------------------------------------------------------------*/
1892 static void 
1893 replLoopSym (ast * body, symbol * sym)
1894 {
1895   /* reached end */
1896   if (!body || IS_AST_LINK (body))
1897     return;
1898
1899   if (IS_AST_SYM_VALUE (body))
1900     {
1901
1902       if (isSymbolEqual (AST_SYMBOL (body), sym))
1903         {
1904
1905           body->type = EX_OP;
1906           body->opval.op = '-';
1907           body->left = newAst_VALUE (symbolVal (sym));
1908           body->right = newAst_VALUE (constVal ("1"));
1909
1910         }
1911
1912       return;
1913
1914     }
1915
1916   replLoopSym (body->left, sym);
1917   replLoopSym (body->right, sym);
1918
1919 }
1920
1921 /*-----------------------------------------------------------------*/
1922 /* reverseLoop - do the actual loop reversal                       */
1923 /*-----------------------------------------------------------------*/
1924 ast *
1925 reverseLoop (ast * loop, symbol * sym, ast * init, ast * end)
1926 {
1927   ast *rloop;
1928
1929   /* create the following tree
1930      <sym> = loopCount ;
1931      for_continue:
1932      forbody
1933      <sym> -= 1;
1934      if (sym) goto for_continue ;
1935      <sym> = end */
1936
1937   /* put it together piece by piece */
1938   rloop = newNode (NULLOP,
1939                    createIf (newAst_VALUE (symbolVal (sym)),
1940                              newNode (GOTO,
1941                                       newAst_VALUE (symbolVal (AST_FOR (loop, continueLabel))),
1942                                       NULL), NULL),
1943                    newNode ('=',
1944                             newAst_VALUE (symbolVal (sym)),
1945                             end));
1946
1947   replLoopSym (loop->left, sym);
1948   setAstLineno (rloop, init->lineno);
1949
1950   rloop = newNode (NULLOP,
1951                    newNode ('=',
1952                             newAst_VALUE (symbolVal (sym)),
1953                             newNode ('-', end, init)),
1954                    createLabel (AST_FOR (loop, continueLabel),
1955                                 newNode (NULLOP,
1956                                          loop->left,
1957                                          newNode (NULLOP,
1958                                                   newNode (SUB_ASSIGN,
1959                                                            newAst_VALUE (symbolVal (sym)),
1960                                                            newAst_VALUE (constVal ("1"))),
1961                                                   rloop))));
1962
1963   rloop->lineno=init->lineno;
1964   return decorateType (rloop, RESULT_CHECK);
1965
1966 }
1967
1968 /*-----------------------------------------------------------------*/
1969 /* searchLitOp - search tree (*ops only) for an ast with literal */
1970 /*-----------------------------------------------------------------*/
1971 static ast *
1972 searchLitOp (ast *tree, ast **parent, const char *ops)
1973 {
1974   ast *ret;
1975
1976   if (tree && optimize.global_cse)
1977     {
1978       /* is there a literal operand? */
1979       if (tree->right &&
1980           IS_AST_OP(tree->right) &&
1981           tree->right->right &&
1982           (tree->right->opval.op == ops[0] || tree->right->opval.op == ops[1]))
1983         {
1984           if (IS_LITERAL (RTYPE (tree->right)) !=
1985               IS_LITERAL (LTYPE (tree->right)))
1986             {
1987               tree->right->decorated = 0;
1988               tree->decorated = 0;
1989               *parent = tree;
1990               return tree->right;
1991             }
1992           ret = searchLitOp (tree->right, parent, ops);
1993           if (ret)
1994             return ret;
1995         }
1996       if (tree->left &&
1997           IS_AST_OP(tree->left) &&
1998           tree->left->right &&
1999           (tree->left->opval.op == ops[0] || tree->left->opval.op == ops[1]))
2000         {
2001           if (IS_LITERAL (RTYPE (tree->left)) !=
2002               IS_LITERAL (LTYPE (tree->left)))
2003             {
2004               tree->left->decorated = 0;
2005               tree->decorated = 0;
2006               *parent = tree;
2007               return tree->left;
2008             }
2009           ret = searchLitOp (tree->left, parent, ops);
2010           if (ret)
2011             return ret;
2012         }
2013     }
2014   return NULL;
2015 }
2016
2017 /*-----------------------------------------------------------------*/
2018 /* getResultFromType                                               */
2019 /*-----------------------------------------------------------------*/
2020 RESULT_TYPE
2021 getResultTypeFromType (sym_link *type)
2022 {
2023   /* type = getSpec (type); */
2024   if (IS_BIT (type))
2025     return RESULT_TYPE_BIT;
2026   if (IS_BITFIELD (type))
2027     {
2028       int blen = SPEC_BLEN (type);
2029       
2030       if (blen <= 1)
2031         return RESULT_TYPE_BIT;
2032       if (blen <= 8)
2033         return RESULT_TYPE_CHAR;
2034       return RESULT_TYPE_INT;
2035     }
2036   if (IS_CHAR (type))
2037     return RESULT_TYPE_CHAR;
2038   if (   IS_INT (type)
2039       && !IS_LONG (type))
2040     return RESULT_TYPE_INT;
2041   return RESULT_TYPE_OTHER;
2042 }
2043
2044 /*-----------------------------------------------------------------*/
2045 /* addCast - adds casts to a type specified by RESULT_TYPE         */
2046 /*-----------------------------------------------------------------*/
2047 static ast *
2048 addCast (ast *tree, RESULT_TYPE resultType, bool upcast)
2049 {
2050   sym_link *newLink;
2051   bool upCasted = FALSE;
2052   
2053   switch (resultType)
2054     {
2055       case RESULT_TYPE_NONE:
2056         /* char: promote to int */
2057         if (!upcast ||
2058             getSize (tree->etype) >= INTSIZE)
2059           return tree;
2060         newLink = newIntLink();
2061         upCasted = TRUE;
2062         break;
2063       case RESULT_TYPE_CHAR:
2064         if (IS_CHAR (tree->etype) ||
2065             IS_FLOAT(tree->etype))
2066           return tree;
2067         newLink = newCharLink();
2068         break;
2069       case RESULT_TYPE_INT:
2070 #if 0
2071         if (getSize (tree->etype) > INTSIZE)
2072           {
2073             /* warn ("Loosing significant digits"); */
2074             return;
2075           }
2076 #endif
2077         /* char: promote to int */
2078         if (!upcast ||
2079             getSize (tree->etype) >= INTSIZE)
2080           return tree;
2081         newLink = newIntLink();
2082         upCasted = TRUE;
2083         break;
2084       case RESULT_TYPE_OTHER:
2085         if (!upcast)
2086           return tree;
2087         /* return type is long, float: promote char to int */
2088         if (getSize (tree->etype) >= INTSIZE)
2089           return tree;
2090         newLink = newIntLink();
2091         upCasted = TRUE;
2092         break;
2093       default:
2094         return tree;
2095     }
2096   tree->decorated = 0;
2097   tree = newNode (CAST, newAst_LINK (newLink), tree);
2098   tree->lineno = tree->right->lineno;
2099   /* keep unsigned type during cast to smaller type,
2100      but not when promoting from char to int */
2101   if (!upCasted)
2102     SPEC_USIGN (tree->left->opval.lnk) = IS_UNSIGNED (tree->right->etype) ? 1 : 0;
2103   return decorateType (tree, resultType);
2104 }
2105
2106 /*-----------------------------------------------------------------*/
2107 /* resultTypePropagate - decides if resultType can be propagated   */
2108 /*-----------------------------------------------------------------*/
2109 static RESULT_TYPE
2110 resultTypePropagate (ast *tree, RESULT_TYPE resultType)
2111 {
2112   switch (tree->opval.op)
2113     {
2114       case '=':
2115       case '?':
2116       case ':':
2117       case '|':
2118       case '^':
2119       case '~':
2120       case '*':
2121       case '+':
2122       case '-':
2123       case LABEL:
2124         return resultType;
2125       case '&':
2126         if (!tree->right)
2127           /* can be unary */
2128           return RESULT_TYPE_NONE;
2129         else
2130           return resultType;
2131       case IFX:
2132         return RESULT_TYPE_IFX;
2133       default:
2134         return RESULT_TYPE_NONE;
2135     }
2136 }
2137
2138 /*-----------------------------------------------------------------*/
2139 /* getLeftResultType - gets type from left branch for propagation  */
2140 /*-----------------------------------------------------------------*/
2141 static RESULT_TYPE
2142 getLeftResultType (ast *tree, RESULT_TYPE resultType)
2143 {
2144   switch (tree->opval.op)
2145     {
2146       case '=':
2147       case CAST:
2148         if (IS_PTR (LTYPE (tree)))
2149           return RESULT_TYPE_NONE;
2150         else
2151           return getResultTypeFromType (LETYPE (tree));
2152       case RETURN:
2153         if (IS_PTR (currFunc->type->next))
2154           return RESULT_TYPE_NONE;
2155         else
2156           return getResultTypeFromType (currFunc->type->next);
2157       case '[':
2158         if (!IS_ARRAY (LTYPE (tree)))
2159           return resultType;
2160         if (DCL_ELEM (LTYPE (tree)) > 0 && DCL_ELEM (LTYPE (tree)) <= 256)
2161           return RESULT_TYPE_CHAR;
2162         return resultType;
2163       default:
2164         return resultType;
2165     }
2166 }
2167
2168 /*--------------------------------------------------------------------*/
2169 /* decorateType - compute type for this tree, also does type checking.*/
2170 /* This is done bottom up, since type has to flow upwards.            */
2171 /* resultType flows top-down and forces e.g. char-arithmetik, if the  */
2172 /* result is a char and the operand(s) are int's.                     */
2173 /* It also does constant folding, and parameter checking.             */
2174 /*--------------------------------------------------------------------*/
2175 ast *
2176 decorateType (ast * tree, RESULT_TYPE resultType)
2177 {
2178   int parmNumber;
2179   sym_link *p;
2180   RESULT_TYPE resultTypeProp;
2181
2182   if (!tree)
2183     return tree;
2184
2185   /* if already has type then do nothing */
2186   if (tree->decorated)
2187     return tree;
2188
2189   tree->decorated = 1;
2190
2191 #if 0
2192   /* print the line          */
2193   /* if not block & function */
2194   if (tree->type == EX_OP &&
2195       (tree->opval.op != FUNCTION &&
2196        tree->opval.op != BLOCK &&
2197        tree->opval.op != NULLOP))
2198     {
2199       filename = tree->filename;
2200       lineno = tree->lineno;
2201     }
2202 #endif
2203
2204   /* if any child is an error | this one is an error do nothing */
2205   if (tree->isError ||
2206       (tree->left && tree->left->isError) ||
2207       (tree->right && tree->right->isError))
2208     return tree;
2209
2210 /*------------------------------------------------------------------*/
2211 /*----------------------------*/
2212 /*   leaf has been reached    */
2213 /*----------------------------*/
2214   lineno=tree->lineno;
2215   /* if this is of type value */
2216   /* just get the type        */
2217   if (tree->type == EX_VALUE)
2218     {
2219
2220       if (IS_LITERAL (tree->opval.val->etype))
2221         {
2222
2223           /* if this is a character array then declare it */
2224           if (IS_ARRAY (tree->opval.val->type))
2225             tree->opval.val = stringToSymbol (tree->opval.val);
2226
2227           /* otherwise just copy the type information */
2228           COPYTYPE (TTYPE (tree), TETYPE (tree), tree->opval.val->type);
2229           return tree;
2230         }
2231
2232       if (tree->opval.val->sym)
2233         {
2234           /* if the undefined flag is set then give error message */
2235           if (tree->opval.val->sym->undefined)
2236             {
2237               werror (E_ID_UNDEF, tree->opval.val->sym->name);
2238               /* assume int */
2239               TTYPE (tree) = TETYPE (tree) =
2240                 tree->opval.val->type = tree->opval.val->sym->type =
2241                 tree->opval.val->etype = tree->opval.val->sym->etype =
2242                 copyLinkChain (INTTYPE);
2243             }
2244           else
2245             {
2246
2247               /* if impilicit i.e. struct/union member then no type */
2248               if (tree->opval.val->sym->implicit)
2249                 TTYPE (tree) = TETYPE (tree) = NULL;
2250
2251               else
2252                 {
2253
2254                   /* else copy the type */
2255                   COPYTYPE (TTYPE (tree), TETYPE (tree), tree->opval.val->type);
2256
2257                   /* and mark it as referenced */
2258                   tree->opval.val->sym->isref = 1;
2259                 }
2260             }
2261         }
2262
2263       return tree;
2264     }
2265
2266   /* if type link for the case of cast */
2267   if (tree->type == EX_LINK)
2268     {
2269       COPYTYPE (TTYPE (tree), TETYPE (tree), tree->opval.lnk);
2270       return tree;
2271     }
2272
2273   {
2274     ast *dtl, *dtr;
2275
2276     #if 0
2277     if (tree->opval.op == NULLOP || tree->opval.op == BLOCK)
2278       {
2279         if (tree->left && tree->left->type == EX_OPERAND
2280             && (tree->left->opval.op == INC_OP
2281                 || tree->left->opval.op == DEC_OP)
2282             && tree->left->left)
2283           {
2284             tree->left->right = tree->left->left;
2285             tree->left->left = NULL;
2286           }
2287         if (tree->right && tree->right->type == EX_OPERAND
2288             && (tree->right->opval.op == INC_OP
2289                 || tree->right->opval.op == DEC_OP)
2290             && tree->right->left)
2291           {
2292             tree->right->right = tree->right->left;
2293             tree->right->left = NULL;
2294           }
2295       }
2296     #endif
2297
2298     /* Before decorating the left branch we've to decide in dependence
2299        upon tree->opval.op, if resultType can be propagated */
2300     resultTypeProp = resultTypePropagate (tree, resultType);
2301
2302     if (tree->opval.op == '?')
2303       dtl = decorateType (tree->left, RESULT_TYPE_IFX);
2304     else
2305       dtl = decorateType (tree->left, resultTypeProp);
2306
2307     /* if an array node, we may need to swap branches */
2308     if (tree->opval.op == '[')
2309       {
2310         /* determine which is the array & which the index */
2311         if ((IS_ARRAY (RTYPE (tree)) || IS_PTR (RTYPE (tree))) &&
2312             IS_INTEGRAL (LTYPE (tree)))
2313           {
2314             ast *tempTree = tree->left;
2315             tree->left = tree->right;
2316             tree->right = tempTree;
2317           }
2318       }
2319
2320     /* After decorating the left branch there's type information available
2321        in tree->left->?type. If the op is e.g. '=' we extract the type
2322        information from there and propagate it to the right branch. */
2323     resultTypeProp = getLeftResultType (tree, resultTypeProp);
2324     
2325     switch (tree->opval.op)
2326       {
2327         case '?':
2328           /* delay right side for '?' operator since conditional macro
2329              expansions might rely on this */
2330           dtr = tree->right;
2331           break;
2332         case CALL: 
2333           /* decorate right side for CALL (parameter list) in processParms();
2334              there is resultType available */
2335           dtr = tree->right;
2336           break;
2337         default:     
2338           dtr = decorateType (tree->right, resultTypeProp);
2339           break;
2340       }
2341
2342     /* this is to take care of situations
2343        when the tree gets rewritten */
2344     if (dtl != tree->left)
2345       tree->left = dtl;
2346     if (dtr != tree->right)
2347       tree->right = dtr;
2348     if ((dtl && dtl->isError) || (dtr && dtr->isError))
2349       return tree;
2350   }
2351
2352   /* depending on type of operator do */
2353
2354   switch (tree->opval.op)
2355     {
2356         /*------------------------------------------------------------------*/
2357         /*----------------------------*/
2358         /*        array node          */
2359         /*----------------------------*/
2360     case '[':
2361
2362       /* first check if this is a array or a pointer */
2363       if ((!IS_ARRAY (LTYPE (tree))) && (!IS_PTR (LTYPE (tree))))
2364         {
2365           werror (E_NEED_ARRAY_PTR, "[]");
2366           goto errorTreeReturn;
2367         }
2368
2369       /* check if the type of the idx */
2370       if (!IS_INTEGRAL (RTYPE (tree)))
2371         {
2372           werror (E_IDX_NOT_INT);
2373           goto errorTreeReturn;
2374         }
2375
2376       /* if the left is an rvalue then error */
2377       if (LRVAL (tree))
2378         {
2379           werror (E_LVALUE_REQUIRED, "array access");
2380           goto errorTreeReturn;
2381         }
2382
2383       if (IS_LITERAL (RTYPE (tree)))
2384         {
2385           int arrayIndex = (int) floatFromVal (valFromType (RETYPE (tree)));
2386           int arraySize = DCL_ELEM (LTYPE (tree));
2387           if (arraySize && arrayIndex >= arraySize)
2388             {
2389               werror (W_IDX_OUT_OF_BOUNDS, arrayIndex, arraySize);
2390             }
2391         }
2392
2393       RRVAL (tree) = 1;
2394       COPYTYPE (TTYPE (tree), TETYPE (tree), LTYPE (tree)->next);
2395       return tree;
2396
2397       /*------------------------------------------------------------------*/
2398       /*----------------------------*/
2399       /*      struct/union          */
2400       /*----------------------------*/
2401     case '.':
2402       /* if this is not a structure */
2403       if (!IS_STRUCT (LTYPE (tree)))
2404         {
2405           werror (E_STRUCT_UNION, ".");
2406           goto errorTreeReturn;
2407         }
2408       TTYPE (tree) = structElemType (LTYPE (tree),
2409                                      (tree->right->type == EX_VALUE ?
2410                                tree->right->opval.val : NULL));
2411       TETYPE (tree) = getSpec (TTYPE (tree));
2412       return tree;
2413
2414       /*------------------------------------------------------------------*/
2415       /*----------------------------*/
2416       /*    struct/union pointer    */
2417       /*----------------------------*/
2418     case PTR_OP:
2419       /* if not pointer to a structure */
2420       if (!IS_PTR (LTYPE (tree)) && !IS_ARRAY (LTYPE(tree)))
2421         {
2422           werror (E_PTR_REQD);
2423           goto errorTreeReturn;
2424         }
2425
2426       if (!IS_STRUCT (LTYPE (tree)->next))
2427         {
2428           werror (E_STRUCT_UNION, "->");
2429           goto errorTreeReturn;
2430         }
2431
2432       TTYPE (tree) = structElemType (LTYPE (tree)->next,
2433                                      (tree->right->type == EX_VALUE ?
2434                                tree->right->opval.val : NULL));
2435       TETYPE (tree) = getSpec (TTYPE (tree));
2436
2437       /* adjust the storage class */
2438       switch (DCL_TYPE(tree->left->ftype)) {
2439       case POINTER:
2440         SPEC_SCLS(TETYPE(tree)) = S_DATA; 
2441         break;
2442       case FPOINTER:
2443         SPEC_SCLS(TETYPE(tree)) = S_XDATA; 
2444         break;
2445       case CPOINTER:
2446         SPEC_SCLS(TETYPE(tree)) = S_CODE; 
2447         break;
2448       case GPOINTER:
2449         SPEC_SCLS (TETYPE (tree)) = 0;
2450         break;
2451       case PPOINTER:
2452         SPEC_SCLS(TETYPE(tree)) = S_XSTACK; 
2453         break;
2454       case IPOINTER:
2455         SPEC_SCLS(TETYPE(tree)) = S_IDATA;
2456         break;
2457       case EEPPOINTER:
2458         SPEC_SCLS(TETYPE(tree)) = S_EEPROM;
2459         break;
2460       case UPOINTER:
2461         SPEC_SCLS (TETYPE (tree)) = 0;
2462         break;
2463       case ARRAY:
2464       case FUNCTION:
2465         break;
2466       }
2467       
2468       /* This breaks with extern declarations, bitfields, and perhaps other */
2469       /* cases (gcse). Let's leave this optimization disabled for now and   */
2470       /* ponder if there's a safe way to do this. -- EEP                    */
2471       #if 0
2472       if (IS_ADDRESS_OF_OP (tree->left) && IS_AST_SYM_VALUE(tree->left->left)
2473           && SPEC_ABSA (AST_SYMBOL (tree->left->left)->etype))
2474         {
2475             /* If defined    struct type at addr var
2476                then rewrite  (&struct var)->member
2477                as            temp
2478                and define    membertype at (addr+offsetof(struct var,member)) temp
2479             */
2480             symbol *sym;
2481             symbol *element = getStructElement (SPEC_STRUCT (LETYPE(tree)),
2482                                                 AST_SYMBOL(tree->right));
2483
2484             sym = newSymbol(genSymName (0), 0);
2485             sym->type = TTYPE (tree);
2486             sym->etype = getSpec(sym->type);
2487             sym->lineDef = tree->lineno;
2488             sym->cdef = 1;
2489             sym->isref = 1;
2490             SPEC_STAT (sym->etype) = 1;
2491             SPEC_ADDR (sym->etype) = SPEC_ADDR (AST_SYMBOL (tree->left->left)->etype)
2492                                      + element->offset;
2493             SPEC_ABSA(sym->etype) = 1;
2494             addSym (SymbolTab, sym, sym->name, 0, 0, 0);
2495             allocGlobal (sym);
2496             
2497             AST_VALUE (tree) = symbolVal(sym);
2498             TLVAL (tree) = 1;
2499             TRVAL (tree) = 0;
2500             tree->type = EX_VALUE;
2501             tree->left = NULL;
2502             tree->right = NULL;
2503         }
2504       #endif
2505       
2506       return tree;
2507
2508       /*------------------------------------------------------------------*/
2509       /*----------------------------*/
2510       /*  ++/-- operation           */
2511       /*----------------------------*/
2512     case INC_OP:
2513     case DEC_OP:
2514       {
2515         sym_link *ltc = (tree->right ? RTYPE (tree) : LTYPE (tree));
2516         COPYTYPE (TTYPE (tree), TETYPE (tree), ltc);
2517         if (!tree->initMode && IS_CONSTANT(TTYPE(tree)))
2518           werror (E_CODE_WRITE, tree->opval.op==INC_OP ? "++" : "--");
2519
2520         if (tree->right)
2521           RLVAL (tree) = 1;
2522         else
2523           LLVAL (tree) = 1;
2524         return tree;
2525       }
2526
2527       /*------------------------------------------------------------------*/
2528       /*----------------------------*/
2529       /*  bitwise and               */
2530       /*----------------------------*/
2531     case '&':                   /* can be unary   */
2532       /* if right is NULL then unary operation  */
2533       if (tree->right)          /* not an unary operation */
2534         {
2535
2536           if (!IS_INTEGRAL (LTYPE (tree)) || !IS_INTEGRAL (RTYPE (tree)))
2537             {
2538               werror (E_BITWISE_OP);
2539               werror (W_CONTINUE, "left & right types are ");
2540               printTypeChain (LTYPE (tree), stderr);
2541               fprintf (stderr, ",");
2542               printTypeChain (RTYPE (tree), stderr);
2543               fprintf (stderr, "\n");
2544               goto errorTreeReturn;
2545             }
2546
2547           /* if they are both literal */
2548           if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2549             {
2550               tree->type = EX_VALUE;
2551               tree->opval.val = valBitwise (valFromType (LETYPE (tree)),
2552                                           valFromType (RETYPE (tree)), '&');
2553
2554               tree->right = tree->left = NULL;
2555               TETYPE (tree) = tree->opval.val->etype;
2556               TTYPE (tree) = tree->opval.val->type;
2557               return tree;
2558             }
2559
2560           /* see if this is a GETHBIT operation if yes
2561              then return that */
2562           {
2563             ast *otree = optimizeGetHbit (tree);
2564
2565             if (otree != tree)
2566               return decorateType (otree, RESULT_CHECK);
2567           }
2568
2569           /* if left is a literal exchange left & right */
2570           if (IS_LITERAL (LTYPE (tree)))
2571             {
2572               ast *tTree = tree->left;
2573               tree->left = tree->right;
2574               tree->right = tTree;
2575             }
2576
2577           /* if right is a literal and */
2578           /* we can find a 2nd literal in an and-tree then */
2579           /* rearrange the tree */
2580           if (IS_LITERAL (RTYPE (tree)))
2581             {
2582               ast *parent;
2583               ast *litTree = searchLitOp (tree, &parent, "&");
2584               if (litTree)
2585                 {
2586                   DEBUG_CF("&")
2587                   ast *tTree = litTree->left;
2588                   litTree->left = tree->right;
2589                   tree->right = tTree;
2590                   /* both operands in litTree are literal now */
2591                   decorateType (parent, resultType);
2592                 }
2593             }
2594
2595           LRVAL (tree) = RRVAL (tree) = 1;
2596           
2597           TTYPE (tree) = computeType (LTYPE (tree),
2598                                       RTYPE (tree),
2599                                       resultType,
2600                                       tree->opval.op);
2601           TETYPE (tree) = getSpec (TTYPE (tree));
2602
2603           return tree;
2604         }
2605
2606       /*------------------------------------------------------------------*/
2607       /*----------------------------*/
2608       /*  address of                */
2609       /*----------------------------*/
2610       p = newLink (DECLARATOR);
2611       /* if bit field then error */
2612       if (IS_BITVAR (tree->left->etype))
2613         {
2614           werror (E_ILLEGAL_ADDR, "address of bit variable");
2615           goto errorTreeReturn;
2616         }
2617
2618       if (LETYPE(tree) && SPEC_SCLS (tree->left->etype) == S_REGISTER)
2619         {
2620           werror (E_ILLEGAL_ADDR, "address of register variable");
2621           goto errorTreeReturn;
2622         }
2623
2624       if (IS_FUNC (LTYPE (tree)))
2625         {
2626           // this ought to be ignored
2627           return (tree->left);
2628         }
2629
2630       if (IS_LITERAL(LTYPE(tree)))
2631         {
2632           werror (E_ILLEGAL_ADDR, "address of literal");
2633           goto errorTreeReturn;
2634         }
2635
2636      if (LRVAL (tree))
2637         {
2638           werror (E_LVALUE_REQUIRED, "address of");
2639           goto errorTreeReturn;
2640         }
2641       if (!LETYPE (tree))
2642         DCL_TYPE (p) = POINTER;
2643       else if (SPEC_SCLS (tree->left->etype) == S_CODE)
2644         DCL_TYPE (p) = CPOINTER;
2645       else if (SPEC_SCLS (tree->left->etype) == S_XDATA)
2646         DCL_TYPE (p) = FPOINTER;
2647       else if (SPEC_SCLS (tree->left->etype) == S_XSTACK)
2648         DCL_TYPE (p) = PPOINTER;
2649       else if (SPEC_SCLS (tree->left->etype) == S_IDATA)
2650         DCL_TYPE (p) = IPOINTER;
2651       else if (SPEC_SCLS (tree->left->etype) == S_EEPROM)
2652         DCL_TYPE (p) = EEPPOINTER;
2653       else if (SPEC_OCLS(tree->left->etype))
2654           DCL_TYPE (p) = PTR_TYPE(SPEC_OCLS(tree->left->etype));
2655       else
2656           DCL_TYPE (p) = POINTER;
2657
2658       if (IS_AST_SYM_VALUE (tree->left))
2659         {
2660           AST_SYMBOL (tree->left)->addrtaken = 1;
2661           AST_SYMBOL (tree->left)->allocreq = 1;
2662         }
2663
2664       p->next = LTYPE (tree);
2665       TTYPE (tree) = p;
2666       TETYPE (tree) = getSpec (TTYPE (tree));
2667       LLVAL (tree) = 1;
2668       TLVAL (tree) = 1;
2669
2670       #if 0
2671       if (IS_AST_OP (tree->left) && tree->left->opval.op == PTR_OP
2672           && IS_AST_VALUE (tree->left->left) && !IS_AST_SYM_VALUE (tree->left->left))
2673         {
2674           symbol *element = getStructElement (SPEC_STRUCT (LETYPE(tree->left)),
2675                                       AST_SYMBOL(tree->left->right));
2676           AST_VALUE(tree) = valPlus(AST_VALUE(tree->left->left),
2677                                     valueFromLit(element->offset));
2678           tree->left = NULL;
2679           tree->right = NULL;
2680           tree->type = EX_VALUE;
2681           tree->values.literalFromCast = 1;
2682         }
2683       #endif
2684
2685       return tree;
2686
2687       /*------------------------------------------------------------------*/
2688       /*----------------------------*/
2689       /*  bitwise or                */
2690       /*----------------------------*/
2691     case '|':
2692       /* if the rewrite succeeds then don't go any furthur */
2693       {
2694         ast *wtree = optimizeRRCRLC (tree);
2695         if (wtree != tree)
2696           return decorateType (wtree, RESULT_CHECK);
2697         
2698         wtree = optimizeSWAP (tree);
2699         if (wtree != tree)
2700           return decorateType (wtree, RESULT_CHECK);
2701       }
2702
2703       /* if left is a literal exchange left & right */
2704       if (IS_LITERAL (LTYPE (tree)))
2705         {
2706           ast *tTree = tree->left;
2707           tree->left = tree->right;
2708           tree->right = tTree;
2709         }
2710
2711       /* if right is a literal and */
2712       /* we can find a 2nd literal in an or-tree then */
2713       /* rearrange the tree */
2714       if (IS_LITERAL (RTYPE (tree)))
2715         {
2716           ast *parent;
2717           ast *litTree = searchLitOp (tree, &parent, "|");
2718           if (litTree)
2719             {
2720               DEBUG_CF("|")
2721               ast *tTree = litTree->left;
2722               litTree->left = tree->right;
2723               tree->right = tTree;
2724               /* both operands in tTree are literal now */
2725               decorateType (parent, resultType);
2726             }
2727         }
2728       /* fall through */
2729
2730       /*------------------------------------------------------------------*/
2731       /*----------------------------*/
2732       /*  bitwise xor               */
2733       /*----------------------------*/
2734     case '^':
2735       if (!IS_INTEGRAL (LTYPE (tree)) || !IS_INTEGRAL (RTYPE (tree)))
2736         {
2737           werror (E_BITWISE_OP);
2738           werror (W_CONTINUE, "left & right types are ");
2739           printTypeChain (LTYPE (tree), stderr);
2740           fprintf (stderr, ",");
2741           printTypeChain (RTYPE (tree), stderr);
2742           fprintf (stderr, "\n");
2743           goto errorTreeReturn;
2744         }
2745
2746       /* if they are both literal then rewrite the tree */
2747       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2748         {
2749           tree->type = EX_VALUE;
2750           tree->opval.val = valBitwise (valFromType (LETYPE (tree)),
2751                                         valFromType (RETYPE (tree)),
2752                                         tree->opval.op);
2753           tree->right = tree->left = NULL;
2754           TETYPE (tree) = tree->opval.val->etype;
2755           TTYPE (tree) = tree->opval.val->type;
2756           return tree;
2757         }
2758
2759       /* if left is a literal exchange left & right */
2760       if (IS_LITERAL (LTYPE (tree)))
2761         {
2762           ast *tTree = tree->left;
2763           tree->left = tree->right;
2764           tree->right = tTree;
2765         }
2766
2767       /* if right is a literal and */
2768       /* we can find a 2nd literal in a xor-tree then */
2769       /* rearrange the tree */
2770       if (IS_LITERAL (RTYPE (tree)) &&
2771           tree->opval.op == '^') /* the same source is used by 'bitwise or' */
2772         {
2773           ast *parent;
2774           ast *litTree = searchLitOp (tree, &parent, "^");
2775           if (litTree)
2776             {
2777               DEBUG_CF("^")
2778               ast *tTree = litTree->left;
2779               litTree->left = tree->right;
2780               tree->right = tTree;
2781               /* both operands in litTree are literal now */
2782               decorateType (parent, resultType);
2783             }
2784         }
2785
2786       LRVAL (tree) = RRVAL (tree) = 1;
2787
2788       TTYPE (tree) = computeType (LTYPE (tree),
2789                                   RTYPE (tree),
2790                                   resultType,
2791                                   tree->opval.op);
2792       TETYPE (tree) = getSpec (TTYPE (tree));
2793
2794       return tree;
2795
2796       /*------------------------------------------------------------------*/
2797       /*----------------------------*/
2798       /*  division                  */
2799       /*----------------------------*/
2800     case '/':
2801       if (!IS_ARITHMETIC (LTYPE (tree)) || !IS_ARITHMETIC (RTYPE (tree)))
2802         {
2803           werror (E_INVALID_OP, "divide");
2804           goto errorTreeReturn;
2805         }
2806       /* if they are both literal then */
2807       /* rewrite the tree */
2808       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2809         {
2810           tree->type = EX_VALUE;
2811           tree->opval.val = valDiv (valFromType (LETYPE (tree)),
2812                                     valFromType (RETYPE (tree)));
2813           tree->right = tree->left = NULL;
2814           TETYPE (tree) = getSpec (TTYPE (tree) =
2815                                    tree->opval.val->type);
2816           return tree;
2817         }
2818
2819       LRVAL (tree) = RRVAL (tree) = 1;
2820
2821       TETYPE (tree) = getSpec (TTYPE (tree) =
2822                                computeType (LTYPE (tree),
2823                                             RTYPE (tree),
2824                                             resultType,
2825                                             tree->opval.op));
2826
2827       /* if right is a literal and */
2828       /* left is also a division by a literal then */
2829       /* rearrange the tree */
2830       if (IS_LITERAL (RTYPE (tree))
2831           /* avoid infinite loop */
2832           && (TYPE_UDWORD) floatFromVal (tree->right->opval.val) != 1)
2833         {
2834           ast *parent;
2835           ast *litTree = searchLitOp (tree, &parent, "/");
2836           if (litTree)
2837             {
2838               if (IS_LITERAL (RTYPE (litTree)))
2839                 {
2840                   /* foo_div */
2841                   DEBUG_CF("div r")
2842                   litTree->right = newNode ('*',
2843                                             litTree->right,
2844                                             copyAst (tree->right));
2845                   litTree->right->lineno = tree->lineno;
2846
2847                   tree->right->opval.val = constVal ("1");
2848                   decorateType (parent, resultType);
2849                 }
2850               else
2851                 {
2852                   /* litTree->left is literal: no gcse possible.
2853                      We can't call decorateType(parent, RESULT_CHECK), because
2854                      this would cause an infinit loop. */
2855                   parent->decorated = 1;
2856                   decorateType (litTree, resultType);
2857                 }
2858             }
2859         }
2860
2861       return tree;
2862
2863       /*------------------------------------------------------------------*/
2864       /*----------------------------*/
2865       /*            modulus         */
2866       /*----------------------------*/
2867     case '%':
2868       if (!IS_INTEGRAL (LTYPE (tree)) || !IS_INTEGRAL (RTYPE (tree)))
2869         {
2870           werror (E_BITWISE_OP);
2871           werror (W_CONTINUE, "left & right types are ");
2872           printTypeChain (LTYPE (tree), stderr);
2873           fprintf (stderr, ",");
2874           printTypeChain (RTYPE (tree), stderr);
2875           fprintf (stderr, "\n");
2876           goto errorTreeReturn;
2877         }
2878       /* if they are both literal then */
2879       /* rewrite the tree */
2880       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2881         {
2882           tree->type = EX_VALUE;
2883           tree->opval.val = valMod (valFromType (LETYPE (tree)),
2884                                     valFromType (RETYPE (tree)));
2885           tree->right = tree->left = NULL;
2886           TETYPE (tree) = getSpec (TTYPE (tree) =
2887                                    tree->opval.val->type);
2888           return tree;
2889         }
2890       LRVAL (tree) = RRVAL (tree) = 1;
2891       TETYPE (tree) = getSpec (TTYPE (tree) =
2892                                computeType (LTYPE (tree),
2893                                             RTYPE (tree),
2894                                             resultType,
2895                                             tree->opval.op));
2896       return tree;
2897
2898       /*------------------------------------------------------------------*/
2899       /*----------------------------*/
2900       /*  address dereference       */
2901       /*----------------------------*/
2902     case '*':                   /* can be unary  : if right is null then unary operation */
2903       if (!tree->right)
2904         {
2905           if (!IS_PTR (LTYPE (tree)) && !IS_ARRAY (LTYPE (tree)))
2906             {
2907               werror (E_PTR_REQD);
2908               goto errorTreeReturn;
2909             }
2910
2911           if (LRVAL (tree))
2912             {
2913               werror (E_LVALUE_REQUIRED, "pointer deref");
2914               goto errorTreeReturn;
2915             }
2916           if (IS_ADDRESS_OF_OP(tree->left))
2917             {
2918               /* replace *&obj with obj */
2919               return tree->left->left;
2920             }
2921           TTYPE (tree) = copyLinkChain (LTYPE (tree)->next);
2922           TETYPE (tree) = getSpec (TTYPE (tree));
2923           /* adjust the storage class */
2924           switch (DCL_TYPE(tree->left->ftype)) {
2925             case POINTER:
2926               SPEC_SCLS(TETYPE(tree)) = S_DATA;
2927               break;
2928             case FPOINTER:
2929               SPEC_SCLS(TETYPE(tree)) = S_XDATA; 
2930               break;
2931             case CPOINTER:
2932               SPEC_SCLS(TETYPE(tree)) = S_CODE; 
2933               break;
2934             case GPOINTER:
2935               SPEC_SCLS (TETYPE (tree)) = 0;
2936               break;
2937             case PPOINTER:
2938               SPEC_SCLS(TETYPE(tree)) = S_XSTACK; 
2939               break;
2940             case IPOINTER:
2941               SPEC_SCLS(TETYPE(tree)) = S_IDATA;
2942               break;
2943             case EEPPOINTER:
2944               SPEC_SCLS(TETYPE(tree)) = S_EEPROM;
2945               break;
2946             case UPOINTER:
2947               SPEC_SCLS (TETYPE (tree)) = 0;
2948               break;
2949             case ARRAY:
2950             case FUNCTION:
2951               break;
2952           }
2953           return tree;
2954         }
2955
2956       /*------------------------------------------------------------------*/
2957       /*----------------------------*/
2958       /*      multiplication        */
2959       /*----------------------------*/
2960       if (!IS_ARITHMETIC (LTYPE (tree)) || !IS_ARITHMETIC (RTYPE (tree)))
2961         {
2962           werror (E_INVALID_OP, "multiplication");
2963           goto errorTreeReturn;
2964         }
2965
2966       /* if they are both literal then */
2967       /* rewrite the tree */
2968       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2969         {
2970           tree->type = EX_VALUE;
2971           tree->opval.val = valMult (valFromType (LETYPE (tree)),
2972                                      valFromType (RETYPE (tree)));
2973           tree->right = tree->left = NULL;
2974           TETYPE (tree) = getSpec (TTYPE (tree) =
2975                                    tree->opval.val->type);
2976           return tree;
2977         }
2978
2979       /* if left is a literal exchange left & right */
2980       if (IS_LITERAL (LTYPE (tree)))
2981         {
2982           ast *tTree = tree->left;
2983           tree->left = tree->right;
2984           tree->right = tTree;
2985         }
2986
2987       /* if right is a literal and */
2988       /* we can find a 2nd literal in a mul-tree then */
2989       /* rearrange the tree */
2990       if (IS_LITERAL (RTYPE (tree)))
2991         {
2992           ast *parent;
2993           ast *litTree = searchLitOp (tree, &parent, "*");
2994           if (litTree)
2995             {
2996               DEBUG_CF("mul")
2997               ast *tTree = litTree->left;
2998               litTree->left = tree->right;
2999               tree->right = tTree;
3000               /* both operands in litTree are literal now */
3001               decorateType (parent, resultType);
3002             }
3003         }
3004
3005       LRVAL (tree) = RRVAL (tree) = 1;
3006       tree->left  = addCast (tree->left,  resultType, FALSE);
3007       tree->right = addCast (tree->right, resultType, FALSE);
3008       TETYPE (tree) = getSpec (TTYPE (tree) =
3009                                    computeType (LTYPE (tree),
3010                                                 RTYPE (tree),
3011                                                 resultType,
3012                                                 tree->opval.op));
3013
3014       return tree;
3015
3016       /*------------------------------------------------------------------*/
3017       /*----------------------------*/
3018       /*    unary '+' operator      */
3019       /*----------------------------*/
3020     case '+':
3021       /* if unary plus */
3022       if (!tree->right)
3023         {
3024           if (!IS_ARITHMETIC (LTYPE (tree)))
3025             {
3026               werror (E_UNARY_OP, '+');
3027               goto errorTreeReturn;
3028             }
3029
3030           /* if left is a literal then do it */
3031           if (IS_LITERAL (LTYPE (tree)))
3032             {
3033               tree->type = EX_VALUE;
3034               tree->opval.val = valFromType (LETYPE (tree));
3035               tree->left = NULL;
3036               TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
3037               return tree;
3038             }
3039           LRVAL (tree) = 1;
3040           COPYTYPE (TTYPE (tree), TETYPE (tree), LTYPE (tree));
3041           return tree;
3042         }
3043
3044       /*------------------------------------------------------------------*/
3045       /*----------------------------*/
3046       /*      addition              */
3047       /*----------------------------*/
3048
3049       /* this is not a unary operation */
3050       /* if both pointers then problem */
3051       if ((IS_PTR (LTYPE (tree)) || IS_ARRAY (LTYPE (tree))) &&
3052           (IS_PTR (RTYPE (tree)) || IS_ARRAY (RTYPE (tree))))
3053         {
3054           werror (E_PTR_PLUS_PTR);
3055           goto errorTreeReturn;
3056         }
3057
3058       if (!IS_ARITHMETIC (LTYPE (tree)) &&
3059           !IS_PTR (LTYPE (tree)) && !IS_ARRAY (LTYPE (tree)))
3060         {
3061           werror (E_PLUS_INVALID, "+");
3062           goto errorTreeReturn;
3063         }
3064
3065       if (!IS_ARITHMETIC (RTYPE (tree)) &&
3066           !IS_PTR (RTYPE (tree)) && !IS_ARRAY (RTYPE (tree)))
3067         {
3068           werror (E_PLUS_INVALID, "+");
3069           goto errorTreeReturn;
3070         }
3071       /* if they are both literal then */
3072       /* rewrite the tree */
3073       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
3074         {
3075           tree->type = EX_VALUE;
3076           tree->left  = addCast (tree->left,  resultType, TRUE);
3077           tree->right = addCast (tree->right, resultType, TRUE);
3078           tree->opval.val = valPlus (valFromType (LETYPE (tree)),
3079                                      valFromType (RETYPE (tree)));
3080           tree->right = tree->left = NULL;
3081           TETYPE (tree) = getSpec (TTYPE (tree) =
3082                                    tree->opval.val->type);
3083           return tree;
3084         }
3085
3086       /* if the right is a pointer or left is a literal
3087          xchange left & right */
3088       if (IS_ARRAY (RTYPE (tree)) ||
3089           IS_PTR (RTYPE (tree)) ||
3090           IS_LITERAL (LTYPE (tree)))
3091         {
3092           ast *tTree = tree->left;
3093           tree->left = tree->right;
3094           tree->right = tTree;
3095         }
3096
3097       /* if right is a literal and */
3098       /* left is also an addition/subtraction with a literal then */
3099       /* rearrange the tree */
3100       if (IS_LITERAL (RTYPE (tree)))
3101         {
3102           ast *litTree, *parent;
3103           litTree = searchLitOp (tree, &parent, "+-");
3104           if (litTree)
3105             {
3106               if (litTree->opval.op == '+')
3107                 {
3108                   /* foo_aa */
3109                   DEBUG_CF("+ 1 AA")
3110                   ast *tTree = litTree->left;
3111                   litTree->left = tree->right;
3112                   tree->right = tree->left;
3113                   tree->left = tTree;
3114                 }
3115               else if (litTree->opval.op == '-')
3116                 {
3117                   if (IS_LITERAL (RTYPE (litTree)))
3118                     {
3119                       DEBUG_CF("+ 2 ASR")
3120                       /* foo_asr */
3121                       ast *tTree = litTree->left;
3122                       litTree->left = tree->right;
3123                       tree->right = tTree;
3124                     }
3125                   else
3126                     {
3127                       DEBUG_CF("+ 3 ASL")
3128                       /* foo_asl */
3129                       ast *tTree = litTree->right;
3130                       litTree->right = tree->right;
3131                       tree->right = tTree;
3132                       litTree->opval.op = '+';
3133                       tree->opval.op = '-';
3134                     }
3135                 }
3136               decorateType (parent, resultType);
3137             }
3138         }
3139
3140       LRVAL (tree) = RRVAL (tree) = 1;
3141       /* if the left is a pointer */
3142       if (IS_PTR (LTYPE (tree)) || IS_AGGREGATE (LTYPE (tree)) )
3143         TETYPE (tree) = getSpec (TTYPE (tree) =
3144                                  LTYPE (tree));
3145       else
3146         {
3147           tree->left  = addCast (tree->left,  resultType, TRUE);
3148           tree->right = addCast (tree->right, resultType, TRUE);
3149           TETYPE (tree) = getSpec (TTYPE (tree) =
3150                                      computeType (LTYPE (tree),
3151                                                   RTYPE (tree),
3152                                                   resultType,
3153                                                   tree->opval.op));
3154         }
3155         
3156       return tree;
3157
3158       /*------------------------------------------------------------------*/
3159       /*----------------------------*/
3160       /*      unary '-'             */
3161       /*----------------------------*/
3162     case '-':                   /* can be unary   */
3163       /* if right is null then unary */
3164       if (!tree->right)
3165         {
3166
3167           if (!IS_ARITHMETIC (LTYPE (tree)))
3168             {
3169               werror (E_UNARY_OP, tree->opval.op);
3170               goto errorTreeReturn;
3171             }
3172
3173           /* if left is a literal then do it */
3174           if (IS_LITERAL (LTYPE (tree)))
3175             {
3176               tree->type = EX_VALUE;
3177               tree->opval.val = valUnaryPM (valFromType (LETYPE (tree)));
3178               tree->left = NULL;
3179               TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
3180               SPEC_USIGN(TETYPE(tree)) = 0;
3181               return tree;
3182             }
3183           LRVAL (tree) = 1;
3184           TETYPE(tree) = getSpec (TTYPE (tree) = LTYPE (tree));
3185           return tree;
3186         }
3187
3188       /*------------------------------------------------------------------*/
3189       /*----------------------------*/
3190       /*    subtraction             */
3191       /*----------------------------*/
3192
3193       if (!(IS_PTR (LTYPE (tree)) ||
3194             IS_ARRAY (LTYPE (tree)) ||
3195             IS_ARITHMETIC (LTYPE (tree))))
3196         {
3197           werror (E_PLUS_INVALID, "-");
3198           goto errorTreeReturn;
3199         }
3200
3201       if (!(IS_PTR (RTYPE (tree)) ||
3202             IS_ARRAY (RTYPE (tree)) ||
3203             IS_ARITHMETIC (RTYPE (tree))))
3204         {
3205           werror (E_PLUS_INVALID, "-");
3206           goto errorTreeReturn;
3207         }
3208
3209       if ((IS_PTR (LTYPE (tree)) || IS_ARRAY (LTYPE (tree))) &&
3210           !(IS_PTR (RTYPE (tree)) || IS_ARRAY (RTYPE (tree)) ||
3211             IS_INTEGRAL (RTYPE (tree))))
3212         {
3213           werror (E_PLUS_INVALID, "-");
3214           goto errorTreeReturn;
3215         }
3216
3217       /* if they are both literal then */
3218       /* rewrite the tree */
3219       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
3220         {
3221           tree->type = EX_VALUE;
3222           tree->left  = addCast (tree->left,  resultType, TRUE);
3223           tree->right = addCast (tree->right, resultType, TRUE);
3224           tree->opval.val = valMinus (valFromType (LETYPE (tree)),
3225                                       valFromType (RETYPE (tree)));
3226           tree->right = tree->left = NULL;
3227           TETYPE (tree) = getSpec (TTYPE (tree) =
3228                                    tree->opval.val->type);
3229           return tree;
3230         }
3231
3232       /* if the left & right are equal then zero */
3233       if (isAstEqual (tree->left, tree->right))
3234         {
3235           tree->type = EX_VALUE;
3236           tree->left = tree->right = NULL;
3237           tree->opval.val = constVal ("0");
3238           TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
3239           return tree;
3240         }
3241
3242       /* if both of them are pointers or arrays then */
3243       /* the result is going to be an integer        */
3244       if ((IS_ARRAY (LTYPE (tree)) || IS_PTR (LTYPE (tree))) &&
3245           (IS_ARRAY (RTYPE (tree)) || IS_PTR (RTYPE (tree))))
3246         TETYPE (tree) = TTYPE (tree) = newIntLink ();
3247       else
3248         /* if only the left is a pointer */
3249         /* then result is a pointer      */
3250       if (IS_PTR (LTYPE (tree)) || IS_ARRAY (LTYPE (tree)))
3251         TETYPE (tree) = getSpec (TTYPE (tree) =
3252                                  LTYPE (tree));
3253       else
3254         {
3255           tree->left  = addCast (tree->left,  resultType, TRUE);
3256           tree->right = addCast (tree->right, resultType, TRUE);
3257
3258           TETYPE (tree) = getSpec (TTYPE (tree) =
3259                                      computeType (LTYPE (tree),
3260                                                   RTYPE (tree),
3261                                                   resultType,
3262                                                   tree->opval.op));
3263         }
3264
3265       LRVAL (tree) = RRVAL (tree) = 1;
3266
3267       /* if right is a literal and */
3268       /* left is also an addition/subtraction with a literal then */
3269       /* rearrange the tree */
3270       if (IS_LITERAL (RTYPE (tree))
3271           /* avoid infinite loop */
3272           && (TYPE_UDWORD) floatFromVal (tree->right->opval.val) != 0)
3273         {
3274           ast *litTree, *litParent;
3275           litTree = searchLitOp (tree, &litParent, "+-");
3276           if (litTree)
3277             {
3278               if (litTree->opval.op == '+')
3279                 {
3280                   /* foo_sa */
3281                   DEBUG_CF("- 1 SA")
3282                   ast *tTree = litTree->left;
3283                   litTree->left = litTree->right;
3284                   litTree->right = tree->right;
3285                   tree->right = tTree;
3286                   tree->opval.op = '+';
3287                   litTree->opval.op = '-';
3288                 }
3289               else if (litTree->opval.op == '-')
3290                 {
3291                   if (IS_LITERAL (RTYPE (litTree)))
3292                     {
3293                       /* foo_ssr */
3294                       DEBUG_CF("- 2 SSR")
3295                       ast *tTree = litTree->left;
3296                       litTree->left = tree->right;
3297                       tree->right = litParent->left;
3298                       litParent->left = tTree;
3299                       litTree->opval.op = '+';
3300                       
3301                       tree->decorated = 0;
3302                       decorateType (tree, resultType);
3303                     }
3304                   else
3305                     {
3306                       /* foo_ssl */
3307                       DEBUG_CF("- 3 SSL")
3308                       ast *tTree = litTree->right;
3309                       litTree->right = tree->right;
3310                       tree->right = tTree;
3311                     }
3312                 }
3313               decorateType (litParent, resultType);
3314             }
3315         }
3316       return tree;
3317
3318       /*------------------------------------------------------------------*/
3319       /*----------------------------*/
3320       /*    complement              */
3321       /*----------------------------*/
3322     case '~':
3323       /* can be only integral type */
3324       if (!IS_INTEGRAL (LTYPE (tree)))
3325         {
3326           werror (E_UNARY_OP, tree->opval.op);
3327           goto errorTreeReturn;
3328         }
3329
3330       /* if left is a literal then do it */
3331       if (IS_LITERAL (LTYPE (tree)))
3332         {
3333           tree->type = EX_VALUE;
3334           tree->opval.val = valComplement (valFromType (LETYPE (tree)));
3335           tree->left = NULL;
3336           TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
3337           return addCast (tree, resultType, TRUE);
3338         }
3339       tree->left = addCast (tree->left, resultType, TRUE);
3340       LRVAL (tree) = 1;
3341       COPYTYPE (TTYPE (tree), TETYPE (tree), LTYPE (tree));
3342       return tree;
3343
3344       /*------------------------------------------------------------------*/
3345       /*----------------------------*/
3346       /*           not              */
3347       /*----------------------------*/
3348     case '!':
3349       /* can be pointer */
3350       if (!IS_ARITHMETIC (LTYPE (tree)) &&
3351           !IS_PTR (LTYPE (tree)) &&
3352           !IS_ARRAY (LTYPE (tree)))
3353         {
3354           werror (E_UNARY_OP, tree->opval.op);
3355           goto errorTreeReturn;
3356         }
3357
3358       /* if left is a literal then do it */
3359       if (IS_LITERAL (LTYPE (tree)))
3360         {
3361           tree->type = EX_VALUE;
3362           tree->opval.val = valNot (valFromType (LETYPE (tree)));
3363           tree->left = NULL;
3364           TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
3365           return tree;
3366         }
3367       LRVAL (tree) = 1;
3368       TTYPE (tree) = TETYPE (tree) = newCharLink ();
3369       return tree;
3370
3371       /*------------------------------------------------------------------*/
3372       /*----------------------------*/
3373       /*           shift            */
3374       /*----------------------------*/
3375     case RRC:
3376     case RLC:
3377     case SWAP:
3378       TTYPE (tree) = LTYPE (tree);
3379       TETYPE (tree) = LETYPE (tree);
3380       return tree;
3381
3382     case GETHBIT:
3383       TTYPE (tree) = TETYPE (tree) = newCharLink ();
3384       return tree;
3385
3386     case LEFT_OP:
3387     case RIGHT_OP:
3388       if (!IS_INTEGRAL (LTYPE (tree)) || !IS_INTEGRAL (tree->left->etype))
3389         {
3390           werror (E_SHIFT_OP_INVALID);
3391           werror (W_CONTINUE, "left & right types are ");
3392           printTypeChain (LTYPE (tree), stderr);
3393           fprintf (stderr, ",");
3394           printTypeChain (RTYPE (tree), stderr);
3395           fprintf (stderr, "\n");
3396           goto errorTreeReturn;
3397         }
3398
3399       /* make smaller type only if it's a LEFT_OP */
3400       if (tree->opval.op == LEFT_OP)
3401         tree->left = addCast (tree->left, resultType, TRUE);
3402       
3403       /* if they are both literal then */
3404       /* rewrite the tree */
3405       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
3406         {
3407           tree->type = EX_VALUE;
3408           tree->opval.val = valShift (valFromType (LETYPE (tree)),
3409                                       valFromType (RETYPE (tree)),
3410                                       (tree->opval.op == LEFT_OP ? 1 : 0));
3411           tree->right = tree->left = NULL;
3412           TETYPE (tree) = getSpec (TTYPE (tree) =
3413                                    tree->opval.val->type);
3414           return tree;
3415         }
3416
3417       LRVAL (tree) = RRVAL (tree) = 1;
3418       if (tree->opval.op == LEFT_OP)
3419         {
3420           TETYPE (tree) = getSpec (TTYPE (tree) =
3421                                        computeType (LTYPE (tree),
3422                                                     NULL,
3423                                                     resultType,
3424                                                     tree->opval.op));
3425         }
3426       else /* RIGHT_OP */
3427         {
3428           /* no promotion necessary */
3429           TTYPE (tree) = TETYPE (tree) = copyLinkChain (LTYPE (tree));
3430           if (IS_LITERAL (TTYPE (tree)))
3431             SPEC_SCLS (TTYPE (tree)) &= ~S_LITERAL;
3432         }
3433
3434       /* if only the right side is a literal & we are
3435          shifting more than size of the left operand then zero */
3436       if (IS_LITERAL (RTYPE (tree)) &&
3437           ((TYPE_UDWORD) floatFromVal (valFromType (RETYPE (tree)))) >=
3438           (getSize (TETYPE (tree)) * 8))
3439         {
3440           if (tree->opval.op==LEFT_OP ||
3441               (tree->opval.op==RIGHT_OP && SPEC_USIGN(LETYPE(tree))))
3442             {
3443               lineno=tree->lineno;
3444               werror (W_SHIFT_CHANGED,
3445                       (tree->opval.op == LEFT_OP ? "left" : "right"));
3446               tree->type = EX_VALUE;
3447               tree->left = tree->right = NULL;
3448               tree->opval.val = constVal ("0");
3449               TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
3450               return tree;
3451             }
3452         }
3453
3454       return tree;
3455
3456       /*------------------------------------------------------------------*/
3457       /*----------------------------*/
3458       /*         casting            */
3459       /*----------------------------*/
3460     case CAST:                  /* change the type   */
3461       /* cannot cast to an aggregate type */
3462       if (IS_AGGREGATE (LTYPE (tree)))
3463         {
3464           werror (E_CAST_ILLEGAL);
3465           goto errorTreeReturn;
3466         }
3467
3468       /* make sure the type is complete and sane */
3469       checkTypeSanity(LETYPE(tree), "(cast)");
3470
3471       /* If code memory is read only, then pointers to code memory */
3472       /* implicitly point to constants -- make this explicit       */
3473       {
3474         sym_link *t = LTYPE(tree);
3475         while (t && t->next)
3476           {
3477             if (IS_CODEPTR(t) && port->mem.code_ro)
3478               {
3479                 if (IS_SPEC(t->next))
3480                   SPEC_CONST (t->next) = 1;
3481                 else
3482                   DCL_PTR_CONST (t->next) = 1;
3483               }
3484             t = t->next;
3485           }
3486       }
3487
3488 #if 0
3489       /* if the right is a literal replace the tree */
3490       if (IS_LITERAL (RETYPE (tree))) {
3491               if (!IS_PTR (LTYPE (tree))) {
3492                       tree->type = EX_VALUE;
3493                       tree->opval.val =
3494                               valCastLiteral (LTYPE (tree),
3495                                               floatFromVal (valFromType (RETYPE (tree))));
3496                       tree->left = NULL;
3497                       tree->right = NULL;
3498                       TTYPE (tree) = tree->opval.val->type;
3499                       tree->values.literalFromCast = 1;
3500               } else if (IS_GENPTR(LTYPE(tree)) && !IS_PTR(RTYPE(tree)) &&
3501                          ((int)floatFromVal(valFromType(RETYPE(tree)))) !=0 ) /* special case of NULL */  {
3502                       sym_link *rest = LTYPE(tree)->next;
3503                       werror(W_LITERAL_GENERIC);
3504                       TTYPE(tree) = newLink(DECLARATOR);
3505                       DCL_TYPE(TTYPE(tree)) = FPOINTER;
3506                       TTYPE(tree)->next = rest;
3507                       tree->left->opval.lnk = TTYPE(tree);
3508                       LRVAL (tree) = 1;
3509               } else {
3510                       TTYPE (tree) = LTYPE (tree);
3511                       LRVAL (tree) = 1;
3512               }
3513       } else {
3514               TTYPE (tree) = LTYPE (tree);
3515               LRVAL (tree) = 1;
3516       }
3517 #else
3518 #if 0 // this is already checked, now this could be explicit
3519       /* if pointer to struct then check names */
3520       if (IS_PTR(LTYPE(tree)) && IS_STRUCT(LTYPE(tree)->next) &&
3521           IS_PTR(RTYPE(tree)) && IS_STRUCT(RTYPE(tree)->next) &&
3522           strcmp(SPEC_STRUCT(LETYPE(tree))->tag,SPEC_STRUCT(RETYPE(tree))->tag))
3523         {
3524           werror(W_CAST_STRUCT_PTR,SPEC_STRUCT(RETYPE(tree))->tag,
3525                  SPEC_STRUCT(LETYPE(tree))->tag);
3526         }
3527 #endif
3528       if (IS_ADDRESS_OF_OP(tree->right)
3529           && IS_AST_SYM_VALUE (tree->right->left)
3530           && SPEC_ABSA (AST_SYMBOL (tree->right->left)->etype)) {
3531
3532         tree->type = EX_VALUE;
3533         tree->opval.val =
3534           valCastLiteral (LTYPE (tree),
3535                           SPEC_ADDR (AST_SYMBOL (tree->right->left)->etype));
3536         TTYPE (tree) = tree->opval.val->type;
3537         TETYPE (tree) = getSpec (TTYPE (tree));
3538         tree->left = NULL;
3539         tree->right = NULL;
3540         tree->values.literalFromCast = 1;
3541         return tree;
3542       }
3543
3544       /* handle offsetof macro:            */
3545       /* #define offsetof(TYPE, MEMBER) \  */
3546       /* ((unsigned) &((TYPE *)0)->MEMBER) */
3547       if (IS_ADDRESS_OF_OP(tree->right)
3548           && IS_AST_OP (tree->right->left)
3549           && tree->right->left->opval.op == PTR_OP
3550           && IS_AST_OP (tree->right->left->left)
3551           && tree->right->left->left->opval.op == CAST
3552           && IS_AST_LIT_VALUE(tree->right->left->left->right)) {
3553
3554         symbol *element = getStructElement (
3555           SPEC_STRUCT (LETYPE(tree->right->left)),
3556           AST_SYMBOL(tree->right->left->right)
3557         );
3558
3559         if (element) {
3560           tree->type = EX_VALUE;
3561           tree->opval.val = valCastLiteral (
3562             LTYPE (tree),
3563             element->offset
3564             + floatFromVal (valFromType (RTYPE (tree->right->left->left)))
3565           );
3566
3567           TTYPE (tree) = tree->opval.val->type;
3568           TETYPE (tree) = getSpec (TTYPE (tree));
3569           tree->left = NULL;
3570           tree->right = NULL;
3571           return tree;
3572         }
3573       }
3574
3575       /* if the right is a literal replace the tree */
3576       if (IS_LITERAL (RETYPE (tree))) {
3577         #if 0
3578         if (IS_PTR (LTYPE (tree)) && !IS_GENPTR (LTYPE (tree)) ) {
3579           /* rewrite      (type *)litaddr
3580              as           &temp
3581              and define   type at litaddr temp
3582              (but only if type's storage class is not generic)
3583           */
3584           ast *newTree = newNode ('&', NULL, NULL);
3585           symbol *sym;
3586
3587           TTYPE (newTree) = LTYPE (tree);
3588           TETYPE (newTree) = getSpec(LTYPE (tree));
3589
3590           /* define a global symbol at the casted address*/
3591           sym = newSymbol(genSymName (0), 0);
3592           sym->type = LTYPE (tree)->next;
3593           if (!sym->type)
3594             sym->type = newLink (V_VOID);
3595           sym->etype = getSpec(sym->type);
3596           SPEC_SCLS (sym->etype) = sclsFromPtr (LTYPE (tree));
3597           sym->lineDef = tree->lineno;
3598           sym->cdef = 1;
3599           sym->isref = 1;
3600           SPEC_STAT (sym->etype) = 1;
3601           SPEC_ADDR(sym->etype) = floatFromVal (valFromType (RTYPE (tree)));
3602           SPEC_ABSA(sym->etype) = 1;
3603           addSym (SymbolTab, sym, sym->name, 0, 0, 0);
3604           allocGlobal (sym);
3605
3606           newTree->left = newAst_VALUE(symbolVal(sym));
3607           newTree->left->lineno = tree->lineno;
3608           LTYPE (newTree) = sym->type;
3609           LETYPE (newTree) = sym->etype;
3610           LLVAL (newTree) = 1;
3611           LRVAL (newTree) = 0;
3612           TLVAL (newTree) = 1;
3613           return newTree;
3614         }
3615         #endif
3616         if (!IS_PTR (LTYPE (tree))) {
3617           tree->type = EX_VALUE;
3618           tree->opval.val =
3619           valCastLiteral (LTYPE (tree),
3620                           floatFromVal (valFromType (RTYPE (tree))));
3621           TTYPE (tree) = tree->opval.val->type;
3622           tree->left = NULL;
3623           tree->right = NULL;
3624           tree->values.literalFromCast = 1;
3625           TETYPE (tree) = getSpec (TTYPE (tree));
3626           return tree;
3627         }
3628       }
3629       TTYPE (tree) = LTYPE (tree);
3630       LRVAL (tree) = 1;
3631
3632 #endif
3633       TETYPE (tree) = getSpec (TTYPE (tree));
3634
3635       return tree;
3636
3637       /*------------------------------------------------------------------*/
3638       /*----------------------------*/
3639       /*       logical &&, ||       */
3640       /*----------------------------*/
3641     case AND_OP:
3642     case OR_OP:
3643       /* each must be arithmetic type or be a pointer */
3644       if (!IS_PTR (LTYPE (tree)) &&
3645           !IS_ARRAY (LTYPE (tree)) &&
3646           !IS_INTEGRAL (LTYPE (tree)))
3647         {
3648           werror (E_COMPARE_OP);
3649           goto errorTreeReturn;
3650         }
3651
3652       if (!IS_PTR (RTYPE (tree)) &&
3653           !IS_ARRAY (RTYPE (tree)) &&
3654           !IS_INTEGRAL (RTYPE (tree)))
3655         {
3656           werror (E_COMPARE_OP);
3657           goto errorTreeReturn;
3658         }
3659       /* if they are both literal then */
3660       /* rewrite the tree */
3661       if (IS_LITERAL (RTYPE (tree)) &&
3662           IS_LITERAL (LTYPE (tree)))
3663         {
3664           tree->type = EX_VALUE;
3665           tree->opval.val = valLogicAndOr (valFromType (LTYPE (tree)),
3666                                            valFromType (RTYPE (tree)),
3667                                            tree->opval.op);
3668           tree->right = tree->left = NULL;
3669           TETYPE (tree) = getSpec (TTYPE (tree) =
3670                                    tree->opval.val->type);
3671           return tree;
3672         }
3673       LRVAL (tree) = RRVAL (tree) = 1;
3674       TTYPE (tree) = TETYPE (tree) = newCharLink ();
3675       return tree;
3676
3677       /*------------------------------------------------------------------*/
3678       /*----------------------------*/
3679       /*     comparison operators   */
3680       /*----------------------------*/
3681     case '>':
3682     case '<':
3683     case LE_OP:
3684     case GE_OP:
3685     case EQ_OP:
3686     case NE_OP:
3687       {
3688         ast *lt = optimizeCompare (tree);
3689
3690         if (tree != lt)
3691           return lt;
3692       }
3693
3694       /* if they are pointers they must be castable */
3695       if (IS_PTR (LTYPE (tree)) && IS_PTR (RTYPE (tree)))
3696         {
3697           if (tree->opval.op==EQ_OP &&
3698               !IS_GENPTR(LTYPE(tree)) && IS_GENPTR(RTYPE(tree))) {
3699             // we cannot cast a gptr to a !gptr: switch the leaves
3700             struct ast *s=tree->left;
3701             tree->left=tree->right;
3702             tree->right=s;
3703           }
3704           if (compareType (LTYPE (tree), RTYPE (tree)) == 0)
3705             {
3706               werror (E_COMPARE_OP);
3707               fprintf (stderr, "comparing type ");
3708               printTypeChain (LTYPE (tree), stderr);
3709               fprintf (stderr, "to type ");
3710               printTypeChain (RTYPE (tree), stderr);
3711               fprintf (stderr, "\n");
3712               goto errorTreeReturn;
3713             }
3714         }
3715       /* else they should be promotable to one another */
3716       else
3717         {
3718           if (!((IS_PTR (LTYPE (tree)) && IS_LITERAL (RTYPE (tree))) ||
3719                 (IS_PTR (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))))
3720
3721             if (compareType (LTYPE (tree), RTYPE (tree)) == 0)
3722               {
3723                 werror (E_COMPARE_OP);
3724                 fprintf (stderr, "comparing type ");
3725                 printTypeChain (LTYPE (tree), stderr);
3726                 fprintf (stderr, "to type ");
3727                 printTypeChain (RTYPE (tree), stderr);
3728                 fprintf (stderr, "\n");
3729                 goto errorTreeReturn;
3730               }
3731         }
3732       /* if unsigned value < 0  then always false */
3733       /* if (unsigned value) > 0 then '(unsigned value) ? 1 : 0' */
3734       if (SPEC_USIGN(LETYPE(tree)) &&
3735           !IS_CHAR(LETYPE(tree)) && /* promotion to signed int */
3736           IS_LITERAL(RTYPE(tree))  &&
3737           ((int) floatFromVal (valFromType (RETYPE (tree)))) == 0)
3738         {
3739           if (tree->opval.op == '<')
3740             {
3741               return tree->right;
3742             }
3743           if (tree->opval.op == '>')
3744             {
3745               if (resultType == RESULT_TYPE_IFX)
3746                 {
3747                   /* the parent is an ifx: */
3748                   /* if (unsigned value) */
3749                   return tree->left;
3750                 }
3751               
3752               /* (unsigned value) ? 1 : 0 */
3753               tree->opval.op = '?';
3754               tree->right = newNode (':',
3755                                      newAst_VALUE (constVal ("1")),
3756                                      tree->right); /* val 0 */
3757               tree->right->lineno = tree->lineno;
3758               tree->right->left->lineno = tree->lineno;
3759               decorateType (tree->right, RESULT_CHECK);
3760             }
3761         }
3762       /* if they are both literal then */
3763       /* rewrite the tree */
3764       if (IS_LITERAL (RTYPE (tree)) &&
3765           IS_LITERAL (LTYPE (tree)))
3766         {
3767           tree->type = EX_VALUE;
3768           tree->opval.val = valCompare (valFromType (LETYPE (tree)),
3769                                         valFromType (RETYPE (tree)),
3770                                         tree->opval.op);
3771           tree->right = tree->left = NULL;
3772           TETYPE (tree) = getSpec (TTYPE (tree) =
3773                                    tree->opval.val->type);
3774           return tree;
3775         }
3776       LRVAL (tree) = RRVAL (tree) = 1;
3777       TTYPE (tree) = TETYPE (tree) = newCharLink ();
3778       return tree;
3779
3780       /*------------------------------------------------------------------*/
3781       /*----------------------------*/
3782       /*             sizeof         */
3783       /*----------------------------*/
3784     case SIZEOF:                /* evaluate wihout code generation */
3785       /* change the type to a integer */
3786       {
3787         int size = getSize (tree->right->ftype);
3788         SNPRINTF(buffer, sizeof(buffer), "%d", size);
3789         if (!size && !IS_VOID(tree->right->ftype))
3790           werrorfl (tree->filename, tree->lineno, E_SIZEOF_INCOMPLETE_TYPE);
3791       }
3792       tree->type = EX_VALUE;
3793       tree->opval.val = constVal (buffer);
3794       tree->right = tree->left = NULL;
3795       TETYPE (tree) = getSpec (TTYPE (tree) =
3796                                tree->opval.val->type);
3797       return tree;
3798
3799       /*------------------------------------------------------------------*/
3800       /*----------------------------*/
3801       /*             typeof         */
3802       /*----------------------------*/
3803     case TYPEOF:
3804         /* return typeof enum value */
3805         tree->type = EX_VALUE;
3806         {
3807             int typeofv = 0;
3808             if (IS_SPEC(tree->right->ftype)) {
3809                 switch (SPEC_NOUN(tree->right->ftype)) {
3810                 case V_INT:
3811                     if (SPEC_LONG(tree->right->ftype)) typeofv = TYPEOF_LONG;
3812                     else typeofv = TYPEOF_INT;
3813                     break;
3814                 case V_FLOAT:
3815                     typeofv = TYPEOF_FLOAT;
3816                     break;
3817                 case V_CHAR:
3818                     typeofv = TYPEOF_CHAR;
3819                     break;
3820                 case V_VOID:
3821                     typeofv = TYPEOF_VOID;
3822                     break;
3823                 case V_STRUCT:
3824                     typeofv = TYPEOF_STRUCT;
3825                     break;
3826                 case V_BITFIELD:
3827                     typeofv = TYPEOF_BITFIELD;
3828                     break;
3829                 case V_BIT:
3830                     typeofv = TYPEOF_BIT;
3831                     break;
3832                 case V_SBIT:
3833                     typeofv = TYPEOF_SBIT;
3834                     break;
3835                 default:
3836                     break;
3837                 }
3838             } else {
3839                 switch (DCL_TYPE(tree->right->ftype)) {
3840                 case POINTER:
3841                     typeofv = TYPEOF_POINTER;
3842                     break;
3843                 case FPOINTER:
3844                     typeofv = TYPEOF_FPOINTER;
3845                     break;
3846                 case CPOINTER:
3847                     typeofv = TYPEOF_CPOINTER;
3848                     break;
3849                 case GPOINTER:
3850                     typeofv = TYPEOF_GPOINTER;
3851                     break;
3852                 case PPOINTER:
3853                     typeofv = TYPEOF_PPOINTER;
3854                     break;
3855                 case IPOINTER:
3856                     typeofv = TYPEOF_IPOINTER;
3857                     break;
3858                 case ARRAY:
3859                     typeofv = TYPEOF_ARRAY;
3860                     break;
3861                 case FUNCTION:
3862                     typeofv = TYPEOF_FUNCTION;
3863                     break;
3864                 default:
3865                     break;
3866                 }
3867             }
3868             SNPRINTF (buffer, sizeof(buffer), "%d", typeofv);
3869             tree->opval.val = constVal (buffer);
3870             tree->right = tree->left = NULL;
3871             TETYPE (tree) = getSpec (TTYPE (tree) =
3872                                      tree->opval.val->type);
3873         }
3874         return tree;
3875       /*------------------------------------------------------------------*/
3876       /*----------------------------*/
3877       /* conditional operator  '?'  */
3878       /*----------------------------*/
3879     case '?':
3880       /* the type is value of the colon operator (on the right) */
3881       assert (IS_COLON_OP (tree->right));
3882       /* if already known then replace the tree : optimizer will do it
3883          but faster to do it here */
3884       if (IS_LITERAL (LTYPE (tree)))
3885         {
3886           if (((int) floatFromVal (valFromType (LETYPE (tree)))) != 0)
3887             return decorateType (tree->right->left, resultTypeProp);
3888           else
3889             return decorateType (tree->right->right, resultTypeProp);
3890         }
3891       else
3892         {
3893           tree->right = decorateType (tree->right, resultTypeProp);
3894           TTYPE (tree) = RTYPE (tree);
3895           TETYPE (tree) = getSpec (TTYPE (tree));
3896         }
3897       return tree;
3898
3899     case ':':
3900       /* if they don't match we have a problem */
3901       if (compareType (LTYPE (tree), RTYPE (tree)) == 0)
3902         {
3903           werror (E_TYPE_MISMATCH, "conditional operator", " ");
3904           goto errorTreeReturn;
3905         }
3906
3907       TTYPE (tree) = computeType (LTYPE (tree), RTYPE (tree),
3908                                   resultType, tree->opval.op);
3909       TETYPE (tree) = getSpec (TTYPE (tree));
3910       return tree;
3911
3912
3913 #if 0 // assignment operators are converted by the parser
3914       /*------------------------------------------------------------------*/
3915       /*----------------------------*/
3916       /*    assignment operators    */
3917       /*----------------------------*/
3918     case MUL_ASSIGN:
3919     case DIV_ASSIGN:
3920       /* for these it must be both must be integral */
3921       if (!IS_ARITHMETIC (LTYPE (tree)) ||
3922           !IS_ARITHMETIC (RTYPE (tree)))
3923         {
3924           werror (E_OPS_INTEGRAL);
3925           goto errorTreeReturn;
3926         }
3927       RRVAL (tree) = 1;
3928       TETYPE (tree) = getSpec (TTYPE (tree) = LTYPE (tree));
3929
3930       if (!tree->initMode && IS_CONSTANT (LTYPE (tree)))
3931         werror (E_CODE_WRITE, tree->opval.op==MUL_ASSIGN ? "*=" : "/=");
3932
3933       if (LRVAL (tree))
3934         {
3935           werror (E_LVALUE_REQUIRED, tree->opval.op==MUL_ASSIGN ? "*=" : "/=");
3936           goto errorTreeReturn;
3937         }
3938       LLVAL (tree) = 1;
3939
3940       return tree;
3941
3942     case AND_ASSIGN:
3943     case OR_ASSIGN:
3944     case XOR_ASSIGN:
3945     case RIGHT_ASSIGN:
3946     case LEFT_ASSIGN:
3947       /* for these it must be both must be integral */
3948       if (!IS_INTEGRAL (LTYPE (tree)) ||
3949           !IS_INTEGRAL (RTYPE (tree)))
3950         {
3951           werror (E_OPS_INTEGRAL);
3952           goto errorTreeReturn;
3953         }
3954       RRVAL (tree) = 1;
3955       TETYPE (tree) = getSpec (TTYPE (tree) = LTYPE (tree));
3956
3957       if (!tree->initMode && IS_CONSTANT (LETYPE (tree)))
3958         werror (E_CODE_WRITE, "&= or |= or ^= or >>= or <<=");
3959
3960       if (LRVAL (tree))
3961         {
3962           werror (E_LVALUE_REQUIRED, "&= or |= or ^= or >>= or <<=");
3963           goto errorTreeReturn;
3964         }
3965       LLVAL (tree) = 1;
3966
3967       return tree;
3968
3969       /*------------------------------------------------------------------*/
3970       /*----------------------------*/
3971       /*    -= operator             */
3972       /*----------------------------*/
3973     case SUB_ASSIGN:
3974       if (!(IS_PTR (LTYPE (tree)) ||
3975             IS_ARITHMETIC (LTYPE (tree))))
3976         {
3977           werror (E_PLUS_INVALID, "-=");
3978           goto errorTreeReturn;
3979         }
3980
3981       if (!(IS_PTR (RTYPE (tree)) ||
3982             IS_ARITHMETIC (RTYPE (tree))))
3983         {
3984           werror (E_PLUS_INVALID, "-=");
3985           goto errorTreeReturn;
3986         }
3987       RRVAL (tree) = 1;
3988       TETYPE (tree) = getSpec (TTYPE (tree) =
3989                                computeType (LTYPE (tree),
3990                                             RTYPE (tree),
3991                                             RESULT_TYPE_NOPROM,
3992                                             tree->opval.op));
3993
3994       if (!tree->initMode && IS_CONSTANT (LETYPE (tree)))
3995         werror (E_CODE_WRITE, "-=");
3996
3997       if (LRVAL (tree))
3998         {
3999           werror (E_LVALUE_REQUIRED, "-=");
4000           goto errorTreeReturn;
4001         }
4002       LLVAL (tree) = 1;
4003
4004       return tree;
4005
4006       /*------------------------------------------------------------------*/
4007       /*----------------------------*/
4008       /*          += operator       */
4009       /*----------------------------*/
4010     case ADD_ASSIGN:
4011       /* this is not a unary operation */
4012       /* if both pointers then problem */
4013       if (IS_PTR (LTYPE (tree)) && IS_PTR (RTYPE (tree)))
4014         {
4015           werror (E_PTR_PLUS_PTR);
4016           goto errorTreeReturn;
4017         }
4018
4019       if (!IS_ARITHMETIC (LTYPE (tree)) && !IS_PTR (LTYPE (tree)))
4020         {
4021           werror (E_PLUS_INVALID, "+=");
4022           goto errorTreeReturn;
4023         }
4024
4025       if (!IS_ARITHMETIC (RTYPE (tree)) && !IS_PTR (RTYPE (tree)))
4026         {
4027           werror (E_PLUS_INVALID, "+=");
4028           goto errorTreeReturn;
4029         }
4030       RRVAL (tree) = 1;
4031       TETYPE (tree) = getSpec (TTYPE (tree) =
4032                                computeType (LTYPE (tree),
4033                                             RTYPE (tree),
4034                                             RESULT_TYPE_NOPROM,
4035                                             tree->opval.op));
4036
4037       if (!tree->initMode && IS_CONSTANT (LETYPE (tree)))
4038         werror (E_CODE_WRITE, "+=");
4039
4040       if (LRVAL (tree))
4041         {
4042           werror (E_LVALUE_REQUIRED, "+=");
4043           goto errorTreeReturn;
4044         }
4045
4046       tree->right = decorateType (newNode ('+', copyAst (tree->left), tree->right), RESULT_CHECK);
4047       tree->opval.op = '=';
4048
4049       return tree;
4050 #endif
4051
4052       /*------------------------------------------------------------------*/
4053       /*----------------------------*/
4054       /*      straight assignemnt   */
4055       /*----------------------------*/
4056     case '=':
4057       /* cannot be an aggregate */
4058       if (IS_AGGREGATE (LTYPE (tree)))
4059         {
4060           werror (E_AGGR_ASSIGN);
4061           goto errorTreeReturn;
4062         }
4063
4064       /* they should either match or be castable */
4065       if (compareType (LTYPE (tree), RTYPE (tree)) == 0)
4066         {
4067           werror (E_TYPE_MISMATCH, "assignment", " ");
4068           printFromToType(RTYPE(tree),LTYPE(tree));
4069         }
4070
4071       /* if the left side of the tree is of type void
4072          then report error */
4073       if (IS_VOID (LTYPE (tree)))
4074         {
4075           werror (E_CAST_ZERO);
4076           printFromToType(RTYPE(tree), LTYPE(tree));
4077         }
4078
4079       TETYPE (tree) = getSpec (TTYPE (tree) =
4080                                LTYPE (tree));
4081       RRVAL (tree) = 1;
4082       LLVAL (tree) = 1;
4083       if (!tree->initMode ) {
4084         if (IS_CONSTANT(LTYPE(tree)))
4085           werror (E_CODE_WRITE, "=");
4086       }
4087       if (LRVAL (tree))
4088         {
4089           werror (E_LVALUE_REQUIRED, "=");
4090           goto errorTreeReturn;
4091         }
4092
4093       return tree;
4094
4095       /*------------------------------------------------------------------*/
4096       /*----------------------------*/
4097       /*      comma operator        */
4098       /*----------------------------*/
4099     case ',':
4100       TETYPE (tree) = getSpec (TTYPE (tree) = RTYPE (tree));
4101       return tree;
4102
4103       /*------------------------------------------------------------------*/
4104       /*----------------------------*/
4105       /*       function call        */
4106       /*----------------------------*/
4107     case CALL:
4108       
4109       /* undo any explicit pointer derefernce; PCALL will handle it instead */
4110       if (IS_FUNC (LTYPE (tree)) && tree->left->type == EX_OP)
4111         {
4112           if (tree->left->opval.op == '*' && !tree->left->right)
4113             tree->left = tree->left->left;
4114         }
4115
4116       /* require a function or pointer to function */
4117       if (!IS_FUNC (LTYPE (tree))
4118           && !(IS_CODEPTR (LTYPE (tree)) && IS_FUNC (LTYPE (tree)->next)))
4119         {
4120           werrorfl (tree->filename, tree->lineno, E_FUNCTION_EXPECTED);
4121           goto errorTreeReturn;
4122         }
4123
4124       /* if there are parms, make sure that
4125          parms are decorate / process / reverse only once */
4126       if (!tree->right ||
4127           !tree->right->decorated)
4128         {
4129           sym_link *functype;      
4130           parmNumber = 1;
4131
4132           if (IS_CODEPTR(LTYPE(tree)))
4133             functype = LTYPE (tree)->next;
4134           else
4135             functype = LTYPE (tree);
4136
4137           if (processParms (tree->left, FUNC_ARGS(functype),
4138                             &tree->right, &parmNumber, TRUE))
4139             {
4140               goto errorTreeReturn;
4141             }
4142         
4143           if ((options.stackAuto || IFFUNC_ISREENT (functype)) && 
4144              !IFFUNC_ISBUILTIN(functype))
4145             {
4146               reverseParms (tree->right);
4147             }
4148
4149            TTYPE (tree) = functype->next;
4150            TETYPE (tree) = getSpec (TTYPE (tree));
4151         }
4152       return tree;
4153
4154       /*------------------------------------------------------------------*/
4155       /*----------------------------*/
4156       /*     return statement       */
4157       /*----------------------------*/
4158     case RETURN:
4159       if (!tree->right)
4160         goto voidcheck;
4161
4162       if (compareType (currFunc->type->next, RTYPE (tree)) == 0)
4163         {
4164           werrorfl (tree->filename, tree->lineno, W_RETURN_MISMATCH);
4165           printFromToType (RTYPE(tree), currFunc->type->next);
4166           goto errorTreeReturn;
4167         }
4168
4169       if (IS_VOID (currFunc->type->next)
4170           && tree->right &&
4171           !IS_VOID (RTYPE (tree)))
4172         {
4173           werrorfl (tree->filename, tree->lineno, E_FUNC_VOID);
4174           goto errorTreeReturn;
4175         }
4176
4177       /* if there is going to be a casting required then add it */
4178       if (compareType (currFunc->type->next, RTYPE (tree)) < 0)
4179         {
4180           tree->right =
4181             decorateType (newNode (CAST,
4182                           newAst_LINK (copyLinkChain (currFunc->type->next)),
4183                                         tree->right),
4184                           RESULT_CHECK);
4185         }
4186
4187       RRVAL (tree) = 1;
4188       return tree;
4189
4190     voidcheck:
4191
4192       if (!IS_VOID (currFunc->type->next) && tree->right == NULL)
4193         {
4194           werror (W_VOID_FUNC, currFunc->name);
4195           goto errorTreeReturn;
4196         }
4197
4198       TTYPE (tree) = TETYPE (tree) = NULL;
4199       return tree;
4200
4201       /*------------------------------------------------------------------*/
4202       /*----------------------------*/
4203       /*     switch statement       */
4204       /*----------------------------*/
4205     case SWITCH:
4206       /* the switch value must be an integer */
4207       if (!IS_INTEGRAL (LTYPE (tree)))
4208         {
4209           werrorfl (tree->filename, tree->lineno, E_SWITCH_NON_INTEGER);
4210           goto errorTreeReturn;
4211         }
4212       LRVAL (tree) = 1;
4213       TTYPE (tree) = TETYPE (tree) = NULL;
4214       return tree;
4215
4216       /*------------------------------------------------------------------*/
4217       /*----------------------------*/
4218       /* ifx Statement              */
4219       /*----------------------------*/
4220     case IFX:
4221       tree->left = backPatchLabels (tree->left,
4222                                     tree->trueLabel,
4223                                     tree->falseLabel);
4224       TTYPE (tree) = TETYPE (tree) = NULL;
4225       return tree;
4226
4227       /*------------------------------------------------------------------*/
4228       /*----------------------------*/
4229       /* for Statement              */
4230       /*----------------------------*/
4231     case FOR:
4232
4233       decorateType (resolveSymbols (AST_FOR (tree, initExpr)), RESULT_CHECK);
4234       decorateType (resolveSymbols (AST_FOR (tree, condExpr)), RESULT_CHECK);
4235       decorateType (resolveSymbols (AST_FOR (tree, loopExpr)), RESULT_CHECK);
4236
4237       /* if the for loop is reversible then
4238          reverse it otherwise do what we normally
4239          do */
4240       {
4241         symbol *sym;
4242         ast *init, *end;
4243
4244         if (isLoopReversible (tree, &sym, &init, &end))
4245           return reverseLoop (tree, sym, init, end);
4246         else
4247           return decorateType (createFor (AST_FOR (tree, trueLabel),
4248                                           AST_FOR (tree, continueLabel),
4249                                           AST_FOR (tree, falseLabel),
4250                                           AST_FOR (tree, condLabel),
4251                                           AST_FOR (tree, initExpr),
4252                                           AST_FOR (tree, condExpr),
4253                                           AST_FOR (tree, loopExpr),
4254                                           tree->left), RESULT_CHECK);
4255       }
4256     case PARAM:
4257       werror (E_INTERNAL_ERROR, __FILE__, __LINE__,
4258               "node PARAM shouldn't be processed here");
4259               /* but in processParams() */
4260       return tree;
4261     default:
4262       TTYPE (tree) = TETYPE (tree) = NULL;
4263       return tree;
4264     }
4265
4266   /* some error found this tree will be killed */
4267 errorTreeReturn:
4268   TTYPE (tree) = TETYPE (tree) = newCharLink ();
4269   tree->opval.op = NULLOP;
4270   tree->isError = 1;
4271
4272   return tree;
4273 }
4274
4275 /*-----------------------------------------------------------------*/
4276 /* sizeofOp - processes size of operation                          */
4277 /*-----------------------------------------------------------------*/
4278 value *
4279 sizeofOp (sym_link * type)
4280 {
4281   char buff[10];
4282   int size;
4283
4284   /* make sure the type is complete and sane */
4285   checkTypeSanity(type, "(sizeof)");
4286
4287   /* get the size and convert it to character  */
4288   SNPRINTF (buff, sizeof(buff), "%d", size = getSize (type));
4289   if (!size && !IS_VOID(type))
4290     werror (E_SIZEOF_INCOMPLETE_TYPE);
4291
4292   /* now convert into value  */
4293   return constVal (buff);
4294 }
4295
4296
4297 #define IS_AND(ex) (ex->type == EX_OP && ex->opval.op == AND_OP )
4298 #define IS_OR(ex)  (ex->type == EX_OP && ex->opval.op == OR_OP )
4299 #define IS_NOT(ex) (ex->type == EX_OP && ex->opval.op == '!' )
4300 #define IS_ANDORNOT(ex) (IS_AND(ex) || IS_OR(ex) || IS_NOT(ex))
4301 #define IS_IFX(ex) (ex->type == EX_OP && ex->opval.op == IFX )
4302 #define IS_LT(ex)  (ex->type == EX_OP && ex->opval.op == '<' )
4303 #define IS_GT(ex)  (ex->type == EX_OP && ex->opval.op == '>')
4304
4305 /*-----------------------------------------------------------------*/
4306 /* backPatchLabels - change and or not operators to flow control    */
4307 /*-----------------------------------------------------------------*/
4308 ast *
4309 backPatchLabels (ast * tree, symbol * trueLabel, symbol * falseLabel)
4310 {
4311
4312   if (!tree)
4313     return NULL;
4314
4315   if (!(IS_ANDORNOT (tree)))
4316     return tree;
4317
4318   /* if this an and */
4319   if (IS_AND (tree))
4320     {
4321       static int localLbl = 0;
4322       symbol *localLabel;
4323
4324       SNPRINTF(buffer, sizeof(buffer), "_andif_%d", localLbl++);
4325       localLabel = newSymbol (buffer, NestLevel);
4326
4327       tree->left = backPatchLabels (tree->left, localLabel, falseLabel);
4328
4329       /* if left is already a IFX then just change the if true label in that */
4330       if (!IS_IFX (tree->left))
4331         tree->left = newIfxNode (tree->left, localLabel, falseLabel);
4332
4333       tree->right = backPatchLabels (tree->right, trueLabel, falseLabel);
4334       /* right is a IFX then just join */
4335       if (IS_IFX (tree->right))
4336         return newNode (NULLOP, tree->left, createLabel (localLabel, tree->right));
4337
4338       tree->right = createLabel (localLabel, tree->right);
4339       tree->right = newIfxNode (tree->right, trueLabel, falseLabel);
4340
4341       return newNode (NULLOP, tree->left, tree->right);
4342     }
4343
4344   /* if this is an or operation */
4345   if (IS_OR (tree))
4346     {
4347       static int localLbl = 0;
4348       symbol *localLabel;
4349
4350       SNPRINTF(buffer, sizeof(buffer), "_orif_%d", localLbl++);
4351       localLabel = newSymbol (buffer, NestLevel);
4352
4353       tree->left = backPatchLabels (tree->left, trueLabel, localLabel);
4354
4355       /* if left is already a IFX then just change the if true label in that */
4356       if (!IS_IFX (tree->left))
4357         tree->left = newIfxNode (tree->left, trueLabel, localLabel);
4358
4359       tree->right = backPatchLabels (tree->right, trueLabel, falseLabel);
4360       /* right is a IFX then just join */
4361       if (IS_IFX (tree->right))
4362         return newNode (NULLOP, tree->left, createLabel (localLabel, tree->right));
4363
4364       tree->right = createLabel (localLabel, tree->right);
4365       tree->right = newIfxNode (tree->right, trueLabel, falseLabel);
4366
4367       return newNode (NULLOP, tree->left, tree->right);
4368     }
4369
4370   /* change not */
4371   if (IS_NOT (tree))
4372     {
4373       int wasnot = IS_NOT (tree->left);
4374       tree->left = backPatchLabels (tree->left, falseLabel, trueLabel);
4375
4376       /* if the left is already a IFX */
4377       if (!IS_IFX (tree->left))
4378         tree->left = newNode (IFX, tree->left, NULL);
4379
4380       if (wasnot)
4381         {
4382           tree->left->trueLabel = trueLabel;
4383           tree->left->falseLabel = falseLabel;
4384         }
4385       else
4386         {
4387           tree->left->trueLabel = falseLabel;
4388           tree->left->falseLabel = trueLabel;
4389         }
4390       return tree->left;
4391     }
4392
4393   if (IS_IFX (tree))
4394     {
4395       tree->trueLabel = trueLabel;
4396       tree->falseLabel = falseLabel;
4397     }
4398
4399   return tree;
4400 }
4401
4402
4403 /*-----------------------------------------------------------------*/
4404 /* createBlock - create expression tree for block                  */
4405 /*-----------------------------------------------------------------*/
4406 ast *
4407 createBlock (symbol * decl, ast * body)
4408 {
4409   ast *ex;
4410
4411   /* if the block has nothing */
4412   if (!body && !decl)
4413     return NULL;
4414
4415   ex = newNode (BLOCK, NULL, body);
4416   ex->values.sym = decl;
4417   
4418   ex->right = ex->right;
4419   ex->level++;
4420   ex->lineno = 0;
4421   return ex;
4422 }
4423
4424 /*-----------------------------------------------------------------*/
4425 /* createLabel - creates the expression tree for labels            */
4426 /*-----------------------------------------------------------------*/
4427 ast *
4428 createLabel (symbol * label, ast * stmnt)
4429 {
4430   symbol *csym;
4431   char name[SDCC_NAME_MAX + 1];
4432   ast *rValue;
4433
4434   /* must create fresh symbol if the symbol name  */
4435   /* exists in the symbol table, since there can  */
4436   /* be a variable with the same name as the labl */
4437   if ((csym = findSym (SymbolTab, NULL, label->name)) &&
4438       (csym->level == label->level))
4439     label = newSymbol (label->name, label->level);
4440
4441   /* change the name before putting it in add _ */
4442   SNPRINTF(name, sizeof(name), "%s", label->name);
4443
4444   /* put the label in the LabelSymbol table    */
4445   /* but first check if a label of the same    */
4446   /* name exists                               */
4447   if ((csym = findSym (LabelTab, NULL, name)))
4448     werror (E_DUPLICATE_LABEL, label->name);
4449   else
4450     addSym (LabelTab, label, name, label->level, 0, 0);
4451
4452   label->isitmp = 1;
4453   label->islbl = 1;
4454   label->key = labelKey++;
4455   rValue = newNode (LABEL, newAst_VALUE (symbolVal (label)), stmnt);
4456   rValue->lineno = 0;
4457
4458   return rValue;
4459 }
4460
4461 /*-----------------------------------------------------------------*/
4462 /* createCase - generates the parsetree for a case statement       */
4463 /*-----------------------------------------------------------------*/
4464 ast *
4465 createCase (ast * swStat, ast * caseVal, ast * stmnt)
4466 {
4467   char caseLbl[SDCC_NAME_MAX + 1];
4468   ast *rexpr;
4469   value *val;
4470
4471   /* if the switch statement does not exist */
4472   /* then case is out of context            */
4473   if (!swStat)
4474     {
4475       werrorfl (caseVal->filename, caseVal->lineno, E_CASE_CONTEXT);
4476       return NULL;
4477     }
4478
4479   caseVal = decorateType (resolveSymbols (caseVal), RESULT_CHECK);
4480   /* if not a constant then error  */
4481   if (!IS_LITERAL (caseVal->ftype))
4482     {
4483       werrorfl (caseVal->filename, caseVal->lineno, E_CASE_CONSTANT);
4484       return NULL;
4485     }
4486
4487   /* if not a integer than error */
4488   if (!IS_INTEGRAL (caseVal->ftype))
4489     {
4490       werrorfl (caseVal->filename, caseVal->lineno, E_CASE_NON_INTEGER);
4491       return NULL;
4492     }
4493
4494   /* find the end of the switch values chain   */
4495   if (!(val = swStat->values.switchVals.swVals))
4496     swStat->values.switchVals.swVals = caseVal->opval.val;
4497   else
4498     {
4499       /* also order the cases according to value */
4500       value *pval = NULL;
4501       int cVal = (int) floatFromVal (caseVal->opval.val);
4502       while (val && (int) floatFromVal (val) < cVal)
4503         {
4504           pval = val;
4505           val = val->next;
4506         }
4507
4508       /* if we reached the end then */
4509       if (!val)
4510         {
4511           pval->next = caseVal->opval.val;
4512         }
4513       else if ((int) floatFromVal (val) == cVal)
4514         {
4515           werrorfl (caseVal->filename, caseVal->lineno, E_DUPLICATE_LABEL,
4516                     "case");
4517           return NULL;
4518         }
4519       else
4520         {
4521           /* we found a value greater than */
4522           /* the current value we must add this */
4523           /* before the value */
4524           caseVal->opval.val->next = val;
4525
4526           /* if this was the first in chain */
4527           if (swStat->values.switchVals.swVals == val)
4528             swStat->values.switchVals.swVals =
4529               caseVal->opval.val;
4530           else
4531             pval->next = caseVal->opval.val;
4532         }
4533
4534     }
4535
4536   /* create the case label   */
4537   SNPRINTF(caseLbl, sizeof(caseLbl), 
4538            "_case_%d_%d",
4539            swStat->values.switchVals.swNum,
4540            (int) floatFromVal (caseVal->opval.val));
4541
4542   rexpr = createLabel (newSymbol (caseLbl, 0), stmnt);
4543   rexpr->lineno = 0;
4544   return rexpr;
4545 }
4546
4547 /*-----------------------------------------------------------------*/
4548 /* createDefault - creates the parse tree for the default statement */
4549 /*-----------------------------------------------------------------*/
4550 ast *
4551 createDefault (ast * swStat, ast * defaultVal, ast * stmnt)
4552 {
4553   char defLbl[SDCC_NAME_MAX + 1];
4554
4555   /* if the switch statement does not exist */
4556   /* then case is out of context            */
4557   if (!swStat)
4558     {
4559       werrorfl (defaultVal->filename, defaultVal->lineno, E_CASE_CONTEXT);
4560       return NULL;
4561     }
4562
4563   if (swStat->values.switchVals.swDefault)
4564     {
4565       werrorfl (defaultVal->filename, defaultVal->lineno, E_DUPLICATE_LABEL,
4566                 "default");
4567       return NULL;
4568     }
4569
4570   /* turn on the default flag   */
4571   swStat->values.switchVals.swDefault = 1;
4572
4573   /* create the label  */
4574   SNPRINTF (defLbl, sizeof(defLbl),
4575             "_default_%d", swStat->values.switchVals.swNum);
4576   return createLabel (newSymbol (defLbl, 0), stmnt);
4577 }
4578
4579 /*-----------------------------------------------------------------*/
4580 /* createIf - creates the parsetree for the if statement           */
4581 /*-----------------------------------------------------------------*/
4582 ast *
4583 createIf (ast * condAst, ast * ifBody, ast * elseBody)
4584 {
4585   static int Lblnum = 0;
4586   ast *ifTree;
4587   symbol *ifTrue, *ifFalse, *ifEnd;
4588
4589   /* if neither exists */
4590   if (!elseBody && !ifBody) {
4591     // if there are no side effects (i++, j() etc)
4592     if (!hasSEFcalls(condAst)) {
4593       return condAst;
4594     }
4595   }
4596
4597   /* create the labels */
4598   SNPRINTF (buffer, sizeof(buffer), "_iffalse_%d", Lblnum);
4599   ifFalse = newSymbol (buffer, NestLevel);
4600   /* if no else body then end == false */
4601   if (!elseBody)
4602     ifEnd = ifFalse;
4603   else
4604     {
4605       SNPRINTF(buffer, sizeof(buffer), "_ifend_%d", Lblnum);
4606       ifEnd = newSymbol (buffer, NestLevel);
4607     }
4608
4609   SNPRINTF (buffer, sizeof(buffer), "_iftrue_%d", Lblnum);
4610   ifTrue = newSymbol (buffer, NestLevel);
4611
4612   Lblnum++;
4613
4614   /* attach the ifTrue label to the top of it body */
4615   ifBody = createLabel (ifTrue, ifBody);
4616   /* attach a goto end to the ifBody if else is present */
4617   if (elseBody)
4618     {
4619       ifBody = newNode (NULLOP, ifBody,
4620                         newNode (GOTO,
4621                                  newAst_VALUE (symbolVal (ifEnd)),
4622                                  NULL));
4623       /* put the elseLabel on the else body */
4624       elseBody = createLabel (ifFalse, elseBody);
4625       /* out the end at the end of the body */
4626       elseBody = newNode (NULLOP,
4627                           elseBody,
4628                           createLabel (ifEnd, NULL));
4629     }
4630   else
4631     {
4632       ifBody = newNode (NULLOP, ifBody,
4633                         createLabel (ifFalse, NULL));
4634     }
4635   condAst = backPatchLabels (condAst, ifTrue, ifFalse);
4636   if (IS_IFX (condAst))
4637     ifTree = condAst;
4638   else
4639     ifTree = newIfxNode (condAst, ifTrue, ifFalse);
4640
4641   return newNode (NULLOP, ifTree,
4642                   newNode (NULLOP, ifBody, elseBody));
4643
4644 }
4645
4646 /*-----------------------------------------------------------------*/
4647 /* createDo - creates parse tree for do                            */
4648 /*        _dobody_n:                                               */
4649 /*            statements                                           */
4650 /*        _docontinue_n:                                           */
4651 /*            condition_expression +-> trueLabel -> _dobody_n      */
4652 /*                                 |                               */
4653 /*                                 +-> falseLabel-> _dobreak_n     */
4654 /*        _dobreak_n:                                              */
4655 /*-----------------------------------------------------------------*/
4656 ast *
4657 createDo (symbol * trueLabel, symbol * continueLabel,
4658           symbol * falseLabel, ast * condAst, ast * doBody)
4659 {
4660   ast *doTree;
4661
4662
4663   /* if the body does not exist then it is simple */
4664   if (!doBody)
4665     {
4666       condAst = backPatchLabels (condAst, continueLabel, NULL);
4667       doTree = (IS_IFX (condAst) ? createLabel (continueLabel, condAst)
4668                 : newNode (IFX, createLabel (continueLabel, condAst), NULL));
4669       doTree->trueLabel = continueLabel;
4670       doTree->falseLabel = NULL;
4671       return doTree;
4672     }
4673
4674   /* otherwise we have a body */
4675   condAst = backPatchLabels (condAst, trueLabel, falseLabel);
4676
4677   /* attach the body label to the top */
4678   doBody = createLabel (trueLabel, doBody);
4679   /* attach the continue label to end of body */
4680   doBody = newNode (NULLOP, doBody,
4681                     createLabel (continueLabel, NULL));
4682
4683   /* now put the break label at the end */
4684   if (IS_IFX (condAst))
4685     doTree = condAst;
4686   else
4687     doTree = newIfxNode (condAst, trueLabel, falseLabel);
4688
4689   doTree = newNode (NULLOP, doTree, createLabel (falseLabel, NULL));
4690
4691   /* putting it together */
4692   return newNode (NULLOP, doBody, doTree);
4693 }
4694
4695 /*-----------------------------------------------------------------*/
4696 /* createFor - creates parse tree for 'for' statement              */
4697 /*        initExpr                                                 */
4698 /*   _forcond_n:                                                   */
4699 /*        condExpr  +-> trueLabel -> _forbody_n                    */
4700 /*                  |                                              */
4701 /*                  +-> falseLabel-> _forbreak_n                   */
4702 /*   _forbody_n:                                                   */
4703 /*        statements                                               */
4704 /*   _forcontinue_n:                                               */
4705 /*        loopExpr                                                 */
4706 /*        goto _forcond_n ;                                        */
4707 /*   _forbreak_n:                                                  */
4708 /*-----------------------------------------------------------------*/
4709 ast *
4710 createFor (symbol * trueLabel, symbol * continueLabel,
4711            symbol * falseLabel, symbol * condLabel,
4712            ast * initExpr, ast * condExpr, ast * loopExpr,
4713            ast * forBody)
4714 {
4715   ast *forTree;
4716
4717   /* if loopexpression not present then we can generate it */
4718   /* the same way as a while */
4719   if (!loopExpr)
4720     return newNode (NULLOP, initExpr,
4721                     createWhile (trueLabel, continueLabel,
4722                                  falseLabel, condExpr, forBody));
4723   /* vanilla for statement */
4724   condExpr = backPatchLabels (condExpr, trueLabel, falseLabel);
4725
4726   if (condExpr && !IS_IFX (condExpr))
4727     condExpr = newIfxNode (condExpr, trueLabel, falseLabel);
4728
4729
4730   /* attach condition label to condition */
4731   condExpr = createLabel (condLabel, condExpr);
4732
4733   /* attach body label to body */
4734   forBody = createLabel (trueLabel, forBody);
4735
4736   /* attach continue to forLoop expression & attach */
4737   /* goto the forcond @ and of loopExpression       */
4738   loopExpr = createLabel (continueLabel,
4739                           newNode (NULLOP,
4740                                    loopExpr,
4741                                    newNode (GOTO,
4742                                        newAst_VALUE (symbolVal (condLabel)),
4743                                             NULL)));
4744   /* now start putting them together */
4745   forTree = newNode (NULLOP, initExpr, condExpr);
4746   forTree = newNode (NULLOP, forTree, forBody);
4747   forTree = newNode (NULLOP, forTree, loopExpr);
4748   /* finally add the break label */
4749   forTree = newNode (NULLOP, forTree,
4750                      createLabel (falseLabel, NULL));
4751   return forTree;
4752 }
4753
4754 /*-----------------------------------------------------------------*/
4755 /* createWhile - creates parse tree for while statement            */
4756 /*               the while statement will be created as follows    */
4757 /*                                                                 */
4758 /*      _while_continue_n:                                         */
4759 /*            condition_expression +-> trueLabel -> _while_boby_n  */
4760 /*                                 |                               */
4761 /*                                 +-> falseLabel -> _while_break_n */
4762 /*      _while_body_n:                                             */
4763 /*            statements                                           */
4764 /*            goto _while_continue_n                               */
4765 /*      _while_break_n:                                            */
4766 /*-----------------------------------------------------------------*/
4767 ast *
4768 createWhile (symbol * trueLabel, symbol * continueLabel,
4769              symbol * falseLabel, ast * condExpr, ast * whileBody)
4770 {
4771   ast *whileTree;
4772
4773   /* put the continue label */
4774   condExpr = backPatchLabels (condExpr, trueLabel, falseLabel);
4775   condExpr = createLabel (continueLabel, condExpr);
4776   condExpr->lineno = 0;
4777
4778   /* put the body label in front of the body */
4779   whileBody = createLabel (trueLabel, whileBody);
4780   whileBody->lineno = 0;
4781   /* put a jump to continue at the end of the body */
4782   /* and put break label at the end of the body */
4783   whileBody = newNode (NULLOP,
4784                        whileBody,
4785                        newNode (GOTO,
4786                                 newAst_VALUE (symbolVal (continueLabel)),
4787                                 createLabel (falseLabel, NULL)));
4788
4789   /* put it all together */
4790   if (IS_IFX (condExpr))
4791     whileTree = condExpr;
4792   else
4793     {
4794       whileTree = newNode (IFX, condExpr, NULL);
4795       /* put the true & false labels in place */
4796       whileTree->trueLabel = trueLabel;
4797       whileTree->falseLabel = falseLabel;
4798     }
4799
4800   return newNode (NULLOP, whileTree, whileBody);
4801 }
4802
4803 /*-----------------------------------------------------------------*/
4804 /* optimizeGetHbit - get highest order bit of the expression       */
4805 /*-----------------------------------------------------------------*/
4806 ast *
4807 optimizeGetHbit (ast * tree)
4808 {
4809   int i, j;
4810   /* if this is not a bit and */
4811   if (!IS_BITAND (tree))
4812     return tree;
4813
4814   /* will look for tree of the form
4815      ( expr >> ((sizeof expr) -1) ) & 1 */
4816   if (!IS_AST_LIT_VALUE (tree->right))
4817     return tree;
4818
4819   if (AST_LIT_VALUE (tree->right) != 1)
4820     return tree;
4821
4822   if (!IS_RIGHT_OP (tree->left))
4823     return tree;
4824
4825   if (!IS_AST_LIT_VALUE (tree->left->right))
4826     return tree;
4827
4828   if ((i = (int) AST_LIT_VALUE (tree->left->right)) !=
4829       (j = (getSize (TTYPE (tree->left->left)) * 8 - 1)))
4830     return tree;
4831       
4832   /* make sure the port supports GETHBIT */
4833   if (port->hasExtBitOp
4834       && !port->hasExtBitOp(GETHBIT, getSize (TTYPE (tree->left->left))))
4835     return tree;
4836
4837   return decorateType (newNode (GETHBIT, tree->left->left, NULL), RESULT_CHECK);
4838
4839 }
4840
4841 /*-----------------------------------------------------------------*/
4842 /* optimizeRRCRLC :- optimize for Rotate Left/Right with carry     */
4843 /*-----------------------------------------------------------------*/
4844 ast *
4845 optimizeRRCRLC (ast * root)
4846 {
4847   /* will look for trees of the form
4848      (?expr << 1) | (?expr >> 7) or
4849      (?expr >> 7) | (?expr << 1) will make that
4850      into a RLC : operation ..
4851      Will also look for
4852      (?expr >> 1) | (?expr << 7) or
4853      (?expr << 7) | (?expr >> 1) will make that
4854      into a RRC operation
4855      note : by 7 I mean (number of bits required to hold the
4856      variable -1 ) */
4857   /* if the root operations is not a | operation the not */
4858   if (!IS_BITOR (root))
4859     return root;
4860
4861   /* I have to think of a better way to match patterns this sucks */
4862   /* that aside let start looking for the first case : I use a the
4863      negative check a lot to improve the efficiency */
4864   /* (?expr << 1) | (?expr >> 7) */
4865   if (IS_LEFT_OP (root->left) &&
4866       IS_RIGHT_OP (root->right))
4867     {
4868
4869       if (!SPEC_USIGN (TETYPE (root->left->left)))
4870         return root;
4871
4872       if (!IS_AST_LIT_VALUE (root->left->right) ||
4873           !IS_AST_LIT_VALUE (root->right->right))
4874         goto tryNext0;
4875
4876       /* make sure it is the same expression */
4877       if (!isAstEqual (root->left->left,
4878                        root->right->left))
4879         goto tryNext0;
4880
4881       if (AST_LIT_VALUE (root->left->right) != 1)
4882         goto tryNext0;
4883
4884       if (AST_LIT_VALUE (root->right->right) !=
4885           (getSize (TTYPE (root->left->left)) * 8 - 1))
4886         goto tryNext0;
4887
4888       /* make sure the port supports RLC */
4889       if (port->hasExtBitOp
4890           && !port->hasExtBitOp(RLC, getSize (TTYPE (root->left->left))))
4891         return root;
4892
4893       /* whew got the first case : create the AST */
4894       return newNode (RLC, root->left->left, NULL);
4895     }
4896
4897 tryNext0:
4898   /* check for second case */
4899   /* (?expr >> 7) | (?expr << 1) */
4900   if (IS_LEFT_OP (root->right) &&
4901       IS_RIGHT_OP (root->left))
4902     {
4903
4904       if (!SPEC_USIGN (TETYPE (root->left->left)))
4905         return root;
4906
4907       if (!IS_AST_LIT_VALUE (root->left->right) ||
4908           !IS_AST_LIT_VALUE (root->right->right))
4909         goto tryNext1;
4910
4911       /* make sure it is the same symbol */
4912       if (!isAstEqual (root->left->left,
4913                        root->right->left))
4914         goto tryNext1;
4915
4916       if (AST_LIT_VALUE (root->right->right) != 1)
4917         goto tryNext1;
4918
4919       if (AST_LIT_VALUE (root->left->right) !=
4920           (getSize (TTYPE (root->left->left)) * 8 - 1))
4921         goto tryNext1;
4922
4923       /* make sure the port supports RLC */
4924       if (port->hasExtBitOp
4925           && !port->hasExtBitOp(RLC, getSize (TTYPE (root->left->left))))
4926         return root;
4927
4928       /* whew got the first case : create the AST */
4929       return newNode (RLC, root->left->left, NULL);
4930
4931     }
4932
4933 tryNext1:
4934   /* third case for RRC */
4935   /*  (?symbol >> 1) | (?symbol << 7) */
4936   if (IS_LEFT_OP (root->right) &&
4937       IS_RIGHT_OP (root->left))
4938     {
4939
4940       if (!SPEC_USIGN (TETYPE (root->left->left)))
4941         return root;
4942
4943       if (!IS_AST_LIT_VALUE (root->left->right) ||
4944           !IS_AST_LIT_VALUE (root->right->right))
4945         goto tryNext2;
4946
4947       /* make sure it is the same symbol */
4948       if (!isAstEqual (root->left->left,
4949                        root->right->left))
4950         goto tryNext2;
4951
4952       if (AST_LIT_VALUE (root->left->right) != 1)
4953         goto tryNext2;
4954
4955       if (AST_LIT_VALUE (root->right->right) !=
4956           (getSize (TTYPE (root->left->left)) * 8 - 1))
4957         goto tryNext2;
4958
4959       /* make sure the port supports RRC */
4960       if (port->hasExtBitOp
4961           && !port->hasExtBitOp(RRC, getSize (TTYPE (root->left->left))))
4962         return root;
4963
4964       /* whew got the first case : create the AST */
4965       return newNode (RRC, root->left->left, NULL);
4966
4967     }
4968 tryNext2:
4969   /* fourth and last case for now */
4970   /* (?symbol << 7) | (?symbol >> 1) */
4971   if (IS_RIGHT_OP (root->right) &&
4972       IS_LEFT_OP (root->left))
4973     {
4974
4975       if (!SPEC_USIGN (TETYPE (root->left->left)))
4976         return root;
4977
4978       if (!IS_AST_LIT_VALUE (root->left->right) ||
4979           !IS_AST_LIT_VALUE (root->right->right))
4980         return root;
4981
4982       /* make sure it is the same symbol */
4983       if (!isAstEqual (root->left->left,
4984                        root->right->left))
4985         return root;
4986
4987       if (AST_LIT_VALUE (root->right->right) != 1)
4988         return root;
4989
4990       if (AST_LIT_VALUE (root->left->right) !=
4991           (getSize (TTYPE (root->left->left)) * 8 - 1))
4992         return root;
4993
4994       /* make sure the port supports RRC */
4995       if (port->hasExtBitOp
4996           && !port->hasExtBitOp(RRC, getSize (TTYPE (root->left->left))))
4997         return root;
4998
4999       /* whew got the first case : create the AST */
5000       return newNode (RRC, root->left->left, NULL);
5001
5002     }
5003
5004   /* not found return root */
5005   return root;
5006 }
5007
5008 /*-----------------------------------------------------------------*/
5009 /* optimizeSWAP :- optimize for nibble/byte/word swaps             */
5010 /*-----------------------------------------------------------------*/
5011 ast *
5012 optimizeSWAP (ast * root)
5013 {
5014   /* will look for trees of the form
5015      (?expr << 4) | (?expr >> 4) or
5016      (?expr >> 4) | (?expr << 4) will make that
5017      into a SWAP : operation ..
5018      note : by 4 I mean (number of bits required to hold the
5019      variable /2 ) */
5020   /* if the root operations is not a | operation the not */
5021   if (!IS_BITOR (root))
5022     return root;
5023
5024   /* (?expr << 4) | (?expr >> 4) */
5025   if ((IS_LEFT_OP (root->left) && IS_RIGHT_OP (root->right))
5026       || (IS_RIGHT_OP (root->left) && IS_LEFT_OP (root->right)))
5027     {
5028
5029       if (!SPEC_USIGN (TETYPE (root->left->left)))
5030         return root;
5031
5032       if (!IS_AST_LIT_VALUE (root->left->right) ||
5033           !IS_AST_LIT_VALUE (root->right->right))
5034         return root;
5035
5036       /* make sure it is the same expression */
5037       if (!isAstEqual (root->left->left,
5038                        root->right->left))
5039         return root;
5040
5041       if (AST_LIT_VALUE (root->left->right) !=
5042           (getSize (TTYPE (root->left->left)) * 4))
5043         return root;
5044
5045       if (AST_LIT_VALUE (root->right->right) !=
5046           (getSize (TTYPE (root->left->left)) * 4))
5047         return root;
5048
5049       /* make sure the port supports SWAP */
5050       if (port->hasExtBitOp
5051           && !port->hasExtBitOp(SWAP, getSize (TTYPE (root->left->left))))
5052         return root;
5053
5054       /* found it : create the AST */
5055       return newNode (SWAP, root->left->left, NULL);
5056     }
5057
5058
5059   /* not found return root */
5060   return root;
5061 }
5062
5063 /*-----------------------------------------------------------------*/
5064 /* optimizeCompare - otimizes compares for bit variables     */
5065 /*-----------------------------------------------------------------*/
5066 static ast *
5067 optimizeCompare (ast * root)
5068 {
5069   ast *optExpr = NULL;
5070   value *vleft;
5071   value *vright;
5072   unsigned int litValue;
5073
5074   /* if nothing then return nothing */
5075   if (!root)
5076     return NULL;
5077
5078   /* if not a compare op then do leaves */
5079   if (!IS_COMPARE_OP (root))
5080     {
5081       root->left = optimizeCompare (root->left);
5082       root->right = optimizeCompare (root->right);
5083       return root;
5084     }
5085
5086   /* if left & right are the same then depending
5087      of the operation do */
5088   if (isAstEqual (root->left, root->right))
5089     {
5090       switch (root->opval.op)
5091         {
5092         case '>':
5093         case '<':
5094         case NE_OP:
5095           optExpr = newAst_VALUE (constVal ("0"));
5096           break;
5097         case GE_OP:
5098         case LE_OP:
5099         case EQ_OP:
5100           optExpr = newAst_VALUE (constVal ("1"));
5101           break;
5102         }
5103
5104       return decorateType (optExpr, RESULT_CHECK);
5105     }
5106
5107   vleft = (root->left->type == EX_VALUE ?
5108            root->left->opval.val : NULL);
5109
5110   vright = (root->right->type == EX_VALUE ?
5111             root->right->opval.val : NULL);
5112
5113   /* if left is a BITVAR in BITSPACE */
5114   /* and right is a LITERAL then opt- */
5115   /* imize else do nothing       */
5116   if (vleft && vright &&
5117       IS_BITVAR (vleft->etype) &&
5118       IN_BITSPACE (SPEC_OCLS (vleft->etype)) &&
5119       IS_LITERAL (vright->etype))
5120     {
5121
5122       /* if right side > 1 then comparison may never succeed */
5123       if ((litValue = (int) floatFromVal (vright)) > 1)
5124         {
5125           werror (W_BAD_COMPARE);
5126           goto noOptimize;
5127         }
5128
5129       if (litValue)
5130         {
5131           switch (root->opval.op)
5132             {
5133             case '>':           /* bit value greater than 1 cannot be */
5134               werror (W_BAD_COMPARE);
5135               goto noOptimize;
5136               break;
5137
5138             case '<':           /* bit value < 1 means 0 */
5139             case NE_OP:
5140               optExpr = newNode ('!', newAst_VALUE (vleft), NULL);
5141               break;
5142
5143             case LE_OP: /* bit value <= 1 means no check */
5144               optExpr = newAst_VALUE (vright);
5145               break;
5146
5147             case GE_OP: /* bit value >= 1 means only check for = */
5148             case EQ_OP:
5149               optExpr = newAst_VALUE (vleft);
5150               break;
5151             }
5152         }
5153       else
5154         {                       /* literal is zero */
5155           switch (root->opval.op)
5156             {
5157             case '<':           /* bit value < 0 cannot be */
5158               werror (W_BAD_COMPARE);
5159               goto noOptimize;
5160               break;
5161
5162             case '>':           /* bit value > 0 means 1 */
5163             case NE_OP:
5164               optExpr = newAst_VALUE (vleft);
5165               break;
5166
5167             case LE_OP: /* bit value <= 0 means no check */
5168             case GE_OP: /* bit value >= 0 means no check */
5169               werror (W_BAD_COMPARE);
5170               goto noOptimize;
5171               break;
5172
5173             case EQ_OP: /* bit == 0 means ! of bit */
5174               optExpr = newNode ('!', newAst_VALUE (vleft), NULL);
5175               break;
5176             }
5177         }
5178       return decorateType (resolveSymbols (optExpr), RESULT_CHECK);
5179     }                           /* end-of-if of BITVAR */
5180
5181 noOptimize:
5182   return root;
5183 }
5184 /*-----------------------------------------------------------------*/
5185 /* addSymToBlock : adds the symbol to the first block we find      */
5186 /*-----------------------------------------------------------------*/
5187 void 
5188 addSymToBlock (symbol * sym, ast * tree)
5189 {
5190   /* reached end of tree or a leaf */
5191   if (!tree || IS_AST_LINK (tree) || IS_AST_VALUE (tree))
5192     return;
5193
5194   /* found a block */
5195   if (IS_AST_OP (tree) &&
5196       tree->opval.op == BLOCK)
5197     {
5198
5199       symbol *lsym = copySymbol (sym);
5200
5201       lsym->next = AST_VALUES (tree, sym);
5202       AST_VALUES (tree, sym) = lsym;
5203       return;
5204     }
5205
5206   addSymToBlock (sym, tree->left);
5207   addSymToBlock (sym, tree->right);
5208 }
5209
5210 /*-----------------------------------------------------------------*/
5211 /* processRegParms - do processing for register parameters         */
5212 /*-----------------------------------------------------------------*/
5213 static void 
5214 processRegParms (value * args, ast * body)
5215 {
5216   while (args)
5217     {
5218       if (IS_REGPARM (args->etype))
5219         addSymToBlock (args->sym, body);
5220       args = args->next;
5221     }
5222 }
5223
5224 /*-----------------------------------------------------------------*/
5225 /* resetParmKey - resets the operandkeys for the symbols           */
5226 /*-----------------------------------------------------------------*/
5227 DEFSETFUNC (resetParmKey)
5228 {
5229   symbol *sym = item;
5230
5231   sym->key = 0;
5232   sym->defs = NULL;
5233   sym->uses = NULL;
5234   sym->remat = 0;
5235   return 1;
5236 }
5237
5238 /*-----------------------------------------------------------------*/
5239 /* createFunction - This is the key node that calls the iCode for  */
5240 /*                  generating the code for a function. Note code  */
5241 /*                  is generated function by function, later when  */
5242 /*                  add inter-procedural analysis this will change */
5243 /*-----------------------------------------------------------------*/
5244 ast *
5245 createFunction (symbol * name, ast * body)
5246 {
5247   ast *ex;
5248   symbol *csym;
5249   int stack = 0;
5250   sym_link *fetype;
5251   iCode *piCode = NULL;
5252
5253   if (getenv("SDCC_DEBUG_FUNCTION_POINTERS"))
5254     fprintf (stderr, "SDCCast.c:createFunction(%s)\n", name->name);
5255
5256   /* if check function return 0 then some problem */
5257   if (checkFunction (name, NULL) == 0)
5258     return NULL;
5259
5260   /* create a dummy block if none exists */
5261   if (!body)
5262     body = newNode (BLOCK, NULL, NULL);
5263
5264   noLineno++;
5265
5266   /* check if the function name already in the symbol table */
5267   if ((csym = findSym (SymbolTab, NULL, name->name)))
5268     {
5269       name = csym;
5270       /* special case for compiler defined functions
5271          we need to add the name to the publics list : this
5272          actually means we are now compiling the compiler
5273          support routine */
5274       if (name->cdef)
5275         {
5276           addSet (&publics, name);
5277         }
5278     }
5279   else
5280     {
5281       addSymChain (name);
5282       allocVariables (name);
5283     }
5284   name->lastLine = mylineno;
5285   currFunc = name;
5286
5287   /* set the stack pointer */
5288   /* PENDING: check this for the mcs51 */
5289   stackPtr = -port->stack.direction * port->stack.call_overhead;
5290   if (IFFUNC_ISISR (name->type))
5291     stackPtr -= port->stack.direction * port->stack.isr_overhead;
5292   if (IFFUNC_ISREENT (name->type) || options.stackAuto)
5293     stackPtr -= port->stack.direction * port->stack.reent_overhead;
5294
5295   xstackPtr = -port->stack.direction * port->stack.call_overhead;
5296
5297   fetype = getSpec (name->type);        /* get the specifier for the function */
5298   /* if this is a reentrant function then */
5299   if (IFFUNC_ISREENT (name->type))
5300     reentrant++;
5301
5302   allocParms (FUNC_ARGS(name->type));   /* allocate the parameters */
5303
5304   /* do processing for parameters that are passed in registers */
5305   processRegParms (FUNC_ARGS(name->type), body);
5306
5307   /* set the stack pointer */
5308   stackPtr = 0;
5309   xstackPtr = -1;
5310
5311   /* allocate & autoinit the block variables */
5312   processBlockVars (body, &stack, ALLOCATE);
5313
5314   /* save the stack information */
5315   if (options.useXstack)
5316     name->xstack = SPEC_STAK (fetype) = stack;
5317   else
5318     name->stack = SPEC_STAK (fetype) = stack;
5319
5320   /* name needs to be mangled */
5321   SNPRINTF (name->rname, sizeof(name->rname), "%s%s", port->fun_prefix, name->name);
5322
5323   body = resolveSymbols (body); /* resolve the symbols */
5324   body = decorateType (body, RESULT_TYPE_NONE); /* propagateType & do semantic checks */
5325                                         
5326
5327   ex = newAst_VALUE (symbolVal (name)); /* create name */
5328   ex = newNode (FUNCTION, ex, body);
5329   ex->values.args = FUNC_ARGS(name->type);
5330   ex->decorated=1;
5331   if (options.dump_tree) PA(ex);
5332   if (fatalError)
5333     {
5334       werror (E_FUNC_NO_CODE, name->name);
5335       goto skipall;
5336     }
5337
5338   /* create the node & generate intermediate code */
5339   GcurMemmap = code;
5340   codeOutFile = code->oFile;
5341   piCode = iCodeFromAst (ex);
5342
5343   if (fatalError)
5344     {
5345       werror (E_FUNC_NO_CODE, name->name);
5346       goto skipall;
5347     }
5348
5349   eBBlockFromiCode (piCode);
5350
5351   /* if there are any statics then do them */
5352   if (staticAutos)
5353     {
5354       GcurMemmap = statsg;
5355       codeOutFile = statsg->oFile;
5356       eBBlockFromiCode (iCodeFromAst (decorateType (resolveSymbols (staticAutos), RESULT_CHECK)));
5357       staticAutos = NULL;
5358     }
5359
5360 skipall:
5361
5362   /* dealloc the block variables */
5363   processBlockVars (body, &stack, DEALLOCATE);
5364   outputDebugStackSymbols();
5365   /* deallocate paramaters */
5366   deallocParms (FUNC_ARGS(name->type));
5367
5368   if (IFFUNC_ISREENT (name->type))
5369     reentrant--;
5370
5371   /* we are done freeup memory & cleanup */
5372   noLineno--;
5373   if (port->reset_labelKey) labelKey = 1;
5374   name->key = 0;
5375   FUNC_HASBODY(name->type) = 1;
5376   addSet (&operKeyReset, name);
5377   applyToSet (operKeyReset, resetParmKey);
5378
5379   if (options.debug)
5380     cdbStructBlock(1);
5381
5382   cleanUpLevel (LabelTab, 0);
5383   cleanUpBlock (StructTab, 1);
5384   cleanUpBlock (TypedefTab, 1);
5385
5386   xstack->syms = NULL;
5387   istack->syms = NULL;
5388   return NULL;
5389 }
5390
5391
5392 #define INDENT(x,f) { int i ; fprintf (f, "%d:", tree->lineno); for (i=0;i < x; i++) fprintf(f," "); }
5393 /*-----------------------------------------------------------------*/
5394 /* ast_print : prints the ast (for debugging purposes)             */
5395 /*-----------------------------------------------------------------*/
5396
5397 void ast_print (ast * tree, FILE *outfile, int indent)
5398 {
5399
5400         if (!tree) return ;
5401
5402         /* can print only decorated trees */
5403         if (!tree->decorated) return;
5404
5405         /* if any child is an error | this one is an error do nothing */
5406         if (tree->isError ||
5407             (tree->left && tree->left->isError) ||
5408             (tree->right && tree->right->isError)) {
5409                 fprintf(outfile,"ERROR_NODE(%p)\n",tree);
5410         }
5411
5412
5413         /* print the line          */
5414         /* if not block & function */
5415         if (tree->type == EX_OP &&
5416             (tree->opval.op != FUNCTION &&
5417              tree->opval.op != BLOCK &&
5418              tree->opval.op != NULLOP)) {
5419         }
5420
5421         if (tree->opval.op == FUNCTION) {
5422                 int arg=0;
5423                 value *args=FUNC_ARGS(tree->left->opval.val->type);
5424                 fprintf(outfile,"FUNCTION (%s=%p) type (",
5425                         tree->left->opval.val->name, tree);
5426                 printTypeChain (tree->left->opval.val->type->next,outfile);
5427                 fprintf(outfile,") args (");
5428                 do {
5429                   if (arg) {
5430                     fprintf (outfile, ", ");
5431                   }
5432                   printTypeChain (args ? args->type : NULL, outfile);
5433                   arg++;
5434                   args= args ? args->next : NULL;
5435                 } while (args);
5436                 fprintf(outfile,")\n");
5437                 ast_print(tree->left,outfile,indent);
5438                 ast_print(tree->right,outfile,indent);
5439                 return ;
5440         }
5441         if (tree->opval.op == BLOCK) {
5442                 symbol *decls = tree->values.sym;
5443                 INDENT(indent,outfile);
5444                 fprintf(outfile,"{\n");
5445                 while (decls) {
5446                         INDENT(indent+2,outfile);
5447                         fprintf(outfile,"DECLARE SYMBOL (%s=%p) type (",
5448                                 decls->name, decls);
5449                         printTypeChain(decls->type,outfile);
5450                         fprintf(outfile,")\n");
5451
5452                         decls = decls->next;
5453                 }
5454                 ast_print(tree->right,outfile,indent+2);
5455                 INDENT(indent,outfile);
5456                 fprintf(outfile,"}\n");
5457                 return;
5458         }
5459         if (tree->opval.op == NULLOP) {
5460                 ast_print(tree->left,outfile,indent);
5461                 ast_print(tree->right,outfile,indent);
5462                 return ;
5463         }
5464         INDENT(indent,outfile);
5465
5466         /*------------------------------------------------------------------*/
5467         /*----------------------------*/
5468         /*   leaf has been reached    */
5469         /*----------------------------*/
5470         /* if this is of type value */
5471         /* just get the type        */
5472         if (tree->type == EX_VALUE) {
5473
5474                 if (IS_LITERAL (tree->opval.val->etype)) {
5475                         fprintf(outfile,"CONSTANT (%p) value = ", tree);
5476                         if (SPEC_USIGN (tree->opval.val->etype))
5477                                 fprintf(outfile,"%u", (TYPE_UDWORD) floatFromVal(tree->opval.val));
5478                         else
5479                                 fprintf(outfile,"%d", (TYPE_DWORD) floatFromVal(tree->opval.val));
5480                         fprintf(outfile,", 0x%x, %f", (TYPE_UDWORD) floatFromVal(tree->opval.val),
5481                                                       floatFromVal(tree->opval.val));
5482                 } else if (tree->opval.val->sym) {
5483                         /* if the undefined flag is set then give error message */
5484                         if (tree->opval.val->sym->undefined) {
5485                                 fprintf(outfile,"UNDEFINED SYMBOL ");
5486                         } else {
5487                                 fprintf(outfile,"SYMBOL ");
5488                         }
5489                         fprintf(outfile,"(%s=%p)",
5490                                 tree->opval.val->sym->name,tree);
5491                 }
5492                 if (tree->ftype) {
5493                         fprintf(outfile," type (");
5494                         printTypeChain(tree->ftype,outfile);
5495                         fprintf(outfile,")\n");
5496                 } else {
5497                         fprintf(outfile,"\n");
5498                 }
5499                 return ;
5500         }
5501
5502         /* if type link for the case of cast */
5503         if (tree->type == EX_LINK) {
5504                 fprintf(outfile,"TYPENODE (%p) type = (",tree);
5505                 printTypeChain(tree->opval.lnk,outfile);
5506                 fprintf(outfile,")\n");
5507                 return ;
5508         }
5509
5510
5511         /* depending on type of operator do */
5512
5513         switch (tree->opval.op) {
5514                 /*------------------------------------------------------------------*/
5515                 /*----------------------------*/
5516                 /*        array node          */
5517                 /*----------------------------*/
5518         case '[':
5519                 fprintf(outfile,"ARRAY_OP (%p) type (",tree);
5520                 printTypeChain(tree->ftype,outfile);
5521                 fprintf(outfile,")\n");
5522                 ast_print(tree->left,outfile,indent+2);
5523                 ast_print(tree->right,outfile,indent+2);
5524                 return;
5525
5526                 /*------------------------------------------------------------------*/
5527                 /*----------------------------*/
5528                 /*      struct/union          */
5529                 /*----------------------------*/
5530         case '.':
5531                 fprintf(outfile,"STRUCT_ACCESS (%p) type (",tree);
5532                 printTypeChain(tree->ftype,outfile);
5533                 fprintf(outfile,")\n");
5534                 ast_print(tree->left,outfile,indent+2);
5535                 ast_print(tree->right,outfile,indent+2);
5536                 return ;
5537
5538                 /*------------------------------------------------------------------*/
5539                 /*----------------------------*/
5540                 /*    struct/union pointer    */
5541                 /*----------------------------*/
5542         case PTR_OP:
5543                 fprintf(outfile,"PTR_ACCESS (%p) type (",tree);
5544                 printTypeChain(tree->ftype,outfile);
5545                 fprintf(outfile,")\n");
5546                 ast_print(tree->left,outfile,indent+2);
5547                 ast_print(tree->right,outfile,indent+2);
5548                 return ;
5549
5550                 /*------------------------------------------------------------------*/
5551                 /*----------------------------*/
5552                 /*  ++/-- operation           */
5553                 /*----------------------------*/
5554         case INC_OP:
5555                 if (tree->left)
5556                   fprintf(outfile,"post-");
5557                 else
5558                   fprintf(outfile,"pre-");
5559                 fprintf(outfile,"INC_OP (%p) type (",tree);
5560                 printTypeChain(tree->ftype,outfile);
5561                 fprintf(outfile,")\n");
5562                 ast_print(tree->left,outfile,indent+2); /* postincrement case */
5563                 ast_print(tree->right,outfile,indent+2); /* preincrement case */
5564                 return ;
5565
5566         case DEC_OP:
5567                 if (tree->left)
5568                   fprintf(outfile,"post-");
5569                 else
5570                   fprintf(outfile,"pre-");
5571                 fprintf(outfile,"DEC_OP (%p) type (",tree);
5572                 printTypeChain(tree->ftype,outfile);
5573                 fprintf(outfile,")\n");
5574                 ast_print(tree->left,outfile,indent+2); /* postdecrement case */
5575                 ast_print(tree->right,outfile,indent+2); /* predecrement case */
5576                 return ;
5577
5578                 /*------------------------------------------------------------------*/
5579                 /*----------------------------*/
5580                 /*  bitwise and               */
5581                 /*----------------------------*/
5582         case '&':
5583                 if (tree->right) {
5584                         fprintf(outfile,"& (%p) type (",tree);
5585                         printTypeChain(tree->ftype,outfile);
5586                         fprintf(outfile,")\n");
5587                         ast_print(tree->left,outfile,indent+2);
5588                         ast_print(tree->right,outfile,indent+2);
5589                 } else {
5590                         fprintf(outfile,"ADDRESS_OF (%p) type (",tree);
5591                         printTypeChain(tree->ftype,outfile);
5592                         fprintf(outfile,")\n");
5593                         ast_print(tree->left,outfile,indent+2);
5594                         ast_print(tree->right,outfile,indent+2);
5595                 }
5596                 return ;
5597                 /*----------------------------*/
5598                 /*  bitwise or                */
5599                 /*----------------------------*/
5600         case '|':
5601                 fprintf(outfile,"OR (%p) type (",tree);
5602                 printTypeChain(tree->ftype,outfile);
5603                 fprintf(outfile,")\n");
5604                 ast_print(tree->left,outfile,indent+2);
5605                 ast_print(tree->right,outfile,indent+2);
5606                 return ;
5607                 /*------------------------------------------------------------------*/
5608                 /*----------------------------*/
5609                 /*  bitwise xor               */
5610                 /*----------------------------*/
5611         case '^':
5612                 fprintf(outfile,"XOR (%p) type (",tree);
5613                 printTypeChain(tree->ftype,outfile);
5614                 fprintf(outfile,")\n");
5615                 ast_print(tree->left,outfile,indent+2);
5616                 ast_print(tree->right,outfile,indent+2);
5617                 return ;
5618
5619                 /*------------------------------------------------------------------*/
5620                 /*----------------------------*/
5621                 /*  division                  */
5622                 /*----------------------------*/
5623         case '/':
5624                 fprintf(outfile,"DIV (%p) type (",tree);
5625                 printTypeChain(tree->ftype,outfile);
5626                 fprintf(outfile,")\n");
5627                 ast_print(tree->left,outfile,indent+2);
5628                 ast_print(tree->right,outfile,indent+2);
5629                 return ;
5630                 /*------------------------------------------------------------------*/
5631                 /*----------------------------*/
5632                 /*            modulus         */
5633                 /*----------------------------*/
5634         case '%':
5635                 fprintf(outfile,"MOD (%p) type (",tree);
5636                 printTypeChain(tree->ftype,outfile);
5637                 fprintf(outfile,")\n");
5638                 ast_print(tree->left,outfile,indent+2);
5639                 ast_print(tree->right,outfile,indent+2);
5640                 return ;
5641
5642                 /*------------------------------------------------------------------*/
5643                 /*----------------------------*/
5644                 /*  address dereference       */
5645                 /*----------------------------*/
5646         case '*':                       /* can be unary  : if right is null then unary operation */
5647                 if (!tree->right) {
5648                         fprintf(outfile,"DEREF (%p) type (",tree);
5649                         printTypeChain(tree->ftype,outfile);
5650                         fprintf(outfile,")\n");
5651                         ast_print(tree->left,outfile,indent+2);
5652                         return ;
5653                 }                       
5654                 /*------------------------------------------------------------------*/
5655                 /*----------------------------*/
5656                 /*      multiplication        */
5657                 /*----------------------------*/                
5658                 fprintf(outfile,"MULT (%p) type (",tree);
5659                 printTypeChain(tree->ftype,outfile);
5660                 fprintf(outfile,")\n");
5661                 ast_print(tree->left,outfile,indent+2);
5662                 ast_print(tree->right,outfile,indent+2);
5663                 return ;
5664
5665
5666                 /*------------------------------------------------------------------*/
5667                 /*----------------------------*/
5668                 /*    unary '+' operator      */
5669                 /*----------------------------*/
5670         case '+':
5671                 /* if unary plus */
5672                 if (!tree->right) {
5673                         fprintf(outfile,"UPLUS (%p) type (",tree);
5674                         printTypeChain(tree->ftype,outfile);
5675                         fprintf(outfile,")\n");
5676                         ast_print(tree->left,outfile,indent+2);
5677                 } else {
5678                         /*------------------------------------------------------------------*/
5679                         /*----------------------------*/
5680                         /*      addition              */
5681                         /*----------------------------*/
5682                         fprintf(outfile,"ADD (%p) type (",tree);
5683                         printTypeChain(tree->ftype,outfile);
5684                         fprintf(outfile,")\n");
5685                         ast_print(tree->left,outfile,indent+2);
5686                         ast_print(tree->right,outfile,indent+2);
5687                 }
5688                 return;
5689                 /*------------------------------------------------------------------*/
5690                 /*----------------------------*/
5691                 /*      unary '-'             */
5692                 /*----------------------------*/
5693         case '-':                       /* can be unary   */
5694                 if (!tree->right) {
5695                         fprintf(outfile,"UMINUS (%p) type (",tree);
5696                         printTypeChain(tree->ftype,outfile);
5697                         fprintf(outfile,")\n");
5698                         ast_print(tree->left,outfile,indent+2);
5699                 } else {
5700                         /*------------------------------------------------------------------*/
5701                         /*----------------------------*/
5702                         /*      subtraction           */
5703                         /*----------------------------*/
5704                         fprintf(outfile,"SUB (%p) type (",tree);
5705                         printTypeChain(tree->ftype,outfile);
5706                         fprintf(outfile,")\n");
5707                         ast_print(tree->left,outfile,indent+2);
5708                         ast_print(tree->right,outfile,indent+2);
5709                 }
5710                 return;
5711                 /*------------------------------------------------------------------*/
5712                 /*----------------------------*/
5713                 /*    compliment              */
5714                 /*----------------------------*/
5715         case '~':
5716                 fprintf(outfile,"COMPL (%p) type (",tree);
5717                 printTypeChain(tree->ftype,outfile);
5718                 fprintf(outfile,")\n");
5719                 ast_print(tree->left,outfile,indent+2);
5720                 return ;
5721                 /*------------------------------------------------------------------*/
5722                 /*----------------------------*/
5723                 /*           not              */
5724                 /*----------------------------*/
5725         case '!':
5726                 fprintf(outfile,"NOT (%p) type (",tree);
5727                 printTypeChain(tree->ftype,outfile);
5728                 fprintf(outfile,")\n");
5729                 ast_print(tree->left,outfile,indent+2);
5730                 return ;
5731                 /*------------------------------------------------------------------*/
5732                 /*----------------------------*/
5733                 /*           shift            */
5734                 /*----------------------------*/
5735         case RRC:
5736                 fprintf(outfile,"RRC (%p) type (",tree);
5737                 printTypeChain(tree->ftype,outfile);
5738                 fprintf(outfile,")\n");
5739                 ast_print(tree->left,outfile,indent+2);
5740                 return ;
5741
5742         case RLC:
5743                 fprintf(outfile,"RLC (%p) type (",tree);
5744                 printTypeChain(tree->ftype,outfile);
5745                 fprintf(outfile,")\n");
5746                 ast_print(tree->left,outfile,indent+2);
5747                 return ;
5748         case SWAP:
5749                 fprintf(outfile,"SWAP (%p) type (",tree);
5750                 printTypeChain(tree->ftype,outfile);
5751                 fprintf(outfile,")\n");
5752                 ast_print(tree->left,outfile,indent+2);
5753                 return ;
5754         case GETHBIT:
5755                 fprintf(outfile,"GETHBIT (%p) type (",tree);
5756                 printTypeChain(tree->ftype,outfile);
5757                 fprintf(outfile,")\n");
5758                 ast_print(tree->left,outfile,indent+2);
5759                 return ;
5760         case LEFT_OP:
5761                 fprintf(outfile,"LEFT_SHIFT (%p) type (",tree);
5762                 printTypeChain(tree->ftype,outfile);
5763                 fprintf(outfile,")\n");
5764                 ast_print(tree->left,outfile,indent+2);
5765                 ast_print(tree->right,outfile,indent+2);
5766                 return ;
5767         case RIGHT_OP:
5768                 fprintf(outfile,"RIGHT_SHIFT (%p) type (",tree);
5769                 printTypeChain(tree->ftype,outfile);
5770                 fprintf(outfile,")\n");
5771                 ast_print(tree->left,outfile,indent+2);
5772                 ast_print(tree->right,outfile,indent+2);
5773                 return ;
5774                 /*------------------------------------------------------------------*/
5775                 /*----------------------------*/
5776                 /*         casting            */
5777                 /*----------------------------*/
5778         case CAST:                      /* change the type   */
5779                 fprintf(outfile,"CAST (%p) from type (",tree);
5780                 printTypeChain(tree->right->ftype,outfile);
5781                 fprintf(outfile,") to type (");
5782                 printTypeChain(tree->ftype,outfile);
5783                 fprintf(outfile,")\n");
5784                 ast_print(tree->right,outfile,indent+2);
5785                 return ;
5786                 
5787         case AND_OP:
5788                 fprintf(outfile,"ANDAND (%p) type (",tree);
5789                 printTypeChain(tree->ftype,outfile);
5790                 fprintf(outfile,")\n");
5791                 ast_print(tree->left,outfile,indent+2);
5792                 ast_print(tree->right,outfile,indent+2);
5793                 return ;
5794         case OR_OP:
5795                 fprintf(outfile,"OROR (%p) type (",tree);
5796                 printTypeChain(tree->ftype,outfile);
5797                 fprintf(outfile,")\n");
5798                 ast_print(tree->left,outfile,indent+2);
5799                 ast_print(tree->right,outfile,indent+2);
5800                 return ;
5801                 
5802                 /*------------------------------------------------------------------*/
5803                 /*----------------------------*/
5804                 /*     comparison operators   */
5805                 /*----------------------------*/
5806         case '>':
5807                 fprintf(outfile,"GT(>) (%p) type (",tree);
5808                 printTypeChain(tree->ftype,outfile);
5809                 fprintf(outfile,")\n");
5810                 ast_print(tree->left,outfile,indent+2);
5811                 ast_print(tree->right,outfile,indent+2);
5812                 return ;
5813         case '<':
5814                 fprintf(outfile,"LT(<) (%p) type (",tree);
5815                 printTypeChain(tree->ftype,outfile);
5816                 fprintf(outfile,")\n");
5817                 ast_print(tree->left,outfile,indent+2);
5818                 ast_print(tree->right,outfile,indent+2);
5819                 return ;
5820         case LE_OP:
5821                 fprintf(outfile,"LE(<=) (%p) type (",tree);
5822                 printTypeChain(tree->ftype,outfile);
5823                 fprintf(outfile,")\n");
5824                 ast_print(tree->left,outfile,indent+2);
5825                 ast_print(tree->right,outfile,indent+2);
5826                 return ;
5827         case GE_OP:
5828                 fprintf(outfile,"GE(>=) (%p) type (",tree);
5829                 printTypeChain(tree->ftype,outfile);
5830                 fprintf(outfile,")\n");
5831                 ast_print(tree->left,outfile,indent+2);
5832                 ast_print(tree->right,outfile,indent+2);
5833                 return ;
5834         case EQ_OP:
5835                 fprintf(outfile,"EQ(==) (%p) type (",tree);
5836                 printTypeChain(tree->ftype,outfile);
5837                 fprintf(outfile,")\n");
5838                 ast_print(tree->left,outfile,indent+2);
5839                 ast_print(tree->right,outfile,indent+2);
5840                 return ;
5841         case NE_OP:
5842                 fprintf(outfile,"NE(!=) (%p) type (",tree);
5843                 printTypeChain(tree->ftype,outfile);
5844                 fprintf(outfile,")\n");
5845                 ast_print(tree->left,outfile,indent+2);
5846                 ast_print(tree->right,outfile,indent+2);
5847                 /*------------------------------------------------------------------*/
5848                 /*----------------------------*/
5849                 /*             sizeof         */
5850                 /*----------------------------*/
5851         case SIZEOF:            /* evaluate wihout code generation */
5852                 fprintf(outfile,"SIZEOF %d\n",(getSize (tree->right->ftype)));
5853                 return ;
5854
5855                 /*------------------------------------------------------------------*/
5856                 /*----------------------------*/
5857                 /* conditional operator  '?'  */
5858                 /*----------------------------*/
5859         case '?':
5860                 fprintf(outfile,"QUEST(?) (%p) type (",tree);
5861                 printTypeChain(tree->ftype,outfile);
5862                 fprintf(outfile,")\n");
5863                 ast_print(tree->left,outfile,indent+2);
5864                 ast_print(tree->right,outfile,indent+2);
5865                 return;
5866
5867         case ':':
5868                 fprintf(outfile,"COLON(:) (%p) type (",tree);
5869                 printTypeChain(tree->ftype,outfile);
5870                 fprintf(outfile,")\n");
5871                 ast_print(tree->left,outfile,indent+2);
5872                 ast_print(tree->right,outfile,indent+2);
5873                 return ;
5874
5875                 /*------------------------------------------------------------------*/
5876                 /*----------------------------*/
5877                 /*    assignment operators    */
5878                 /*----------------------------*/
5879         case MUL_ASSIGN:
5880                 fprintf(outfile,"MULASS(*=) (%p) type (",tree);
5881                 printTypeChain(tree->ftype,outfile);
5882                 fprintf(outfile,")\n");
5883                 ast_print(tree->left,outfile,indent+2);
5884                 ast_print(tree->right,outfile,indent+2);
5885                 return;
5886         case DIV_ASSIGN:
5887                 fprintf(outfile,"DIVASS(/=) (%p) type (",tree);
5888                 printTypeChain(tree->ftype,outfile);
5889                 fprintf(outfile,")\n");
5890                 ast_print(tree->left,outfile,indent+2);
5891                 ast_print(tree->right,outfile,indent+2);
5892                 return;
5893         case AND_ASSIGN:
5894                 fprintf(outfile,"ANDASS(&=) (%p) type (",tree);
5895                 printTypeChain(tree->ftype,outfile);
5896                 fprintf(outfile,")\n");
5897                 ast_print(tree->left,outfile,indent+2);
5898                 ast_print(tree->right,outfile,indent+2);
5899                 return;
5900         case OR_ASSIGN:
5901                 fprintf(outfile,"ORASS(|=) (%p) type (",tree);
5902                 printTypeChain(tree->ftype,outfile);
5903                 fprintf(outfile,")\n");
5904                 ast_print(tree->left,outfile,indent+2);
5905                 ast_print(tree->right,outfile,indent+2);
5906                 return;
5907         case XOR_ASSIGN:
5908                 fprintf(outfile,"XORASS(^=) (%p) type (",tree);
5909                 printTypeChain(tree->ftype,outfile);
5910                 fprintf(outfile,")\n");
5911                 ast_print(tree->left,outfile,indent+2);
5912                 ast_print(tree->right,outfile,indent+2);
5913                 return;
5914         case RIGHT_ASSIGN:
5915                 fprintf(outfile,"RSHFTASS(>>=) (%p) type (",tree);
5916                 printTypeChain(tree->ftype,outfile);
5917                 fprintf(outfile,")\n");
5918                 ast_print(tree->left,outfile,indent+2);
5919                 ast_print(tree->right,outfile,indent+2);
5920                 return;
5921         case LEFT_ASSIGN:
5922                 fprintf(outfile,"LSHFTASS(<<=) (%p) type (",tree);
5923                 printTypeChain(tree->ftype,outfile);
5924                 fprintf(outfile,")\n");
5925                 ast_print(tree->left,outfile,indent+2);
5926                 ast_print(tree->right,outfile,indent+2);
5927                 return;
5928                 /*------------------------------------------------------------------*/
5929                 /*----------------------------*/
5930                 /*    -= operator             */
5931                 /*----------------------------*/
5932         case SUB_ASSIGN:
5933                 fprintf(outfile,"SUBASS(-=) (%p) type (",tree);
5934                 printTypeChain(tree->ftype,outfile);
5935                 fprintf(outfile,")\n");
5936                 ast_print(tree->left,outfile,indent+2);
5937                 ast_print(tree->right,outfile,indent+2);
5938                 return;
5939                 /*------------------------------------------------------------------*/
5940                 /*----------------------------*/
5941                 /*          += operator       */
5942                 /*----------------------------*/
5943         case ADD_ASSIGN:
5944                 fprintf(outfile,"ADDASS(+=) (%p) type (",tree);
5945                 printTypeChain(tree->ftype,outfile);
5946                 fprintf(outfile,")\n");
5947                 ast_print(tree->left,outfile,indent+2);
5948                 ast_print(tree->right,outfile,indent+2);
5949                 return;
5950                 /*------------------------------------------------------------------*/
5951                 /*----------------------------*/
5952                 /*      straight assignemnt   */
5953                 /*----------------------------*/
5954         case '=':
5955                 fprintf(outfile,"ASSIGN(=) (%p) type (",tree);
5956                 printTypeChain(tree->ftype,outfile);
5957                 fprintf(outfile,")\n");
5958                 ast_print(tree->left,outfile,indent+2);
5959                 ast_print(tree->right,outfile,indent+2);
5960                 return;     
5961                 /*------------------------------------------------------------------*/
5962                 /*----------------------------*/
5963                 /*      comma operator        */
5964                 /*----------------------------*/
5965         case ',':
5966                 fprintf(outfile,"COMMA(,) (%p) type (",tree);
5967                 printTypeChain(tree->ftype,outfile);
5968                 fprintf(outfile,")\n");
5969                 ast_print(tree->left,outfile,indent+2);
5970                 ast_print(tree->right,outfile,indent+2);
5971                 return;
5972                 /*------------------------------------------------------------------*/
5973                 /*----------------------------*/
5974                 /*       function call        */
5975                 /*----------------------------*/
5976         case CALL:
5977         case PCALL:
5978                 fprintf(outfile,"CALL (%p) type (",tree);
5979                 printTypeChain(tree->ftype,outfile);
5980                 fprintf(outfile,")\n");
5981                 ast_print(tree->left,outfile,indent+2);
5982                 ast_print(tree->right,outfile,indent+2);
5983                 return;
5984         case PARAM:
5985                 fprintf(outfile,"PARMS\n");
5986                 ast_print(tree->left,outfile,indent+2);
5987                 if (tree->right /*&& !IS_AST_PARAM(tree->right)*/) {
5988                         ast_print(tree->right,outfile,indent+2);
5989                 }
5990                 return ;
5991                 /*------------------------------------------------------------------*/
5992                 /*----------------------------*/
5993                 /*     return statement       */
5994                 /*----------------------------*/
5995         case RETURN:
5996                 fprintf(outfile,"RETURN (%p) type (",tree);
5997                 if (tree->right) {
5998                     printTypeChain(tree->right->ftype,outfile);
5999                 }
6000                 fprintf(outfile,")\n");
6001                 ast_print(tree->right,outfile,indent+2);
6002                 return ;
6003                 /*------------------------------------------------------------------*/
6004                 /*----------------------------*/
6005                 /*     label statement        */
6006                 /*----------------------------*/
6007         case LABEL :
6008                 fprintf(outfile,"LABEL (%p)\n",tree);
6009                 ast_print(tree->left,outfile,indent+2);
6010                 ast_print(tree->right,outfile,indent);
6011                 return;
6012                 /*------------------------------------------------------------------*/
6013                 /*----------------------------*/
6014                 /*     switch statement       */
6015                 /*----------------------------*/
6016         case SWITCH:
6017                 {
6018                         value *val;
6019                         fprintf(outfile,"SWITCH (%p) ",tree);
6020                         ast_print(tree->left,outfile,0);
6021                         for (val = tree->values.switchVals.swVals; val ; val = val->next) {
6022                                 INDENT(indent+2,outfile);
6023                                 fprintf(outfile,"CASE 0x%x GOTO _case_%d_%d\n",
6024                                         (int) floatFromVal(val),
6025                                         tree->values.switchVals.swNum,
6026                                         (int) floatFromVal(val));
6027                         }
6028                         ast_print(tree->right,outfile,indent);
6029                 }
6030                 return ;
6031                 /*------------------------------------------------------------------*/
6032                 /*----------------------------*/
6033                 /* ifx Statement              */
6034                 /*----------------------------*/
6035         case IFX:
6036                 fprintf(outfile,"IF (%p) \n",tree);
6037                 ast_print(tree->left,outfile,indent+2);
6038                 if (tree->trueLabel) {
6039                         INDENT(indent+2,outfile);
6040                         fprintf(outfile,"NE(!=) 0 goto %s\n",tree->trueLabel->name);
6041                 }
6042                 if (tree->falseLabel) {
6043                         INDENT(indent+2,outfile);
6044                         fprintf(outfile,"EQ(==) 0 goto %s\n",tree->falseLabel->name);
6045                 }
6046                 ast_print(tree->right,outfile,indent+2);
6047                 return ;
6048                 /*----------------------------*/
6049                 /* goto Statement              */
6050                 /*----------------------------*/
6051         case GOTO:
6052                 fprintf(outfile,"GOTO (%p) \n",tree);
6053                 ast_print(tree->left,outfile,indent+2);
6054                 fprintf(outfile,"\n");
6055                 return ;
6056                 /*------------------------------------------------------------------*/
6057                 /*----------------------------*/
6058                 /* for Statement              */
6059                 /*----------------------------*/
6060         case FOR:
6061                 fprintf(outfile,"FOR (%p) \n",tree);
6062                 if (AST_FOR( tree, initExpr)) {
6063                         INDENT(indent+2,outfile);
6064                         fprintf(outfile,"INIT EXPR ");
6065                         ast_print(AST_FOR(tree, initExpr),outfile,indent+2);
6066                 }
6067                 if (AST_FOR( tree, condExpr)) {
6068                         INDENT(indent+2,outfile);
6069                         fprintf(outfile,"COND EXPR ");
6070                         ast_print(AST_FOR(tree, condExpr),outfile,indent+2);
6071                 }
6072                 if (AST_FOR( tree, loopExpr)) {
6073                         INDENT(indent+2,outfile);
6074                         fprintf(outfile,"LOOP EXPR ");
6075                         ast_print(AST_FOR(tree, loopExpr),outfile,indent+2);
6076                 }
6077                 fprintf(outfile,"FOR LOOP BODY \n");
6078                 ast_print(tree->left,outfile,indent+2);
6079                 return ;
6080         case CRITICAL:
6081                 fprintf(outfile,"CRITICAL (%p) \n",tree);
6082                 ast_print(tree->left,outfile,indent+2);
6083         default:
6084             return ;
6085         }
6086 }
6087
6088 void PA(ast *t)
6089 {
6090         ast_print(t,stdout,0);
6091 }
6092
6093
6094
6095 /*-----------------------------------------------------------------*/
6096 /* astErrors : returns non-zero if errors present in tree          */
6097 /*-----------------------------------------------------------------*/
6098 int astErrors(ast *t)
6099 {
6100   int errors=0;
6101   
6102   if (t)
6103     {
6104       if (t->isError)
6105         errors++;
6106   
6107       if (t->type == EX_VALUE
6108           && t->opval.val->sym
6109           && t->opval.val->sym->undefined)
6110         errors++;
6111
6112       errors += astErrors(t->left);
6113       errors += astErrors(t->right);
6114     }
6115     
6116   return errors;
6117 }