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