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