* src/SDCCast.c (processParms): fixed bug #920866; decorateType() can return an optim...
[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           return tree;
2066         newLink = newCharLink();
2067         break;
2068       case RESULT_TYPE_INT:
2069 #if 0
2070         if (getSize (tree->etype) > INTSIZE)
2071           {
2072             /* warn ("Loosing significant digits"); */
2073             return;
2074           }
2075 #endif
2076         /* char: promote to int */
2077         if (!upcast ||
2078             getSize (tree->etype) >= INTSIZE)
2079           return tree;
2080         newLink = newIntLink();
2081         upCasted = TRUE;
2082         break;
2083       case RESULT_TYPE_OTHER:
2084         if (!upcast)
2085           return tree;
2086         /* return type is long, float: promote char to int */
2087         if (getSize (tree->etype) >= INTSIZE)
2088           return tree;
2089         newLink = newIntLink();
2090         upCasted = TRUE;
2091         break;
2092       default:
2093         return tree;
2094     }
2095   tree->decorated = 0;
2096   tree = newNode (CAST, newAst_LINK (newLink), tree);
2097   tree->lineno = tree->right->lineno;
2098   /* keep unsigned type during cast to smaller type,
2099      but not when promoting from char to int */
2100   if (!upCasted)
2101     SPEC_USIGN (tree->left->opval.lnk) = IS_UNSIGNED (tree->right->etype) ? 1 : 0;
2102   return decorateType (tree, resultType);
2103 }
2104
2105 /*-----------------------------------------------------------------*/
2106 /* resultTypePropagate - decides if resultType can be propagated   */
2107 /*-----------------------------------------------------------------*/
2108 static RESULT_TYPE
2109 resultTypePropagate (ast *tree, RESULT_TYPE resultType)
2110 {
2111   switch (tree->opval.op)
2112     {
2113       case '=':
2114       case '?':
2115       case ':':
2116       case '|':
2117       case '^':
2118       case '*':
2119       case '+':
2120       case '-':
2121       case LABEL:
2122         return resultType;
2123       case '&':
2124         if (!tree->right)
2125           /* can be unary */
2126           return RESULT_TYPE_NONE;
2127         else
2128           return resultType;
2129       case IFX:
2130         return RESULT_TYPE_IFX;
2131       default:
2132         return RESULT_TYPE_NONE;
2133     }
2134 }
2135
2136 /*-----------------------------------------------------------------*/
2137 /* getLeftResultType - gets type from left branch for propagation  */
2138 /*-----------------------------------------------------------------*/
2139 static RESULT_TYPE
2140 getLeftResultType (ast *tree, RESULT_TYPE resultType)
2141 {
2142   switch (tree->opval.op)
2143     {
2144       case '=':
2145       case CAST:
2146         if (IS_PTR (LTYPE (tree)))
2147           return RESULT_TYPE_NONE;
2148         else
2149           return getResultTypeFromType (LETYPE (tree));
2150       case RETURN:
2151         if (IS_PTR (currFunc->type->next))
2152           return RESULT_TYPE_NONE;
2153         else
2154           return getResultTypeFromType (currFunc->type->next);
2155       case '[':
2156         if (!IS_ARRAY (LTYPE (tree)))
2157           return resultType;
2158         if (DCL_ELEM (LTYPE (tree)) > 0 && DCL_ELEM (LTYPE (tree)) <= 256)
2159           return RESULT_TYPE_CHAR;
2160         return resultType;
2161       default:
2162         return resultType;
2163     }
2164 }
2165
2166 /*--------------------------------------------------------------------*/
2167 /* decorateType - compute type for this tree, also does type checking.*/
2168 /* This is done bottom up, since type has to flow upwards.            */
2169 /* resultType flows top-down and forces e.g. char-arithmetik, if the  */
2170 /* result is a char and the operand(s) are int's.                     */
2171 /* It also does constant folding, and parameter checking.             */
2172 /*--------------------------------------------------------------------*/
2173 ast *
2174 decorateType (ast * tree, RESULT_TYPE resultType)
2175 {
2176   int parmNumber;
2177   sym_link *p;
2178   RESULT_TYPE resultTypeProp;
2179
2180   if (!tree)
2181     return tree;
2182
2183   /* if already has type then do nothing */
2184   if (tree->decorated)
2185     return tree;
2186
2187   tree->decorated = 1;
2188
2189 #if 0
2190   /* print the line          */
2191   /* if not block & function */
2192   if (tree->type == EX_OP &&
2193       (tree->opval.op != FUNCTION &&
2194        tree->opval.op != BLOCK &&
2195        tree->opval.op != NULLOP))
2196     {
2197       filename = tree->filename;
2198       lineno = tree->lineno;
2199     }
2200 #endif
2201
2202   /* if any child is an error | this one is an error do nothing */
2203   if (tree->isError ||
2204       (tree->left && tree->left->isError) ||
2205       (tree->right && tree->right->isError))
2206     return tree;
2207
2208 /*------------------------------------------------------------------*/
2209 /*----------------------------*/
2210 /*   leaf has been reached    */
2211 /*----------------------------*/
2212   lineno=tree->lineno;
2213   /* if this is of type value */
2214   /* just get the type        */
2215   if (tree->type == EX_VALUE)
2216     {
2217
2218       if (IS_LITERAL (tree->opval.val->etype))
2219         {
2220
2221           /* if this is a character array then declare it */
2222           if (IS_ARRAY (tree->opval.val->type))
2223             tree->opval.val = stringToSymbol (tree->opval.val);
2224
2225           /* otherwise just copy the type information */
2226           COPYTYPE (TTYPE (tree), TETYPE (tree), tree->opval.val->type);
2227           return tree;
2228         }
2229
2230       if (tree->opval.val->sym)
2231         {
2232           /* if the undefined flag is set then give error message */
2233           if (tree->opval.val->sym->undefined)
2234             {
2235               werror (E_ID_UNDEF, tree->opval.val->sym->name);
2236               /* assume int */
2237               TTYPE (tree) = TETYPE (tree) =
2238                 tree->opval.val->type = tree->opval.val->sym->type =
2239                 tree->opval.val->etype = tree->opval.val->sym->etype =
2240                 copyLinkChain (INTTYPE);
2241             }
2242           else
2243             {
2244
2245               /* if impilicit i.e. struct/union member then no type */
2246               if (tree->opval.val->sym->implicit)
2247                 TTYPE (tree) = TETYPE (tree) = NULL;
2248
2249               else
2250                 {
2251
2252                   /* else copy the type */
2253                   COPYTYPE (TTYPE (tree), TETYPE (tree), tree->opval.val->type);
2254
2255                   /* and mark it as referenced */
2256                   tree->opval.val->sym->isref = 1;
2257                 }
2258             }
2259         }
2260
2261       return tree;
2262     }
2263
2264   /* if type link for the case of cast */
2265   if (tree->type == EX_LINK)
2266     {
2267       COPYTYPE (TTYPE (tree), TETYPE (tree), tree->opval.lnk);
2268       return tree;
2269     }
2270
2271   {
2272     ast *dtl, *dtr;
2273
2274     #if 0
2275     if (tree->opval.op == NULLOP || tree->opval.op == BLOCK)
2276       {
2277         if (tree->left && tree->left->type == EX_OPERAND
2278             && (tree->left->opval.op == INC_OP
2279                 || tree->left->opval.op == DEC_OP)
2280             && tree->left->left)
2281           {
2282             tree->left->right = tree->left->left;
2283             tree->left->left = NULL;
2284           }
2285         if (tree->right && tree->right->type == EX_OPERAND
2286             && (tree->right->opval.op == INC_OP
2287                 || tree->right->opval.op == DEC_OP)
2288             && tree->right->left)
2289           {
2290             tree->right->right = tree->right->left;
2291             tree->right->left = NULL;
2292           }
2293       }
2294     #endif
2295
2296     /* Before decorating the left branch we've to decide in dependence
2297        upon tree->opval.op, if resultType can be propagated */
2298     resultTypeProp = resultTypePropagate (tree, resultType);
2299
2300     if (tree->opval.op == '?')
2301       dtl = decorateType (tree->left, RESULT_TYPE_IFX);
2302     else
2303       dtl = decorateType (tree->left, resultTypeProp);
2304
2305     /* if an array node, we may need to swap branches */
2306     if (tree->opval.op == '[')
2307       {
2308         /* determine which is the array & which the index */
2309         if ((IS_ARRAY (RTYPE (tree)) || IS_PTR (RTYPE (tree))) &&
2310             IS_INTEGRAL (LTYPE (tree)))
2311           {
2312             ast *tempTree = tree->left;
2313             tree->left = tree->right;
2314             tree->right = tempTree;
2315           }
2316       }
2317
2318     /* After decorating the left branch there's type information available
2319        in tree->left->?type. If the op is e.g. '=' we extract the type
2320        information from there and propagate it to the right branch. */
2321     resultTypeProp = getLeftResultType (tree, resultTypeProp);
2322     
2323     switch (tree->opval.op)
2324       {
2325         case '?':
2326           /* delay right side for '?' operator since conditional macro
2327              expansions might rely on this */
2328           dtr = tree->right;
2329           break;
2330         case CALL: 
2331           /* decorate right side for CALL (parameter list) in processParms();
2332              there is resultType available */
2333           dtr = tree->right;
2334           break;
2335         default:     
2336           dtr = decorateType (tree->right, resultTypeProp);
2337           break;
2338       }
2339
2340     /* this is to take care of situations
2341        when the tree gets rewritten */
2342     if (dtl != tree->left)
2343       tree->left = dtl;
2344     if (dtr != tree->right)
2345       tree->right = dtr;
2346     if ((dtl && dtl->isError) || (dtr && dtr->isError))
2347       return tree;
2348   }
2349
2350   /* depending on type of operator do */
2351
2352   switch (tree->opval.op)
2353     {
2354         /*------------------------------------------------------------------*/
2355         /*----------------------------*/
2356         /*        array node          */
2357         /*----------------------------*/
2358     case '[':
2359
2360       /* first check if this is a array or a pointer */
2361       if ((!IS_ARRAY (LTYPE (tree))) && (!IS_PTR (LTYPE (tree))))
2362         {
2363           werror (E_NEED_ARRAY_PTR, "[]");
2364           goto errorTreeReturn;
2365         }
2366
2367       /* check if the type of the idx */
2368       if (!IS_INTEGRAL (RTYPE (tree)))
2369         {
2370           werror (E_IDX_NOT_INT);
2371           goto errorTreeReturn;
2372         }
2373
2374       /* if the left is an rvalue then error */
2375       if (LRVAL (tree))
2376         {
2377           werror (E_LVALUE_REQUIRED, "array access");
2378           goto errorTreeReturn;
2379         }
2380
2381       if (IS_LITERAL (RTYPE (tree)))
2382         {
2383           int arrayIndex = (int) floatFromVal (valFromType (RETYPE (tree)));
2384           int arraySize = DCL_ELEM (LTYPE (tree));
2385           if (arraySize && arrayIndex >= arraySize)
2386             {
2387               werror (W_IDX_OUT_OF_BOUNDS, arrayIndex, arraySize);
2388             }
2389         }
2390
2391       RRVAL (tree) = 1;
2392       COPYTYPE (TTYPE (tree), TETYPE (tree), LTYPE (tree)->next);
2393       return tree;
2394
2395       /*------------------------------------------------------------------*/
2396       /*----------------------------*/
2397       /*      struct/union          */
2398       /*----------------------------*/
2399     case '.':
2400       /* if this is not a structure */
2401       if (!IS_STRUCT (LTYPE (tree)))
2402         {
2403           werror (E_STRUCT_UNION, ".");
2404           goto errorTreeReturn;
2405         }
2406       TTYPE (tree) = structElemType (LTYPE (tree),
2407                                      (tree->right->type == EX_VALUE ?
2408                                tree->right->opval.val : NULL));
2409       TETYPE (tree) = getSpec (TTYPE (tree));
2410       return tree;
2411
2412       /*------------------------------------------------------------------*/
2413       /*----------------------------*/
2414       /*    struct/union pointer    */
2415       /*----------------------------*/
2416     case PTR_OP:
2417       /* if not pointer to a structure */
2418       if (!IS_PTR (LTYPE (tree)) && !IS_ARRAY (LTYPE(tree)))
2419         {
2420           werror (E_PTR_REQD);
2421           goto errorTreeReturn;
2422         }
2423
2424       if (!IS_STRUCT (LTYPE (tree)->next))
2425         {
2426           werror (E_STRUCT_UNION, "->");
2427           goto errorTreeReturn;
2428         }
2429
2430       TTYPE (tree) = structElemType (LTYPE (tree)->next,
2431                                      (tree->right->type == EX_VALUE ?
2432                                tree->right->opval.val : NULL));
2433       TETYPE (tree) = getSpec (TTYPE (tree));
2434
2435       /* adjust the storage class */
2436       switch (DCL_TYPE(tree->left->ftype)) {
2437       case POINTER:
2438         SPEC_SCLS(TETYPE(tree)) = S_DATA; 
2439         break;
2440       case FPOINTER:
2441         SPEC_SCLS(TETYPE(tree)) = S_XDATA; 
2442         break;
2443       case CPOINTER:
2444         SPEC_SCLS(TETYPE(tree)) = S_CODE; 
2445         break;
2446       case GPOINTER:
2447         SPEC_SCLS (TETYPE (tree)) = 0;
2448         break;
2449       case PPOINTER:
2450         SPEC_SCLS(TETYPE(tree)) = S_XSTACK; 
2451         break;
2452       case IPOINTER:
2453         SPEC_SCLS(TETYPE(tree)) = S_IDATA;
2454         break;
2455       case EEPPOINTER:
2456         SPEC_SCLS(TETYPE(tree)) = S_EEPROM;
2457         break;
2458       case UPOINTER:
2459         SPEC_SCLS (TETYPE (tree)) = 0;
2460         break;
2461       case ARRAY:
2462       case FUNCTION:
2463         break;
2464       }
2465       
2466       /* This breaks with extern declarations, bitfields, and perhaps other */
2467       /* cases (gcse). Let's leave this optimization disabled for now and   */
2468       /* ponder if there's a safe way to do this. -- EEP                    */
2469       #if 0
2470       if (IS_ADDRESS_OF_OP (tree->left) && IS_AST_SYM_VALUE(tree->left->left)
2471           && SPEC_ABSA (AST_SYMBOL (tree->left->left)->etype))
2472         {
2473             /* If defined    struct type at addr var
2474                then rewrite  (&struct var)->member
2475                as            temp
2476                and define    membertype at (addr+offsetof(struct var,member)) temp
2477             */
2478             symbol *sym;
2479             symbol *element = getStructElement (SPEC_STRUCT (LETYPE(tree)),
2480                                                 AST_SYMBOL(tree->right));
2481
2482             sym = newSymbol(genSymName (0), 0);
2483             sym->type = TTYPE (tree);
2484             sym->etype = getSpec(sym->type);
2485             sym->lineDef = tree->lineno;
2486             sym->cdef = 1;
2487             sym->isref = 1;
2488             SPEC_STAT (sym->etype) = 1;
2489             SPEC_ADDR (sym->etype) = SPEC_ADDR (AST_SYMBOL (tree->left->left)->etype)
2490                                      + element->offset;
2491             SPEC_ABSA(sym->etype) = 1;
2492             addSym (SymbolTab, sym, sym->name, 0, 0, 0);
2493             allocGlobal (sym);
2494             
2495             AST_VALUE (tree) = symbolVal(sym);
2496             TLVAL (tree) = 1;
2497             TRVAL (tree) = 0;
2498             tree->type = EX_VALUE;
2499             tree->left = NULL;
2500             tree->right = NULL;
2501         }
2502       #endif
2503       
2504       return tree;
2505
2506       /*------------------------------------------------------------------*/
2507       /*----------------------------*/
2508       /*  ++/-- operation           */
2509       /*----------------------------*/
2510     case INC_OP:
2511     case DEC_OP:
2512       {
2513         sym_link *ltc = (tree->right ? RTYPE (tree) : LTYPE (tree));
2514         COPYTYPE (TTYPE (tree), TETYPE (tree), ltc);
2515         if (!tree->initMode && IS_CONSTANT(TTYPE(tree)))
2516           werror (E_CODE_WRITE, tree->opval.op==INC_OP ? "++" : "--");
2517
2518         if (tree->right)
2519           RLVAL (tree) = 1;
2520         else
2521           LLVAL (tree) = 1;
2522         return tree;
2523       }
2524
2525       /*------------------------------------------------------------------*/
2526       /*----------------------------*/
2527       /*  bitwise and               */
2528       /*----------------------------*/
2529     case '&':                   /* can be unary   */
2530       /* if right is NULL then unary operation  */
2531       if (tree->right)          /* not an unary operation */
2532         {
2533
2534           if (!IS_INTEGRAL (LTYPE (tree)) || !IS_INTEGRAL (RTYPE (tree)))
2535             {
2536               werror (E_BITWISE_OP);
2537               werror (W_CONTINUE, "left & right types are ");
2538               printTypeChain (LTYPE (tree), stderr);
2539               fprintf (stderr, ",");
2540               printTypeChain (RTYPE (tree), stderr);
2541               fprintf (stderr, "\n");
2542               goto errorTreeReturn;
2543             }
2544
2545           /* if they are both literal */
2546           if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2547             {
2548               tree->type = EX_VALUE;
2549               tree->opval.val = valBitwise (valFromType (LETYPE (tree)),
2550                                           valFromType (RETYPE (tree)), '&');
2551
2552               tree->right = tree->left = NULL;
2553               TETYPE (tree) = tree->opval.val->etype;
2554               TTYPE (tree) = tree->opval.val->type;
2555               return tree;
2556             }
2557
2558           /* see if this is a GETHBIT operation if yes
2559              then return that */
2560           {
2561             ast *otree = optimizeGetHbit (tree);
2562
2563             if (otree != tree)
2564               return decorateType (otree, RESULT_CHECK);
2565           }
2566
2567           TTYPE (tree) = computeType (LTYPE (tree),
2568                                       RTYPE (tree),
2569                                       resultType,
2570                                       tree->opval.op);
2571           TETYPE (tree) = getSpec (TTYPE (tree));
2572
2573           /* if left is a literal exchange left & right */
2574           if (IS_LITERAL (LTYPE (tree)))
2575             {
2576               ast *tTree = tree->left;
2577               tree->left = tree->right;
2578               tree->right = tTree;
2579             }
2580
2581           /* if right is a literal and */
2582           /* we can find a 2nd literal in a and-tree then */
2583           /* rearrange the tree */
2584           if (IS_LITERAL (RTYPE (tree)))
2585             {
2586               ast *parent;
2587               ast *litTree = searchLitOp (tree, &parent, "&");
2588               if (litTree)
2589                 {
2590                   DEBUG_CF("&")
2591                   ast *tTree = litTree->left;
2592                   litTree->left = tree->right;
2593                   tree->right = tTree;
2594                   /* both operands in tTree are literal now */
2595                   decorateType (parent, resultType);
2596                 }
2597             }
2598
2599           LRVAL (tree) = RRVAL (tree) = 1;
2600           
2601           return tree;
2602         }
2603
2604       /*------------------------------------------------------------------*/
2605       /*----------------------------*/
2606       /*  address of                */
2607       /*----------------------------*/
2608       p = newLink (DECLARATOR);
2609       /* if bit field then error */
2610       if (IS_BITVAR (tree->left->etype))
2611         {
2612           werror (E_ILLEGAL_ADDR, "address of bit variable");
2613           goto errorTreeReturn;
2614         }
2615
2616       if (LETYPE(tree) && SPEC_SCLS (tree->left->etype) == S_REGISTER)
2617         {
2618           werror (E_ILLEGAL_ADDR, "address of register variable");
2619           goto errorTreeReturn;
2620         }
2621
2622       if (IS_FUNC (LTYPE (tree)))
2623         {
2624           // this ought to be ignored
2625           return (tree->left);
2626         }
2627
2628       if (IS_LITERAL(LTYPE(tree)))
2629         {
2630           werror (E_ILLEGAL_ADDR, "address of literal");
2631           goto errorTreeReturn;
2632         }
2633
2634      if (LRVAL (tree))
2635         {
2636           werror (E_LVALUE_REQUIRED, "address of");
2637           goto errorTreeReturn;
2638         }
2639       if (!LETYPE (tree))
2640         DCL_TYPE (p) = POINTER;
2641       else if (SPEC_SCLS (tree->left->etype) == S_CODE)
2642         DCL_TYPE (p) = CPOINTER;
2643       else if (SPEC_SCLS (tree->left->etype) == S_XDATA)
2644         DCL_TYPE (p) = FPOINTER;
2645       else if (SPEC_SCLS (tree->left->etype) == S_XSTACK)
2646         DCL_TYPE (p) = PPOINTER;
2647       else if (SPEC_SCLS (tree->left->etype) == S_IDATA)
2648         DCL_TYPE (p) = IPOINTER;
2649       else if (SPEC_SCLS (tree->left->etype) == S_EEPROM)
2650         DCL_TYPE (p) = EEPPOINTER;
2651       else if (SPEC_OCLS(tree->left->etype))
2652           DCL_TYPE (p) = PTR_TYPE(SPEC_OCLS(tree->left->etype));
2653       else
2654           DCL_TYPE (p) = POINTER;
2655
2656       if (IS_AST_SYM_VALUE (tree->left))
2657         {
2658           AST_SYMBOL (tree->left)->addrtaken = 1;
2659           AST_SYMBOL (tree->left)->allocreq = 1;
2660         }
2661
2662       p->next = LTYPE (tree);
2663       TTYPE (tree) = p;
2664       TETYPE (tree) = getSpec (TTYPE (tree));
2665       LLVAL (tree) = 1;
2666       TLVAL (tree) = 1;
2667
2668       #if 0
2669       if (IS_AST_OP (tree->left) && tree->left->opval.op == PTR_OP
2670           && IS_AST_VALUE (tree->left->left) && !IS_AST_SYM_VALUE (tree->left->left))
2671         {
2672           symbol *element = getStructElement (SPEC_STRUCT (LETYPE(tree->left)),
2673                                       AST_SYMBOL(tree->left->right));
2674           AST_VALUE(tree) = valPlus(AST_VALUE(tree->left->left),
2675                                     valueFromLit(element->offset));
2676           tree->left = NULL;
2677           tree->right = NULL;
2678           tree->type = EX_VALUE;
2679           tree->values.literalFromCast = 1;
2680         }
2681       #endif
2682
2683       return tree;
2684
2685       /*------------------------------------------------------------------*/
2686       /*----------------------------*/
2687       /*  bitwise or                */
2688       /*----------------------------*/
2689     case '|':
2690       /* if the rewrite succeeds then don't go any furthur */
2691       {
2692         ast *wtree = optimizeRRCRLC (tree);
2693         if (wtree != tree)
2694           return decorateType (wtree, RESULT_CHECK);
2695         
2696         wtree = optimizeSWAP (tree);
2697         if (wtree != tree)
2698           return decorateType (wtree, RESULT_CHECK);
2699       }
2700
2701       /* if left is a literal exchange left & right */
2702       if (IS_LITERAL (LTYPE (tree)))
2703         {
2704           ast *tTree = tree->left;
2705           tree->left = tree->right;
2706           tree->right = tTree;
2707         }
2708
2709       /* if right is a literal and */
2710       /* we can find a 2nd literal in a or-tree then */
2711       /* rearrange the tree */
2712       if (IS_LITERAL (RTYPE (tree)))
2713         {
2714           ast *parent;
2715           ast *litTree = searchLitOp (tree, &parent, "|");
2716           if (litTree)
2717             {
2718               DEBUG_CF("|")
2719               ast *tTree = litTree->left;
2720               litTree->left = tree->right;
2721               tree->right = tTree;
2722               /* both operands in tTree are literal now */
2723               decorateType (parent, resultType);
2724             }
2725         }
2726       /* fall through */
2727
2728       /*------------------------------------------------------------------*/
2729       /*----------------------------*/
2730       /*  bitwise xor               */
2731       /*----------------------------*/
2732     case '^':
2733       if (!IS_INTEGRAL (LTYPE (tree)) || !IS_INTEGRAL (RTYPE (tree)))
2734         {
2735           werror (E_BITWISE_OP);
2736           werror (W_CONTINUE, "left & right types are ");
2737           printTypeChain (LTYPE (tree), stderr);
2738           fprintf (stderr, ",");
2739           printTypeChain (RTYPE (tree), stderr);
2740           fprintf (stderr, "\n");
2741           goto errorTreeReturn;
2742         }
2743
2744       /* if they are both literal then */
2745       /* rewrite the tree */
2746       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2747         {
2748           tree->type = EX_VALUE;
2749           tree->opval.val = valBitwise (valFromType (LETYPE (tree)),
2750                                         valFromType (RETYPE (tree)),
2751                                         tree->opval.op);
2752           tree->right = tree->left = NULL;
2753           TETYPE (tree) = tree->opval.val->etype;
2754           TTYPE (tree) = tree->opval.val->type;
2755           return tree;
2756         }
2757
2758       /* if left is a literal exchange left & right */
2759       if (IS_LITERAL (LTYPE (tree)))
2760         {
2761           ast *tTree = tree->left;
2762           tree->left = tree->right;
2763           tree->right = tTree;
2764         }
2765
2766       /* if right is a literal and */
2767       /* we can find a 2nd literal in a xor-tree then */
2768       /* rearrange the tree */
2769       if (IS_LITERAL (RTYPE (tree)) &&
2770           tree->opval.op == '^') /* the same source is used by 'bitwise or' */
2771         {
2772           ast *parent;
2773           ast *litTree = searchLitOp (tree, &parent, "^");
2774           if (litTree)
2775             {
2776               DEBUG_CF("^")
2777               ast *tTree = litTree->left;
2778               litTree->left = tree->right;
2779               tree->right = tTree;
2780               /* both operands in litTree are literal now */
2781               decorateType (parent, resultType);
2782             }
2783         }
2784
2785       LRVAL (tree) = RRVAL (tree) = 1;
2786       TETYPE (tree) = getSpec (TTYPE (tree) =
2787                                computeType (LTYPE (tree),
2788                                             RTYPE (tree),
2789                                             resultType,
2790                                             tree->opval.op));
2791
2792       return tree;
2793
2794       /*------------------------------------------------------------------*/
2795       /*----------------------------*/
2796       /*  division                  */
2797       /*----------------------------*/
2798     case '/':
2799       if (!IS_ARITHMETIC (LTYPE (tree)) || !IS_ARITHMETIC (RTYPE (tree)))
2800         {
2801           werror (E_INVALID_OP, "divide");
2802           goto errorTreeReturn;
2803         }
2804       /* if they are both literal then */
2805       /* rewrite the tree */
2806       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2807         {
2808           tree->type = EX_VALUE;
2809           tree->opval.val = valDiv (valFromType (LETYPE (tree)),
2810                                     valFromType (RETYPE (tree)));
2811           tree->right = tree->left = NULL;
2812           TETYPE (tree) = getSpec (TTYPE (tree) =
2813                                    tree->opval.val->type);
2814           return tree;
2815         }
2816
2817       LRVAL (tree) = RRVAL (tree) = 1;
2818
2819       TETYPE (tree) = getSpec (TTYPE (tree) =
2820                                computeType (LTYPE (tree),
2821                                             RTYPE (tree),
2822                                             resultType,
2823                                             tree->opval.op));
2824
2825       /* if right is a literal and */
2826       /* left is also a division by a literal then */
2827       /* rearrange the tree */
2828       if (IS_LITERAL (RTYPE (tree))
2829           /* avoid infinite loop */
2830           && (TYPE_UDWORD) floatFromVal (tree->right->opval.val) != 1)
2831         {
2832           ast *parent;
2833           ast *litTree = searchLitOp (tree, &parent, "/");
2834           if (litTree)
2835             {
2836               if (IS_LITERAL (RTYPE (litTree)))
2837                 {
2838                   /* foo_div */
2839                   DEBUG_CF("div r")
2840                   litTree->right = newNode ('*',
2841                                             litTree->right,
2842                                             copyAst (tree->right));
2843                   litTree->right->lineno = tree->lineno;
2844
2845                   tree->right->opval.val = constVal ("1");
2846                   decorateType (parent, resultType);
2847                 }
2848               else
2849                 {
2850                   /* litTree->left is literal: no gcse possible.
2851                      We can't call decorateType(parent, RESULT_CHECK), because
2852                      this would cause an infinit loop. */
2853                   parent->decorated = 1;
2854                   decorateType (litTree, resultType);
2855                 }
2856             }
2857         }
2858
2859       return tree;
2860
2861       /*------------------------------------------------------------------*/
2862       /*----------------------------*/
2863       /*            modulus         */
2864       /*----------------------------*/
2865     case '%':
2866       if (!IS_INTEGRAL (LTYPE (tree)) || !IS_INTEGRAL (RTYPE (tree)))
2867         {
2868           werror (E_BITWISE_OP);
2869           werror (W_CONTINUE, "left & right types are ");
2870           printTypeChain (LTYPE (tree), stderr);
2871           fprintf (stderr, ",");
2872           printTypeChain (RTYPE (tree), stderr);
2873           fprintf (stderr, "\n");
2874           goto errorTreeReturn;
2875         }
2876       /* if they are both literal then */
2877       /* rewrite the tree */
2878       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2879         {
2880           tree->type = EX_VALUE;
2881           tree->opval.val = valMod (valFromType (LETYPE (tree)),
2882                                     valFromType (RETYPE (tree)));
2883           tree->right = tree->left = NULL;
2884           TETYPE (tree) = getSpec (TTYPE (tree) =
2885                                    tree->opval.val->type);
2886           return tree;
2887         }
2888       LRVAL (tree) = RRVAL (tree) = 1;
2889       TETYPE (tree) = getSpec (TTYPE (tree) =
2890                                computeType (LTYPE (tree),
2891                                             RTYPE (tree),
2892                                             resultType,
2893                                             tree->opval.op));
2894       return tree;
2895
2896       /*------------------------------------------------------------------*/
2897       /*----------------------------*/
2898       /*  address dereference       */
2899       /*----------------------------*/
2900     case '*':                   /* can be unary  : if right is null then unary operation */
2901       if (!tree->right)
2902         {
2903           if (!IS_PTR (LTYPE (tree)) && !IS_ARRAY (LTYPE (tree)))
2904             {
2905               werror (E_PTR_REQD);
2906               goto errorTreeReturn;
2907             }
2908
2909           if (LRVAL (tree))
2910             {
2911               werror (E_LVALUE_REQUIRED, "pointer deref");
2912               goto errorTreeReturn;
2913             }
2914           if (IS_ADDRESS_OF_OP(tree->left))
2915             {
2916               /* replace *&obj with obj */
2917               return tree->left->left;
2918             }
2919           TTYPE (tree) = copyLinkChain (LTYPE (tree)->next);
2920           TETYPE (tree) = getSpec (TTYPE (tree));
2921           /* adjust the storage class */
2922           switch (DCL_TYPE(tree->left->ftype)) {
2923             case POINTER:
2924               SPEC_SCLS(TETYPE(tree)) = S_DATA;
2925               break;
2926             case FPOINTER:
2927               SPEC_SCLS(TETYPE(tree)) = S_XDATA; 
2928               break;
2929             case CPOINTER:
2930               SPEC_SCLS(TETYPE(tree)) = S_CODE; 
2931               break;
2932             case GPOINTER:
2933               SPEC_SCLS (TETYPE (tree)) = 0;
2934               break;
2935             case PPOINTER:
2936               SPEC_SCLS(TETYPE(tree)) = S_XSTACK; 
2937               break;
2938             case IPOINTER:
2939               SPEC_SCLS(TETYPE(tree)) = S_IDATA;
2940               break;
2941             case EEPPOINTER:
2942               SPEC_SCLS(TETYPE(tree)) = S_EEPROM;
2943               break;
2944             case UPOINTER:
2945               SPEC_SCLS (TETYPE (tree)) = 0;
2946               break;
2947             case ARRAY:
2948             case FUNCTION:
2949               break;
2950           }
2951           return tree;
2952         }
2953
2954       /*------------------------------------------------------------------*/
2955       /*----------------------------*/
2956       /*      multiplication        */
2957       /*----------------------------*/
2958       if (!IS_ARITHMETIC (LTYPE (tree)) || !IS_ARITHMETIC (RTYPE (tree)))
2959         {
2960           werror (E_INVALID_OP, "multiplication");
2961           goto errorTreeReturn;
2962         }
2963
2964       /* if they are both literal then */
2965       /* rewrite the tree */
2966       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2967         {
2968           tree->type = EX_VALUE;
2969           tree->opval.val = valMult (valFromType (LETYPE (tree)),
2970                                      valFromType (RETYPE (tree)));
2971           tree->right = tree->left = NULL;
2972           TETYPE (tree) = getSpec (TTYPE (tree) =
2973                                    tree->opval.val->type);
2974           return tree;
2975         }
2976
2977       /* if left is a literal exchange left & right */
2978       if (IS_LITERAL (LTYPE (tree)))
2979         {
2980           ast *tTree = tree->left;
2981           tree->left = tree->right;
2982           tree->right = tTree;
2983         }
2984
2985       /* if right is a literal and */
2986       /* we can find a 2nd literal in a mul-tree then */
2987       /* rearrange the tree */
2988       if (IS_LITERAL (RTYPE (tree)))
2989         {
2990           ast *parent;
2991           ast *litTree = searchLitOp (tree, &parent, "*");
2992           if (litTree)
2993             {
2994               DEBUG_CF("mul")
2995               ast *tTree = litTree->left;
2996               litTree->left = tree->right;
2997               tree->right = tTree;
2998               /* both operands in litTree are literal now */
2999               decorateType (parent, resultType);
3000             }
3001         }
3002
3003       LRVAL (tree) = RRVAL (tree) = 1;
3004       tree->left  = addCast (tree->left,  resultType, FALSE);
3005       tree->right = addCast (tree->right, resultType, FALSE);
3006       TETYPE (tree) = getSpec (TTYPE (tree) =
3007                                    computeType (LTYPE (tree),
3008                                                 RTYPE (tree),
3009                                                 resultType,
3010                                                 tree->opval.op));
3011
3012       return tree;
3013
3014       /*------------------------------------------------------------------*/
3015       /*----------------------------*/
3016       /*    unary '+' operator      */
3017       /*----------------------------*/
3018     case '+':
3019       /* if unary plus */
3020       if (!tree->right)
3021         {
3022           if (!IS_ARITHMETIC (LTYPE (tree)))
3023             {
3024               werror (E_UNARY_OP, '+');
3025               goto errorTreeReturn;
3026             }
3027
3028           /* if left is a literal then do it */
3029           if (IS_LITERAL (LTYPE (tree)))
3030             {
3031               tree->type = EX_VALUE;
3032               tree->opval.val = valFromType (LETYPE (tree));
3033               tree->left = NULL;
3034               TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
3035               return tree;
3036             }
3037           LRVAL (tree) = 1;
3038           COPYTYPE (TTYPE (tree), TETYPE (tree), LTYPE (tree));
3039           return tree;
3040         }
3041
3042       /*------------------------------------------------------------------*/
3043       /*----------------------------*/
3044       /*      addition              */
3045       /*----------------------------*/
3046
3047       /* this is not a unary operation */
3048       /* if both pointers then problem */
3049       if ((IS_PTR (LTYPE (tree)) || IS_ARRAY (LTYPE (tree))) &&
3050           (IS_PTR (RTYPE (tree)) || IS_ARRAY (RTYPE (tree))))
3051         {
3052           werror (E_PTR_PLUS_PTR);
3053           goto errorTreeReturn;
3054         }
3055
3056       if (!IS_ARITHMETIC (LTYPE (tree)) &&
3057           !IS_PTR (LTYPE (tree)) && !IS_ARRAY (LTYPE (tree)))
3058         {
3059           werror (E_PLUS_INVALID, "+");
3060           goto errorTreeReturn;
3061         }
3062
3063       if (!IS_ARITHMETIC (RTYPE (tree)) &&
3064           !IS_PTR (RTYPE (tree)) && !IS_ARRAY (RTYPE (tree)))
3065         {
3066           werror (E_PLUS_INVALID, "+");
3067           goto errorTreeReturn;
3068         }
3069       /* if they are both literal then */
3070       /* rewrite the tree */
3071       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
3072         {
3073           tree->type = EX_VALUE;
3074           tree->left  = addCast (tree->left,  resultType, TRUE);
3075           tree->right = addCast (tree->right, resultType, TRUE);
3076           tree->opval.val = valPlus (valFromType (LETYPE (tree)),
3077                                      valFromType (RETYPE (tree)));
3078           tree->right = tree->left = NULL;
3079           TETYPE (tree) = getSpec (TTYPE (tree) =
3080                                    tree->opval.val->type);
3081           return tree;
3082         }
3083
3084       /* if the right is a pointer or left is a literal
3085          xchange left & right */
3086       if (IS_ARRAY (RTYPE (tree)) ||
3087           IS_PTR (RTYPE (tree)) ||
3088           IS_LITERAL (LTYPE (tree)))
3089         {
3090           ast *tTree = tree->left;
3091           tree->left = tree->right;
3092           tree->right = tTree;
3093         }
3094
3095       /* if right is a literal and */
3096       /* left is also an addition/subtraction with a literal then */
3097       /* rearrange the tree */
3098       if (IS_LITERAL (RTYPE (tree)))
3099         {
3100           ast *litTree, *parent;
3101           litTree = searchLitOp (tree, &parent, "+-");
3102           if (litTree)
3103             {
3104               if (litTree->opval.op == '+')
3105                 {
3106                   /* foo_aa */
3107                   DEBUG_CF("+ 1 AA")
3108                   ast *tTree = litTree->left;
3109                   litTree->left = tree->right;
3110                   tree->right = tree->left;
3111                   tree->left = tTree;
3112                 }
3113               else if (litTree->opval.op == '-')
3114                 {
3115                   if (IS_LITERAL (RTYPE (litTree)))
3116                     {
3117                       DEBUG_CF("+ 2 ASR")
3118                       /* foo_asr */
3119                       ast *tTree = litTree->left;
3120                       litTree->left = tree->right;
3121                       tree->right = tTree;
3122                     }
3123                   else
3124                     {
3125                       DEBUG_CF("+ 3 ASL")
3126                       /* foo_asl */
3127                       ast *tTree = litTree->right;
3128                       litTree->right = tree->right;
3129                       tree->right = tTree;
3130                       litTree->opval.op = '+';
3131                       tree->opval.op = '-';
3132                     }
3133                 }
3134               decorateType (parent, resultType);
3135             }
3136         }
3137
3138       LRVAL (tree) = RRVAL (tree) = 1;
3139       /* if the left is a pointer */
3140       if (IS_PTR (LTYPE (tree)) || IS_AGGREGATE (LTYPE (tree)) )
3141         TETYPE (tree) = getSpec (TTYPE (tree) =
3142                                  LTYPE (tree));
3143       else
3144         {
3145           tree->left  = addCast (tree->left,  resultType, TRUE);
3146           tree->right = addCast (tree->right, resultType, TRUE);
3147           TETYPE (tree) = getSpec (TTYPE (tree) =
3148                                      computeType (LTYPE (tree),
3149                                                   RTYPE (tree),
3150                                                   resultType,
3151                                                   tree->opval.op));
3152         }
3153         
3154       return tree;
3155
3156       /*------------------------------------------------------------------*/
3157       /*----------------------------*/
3158       /*      unary '-'             */
3159       /*----------------------------*/
3160     case '-':                   /* can be unary   */
3161       /* if right is null then unary */
3162       if (!tree->right)
3163         {
3164
3165           if (!IS_ARITHMETIC (LTYPE (tree)))
3166             {
3167               werror (E_UNARY_OP, tree->opval.op);
3168               goto errorTreeReturn;
3169             }
3170
3171           /* if left is a literal then do it */
3172           if (IS_LITERAL (LTYPE (tree)))
3173             {
3174               tree->type = EX_VALUE;
3175               tree->opval.val = valUnaryPM (valFromType (LETYPE (tree)));
3176               tree->left = NULL;
3177               TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
3178               SPEC_USIGN(TETYPE(tree)) = 0;
3179               return tree;
3180             }
3181           LRVAL (tree) = 1;
3182           TETYPE(tree) = getSpec (TTYPE (tree) = LTYPE (tree));
3183           return tree;
3184         }
3185
3186       /*------------------------------------------------------------------*/
3187       /*----------------------------*/
3188       /*    subtraction             */
3189       /*----------------------------*/
3190
3191       if (!(IS_PTR (LTYPE (tree)) ||
3192             IS_ARRAY (LTYPE (tree)) ||
3193             IS_ARITHMETIC (LTYPE (tree))))
3194         {
3195           werror (E_PLUS_INVALID, "-");
3196           goto errorTreeReturn;
3197         }
3198
3199       if (!(IS_PTR (RTYPE (tree)) ||
3200             IS_ARRAY (RTYPE (tree)) ||
3201             IS_ARITHMETIC (RTYPE (tree))))
3202         {
3203           werror (E_PLUS_INVALID, "-");
3204           goto errorTreeReturn;
3205         }
3206
3207       if ((IS_PTR (LTYPE (tree)) || IS_ARRAY (LTYPE (tree))) &&
3208           !(IS_PTR (RTYPE (tree)) || IS_ARRAY (RTYPE (tree)) ||
3209             IS_INTEGRAL (RTYPE (tree))))
3210         {
3211           werror (E_PLUS_INVALID, "-");
3212           goto errorTreeReturn;
3213         }
3214
3215       /* if they are both literal then */
3216       /* rewrite the tree */
3217       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
3218         {
3219           tree->type = EX_VALUE;
3220           tree->left  = addCast (tree->left,  resultType, TRUE);
3221           tree->right = addCast (tree->right, resultType, TRUE);
3222           tree->opval.val = valMinus (valFromType (LETYPE (tree)),
3223                                       valFromType (RETYPE (tree)));
3224           tree->right = tree->left = NULL;
3225           TETYPE (tree) = getSpec (TTYPE (tree) =
3226                                    tree->opval.val->type);
3227           return tree;
3228         }
3229
3230       /* if the left & right are equal then zero */
3231       if (isAstEqual (tree->left, tree->right))
3232         {
3233           tree->type = EX_VALUE;
3234           tree->left = tree->right = NULL;
3235           tree->opval.val = constVal ("0");
3236           TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
3237           return tree;
3238         }
3239
3240       /* if both of them are pointers or arrays then */
3241       /* the result is going to be an integer        */
3242       if ((IS_ARRAY (LTYPE (tree)) || IS_PTR (LTYPE (tree))) &&
3243           (IS_ARRAY (RTYPE (tree)) || IS_PTR (RTYPE (tree))))
3244         TETYPE (tree) = TTYPE (tree) = newIntLink ();
3245       else
3246         /* if only the left is a pointer */
3247         /* then result is a pointer      */
3248       if (IS_PTR (LTYPE (tree)) || IS_ARRAY (LTYPE (tree)))
3249         TETYPE (tree) = getSpec (TTYPE (tree) =
3250                                  LTYPE (tree));
3251       else
3252         {
3253           tree->left  = addCast (tree->left,  resultType, TRUE);
3254           tree->right = addCast (tree->right, resultType, TRUE);
3255
3256           TETYPE (tree) = getSpec (TTYPE (tree) =
3257                                      computeType (LTYPE (tree),
3258                                                   RTYPE (tree),
3259                                                   resultType,
3260                                                   tree->opval.op));
3261         }
3262
3263       LRVAL (tree) = RRVAL (tree) = 1;
3264
3265       /* if right is a literal and */
3266       /* left is also an addition/subtraction with a literal then */
3267       /* rearrange the tree */
3268       if (IS_LITERAL (RTYPE (tree))
3269           /* avoid infinite loop */
3270           && (TYPE_UDWORD) floatFromVal (tree->right->opval.val) != 0)
3271         {
3272           ast *litTree, *litParent;
3273           litTree = searchLitOp (tree, &litParent, "+-");
3274           if (litTree)
3275             {
3276               if (litTree->opval.op == '+')
3277                 {
3278                   /* foo_sa */
3279                   DEBUG_CF("- 1 SA")
3280                   ast *tTree = litTree->left;
3281                   litTree->left = litTree->right;
3282                   litTree->right = tree->right;
3283                   tree->right = tTree;
3284                   tree->opval.op = '+';
3285                   litTree->opval.op = '-';
3286                 }
3287               else if (litTree->opval.op == '-')
3288                 {
3289                   if (IS_LITERAL (RTYPE (litTree)))
3290                     {
3291                       /* foo_ssr */
3292                       DEBUG_CF("- 2 SSR")
3293                       ast *tTree = litTree->left;
3294                       litTree->left = tree->right;
3295                       tree->right = litParent->left;
3296                       litParent->left = tTree;
3297                       litTree->opval.op = '+';
3298                       
3299                       tree->decorated = 0;
3300                       decorateType (tree, resultType);
3301                     }
3302                   else
3303                     {
3304                       /* foo_ssl */
3305                       DEBUG_CF("- 3 SSL")
3306                       ast *tTree = litTree->right;
3307                       litTree->right = tree->right;
3308                       tree->right = tTree;
3309                     }
3310                 }
3311               decorateType (litParent, resultType);
3312             }
3313         }
3314       return tree;
3315
3316       /*------------------------------------------------------------------*/
3317       /*----------------------------*/
3318       /*    complement              */
3319       /*----------------------------*/
3320     case '~':
3321       /* can be only integral type */
3322       if (!IS_INTEGRAL (LTYPE (tree)))
3323         {
3324           werror (E_UNARY_OP, tree->opval.op);
3325           goto errorTreeReturn;
3326         }
3327
3328       /* if left is a literal then do it */
3329       if (IS_LITERAL (LTYPE (tree)))
3330         {
3331           tree->type = EX_VALUE;
3332           tree->opval.val = valComplement (valFromType (LETYPE (tree)));
3333           tree->left = NULL;
3334           TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
3335           return tree;
3336         }
3337       LRVAL (tree) = 1;
3338       COPYTYPE (TTYPE (tree), TETYPE (tree), LTYPE (tree));
3339       return tree;
3340
3341       /*------------------------------------------------------------------*/
3342       /*----------------------------*/
3343       /*           not              */
3344       /*----------------------------*/
3345     case '!':
3346       /* can be pointer */
3347       if (!IS_ARITHMETIC (LTYPE (tree)) &&
3348           !IS_PTR (LTYPE (tree)) &&
3349           !IS_ARRAY (LTYPE (tree)))
3350         {
3351           werror (E_UNARY_OP, tree->opval.op);
3352           goto errorTreeReturn;
3353         }
3354
3355       /* if left is a literal then do it */
3356       if (IS_LITERAL (LTYPE (tree)))
3357         {
3358           tree->type = EX_VALUE;
3359           tree->opval.val = valNot (valFromType (LETYPE (tree)));
3360           tree->left = NULL;
3361           TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
3362           return tree;
3363         }
3364       LRVAL (tree) = 1;
3365       TTYPE (tree) = TETYPE (tree) = newCharLink ();
3366       return tree;
3367
3368       /*------------------------------------------------------------------*/
3369       /*----------------------------*/
3370       /*           shift            */
3371       /*----------------------------*/
3372     case RRC:
3373     case RLC:
3374     case SWAP:
3375       TTYPE (tree) = LTYPE (tree);
3376       TETYPE (tree) = LETYPE (tree);
3377       return tree;
3378
3379     case GETHBIT:
3380       TTYPE (tree) = TETYPE (tree) = newCharLink ();
3381       return tree;
3382
3383     case LEFT_OP:
3384     case RIGHT_OP:
3385       if (!IS_INTEGRAL (LTYPE (tree)) || !IS_INTEGRAL (tree->left->etype))
3386         {
3387           werror (E_SHIFT_OP_INVALID);
3388           werror (W_CONTINUE, "left & right types are ");
3389           printTypeChain (LTYPE (tree), stderr);
3390           fprintf (stderr, ",");
3391           printTypeChain (RTYPE (tree), stderr);
3392           fprintf (stderr, "\n");
3393           goto errorTreeReturn;
3394         }
3395
3396       /* make smaller type only if it's a LEFT_OP */
3397       if (tree->opval.op == LEFT_OP)
3398         tree->left = addCast (tree->left, resultType, TRUE);
3399       
3400       /* if they are both literal then */
3401       /* rewrite the tree */
3402       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
3403         {
3404           tree->type = EX_VALUE;
3405           tree->opval.val = valShift (valFromType (LETYPE (tree)),
3406                                       valFromType (RETYPE (tree)),
3407                                       (tree->opval.op == LEFT_OP ? 1 : 0));
3408           tree->right = tree->left = NULL;
3409           TETYPE (tree) = getSpec (TTYPE (tree) =
3410                                    tree->opval.val->type);
3411           return tree;
3412         }
3413
3414       LRVAL (tree) = RRVAL (tree) = 1;
3415       if (tree->opval.op == LEFT_OP)
3416         {
3417           TETYPE (tree) = getSpec (TTYPE (tree) =
3418                                        computeType (LTYPE (tree),
3419                                                     NULL,
3420                                                     resultType,
3421                                                     tree->opval.op));
3422         }
3423       else /* RIGHT_OP */
3424         {
3425           /* no promotion necessary */
3426           TTYPE (tree) = TETYPE (tree) = copyLinkChain (LTYPE (tree));
3427           if (IS_LITERAL (TTYPE (tree)))
3428             SPEC_SCLS (TTYPE (tree)) &= ~S_LITERAL;
3429         }
3430
3431       /* if only the right side is a literal & we are
3432          shifting more than size of the left operand then zero */
3433       if (IS_LITERAL (RTYPE (tree)) &&
3434           ((TYPE_UDWORD) floatFromVal (valFromType (RETYPE (tree)))) >=
3435           (getSize (TETYPE (tree)) * 8))
3436         {
3437           if (tree->opval.op==LEFT_OP ||
3438               (tree->opval.op==RIGHT_OP && SPEC_USIGN(LETYPE(tree))))
3439             {
3440               lineno=tree->lineno;
3441               werror (W_SHIFT_CHANGED,
3442                       (tree->opval.op == LEFT_OP ? "left" : "right"));
3443               tree->type = EX_VALUE;
3444               tree->left = tree->right = NULL;
3445               tree->opval.val = constVal ("0");
3446               TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
3447               return tree;
3448             }
3449         }
3450
3451       return tree;
3452
3453       /*------------------------------------------------------------------*/
3454       /*----------------------------*/
3455       /*         casting            */
3456       /*----------------------------*/
3457     case CAST:                  /* change the type   */
3458       /* cannot cast to an aggregate type */
3459       if (IS_AGGREGATE (LTYPE (tree)))
3460         {
3461           werror (E_CAST_ILLEGAL);
3462           goto errorTreeReturn;
3463         }
3464
3465       /* make sure the type is complete and sane */
3466       checkTypeSanity(LETYPE(tree), "(cast)");
3467
3468       /* If code memory is read only, then pointers to code memory */
3469       /* implicitly point to constants -- make this explicit       */
3470       {
3471         sym_link *t = LTYPE(tree);
3472         while (t && t->next)
3473           {
3474             if (IS_CODEPTR(t) && port->mem.code_ro)
3475               {
3476                 if (IS_SPEC(t->next))
3477                   SPEC_CONST (t->next) = 1;
3478                 else
3479                   DCL_PTR_CONST (t->next) = 1;
3480               }
3481             t = t->next;
3482           }
3483       }
3484
3485 #if 0
3486       /* if the right is a literal replace the tree */
3487       if (IS_LITERAL (RETYPE (tree))) {
3488               if (!IS_PTR (LTYPE (tree))) {
3489                       tree->type = EX_VALUE;
3490                       tree->opval.val =
3491                               valCastLiteral (LTYPE (tree),
3492                                               floatFromVal (valFromType (RETYPE (tree))));
3493                       tree->left = NULL;
3494                       tree->right = NULL;
3495                       TTYPE (tree) = tree->opval.val->type;
3496                       tree->values.literalFromCast = 1;
3497               } else if (IS_GENPTR(LTYPE(tree)) && !IS_PTR(RTYPE(tree)) &&
3498                          ((int)floatFromVal(valFromType(RETYPE(tree)))) !=0 ) /* special case of NULL */  {
3499                       sym_link *rest = LTYPE(tree)->next;
3500                       werror(W_LITERAL_GENERIC);
3501                       TTYPE(tree) = newLink(DECLARATOR);
3502                       DCL_TYPE(TTYPE(tree)) = FPOINTER;
3503                       TTYPE(tree)->next = rest;
3504                       tree->left->opval.lnk = TTYPE(tree);
3505                       LRVAL (tree) = 1;
3506               } else {
3507                       TTYPE (tree) = LTYPE (tree);
3508                       LRVAL (tree) = 1;
3509               }
3510       } else {
3511               TTYPE (tree) = LTYPE (tree);
3512               LRVAL (tree) = 1;
3513       }
3514 #else
3515 #if 0 // this is already checked, now this could be explicit
3516       /* if pointer to struct then check names */
3517       if (IS_PTR(LTYPE(tree)) && IS_STRUCT(LTYPE(tree)->next) &&
3518           IS_PTR(RTYPE(tree)) && IS_STRUCT(RTYPE(tree)->next) &&
3519           strcmp(SPEC_STRUCT(LETYPE(tree))->tag,SPEC_STRUCT(RETYPE(tree))->tag))
3520         {
3521           werror(W_CAST_STRUCT_PTR,SPEC_STRUCT(RETYPE(tree))->tag,
3522                  SPEC_STRUCT(LETYPE(tree))->tag);
3523         }
3524 #endif
3525       if (IS_ADDRESS_OF_OP(tree->right)
3526           && IS_AST_SYM_VALUE (tree->right->left)
3527           && SPEC_ABSA (AST_SYMBOL (tree->right->left)->etype)) {
3528
3529         tree->type = EX_VALUE;
3530         tree->opval.val =
3531           valCastLiteral (LTYPE (tree),
3532                           SPEC_ADDR (AST_SYMBOL (tree->right->left)->etype));
3533         TTYPE (tree) = tree->opval.val->type;
3534         TETYPE (tree) = getSpec (TTYPE (tree));
3535         tree->left = NULL;
3536         tree->right = NULL;
3537         tree->values.literalFromCast = 1;
3538         return tree;
3539       }
3540
3541       /* handle offsetof macro:            */
3542       /* #define offsetof(TYPE, MEMBER) \  */
3543       /* ((unsigned) &((TYPE *)0)->MEMBER) */
3544       if (IS_ADDRESS_OF_OP(tree->right)
3545           && IS_AST_OP (tree->right->left)
3546           && tree->right->left->opval.op == PTR_OP
3547           && IS_AST_OP (tree->right->left->left)
3548           && tree->right->left->left->opval.op == CAST
3549           && IS_AST_LIT_VALUE(tree->right->left->left->right)) {
3550
3551         symbol *element = getStructElement (
3552           SPEC_STRUCT (LETYPE(tree->right->left)),
3553           AST_SYMBOL(tree->right->left->right)
3554         );
3555
3556         if (element) {
3557           tree->type = EX_VALUE;
3558           tree->opval.val = valCastLiteral (
3559             LTYPE (tree),
3560             element->offset
3561             + floatFromVal (valFromType (RTYPE (tree->right->left->left)))
3562           );
3563
3564           TTYPE (tree) = tree->opval.val->type;
3565           TETYPE (tree) = getSpec (TTYPE (tree));
3566           tree->left = NULL;
3567           tree->right = NULL;
3568           return tree;
3569         }
3570       }
3571
3572       /* if the right is a literal replace the tree */
3573       if (IS_LITERAL (RETYPE (tree))) {
3574         #if 0
3575         if (IS_PTR (LTYPE (tree)) && !IS_GENPTR (LTYPE (tree)) ) {
3576           /* rewrite      (type *)litaddr
3577              as           &temp
3578              and define   type at litaddr temp
3579              (but only if type's storage class is not generic)
3580           */
3581           ast *newTree = newNode ('&', NULL, NULL);
3582           symbol *sym;
3583
3584           TTYPE (newTree) = LTYPE (tree);
3585           TETYPE (newTree) = getSpec(LTYPE (tree));
3586
3587           /* define a global symbol at the casted address*/
3588           sym = newSymbol(genSymName (0), 0);
3589           sym->type = LTYPE (tree)->next;
3590           if (!sym->type)
3591             sym->type = newLink (V_VOID);
3592           sym->etype = getSpec(sym->type);
3593           SPEC_SCLS (sym->etype) = sclsFromPtr (LTYPE (tree));
3594           sym->lineDef = tree->lineno;
3595           sym->cdef = 1;
3596           sym->isref = 1;
3597           SPEC_STAT (sym->etype) = 1;
3598           SPEC_ADDR(sym->etype) = floatFromVal (valFromType (RTYPE (tree)));
3599           SPEC_ABSA(sym->etype) = 1;
3600           addSym (SymbolTab, sym, sym->name, 0, 0, 0);
3601           allocGlobal (sym);
3602
3603           newTree->left = newAst_VALUE(symbolVal(sym));
3604           newTree->left->lineno = tree->lineno;
3605           LTYPE (newTree) = sym->type;
3606           LETYPE (newTree) = sym->etype;
3607           LLVAL (newTree) = 1;
3608           LRVAL (newTree) = 0;
3609           TLVAL (newTree) = 1;
3610           return newTree;
3611         }
3612         #endif
3613         if (!IS_PTR (LTYPE (tree))) {
3614           tree->type = EX_VALUE;
3615           tree->opval.val =
3616           valCastLiteral (LTYPE (tree),
3617                           floatFromVal (valFromType (RTYPE (tree))));
3618           TTYPE (tree) = tree->opval.val->type;
3619           tree->left = NULL;
3620           tree->right = NULL;
3621           tree->values.literalFromCast = 1;
3622           TETYPE (tree) = getSpec (TTYPE (tree));
3623           return tree;
3624         }
3625       }
3626       TTYPE (tree) = LTYPE (tree);
3627       LRVAL (tree) = 1;
3628
3629 #endif
3630       TETYPE (tree) = getSpec (TTYPE (tree));
3631
3632       return tree;
3633
3634       /*------------------------------------------------------------------*/
3635       /*----------------------------*/
3636       /*       logical &&, ||       */
3637       /*----------------------------*/
3638     case AND_OP:
3639     case OR_OP:
3640       /* each must be arithmetic type or be a pointer */
3641       if (!IS_PTR (LTYPE (tree)) &&
3642           !IS_ARRAY (LTYPE (tree)) &&
3643           !IS_INTEGRAL (LTYPE (tree)))
3644         {
3645           werror (E_COMPARE_OP);
3646           goto errorTreeReturn;
3647         }
3648
3649       if (!IS_PTR (RTYPE (tree)) &&
3650           !IS_ARRAY (RTYPE (tree)) &&
3651           !IS_INTEGRAL (RTYPE (tree)))
3652         {
3653           werror (E_COMPARE_OP);
3654           goto errorTreeReturn;
3655         }
3656       /* if they are both literal then */
3657       /* rewrite the tree */
3658       if (IS_LITERAL (RTYPE (tree)) &&
3659           IS_LITERAL (LTYPE (tree)))
3660         {
3661           tree->type = EX_VALUE;
3662           tree->opval.val = valLogicAndOr (valFromType (LTYPE (tree)),
3663                                            valFromType (RTYPE (tree)),
3664                                            tree->opval.op);
3665           tree->right = tree->left = NULL;
3666           TETYPE (tree) = getSpec (TTYPE (tree) =
3667                                    tree->opval.val->type);
3668           return tree;
3669         }
3670       LRVAL (tree) = RRVAL (tree) = 1;
3671       TTYPE (tree) = TETYPE (tree) = newCharLink ();
3672       return tree;
3673
3674       /*------------------------------------------------------------------*/
3675       /*----------------------------*/
3676       /*     comparison operators   */
3677       /*----------------------------*/
3678     case '>':
3679     case '<':
3680     case LE_OP:
3681     case GE_OP:
3682     case EQ_OP:
3683     case NE_OP:
3684       {
3685         ast *lt = optimizeCompare (tree);
3686
3687         if (tree != lt)
3688           return lt;
3689       }
3690
3691       /* if they are pointers they must be castable */
3692       if (IS_PTR (LTYPE (tree)) && IS_PTR (RTYPE (tree)))
3693         {
3694           if (tree->opval.op==EQ_OP &&
3695               !IS_GENPTR(LTYPE(tree)) && IS_GENPTR(RTYPE(tree))) {
3696             // we cannot cast a gptr to a !gptr: switch the leaves
3697             struct ast *s=tree->left;
3698             tree->left=tree->right;
3699             tree->right=s;
3700           }
3701           if (compareType (LTYPE (tree), RTYPE (tree)) == 0)
3702             {
3703               werror (E_COMPARE_OP);
3704               fprintf (stderr, "comparing type ");
3705               printTypeChain (LTYPE (tree), stderr);
3706               fprintf (stderr, "to type ");
3707               printTypeChain (RTYPE (tree), stderr);
3708               fprintf (stderr, "\n");
3709               goto errorTreeReturn;
3710             }
3711         }
3712       /* else they should be promotable to one another */
3713       else
3714         {
3715           if (!((IS_PTR (LTYPE (tree)) && IS_LITERAL (RTYPE (tree))) ||
3716                 (IS_PTR (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))))
3717
3718             if (compareType (LTYPE (tree), RTYPE (tree)) == 0)
3719               {
3720                 werror (E_COMPARE_OP);
3721                 fprintf (stderr, "comparing type ");
3722                 printTypeChain (LTYPE (tree), stderr);
3723                 fprintf (stderr, "to type ");
3724                 printTypeChain (RTYPE (tree), stderr);
3725                 fprintf (stderr, "\n");
3726                 goto errorTreeReturn;
3727               }
3728         }
3729       /* if unsigned value < 0  then always false */
3730       /* if (unsigned value) > 0 then '(unsigned value) ? 1 : 0' */
3731       if (SPEC_USIGN(LETYPE(tree)) &&
3732           !IS_CHAR(LETYPE(tree)) && /* promotion to signed int */
3733           IS_LITERAL(RTYPE(tree))  &&
3734           ((int) floatFromVal (valFromType (RETYPE (tree)))) == 0)
3735         {
3736           if (tree->opval.op == '<')
3737             {
3738               return tree->right;
3739             }
3740           if (tree->opval.op == '>')
3741             {
3742               if (resultType == RESULT_TYPE_IFX)
3743                 {
3744                   /* the parent is an ifx: */
3745                   /* if (unsigned value) */
3746                   return tree->left;
3747                 }
3748               
3749               /* (unsigned value) ? 1 : 0 */
3750               tree->opval.op = '?';
3751               tree->right = newNode (':',
3752                                      newAst_VALUE (constVal ("1")),
3753                                      tree->right); /* val 0 */
3754               tree->right->lineno = tree->lineno;
3755               tree->right->left->lineno = tree->lineno;
3756               decorateType (tree->right, RESULT_CHECK);
3757             }
3758         }
3759       /* if they are both literal then */
3760       /* rewrite the tree */
3761       if (IS_LITERAL (RTYPE (tree)) &&
3762           IS_LITERAL (LTYPE (tree)))
3763         {
3764           tree->type = EX_VALUE;
3765           tree->opval.val = valCompare (valFromType (LETYPE (tree)),
3766                                         valFromType (RETYPE (tree)),
3767                                         tree->opval.op);
3768           tree->right = tree->left = NULL;
3769           TETYPE (tree) = getSpec (TTYPE (tree) =
3770                                    tree->opval.val->type);
3771           return tree;
3772         }
3773       LRVAL (tree) = RRVAL (tree) = 1;
3774       TTYPE (tree) = TETYPE (tree) = newCharLink ();
3775       return tree;
3776
3777       /*------------------------------------------------------------------*/
3778       /*----------------------------*/
3779       /*             sizeof         */
3780       /*----------------------------*/
3781     case SIZEOF:                /* evaluate wihout code generation */
3782       /* change the type to a integer */
3783       {
3784         int size = getSize (tree->right->ftype);
3785         SNPRINTF(buffer, sizeof(buffer), "%d", size);
3786         if (!size && !IS_VOID(tree->right->ftype))
3787           werrorfl (tree->filename, tree->lineno, E_SIZEOF_INCOMPLETE_TYPE);
3788       }
3789       tree->type = EX_VALUE;
3790       tree->opval.val = constVal (buffer);
3791       tree->right = tree->left = NULL;
3792       TETYPE (tree) = getSpec (TTYPE (tree) =
3793                                tree->opval.val->type);
3794       return tree;
3795
3796       /*------------------------------------------------------------------*/
3797       /*----------------------------*/
3798       /*             typeof         */
3799       /*----------------------------*/
3800     case TYPEOF:
3801         /* return typeof enum value */
3802         tree->type = EX_VALUE;
3803         {
3804             int typeofv = 0;
3805             if (IS_SPEC(tree->right->ftype)) {
3806                 switch (SPEC_NOUN(tree->right->ftype)) {
3807                 case V_INT:
3808                     if (SPEC_LONG(tree->right->ftype)) typeofv = TYPEOF_LONG;
3809                     else typeofv = TYPEOF_INT;
3810                     break;
3811                 case V_FLOAT:
3812                     typeofv = TYPEOF_FLOAT;
3813                     break;
3814                 case V_CHAR:
3815                     typeofv = TYPEOF_CHAR;
3816                     break;
3817                 case V_VOID:
3818                     typeofv = TYPEOF_VOID;
3819                     break;
3820                 case V_STRUCT:
3821                     typeofv = TYPEOF_STRUCT;
3822                     break;
3823                 case V_BITFIELD:
3824                     typeofv = TYPEOF_BITFIELD;
3825                     break;
3826                 case V_BIT:
3827                     typeofv = TYPEOF_BIT;
3828                     break;
3829                 case V_SBIT:
3830                     typeofv = TYPEOF_SBIT;
3831                     break;
3832                 default:
3833                     break;
3834                 }
3835             } else {
3836                 switch (DCL_TYPE(tree->right->ftype)) {
3837                 case POINTER:
3838                     typeofv = TYPEOF_POINTER;
3839                     break;
3840                 case FPOINTER:
3841                     typeofv = TYPEOF_FPOINTER;
3842                     break;
3843                 case CPOINTER:
3844                     typeofv = TYPEOF_CPOINTER;
3845                     break;
3846                 case GPOINTER:
3847                     typeofv = TYPEOF_GPOINTER;
3848                     break;
3849                 case PPOINTER:
3850                     typeofv = TYPEOF_PPOINTER;
3851                     break;
3852                 case IPOINTER:
3853                     typeofv = TYPEOF_IPOINTER;
3854                     break;
3855                 case ARRAY:
3856                     typeofv = TYPEOF_ARRAY;
3857                     break;
3858                 case FUNCTION:
3859                     typeofv = TYPEOF_FUNCTION;
3860                     break;
3861                 default:
3862                     break;
3863                 }
3864             }
3865             SNPRINTF (buffer, sizeof(buffer), "%d", typeofv);
3866             tree->opval.val = constVal (buffer);
3867             tree->right = tree->left = NULL;
3868             TETYPE (tree) = getSpec (TTYPE (tree) =
3869                                      tree->opval.val->type);
3870         }
3871         return tree;
3872       /*------------------------------------------------------------------*/
3873       /*----------------------------*/
3874       /* conditional operator  '?'  */
3875       /*----------------------------*/
3876     case '?':
3877       /* the type is value of the colon operator (on the right) */
3878       assert (IS_COLON_OP (tree->right));
3879       /* if already known then replace the tree : optimizer will do it
3880          but faster to do it here */
3881       if (IS_LITERAL (LTYPE (tree)))
3882         {
3883           if (((int) floatFromVal (valFromType (LETYPE (tree)))) != 0)
3884             return decorateType (tree->right->left, resultTypeProp);
3885           else
3886             return decorateType (tree->right->right, resultTypeProp);
3887         }
3888       else
3889         {
3890           tree->right = decorateType (tree->right, resultTypeProp);
3891           TTYPE (tree) = RTYPE (tree);
3892           TETYPE (tree) = getSpec (TTYPE (tree));
3893         }
3894       return tree;
3895
3896     case ':':
3897       /* if they don't match we have a problem */
3898       if (compareType (LTYPE (tree), RTYPE (tree)) == 0)
3899         {
3900           werror (E_TYPE_MISMATCH, "conditional operator", " ");
3901           goto errorTreeReturn;
3902         }
3903
3904       TTYPE (tree) = computeType (LTYPE (tree), RTYPE (tree),
3905                                   resultType, tree->opval.op);
3906       TETYPE (tree) = getSpec (TTYPE (tree));
3907       return tree;
3908
3909
3910 #if 0 // assignment operators are converted by the parser
3911       /*------------------------------------------------------------------*/
3912       /*----------------------------*/
3913       /*    assignment operators    */
3914       /*----------------------------*/
3915     case MUL_ASSIGN:
3916     case DIV_ASSIGN:
3917       /* for these it must be both must be integral */
3918       if (!IS_ARITHMETIC (LTYPE (tree)) ||
3919           !IS_ARITHMETIC (RTYPE (tree)))
3920         {
3921           werror (E_OPS_INTEGRAL);
3922           goto errorTreeReturn;
3923         }
3924       RRVAL (tree) = 1;
3925       TETYPE (tree) = getSpec (TTYPE (tree) = LTYPE (tree));
3926
3927       if (!tree->initMode && IS_CONSTANT (LTYPE (tree)))
3928         werror (E_CODE_WRITE, tree->opval.op==MUL_ASSIGN ? "*=" : "/=");
3929
3930       if (LRVAL (tree))
3931         {
3932           werror (E_LVALUE_REQUIRED, tree->opval.op==MUL_ASSIGN ? "*=" : "/=");
3933           goto errorTreeReturn;
3934         }
3935       LLVAL (tree) = 1;
3936
3937       return tree;
3938
3939     case AND_ASSIGN:
3940     case OR_ASSIGN:
3941     case XOR_ASSIGN:
3942     case RIGHT_ASSIGN:
3943     case LEFT_ASSIGN:
3944       /* for these it must be both must be integral */
3945       if (!IS_INTEGRAL (LTYPE (tree)) ||
3946           !IS_INTEGRAL (RTYPE (tree)))
3947         {
3948           werror (E_OPS_INTEGRAL);
3949           goto errorTreeReturn;
3950         }
3951       RRVAL (tree) = 1;
3952       TETYPE (tree) = getSpec (TTYPE (tree) = LTYPE (tree));
3953
3954       if (!tree->initMode && IS_CONSTANT (LETYPE (tree)))
3955         werror (E_CODE_WRITE, "&= or |= or ^= or >>= or <<=");
3956
3957       if (LRVAL (tree))
3958         {
3959           werror (E_LVALUE_REQUIRED, "&= or |= or ^= or >>= or <<=");
3960           goto errorTreeReturn;
3961         }
3962       LLVAL (tree) = 1;
3963
3964       return tree;
3965
3966       /*------------------------------------------------------------------*/
3967       /*----------------------------*/
3968       /*    -= operator             */
3969       /*----------------------------*/
3970     case SUB_ASSIGN:
3971       if (!(IS_PTR (LTYPE (tree)) ||
3972             IS_ARITHMETIC (LTYPE (tree))))
3973         {
3974           werror (E_PLUS_INVALID, "-=");
3975           goto errorTreeReturn;
3976         }
3977
3978       if (!(IS_PTR (RTYPE (tree)) ||
3979             IS_ARITHMETIC (RTYPE (tree))))
3980         {
3981           werror (E_PLUS_INVALID, "-=");
3982           goto errorTreeReturn;
3983         }
3984       RRVAL (tree) = 1;
3985       TETYPE (tree) = getSpec (TTYPE (tree) =
3986                                computeType (LTYPE (tree),
3987                                             RTYPE (tree),
3988                                             RESULT_TYPE_NOPROM,
3989                                             tree->opval.op));
3990
3991       if (!tree->initMode && IS_CONSTANT (LETYPE (tree)))
3992         werror (E_CODE_WRITE, "-=");
3993
3994       if (LRVAL (tree))
3995         {
3996           werror (E_LVALUE_REQUIRED, "-=");
3997           goto errorTreeReturn;
3998         }
3999       LLVAL (tree) = 1;
4000
4001       return tree;
4002
4003       /*------------------------------------------------------------------*/
4004       /*----------------------------*/
4005       /*          += operator       */
4006       /*----------------------------*/
4007     case ADD_ASSIGN:
4008       /* this is not a unary operation */
4009       /* if both pointers then problem */
4010       if (IS_PTR (LTYPE (tree)) && IS_PTR (RTYPE (tree)))
4011         {
4012           werror (E_PTR_PLUS_PTR);
4013           goto errorTreeReturn;
4014         }
4015
4016       if (!IS_ARITHMETIC (LTYPE (tree)) && !IS_PTR (LTYPE (tree)))
4017         {
4018           werror (E_PLUS_INVALID, "+=");
4019           goto errorTreeReturn;
4020         }
4021
4022       if (!IS_ARITHMETIC (RTYPE (tree)) && !IS_PTR (RTYPE (tree)))
4023         {
4024           werror (E_PLUS_INVALID, "+=");
4025           goto errorTreeReturn;
4026         }
4027       RRVAL (tree) = 1;
4028       TETYPE (tree) = getSpec (TTYPE (tree) =
4029                                computeType (LTYPE (tree),
4030                                             RTYPE (tree),
4031                                             RESULT_TYPE_NOPROM,
4032                                             tree->opval.op));
4033
4034       if (!tree->initMode && IS_CONSTANT (LETYPE (tree)))
4035         werror (E_CODE_WRITE, "+=");
4036
4037       if (LRVAL (tree))
4038         {
4039           werror (E_LVALUE_REQUIRED, "+=");
4040           goto errorTreeReturn;
4041         }
4042
4043       tree->right = decorateType (newNode ('+', copyAst (tree->left), tree->right), RESULT_CHECK);
4044       tree->opval.op = '=';
4045
4046       return tree;
4047 #endif
4048
4049       /*------------------------------------------------------------------*/
4050       /*----------------------------*/
4051       /*      straight assignemnt   */
4052       /*----------------------------*/
4053     case '=':
4054       /* cannot be an aggregate */
4055       if (IS_AGGREGATE (LTYPE (tree)))
4056         {
4057           werror (E_AGGR_ASSIGN);
4058           goto errorTreeReturn;
4059         }
4060
4061       /* they should either match or be castable */
4062       if (compareType (LTYPE (tree), RTYPE (tree)) == 0)
4063         {
4064           werror (E_TYPE_MISMATCH, "assignment", " ");
4065           printFromToType(RTYPE(tree),LTYPE(tree));
4066         }
4067
4068       /* if the left side of the tree is of type void
4069          then report error */
4070       if (IS_VOID (LTYPE (tree)))
4071         {
4072           werror (E_CAST_ZERO);
4073           printFromToType(RTYPE(tree), LTYPE(tree));
4074         }
4075
4076       TETYPE (tree) = getSpec (TTYPE (tree) =
4077                                LTYPE (tree));
4078       RRVAL (tree) = 1;
4079       LLVAL (tree) = 1;
4080       if (!tree->initMode ) {
4081         if (IS_CONSTANT(LTYPE(tree)))
4082           werror (E_CODE_WRITE, "=");
4083       }
4084       if (LRVAL (tree))
4085         {
4086           werror (E_LVALUE_REQUIRED, "=");
4087           goto errorTreeReturn;
4088         }
4089
4090       return tree;
4091
4092       /*------------------------------------------------------------------*/
4093       /*----------------------------*/
4094       /*      comma operator        */
4095       /*----------------------------*/
4096     case ',':
4097       TETYPE (tree) = getSpec (TTYPE (tree) = RTYPE (tree));
4098       return tree;
4099
4100       /*------------------------------------------------------------------*/
4101       /*----------------------------*/
4102       /*       function call        */
4103       /*----------------------------*/
4104     case CALL:
4105       
4106       /* undo any explicit pointer derefernce; PCALL will handle it instead */
4107       if (IS_FUNC (LTYPE (tree)) && tree->left->type == EX_OP)
4108         {
4109           if (tree->left->opval.op == '*' && !tree->left->right)
4110             tree->left = tree->left->left;
4111         }
4112
4113       /* require a function or pointer to function */
4114       if (!IS_FUNC (LTYPE (tree))
4115           && !(IS_CODEPTR (LTYPE (tree)) && IS_FUNC (LTYPE (tree)->next)))
4116         {
4117           werrorfl (tree->filename, tree->lineno, E_FUNCTION_EXPECTED);
4118           goto errorTreeReturn;
4119         }
4120
4121       {
4122         sym_link *functype;      
4123         parmNumber = 1;
4124
4125         if (IS_CODEPTR(LTYPE(tree)))
4126           functype = LTYPE (tree)->next;
4127         else
4128           functype = LTYPE (tree);
4129
4130         if (processParms (tree->left, FUNC_ARGS(functype),
4131                           &tree->right, &parmNumber, TRUE)) {
4132           goto errorTreeReturn;
4133         }
4134
4135         if ((options.stackAuto || IFFUNC_ISREENT (functype)) && 
4136             !IFFUNC_ISBUILTIN(functype))
4137           {
4138             reverseParms (tree->right);
4139           }
4140
4141         TTYPE (tree) = functype->next;
4142         TETYPE (tree) = getSpec (TTYPE (tree));
4143       }
4144       return tree;
4145
4146       /*------------------------------------------------------------------*/
4147       /*----------------------------*/
4148       /*     return statement       */
4149       /*----------------------------*/
4150     case RETURN:
4151       if (!tree->right)
4152         goto voidcheck;
4153
4154       if (compareType (currFunc->type->next, RTYPE (tree)) == 0)
4155         {
4156           werrorfl (tree->filename, tree->lineno, W_RETURN_MISMATCH);
4157           printFromToType (RTYPE(tree), currFunc->type->next);
4158           goto errorTreeReturn;
4159         }
4160
4161       if (IS_VOID (currFunc->type->next)
4162           && tree->right &&
4163           !IS_VOID (RTYPE (tree)))
4164         {
4165           werrorfl (tree->filename, tree->lineno, E_FUNC_VOID);
4166           goto errorTreeReturn;
4167         }
4168
4169       /* if there is going to be a casting required then add it */
4170       if (compareType (currFunc->type->next, RTYPE (tree)) < 0)
4171         {
4172           tree->right =
4173             decorateType (newNode (CAST,
4174                           newAst_LINK (copyLinkChain (currFunc->type->next)),
4175                                         tree->right),
4176                           RESULT_CHECK);
4177         }
4178
4179       RRVAL (tree) = 1;
4180       return tree;
4181
4182     voidcheck:
4183
4184       if (!IS_VOID (currFunc->type->next) && tree->right == NULL)
4185         {
4186           werror (W_VOID_FUNC, currFunc->name);
4187           goto errorTreeReturn;
4188         }
4189
4190       TTYPE (tree) = TETYPE (tree) = NULL;
4191       return tree;
4192
4193       /*------------------------------------------------------------------*/
4194       /*----------------------------*/
4195       /*     switch statement       */
4196       /*----------------------------*/
4197     case SWITCH:
4198       /* the switch value must be an integer */
4199       if (!IS_INTEGRAL (LTYPE (tree)))
4200         {
4201           werrorfl (tree->filename, tree->lineno, E_SWITCH_NON_INTEGER);
4202           goto errorTreeReturn;
4203         }
4204       LRVAL (tree) = 1;
4205       TTYPE (tree) = TETYPE (tree) = NULL;
4206       return tree;
4207
4208       /*------------------------------------------------------------------*/
4209       /*----------------------------*/
4210       /* ifx Statement              */
4211       /*----------------------------*/
4212     case IFX:
4213       tree->left = backPatchLabels (tree->left,
4214                                     tree->trueLabel,
4215                                     tree->falseLabel);
4216       TTYPE (tree) = TETYPE (tree) = NULL;
4217       return tree;
4218
4219       /*------------------------------------------------------------------*/
4220       /*----------------------------*/
4221       /* for Statement              */
4222       /*----------------------------*/
4223     case FOR:
4224
4225       decorateType (resolveSymbols (AST_FOR (tree, initExpr)), RESULT_CHECK);
4226       decorateType (resolveSymbols (AST_FOR (tree, condExpr)), RESULT_CHECK);
4227       decorateType (resolveSymbols (AST_FOR (tree, loopExpr)), RESULT_CHECK);
4228
4229       /* if the for loop is reversible then
4230          reverse it otherwise do what we normally
4231          do */
4232       {
4233         symbol *sym;
4234         ast *init, *end;
4235
4236         if (isLoopReversible (tree, &sym, &init, &end))
4237           return reverseLoop (tree, sym, init, end);
4238         else
4239           return decorateType (createFor (AST_FOR (tree, trueLabel),
4240                                           AST_FOR (tree, continueLabel),
4241                                           AST_FOR (tree, falseLabel),
4242                                           AST_FOR (tree, condLabel),
4243                                           AST_FOR (tree, initExpr),
4244                                           AST_FOR (tree, condExpr),
4245                                           AST_FOR (tree, loopExpr),
4246                                           tree->left), RESULT_CHECK);
4247       }
4248     case PARAM:
4249       werror (E_INTERNAL_ERROR, __FILE__, __LINE__,
4250               "node PARAM shouldn't be processed here");
4251               /* but in processParams() */
4252       return tree;
4253     default:
4254       TTYPE (tree) = TETYPE (tree) = NULL;
4255       return tree;
4256     }
4257
4258   /* some error found this tree will be killed */
4259 errorTreeReturn:
4260   TTYPE (tree) = TETYPE (tree) = newCharLink ();
4261   tree->opval.op = NULLOP;
4262   tree->isError = 1;
4263
4264   return tree;
4265 }
4266
4267 /*-----------------------------------------------------------------*/
4268 /* sizeofOp - processes size of operation                          */
4269 /*-----------------------------------------------------------------*/
4270 value *
4271 sizeofOp (sym_link * type)
4272 {
4273   char buff[10];
4274   int size;
4275
4276   /* make sure the type is complete and sane */
4277   checkTypeSanity(type, "(sizeof)");
4278
4279   /* get the size and convert it to character  */
4280   SNPRINTF (buff, sizeof(buff), "%d", size = getSize (type));
4281   if (!size && !IS_VOID(type))
4282     werror (E_SIZEOF_INCOMPLETE_TYPE);
4283
4284   /* now convert into value  */
4285   return constVal (buff);
4286 }
4287
4288
4289 #define IS_AND(ex) (ex->type == EX_OP && ex->opval.op == AND_OP )
4290 #define IS_OR(ex)  (ex->type == EX_OP && ex->opval.op == OR_OP )
4291 #define IS_NOT(ex) (ex->type == EX_OP && ex->opval.op == '!' )
4292 #define IS_ANDORNOT(ex) (IS_AND(ex) || IS_OR(ex) || IS_NOT(ex))
4293 #define IS_IFX(ex) (ex->type == EX_OP && ex->opval.op == IFX )
4294 #define IS_LT(ex)  (ex->type == EX_OP && ex->opval.op == '<' )
4295 #define IS_GT(ex)  (ex->type == EX_OP && ex->opval.op == '>')
4296
4297 /*-----------------------------------------------------------------*/
4298 /* backPatchLabels - change and or not operators to flow control    */
4299 /*-----------------------------------------------------------------*/
4300 ast *
4301 backPatchLabels (ast * tree, symbol * trueLabel, symbol * falseLabel)
4302 {
4303
4304   if (!tree)
4305     return NULL;
4306
4307   if (!(IS_ANDORNOT (tree)))
4308     return tree;
4309
4310   /* if this an and */
4311   if (IS_AND (tree))
4312     {
4313       static int localLbl = 0;
4314       symbol *localLabel;
4315
4316       SNPRINTF(buffer, sizeof(buffer), "_andif_%d", localLbl++);
4317       localLabel = newSymbol (buffer, NestLevel);
4318
4319       tree->left = backPatchLabels (tree->left, localLabel, falseLabel);
4320
4321       /* if left is already a IFX then just change the if true label in that */
4322       if (!IS_IFX (tree->left))
4323         tree->left = newIfxNode (tree->left, localLabel, falseLabel);
4324
4325       tree->right = backPatchLabels (tree->right, trueLabel, falseLabel);
4326       /* right is a IFX then just join */
4327       if (IS_IFX (tree->right))
4328         return newNode (NULLOP, tree->left, createLabel (localLabel, tree->right));
4329
4330       tree->right = createLabel (localLabel, tree->right);
4331       tree->right = newIfxNode (tree->right, trueLabel, falseLabel);
4332
4333       return newNode (NULLOP, tree->left, tree->right);
4334     }
4335
4336   /* if this is an or operation */
4337   if (IS_OR (tree))
4338     {
4339       static int localLbl = 0;
4340       symbol *localLabel;
4341
4342       SNPRINTF(buffer, sizeof(buffer), "_orif_%d", localLbl++);
4343       localLabel = newSymbol (buffer, NestLevel);
4344
4345       tree->left = backPatchLabels (tree->left, trueLabel, localLabel);
4346
4347       /* if left is already a IFX then just change the if true label in that */
4348       if (!IS_IFX (tree->left))
4349         tree->left = newIfxNode (tree->left, trueLabel, localLabel);
4350
4351       tree->right = backPatchLabels (tree->right, trueLabel, falseLabel);
4352       /* right is a IFX then just join */
4353       if (IS_IFX (tree->right))
4354         return newNode (NULLOP, tree->left, createLabel (localLabel, tree->right));
4355
4356       tree->right = createLabel (localLabel, tree->right);
4357       tree->right = newIfxNode (tree->right, trueLabel, falseLabel);
4358
4359       return newNode (NULLOP, tree->left, tree->right);
4360     }
4361
4362   /* change not */
4363   if (IS_NOT (tree))
4364     {
4365       int wasnot = IS_NOT (tree->left);
4366       tree->left = backPatchLabels (tree->left, falseLabel, trueLabel);
4367
4368       /* if the left is already a IFX */
4369       if (!IS_IFX (tree->left))
4370         tree->left = newNode (IFX, tree->left, NULL);
4371
4372       if (wasnot)
4373         {
4374           tree->left->trueLabel = trueLabel;
4375           tree->left->falseLabel = falseLabel;
4376         }
4377       else
4378         {
4379           tree->left->trueLabel = falseLabel;
4380           tree->left->falseLabel = trueLabel;
4381         }
4382       return tree->left;
4383     }
4384
4385   if (IS_IFX (tree))
4386     {
4387       tree->trueLabel = trueLabel;
4388       tree->falseLabel = falseLabel;
4389     }
4390
4391   return tree;
4392 }
4393
4394
4395 /*-----------------------------------------------------------------*/
4396 /* createBlock - create expression tree for block                  */
4397 /*-----------------------------------------------------------------*/
4398 ast *
4399 createBlock (symbol * decl, ast * body)
4400 {
4401   ast *ex;
4402
4403   /* if the block has nothing */
4404   if (!body && !decl)
4405     return NULL;
4406
4407   ex = newNode (BLOCK, NULL, body);
4408   ex->values.sym = decl;
4409   
4410   ex->right = ex->right;
4411   ex->level++;
4412   ex->lineno = 0;
4413   return ex;
4414 }
4415
4416 /*-----------------------------------------------------------------*/
4417 /* createLabel - creates the expression tree for labels            */
4418 /*-----------------------------------------------------------------*/
4419 ast *
4420 createLabel (symbol * label, ast * stmnt)
4421 {
4422   symbol *csym;
4423   char name[SDCC_NAME_MAX + 1];
4424   ast *rValue;
4425
4426   /* must create fresh symbol if the symbol name  */
4427   /* exists in the symbol table, since there can  */
4428   /* be a variable with the same name as the labl */
4429   if ((csym = findSym (SymbolTab, NULL, label->name)) &&
4430       (csym->level == label->level))
4431     label = newSymbol (label->name, label->level);
4432
4433   /* change the name before putting it in add _ */
4434   SNPRINTF(name, sizeof(name), "%s", label->name);
4435
4436   /* put the label in the LabelSymbol table    */
4437   /* but first check if a label of the same    */
4438   /* name exists                               */
4439   if ((csym = findSym (LabelTab, NULL, name)))
4440     werror (E_DUPLICATE_LABEL, label->name);
4441   else
4442     addSym (LabelTab, label, name, label->level, 0, 0);
4443
4444   label->islbl = 1;
4445   label->key = labelKey++;
4446   rValue = newNode (LABEL, newAst_VALUE (symbolVal (label)), stmnt);
4447   rValue->lineno = 0;
4448
4449   return rValue;
4450 }
4451
4452 /*-----------------------------------------------------------------*/
4453 /* createCase - generates the parsetree for a case statement       */
4454 /*-----------------------------------------------------------------*/
4455 ast *
4456 createCase (ast * swStat, ast * caseVal, ast * stmnt)
4457 {
4458   char caseLbl[SDCC_NAME_MAX + 1];
4459   ast *rexpr;
4460   value *val;
4461
4462   /* if the switch statement does not exist */
4463   /* then case is out of context            */
4464   if (!swStat)
4465     {
4466       werrorfl (caseVal->filename, caseVal->lineno, E_CASE_CONTEXT);
4467       return NULL;
4468     }
4469
4470   caseVal = decorateType (resolveSymbols (caseVal), RESULT_CHECK);
4471   /* if not a constant then error  */
4472   if (!IS_LITERAL (caseVal->ftype))
4473     {
4474       werrorfl (caseVal->filename, caseVal->lineno, E_CASE_CONSTANT);
4475       return NULL;
4476     }
4477
4478   /* if not a integer than error */
4479   if (!IS_INTEGRAL (caseVal->ftype))
4480     {
4481       werrorfl (caseVal->filename, caseVal->lineno, E_CASE_NON_INTEGER);
4482       return NULL;
4483     }
4484
4485   /* find the end of the switch values chain   */
4486   if (!(val = swStat->values.switchVals.swVals))
4487     swStat->values.switchVals.swVals = caseVal->opval.val;
4488   else
4489     {
4490       /* also order the cases according to value */
4491       value *pval = NULL;
4492       int cVal = (int) floatFromVal (caseVal->opval.val);
4493       while (val && (int) floatFromVal (val) < cVal)
4494         {
4495           pval = val;
4496           val = val->next;
4497         }
4498
4499       /* if we reached the end then */
4500       if (!val)
4501         {
4502           pval->next = caseVal->opval.val;
4503         }
4504       else if ((int) floatFromVal (val) == cVal)
4505         {
4506           werrorfl (caseVal->filename, caseVal->lineno, E_DUPLICATE_LABEL,
4507                     "case");
4508           return NULL;
4509         }
4510       else
4511         {
4512           /* we found a value greater than */
4513           /* the current value we must add this */
4514           /* before the value */
4515           caseVal->opval.val->next = val;
4516
4517           /* if this was the first in chain */
4518           if (swStat->values.switchVals.swVals == val)
4519             swStat->values.switchVals.swVals =
4520               caseVal->opval.val;
4521           else
4522             pval->next = caseVal->opval.val;
4523         }
4524
4525     }
4526
4527   /* create the case label   */
4528   SNPRINTF(caseLbl, sizeof(caseLbl), 
4529            "_case_%d_%d",
4530            swStat->values.switchVals.swNum,
4531            (int) floatFromVal (caseVal->opval.val));
4532
4533   rexpr = createLabel (newSymbol (caseLbl, 0), stmnt);
4534   rexpr->lineno = 0;
4535   return rexpr;
4536 }
4537
4538 /*-----------------------------------------------------------------*/
4539 /* createDefault - creates the parse tree for the default statement */
4540 /*-----------------------------------------------------------------*/
4541 ast *
4542 createDefault (ast * swStat, ast * defaultVal, ast * stmnt)
4543 {
4544   char defLbl[SDCC_NAME_MAX + 1];
4545
4546   /* if the switch statement does not exist */
4547   /* then case is out of context            */
4548   if (!swStat)
4549     {
4550       werrorfl (defaultVal->filename, defaultVal->lineno, E_CASE_CONTEXT);
4551       return NULL;
4552     }
4553
4554   if (swStat->values.switchVals.swDefault)
4555     {
4556       werrorfl (defaultVal->filename, defaultVal->lineno, E_DUPLICATE_LABEL,
4557                 "default");
4558       return NULL;
4559     }
4560
4561   /* turn on the default flag   */
4562   swStat->values.switchVals.swDefault = 1;
4563
4564   /* create the label  */
4565   SNPRINTF (defLbl, sizeof(defLbl),
4566             "_default_%d", swStat->values.switchVals.swNum);
4567   return createLabel (newSymbol (defLbl, 0), stmnt);
4568 }
4569
4570 /*-----------------------------------------------------------------*/
4571 /* createIf - creates the parsetree for the if statement           */
4572 /*-----------------------------------------------------------------*/
4573 ast *
4574 createIf (ast * condAst, ast * ifBody, ast * elseBody)
4575 {
4576   static int Lblnum = 0;
4577   ast *ifTree;
4578   symbol *ifTrue, *ifFalse, *ifEnd;
4579
4580   /* if neither exists */
4581   if (!elseBody && !ifBody) {
4582     // if there are no side effects (i++, j() etc)
4583     if (!hasSEFcalls(condAst)) {
4584       return condAst;
4585     }
4586   }
4587
4588   /* create the labels */
4589   SNPRINTF (buffer, sizeof(buffer), "_iffalse_%d", Lblnum);
4590   ifFalse = newSymbol (buffer, NestLevel);
4591   /* if no else body then end == false */
4592   if (!elseBody)
4593     ifEnd = ifFalse;
4594   else
4595     {
4596       SNPRINTF(buffer, sizeof(buffer), "_ifend_%d", Lblnum);
4597       ifEnd = newSymbol (buffer, NestLevel);
4598     }
4599
4600   SNPRINTF (buffer, sizeof(buffer), "_iftrue_%d", Lblnum);
4601   ifTrue = newSymbol (buffer, NestLevel);
4602
4603   Lblnum++;
4604
4605   /* attach the ifTrue label to the top of it body */
4606   ifBody = createLabel (ifTrue, ifBody);
4607   /* attach a goto end to the ifBody if else is present */
4608   if (elseBody)
4609     {
4610       ifBody = newNode (NULLOP, ifBody,
4611                         newNode (GOTO,
4612                                  newAst_VALUE (symbolVal (ifEnd)),
4613                                  NULL));
4614       /* put the elseLabel on the else body */
4615       elseBody = createLabel (ifFalse, elseBody);
4616       /* out the end at the end of the body */
4617       elseBody = newNode (NULLOP,
4618                           elseBody,
4619                           createLabel (ifEnd, NULL));
4620     }
4621   else
4622     {
4623       ifBody = newNode (NULLOP, ifBody,
4624                         createLabel (ifFalse, NULL));
4625     }
4626   condAst = backPatchLabels (condAst, ifTrue, ifFalse);
4627   if (IS_IFX (condAst))
4628     ifTree = condAst;
4629   else
4630     ifTree = newIfxNode (condAst, ifTrue, ifFalse);
4631
4632   return newNode (NULLOP, ifTree,
4633                   newNode (NULLOP, ifBody, elseBody));
4634
4635 }
4636
4637 /*-----------------------------------------------------------------*/
4638 /* createDo - creates parse tree for do                            */
4639 /*        _dobody_n:                                               */
4640 /*            statements                                           */
4641 /*        _docontinue_n:                                           */
4642 /*            condition_expression +-> trueLabel -> _dobody_n      */
4643 /*                                 |                               */
4644 /*                                 +-> falseLabel-> _dobreak_n     */
4645 /*        _dobreak_n:                                              */
4646 /*-----------------------------------------------------------------*/
4647 ast *
4648 createDo (symbol * trueLabel, symbol * continueLabel,
4649           symbol * falseLabel, ast * condAst, ast * doBody)
4650 {
4651   ast *doTree;
4652
4653
4654   /* if the body does not exist then it is simple */
4655   if (!doBody)
4656     {
4657       condAst = backPatchLabels (condAst, continueLabel, NULL);
4658       doTree = (IS_IFX (condAst) ? createLabel (continueLabel, condAst)
4659                 : newNode (IFX, createLabel (continueLabel, condAst), NULL));
4660       doTree->trueLabel = continueLabel;
4661       doTree->falseLabel = NULL;
4662       return doTree;
4663     }
4664
4665   /* otherwise we have a body */
4666   condAst = backPatchLabels (condAst, trueLabel, falseLabel);
4667
4668   /* attach the body label to the top */
4669   doBody = createLabel (trueLabel, doBody);
4670   /* attach the continue label to end of body */
4671   doBody = newNode (NULLOP, doBody,
4672                     createLabel (continueLabel, NULL));
4673
4674   /* now put the break label at the end */
4675   if (IS_IFX (condAst))
4676     doTree = condAst;
4677   else
4678     doTree = newIfxNode (condAst, trueLabel, falseLabel);
4679
4680   doTree = newNode (NULLOP, doTree, createLabel (falseLabel, NULL));
4681
4682   /* putting it together */
4683   return newNode (NULLOP, doBody, doTree);
4684 }
4685
4686 /*-----------------------------------------------------------------*/
4687 /* createFor - creates parse tree for 'for' statement              */
4688 /*        initExpr                                                 */
4689 /*   _forcond_n:                                                   */
4690 /*        condExpr  +-> trueLabel -> _forbody_n                    */
4691 /*                  |                                              */
4692 /*                  +-> falseLabel-> _forbreak_n                   */
4693 /*   _forbody_n:                                                   */
4694 /*        statements                                               */
4695 /*   _forcontinue_n:                                               */
4696 /*        loopExpr                                                 */
4697 /*        goto _forcond_n ;                                        */
4698 /*   _forbreak_n:                                                  */
4699 /*-----------------------------------------------------------------*/
4700 ast *
4701 createFor (symbol * trueLabel, symbol * continueLabel,
4702            symbol * falseLabel, symbol * condLabel,
4703            ast * initExpr, ast * condExpr, ast * loopExpr,
4704            ast * forBody)
4705 {
4706   ast *forTree;
4707
4708   /* if loopexpression not present then we can generate it */
4709   /* the same way as a while */
4710   if (!loopExpr)
4711     return newNode (NULLOP, initExpr,
4712                     createWhile (trueLabel, continueLabel,
4713                                  falseLabel, condExpr, forBody));
4714   /* vanilla for statement */
4715   condExpr = backPatchLabels (condExpr, trueLabel, falseLabel);
4716
4717   if (condExpr && !IS_IFX (condExpr))
4718     condExpr = newIfxNode (condExpr, trueLabel, falseLabel);
4719
4720
4721   /* attach condition label to condition */
4722   condExpr = createLabel (condLabel, condExpr);
4723
4724   /* attach body label to body */
4725   forBody = createLabel (trueLabel, forBody);
4726
4727   /* attach continue to forLoop expression & attach */
4728   /* goto the forcond @ and of loopExpression       */
4729   loopExpr = createLabel (continueLabel,
4730                           newNode (NULLOP,
4731                                    loopExpr,
4732                                    newNode (GOTO,
4733                                        newAst_VALUE (symbolVal (condLabel)),
4734                                             NULL)));
4735   /* now start putting them together */
4736   forTree = newNode (NULLOP, initExpr, condExpr);
4737   forTree = newNode (NULLOP, forTree, forBody);
4738   forTree = newNode (NULLOP, forTree, loopExpr);
4739   /* finally add the break label */
4740   forTree = newNode (NULLOP, forTree,
4741                      createLabel (falseLabel, NULL));
4742   return forTree;
4743 }
4744
4745 /*-----------------------------------------------------------------*/
4746 /* createWhile - creates parse tree for while statement            */
4747 /*               the while statement will be created as follows    */
4748 /*                                                                 */
4749 /*      _while_continue_n:                                         */
4750 /*            condition_expression +-> trueLabel -> _while_boby_n  */
4751 /*                                 |                               */
4752 /*                                 +-> falseLabel -> _while_break_n */
4753 /*      _while_body_n:                                             */
4754 /*            statements                                           */
4755 /*            goto _while_continue_n                               */
4756 /*      _while_break_n:                                            */
4757 /*-----------------------------------------------------------------*/
4758 ast *
4759 createWhile (symbol * trueLabel, symbol * continueLabel,
4760              symbol * falseLabel, ast * condExpr, ast * whileBody)
4761 {
4762   ast *whileTree;
4763
4764   /* put the continue label */
4765   condExpr = backPatchLabels (condExpr, trueLabel, falseLabel);
4766   condExpr = createLabel (continueLabel, condExpr);
4767   condExpr->lineno = 0;
4768
4769   /* put the body label in front of the body */
4770   whileBody = createLabel (trueLabel, whileBody);
4771   whileBody->lineno = 0;
4772   /* put a jump to continue at the end of the body */
4773   /* and put break label at the end of the body */
4774   whileBody = newNode (NULLOP,
4775                        whileBody,
4776                        newNode (GOTO,
4777                                 newAst_VALUE (symbolVal (continueLabel)),
4778                                 createLabel (falseLabel, NULL)));
4779
4780   /* put it all together */
4781   if (IS_IFX (condExpr))
4782     whileTree = condExpr;
4783   else
4784     {
4785       whileTree = newNode (IFX, condExpr, NULL);
4786       /* put the true & false labels in place */
4787       whileTree->trueLabel = trueLabel;
4788       whileTree->falseLabel = falseLabel;
4789     }
4790
4791   return newNode (NULLOP, whileTree, whileBody);
4792 }
4793
4794 /*-----------------------------------------------------------------*/
4795 /* optimizeGetHbit - get highest order bit of the expression       */
4796 /*-----------------------------------------------------------------*/
4797 ast *
4798 optimizeGetHbit (ast * tree)
4799 {
4800   int i, j;
4801   /* if this is not a bit and */
4802   if (!IS_BITAND (tree))
4803     return tree;
4804
4805   /* will look for tree of the form
4806      ( expr >> ((sizeof expr) -1) ) & 1 */
4807   if (!IS_AST_LIT_VALUE (tree->right))
4808     return tree;
4809
4810   if (AST_LIT_VALUE (tree->right) != 1)
4811     return tree;
4812
4813   if (!IS_RIGHT_OP (tree->left))
4814     return tree;
4815
4816   if (!IS_AST_LIT_VALUE (tree->left->right))
4817     return tree;
4818
4819   if ((i = (int) AST_LIT_VALUE (tree->left->right)) !=
4820       (j = (getSize (TTYPE (tree->left->left)) * 8 - 1)))
4821     return tree;
4822       
4823   /* make sure the port supports GETHBIT */
4824   if (port->hasExtBitOp
4825       && !port->hasExtBitOp(GETHBIT, getSize (TTYPE (tree->left->left))))
4826     return tree;
4827
4828   return decorateType (newNode (GETHBIT, tree->left->left, NULL), RESULT_CHECK);
4829
4830 }
4831
4832 /*-----------------------------------------------------------------*/
4833 /* optimizeRRCRLC :- optimize for Rotate Left/Right with carry     */
4834 /*-----------------------------------------------------------------*/
4835 ast *
4836 optimizeRRCRLC (ast * root)
4837 {
4838   /* will look for trees of the form
4839      (?expr << 1) | (?expr >> 7) or
4840      (?expr >> 7) | (?expr << 1) will make that
4841      into a RLC : operation ..
4842      Will also look for
4843      (?expr >> 1) | (?expr << 7) or
4844      (?expr << 7) | (?expr >> 1) will make that
4845      into a RRC operation
4846      note : by 7 I mean (number of bits required to hold the
4847      variable -1 ) */
4848   /* if the root operations is not a | operation the not */
4849   if (!IS_BITOR (root))
4850     return root;
4851
4852   /* I have to think of a better way to match patterns this sucks */
4853   /* that aside let start looking for the first case : I use a the
4854      negative check a lot to improve the efficiency */
4855   /* (?expr << 1) | (?expr >> 7) */
4856   if (IS_LEFT_OP (root->left) &&
4857       IS_RIGHT_OP (root->right))
4858     {
4859
4860       if (!SPEC_USIGN (TETYPE (root->left->left)))
4861         return root;
4862
4863       if (!IS_AST_LIT_VALUE (root->left->right) ||
4864           !IS_AST_LIT_VALUE (root->right->right))
4865         goto tryNext0;
4866
4867       /* make sure it is the same expression */
4868       if (!isAstEqual (root->left->left,
4869                        root->right->left))
4870         goto tryNext0;
4871
4872       if (AST_LIT_VALUE (root->left->right) != 1)
4873         goto tryNext0;
4874
4875       if (AST_LIT_VALUE (root->right->right) !=
4876           (getSize (TTYPE (root->left->left)) * 8 - 1))
4877         goto tryNext0;
4878
4879       /* make sure the port supports RLC */
4880       if (port->hasExtBitOp
4881           && !port->hasExtBitOp(RLC, getSize (TTYPE (root->left->left))))
4882         return root;
4883
4884       /* whew got the first case : create the AST */
4885       return newNode (RLC, root->left->left, NULL);
4886     }
4887
4888 tryNext0:
4889   /* check for second case */
4890   /* (?expr >> 7) | (?expr << 1) */
4891   if (IS_LEFT_OP (root->right) &&
4892       IS_RIGHT_OP (root->left))
4893     {
4894
4895       if (!SPEC_USIGN (TETYPE (root->left->left)))
4896         return root;
4897
4898       if (!IS_AST_LIT_VALUE (root->left->right) ||
4899           !IS_AST_LIT_VALUE (root->right->right))
4900         goto tryNext1;
4901
4902       /* make sure it is the same symbol */
4903       if (!isAstEqual (root->left->left,
4904                        root->right->left))
4905         goto tryNext1;
4906
4907       if (AST_LIT_VALUE (root->right->right) != 1)
4908         goto tryNext1;
4909
4910       if (AST_LIT_VALUE (root->left->right) !=
4911           (getSize (TTYPE (root->left->left)) * 8 - 1))
4912         goto tryNext1;
4913
4914       /* make sure the port supports RLC */
4915       if (port->hasExtBitOp
4916           && !port->hasExtBitOp(RLC, getSize (TTYPE (root->left->left))))
4917         return root;
4918
4919       /* whew got the first case : create the AST */
4920       return newNode (RLC, root->left->left, NULL);
4921
4922     }
4923
4924 tryNext1:
4925   /* third case for RRC */
4926   /*  (?symbol >> 1) | (?symbol << 7) */
4927   if (IS_LEFT_OP (root->right) &&
4928       IS_RIGHT_OP (root->left))
4929     {
4930
4931       if (!SPEC_USIGN (TETYPE (root->left->left)))
4932         return root;
4933
4934       if (!IS_AST_LIT_VALUE (root->left->right) ||
4935           !IS_AST_LIT_VALUE (root->right->right))
4936         goto tryNext2;
4937
4938       /* make sure it is the same symbol */
4939       if (!isAstEqual (root->left->left,
4940                        root->right->left))
4941         goto tryNext2;
4942
4943       if (AST_LIT_VALUE (root->left->right) != 1)
4944         goto tryNext2;
4945
4946       if (AST_LIT_VALUE (root->right->right) !=
4947           (getSize (TTYPE (root->left->left)) * 8 - 1))
4948         goto tryNext2;
4949
4950       /* make sure the port supports RRC */
4951       if (port->hasExtBitOp
4952           && !port->hasExtBitOp(RRC, getSize (TTYPE (root->left->left))))
4953         return root;
4954
4955       /* whew got the first case : create the AST */
4956       return newNode (RRC, root->left->left, NULL);
4957
4958     }
4959 tryNext2:
4960   /* fourth and last case for now */
4961   /* (?symbol << 7) | (?symbol >> 1) */
4962   if (IS_RIGHT_OP (root->right) &&
4963       IS_LEFT_OP (root->left))
4964     {
4965
4966       if (!SPEC_USIGN (TETYPE (root->left->left)))
4967         return root;
4968
4969       if (!IS_AST_LIT_VALUE (root->left->right) ||
4970           !IS_AST_LIT_VALUE (root->right->right))
4971         return root;
4972
4973       /* make sure it is the same symbol */
4974       if (!isAstEqual (root->left->left,
4975                        root->right->left))
4976         return root;
4977
4978       if (AST_LIT_VALUE (root->right->right) != 1)
4979         return root;
4980
4981       if (AST_LIT_VALUE (root->left->right) !=
4982           (getSize (TTYPE (root->left->left)) * 8 - 1))
4983         return root;
4984
4985       /* make sure the port supports RRC */
4986       if (port->hasExtBitOp
4987           && !port->hasExtBitOp(RRC, getSize (TTYPE (root->left->left))))
4988         return root;
4989
4990       /* whew got the first case : create the AST */
4991       return newNode (RRC, root->left->left, NULL);
4992
4993     }
4994
4995   /* not found return root */
4996   return root;
4997 }
4998
4999 /*-----------------------------------------------------------------*/
5000 /* optimizeSWAP :- optimize for nibble/byte/word swaps             */
5001 /*-----------------------------------------------------------------*/
5002 ast *
5003 optimizeSWAP (ast * root)
5004 {
5005   /* will look for trees of the form
5006      (?expr << 4) | (?expr >> 4) or
5007      (?expr >> 4) | (?expr << 4) will make that
5008      into a SWAP : operation ..
5009      note : by 4 I mean (number of bits required to hold the
5010      variable /2 ) */
5011   /* if the root operations is not a | operation the not */
5012   if (!IS_BITOR (root))
5013     return root;
5014
5015   /* (?expr << 4) | (?expr >> 4) */
5016   if ((IS_LEFT_OP (root->left) && IS_RIGHT_OP (root->right))
5017       || (IS_RIGHT_OP (root->left) && IS_LEFT_OP (root->right)))
5018     {
5019
5020       if (!SPEC_USIGN (TETYPE (root->left->left)))
5021         return root;
5022
5023       if (!IS_AST_LIT_VALUE (root->left->right) ||
5024           !IS_AST_LIT_VALUE (root->right->right))
5025         return root;
5026
5027       /* make sure it is the same expression */
5028       if (!isAstEqual (root->left->left,
5029                        root->right->left))
5030         return root;
5031
5032       if (AST_LIT_VALUE (root->left->right) !=
5033           (getSize (TTYPE (root->left->left)) * 4))
5034         return root;
5035
5036       if (AST_LIT_VALUE (root->right->right) !=
5037           (getSize (TTYPE (root->left->left)) * 4))
5038         return root;
5039
5040       /* make sure the port supports SWAP */
5041       if (port->hasExtBitOp
5042           && !port->hasExtBitOp(SWAP, getSize (TTYPE (root->left->left))))
5043         return root;
5044
5045       /* found it : create the AST */
5046       return newNode (SWAP, root->left->left, NULL);
5047     }
5048
5049
5050   /* not found return root */
5051   return root;
5052 }
5053
5054 /*-----------------------------------------------------------------*/
5055 /* optimizeCompare - otimizes compares for bit variables     */
5056 /*-----------------------------------------------------------------*/
5057 static ast *
5058 optimizeCompare (ast * root)
5059 {
5060   ast *optExpr = NULL;
5061   value *vleft;
5062   value *vright;
5063   unsigned int litValue;
5064
5065   /* if nothing then return nothing */
5066   if (!root)
5067     return NULL;
5068
5069   /* if not a compare op then do leaves */
5070   if (!IS_COMPARE_OP (root))
5071     {
5072       root->left = optimizeCompare (root->left);
5073       root->right = optimizeCompare (root->right);
5074       return root;
5075     }
5076
5077   /* if left & right are the same then depending
5078      of the operation do */
5079   if (isAstEqual (root->left, root->right))
5080     {
5081       switch (root->opval.op)
5082         {
5083         case '>':
5084         case '<':
5085         case NE_OP:
5086           optExpr = newAst_VALUE (constVal ("0"));
5087           break;
5088         case GE_OP:
5089         case LE_OP:
5090         case EQ_OP:
5091           optExpr = newAst_VALUE (constVal ("1"));
5092           break;
5093         }
5094
5095       return decorateType (optExpr, RESULT_CHECK);
5096     }
5097
5098   vleft = (root->left->type == EX_VALUE ?
5099            root->left->opval.val : NULL);
5100
5101   vright = (root->right->type == EX_VALUE ?
5102             root->right->opval.val : NULL);
5103
5104   /* if left is a BITVAR in BITSPACE */
5105   /* and right is a LITERAL then opt- */
5106   /* imize else do nothing       */
5107   if (vleft && vright &&
5108       IS_BITVAR (vleft->etype) &&
5109       IN_BITSPACE (SPEC_OCLS (vleft->etype)) &&
5110       IS_LITERAL (vright->etype))
5111     {
5112
5113       /* if right side > 1 then comparison may never succeed */
5114       if ((litValue = (int) floatFromVal (vright)) > 1)
5115         {
5116           werror (W_BAD_COMPARE);
5117           goto noOptimize;
5118         }
5119
5120       if (litValue)
5121         {
5122           switch (root->opval.op)
5123             {
5124             case '>':           /* bit value greater than 1 cannot be */
5125               werror (W_BAD_COMPARE);
5126               goto noOptimize;
5127               break;
5128
5129             case '<':           /* bit value < 1 means 0 */
5130             case NE_OP:
5131               optExpr = newNode ('!', newAst_VALUE (vleft), NULL);
5132               break;
5133
5134             case LE_OP: /* bit value <= 1 means no check */
5135               optExpr = newAst_VALUE (vright);
5136               break;
5137
5138             case GE_OP: /* bit value >= 1 means only check for = */
5139             case EQ_OP:
5140               optExpr = newAst_VALUE (vleft);
5141               break;
5142             }
5143         }
5144       else
5145         {                       /* literal is zero */
5146           switch (root->opval.op)
5147             {
5148             case '<':           /* bit value < 0 cannot be */
5149               werror (W_BAD_COMPARE);
5150               goto noOptimize;
5151               break;
5152
5153             case '>':           /* bit value > 0 means 1 */
5154             case NE_OP:
5155               optExpr = newAst_VALUE (vleft);
5156               break;
5157
5158             case LE_OP: /* bit value <= 0 means no check */
5159             case GE_OP: /* bit value >= 0 means no check */
5160               werror (W_BAD_COMPARE);
5161               goto noOptimize;
5162               break;
5163
5164             case EQ_OP: /* bit == 0 means ! of bit */
5165               optExpr = newNode ('!', newAst_VALUE (vleft), NULL);
5166               break;
5167             }
5168         }
5169       return decorateType (resolveSymbols (optExpr), RESULT_CHECK);
5170     }                           /* end-of-if of BITVAR */
5171
5172 noOptimize:
5173   return root;
5174 }
5175 /*-----------------------------------------------------------------*/
5176 /* addSymToBlock : adds the symbol to the first block we find      */
5177 /*-----------------------------------------------------------------*/
5178 void 
5179 addSymToBlock (symbol * sym, ast * tree)
5180 {
5181   /* reached end of tree or a leaf */
5182   if (!tree || IS_AST_LINK (tree) || IS_AST_VALUE (tree))
5183     return;
5184
5185   /* found a block */
5186   if (IS_AST_OP (tree) &&
5187       tree->opval.op == BLOCK)
5188     {
5189
5190       symbol *lsym = copySymbol (sym);
5191
5192       lsym->next = AST_VALUES (tree, sym);
5193       AST_VALUES (tree, sym) = lsym;
5194       return;
5195     }
5196
5197   addSymToBlock (sym, tree->left);
5198   addSymToBlock (sym, tree->right);
5199 }
5200
5201 /*-----------------------------------------------------------------*/
5202 /* processRegParms - do processing for register parameters         */
5203 /*-----------------------------------------------------------------*/
5204 static void 
5205 processRegParms (value * args, ast * body)
5206 {
5207   while (args)
5208     {
5209       if (IS_REGPARM (args->etype))
5210         addSymToBlock (args->sym, body);
5211       args = args->next;
5212     }
5213 }
5214
5215 /*-----------------------------------------------------------------*/
5216 /* resetParmKey - resets the operandkeys for the symbols           */
5217 /*-----------------------------------------------------------------*/
5218 DEFSETFUNC (resetParmKey)
5219 {
5220   symbol *sym = item;
5221
5222   sym->key = 0;
5223   sym->defs = NULL;
5224   sym->uses = NULL;
5225   sym->remat = 0;
5226   return 1;
5227 }
5228
5229 /*-----------------------------------------------------------------*/
5230 /* createFunction - This is the key node that calls the iCode for  */
5231 /*                  generating the code for a function. Note code  */
5232 /*                  is generated function by function, later when  */
5233 /*                  add inter-procedural analysis this will change */
5234 /*-----------------------------------------------------------------*/
5235 ast *
5236 createFunction (symbol * name, ast * body)
5237 {
5238   ast *ex;
5239   symbol *csym;
5240   int stack = 0;
5241   sym_link *fetype;
5242   iCode *piCode = NULL;
5243
5244   if (getenv("SDCC_DEBUG_FUNCTION_POINTERS"))
5245     fprintf (stderr, "SDCCast.c:createFunction(%s)\n", name->name);
5246
5247   /* if check function return 0 then some problem */
5248   if (checkFunction (name, NULL) == 0)
5249     return NULL;
5250
5251   /* create a dummy block if none exists */
5252   if (!body)
5253     body = newNode (BLOCK, NULL, NULL);
5254
5255   noLineno++;
5256
5257   /* check if the function name already in the symbol table */
5258   if ((csym = findSym (SymbolTab, NULL, name->name)))
5259     {
5260       name = csym;
5261       /* special case for compiler defined functions
5262          we need to add the name to the publics list : this
5263          actually means we are now compiling the compiler
5264          support routine */
5265       if (name->cdef)
5266         {
5267           addSet (&publics, name);
5268         }
5269     }
5270   else
5271     {
5272       addSymChain (name);
5273       allocVariables (name);
5274     }
5275   name->lastLine = mylineno;
5276   currFunc = name;
5277
5278   /* set the stack pointer */
5279   /* PENDING: check this for the mcs51 */
5280   stackPtr = -port->stack.direction * port->stack.call_overhead;
5281   if (IFFUNC_ISISR (name->type))
5282     stackPtr -= port->stack.direction * port->stack.isr_overhead;
5283   if (IFFUNC_ISREENT (name->type) || options.stackAuto)
5284     stackPtr -= port->stack.direction * port->stack.reent_overhead;
5285
5286   xstackPtr = -port->stack.direction * port->stack.call_overhead;
5287
5288   fetype = getSpec (name->type);        /* get the specifier for the function */
5289   /* if this is a reentrant function then */
5290   if (IFFUNC_ISREENT (name->type))
5291     reentrant++;
5292
5293   allocParms (FUNC_ARGS(name->type));   /* allocate the parameters */
5294
5295   /* do processing for parameters that are passed in registers */
5296   processRegParms (FUNC_ARGS(name->type), body);
5297
5298   /* set the stack pointer */
5299   stackPtr = 0;
5300   xstackPtr = -1;
5301
5302   /* allocate & autoinit the block variables */
5303   processBlockVars (body, &stack, ALLOCATE);
5304
5305   /* save the stack information */
5306   if (options.useXstack)
5307     name->xstack = SPEC_STAK (fetype) = stack;
5308   else
5309     name->stack = SPEC_STAK (fetype) = stack;
5310
5311   /* name needs to be mangled */
5312   SNPRINTF (name->rname, sizeof(name->rname), "%s%s", port->fun_prefix, name->name);
5313
5314   body = resolveSymbols (body); /* resolve the symbols */
5315   body = decorateType (body, RESULT_TYPE_NONE); /* propagateType & do semantic checks */
5316                                         
5317
5318   ex = newAst_VALUE (symbolVal (name)); /* create name */
5319   ex = newNode (FUNCTION, ex, body);
5320   ex->values.args = FUNC_ARGS(name->type);
5321   ex->decorated=1;
5322   if (options.dump_tree) PA(ex);
5323   if (fatalError)
5324     {
5325       werror (E_FUNC_NO_CODE, name->name);
5326       goto skipall;
5327     }
5328
5329   /* create the node & generate intermediate code */
5330   GcurMemmap = code;
5331   codeOutFile = code->oFile;
5332   piCode = iCodeFromAst (ex);
5333
5334   if (fatalError)
5335     {
5336       werror (E_FUNC_NO_CODE, name->name);
5337       goto skipall;
5338     }
5339
5340   eBBlockFromiCode (piCode);
5341
5342   /* if there are any statics then do them */
5343   if (staticAutos)
5344     {
5345       GcurMemmap = statsg;
5346       codeOutFile = statsg->oFile;
5347       eBBlockFromiCode (iCodeFromAst (decorateType (resolveSymbols (staticAutos), RESULT_CHECK)));
5348       staticAutos = NULL;
5349     }
5350
5351 skipall:
5352
5353   /* dealloc the block variables */
5354   processBlockVars (body, &stack, DEALLOCATE);
5355   outputDebugStackSymbols();
5356   /* deallocate paramaters */
5357   deallocParms (FUNC_ARGS(name->type));
5358
5359   if (IFFUNC_ISREENT (name->type))
5360     reentrant--;
5361
5362   /* we are done freeup memory & cleanup */
5363   noLineno--;
5364   if (port->reset_labelKey) labelKey = 1;
5365   name->key = 0;
5366   FUNC_HASBODY(name->type) = 1;
5367   addSet (&operKeyReset, name);
5368   applyToSet (operKeyReset, resetParmKey);
5369
5370   if (options.debug)
5371     cdbStructBlock(1);
5372
5373   cleanUpLevel (LabelTab, 0);
5374   cleanUpBlock (StructTab, 1);
5375   cleanUpBlock (TypedefTab, 1);
5376
5377   xstack->syms = NULL;
5378   istack->syms = NULL;
5379   return NULL;
5380 }
5381
5382
5383 #define INDENT(x,f) { int i ; fprintf (f, "%d:", tree->lineno); for (i=0;i < x; i++) fprintf(f," "); }
5384 /*-----------------------------------------------------------------*/
5385 /* ast_print : prints the ast (for debugging purposes)             */
5386 /*-----------------------------------------------------------------*/
5387
5388 void ast_print (ast * tree, FILE *outfile, int indent)
5389 {
5390
5391         if (!tree) return ;
5392
5393         /* can print only decorated trees */
5394         if (!tree->decorated) return;
5395
5396         /* if any child is an error | this one is an error do nothing */
5397         if (tree->isError ||
5398             (tree->left && tree->left->isError) ||
5399             (tree->right && tree->right->isError)) {
5400                 fprintf(outfile,"ERROR_NODE(%p)\n",tree);
5401         }
5402
5403
5404         /* print the line          */
5405         /* if not block & function */
5406         if (tree->type == EX_OP &&
5407             (tree->opval.op != FUNCTION &&
5408              tree->opval.op != BLOCK &&
5409              tree->opval.op != NULLOP)) {
5410         }
5411
5412         if (tree->opval.op == FUNCTION) {
5413                 int arg=0;
5414                 value *args=FUNC_ARGS(tree->left->opval.val->type);
5415                 fprintf(outfile,"FUNCTION (%s=%p) type (",
5416                         tree->left->opval.val->name, tree);
5417                 printTypeChain (tree->left->opval.val->type->next,outfile);
5418                 fprintf(outfile,") args (");
5419                 do {
5420                   if (arg) {
5421                     fprintf (outfile, ", ");
5422                   }
5423                   printTypeChain (args ? args->type : NULL, outfile);
5424                   arg++;
5425                   args= args ? args->next : NULL;
5426                 } while (args);
5427                 fprintf(outfile,")\n");
5428                 ast_print(tree->left,outfile,indent);
5429                 ast_print(tree->right,outfile,indent);
5430                 return ;
5431         }
5432         if (tree->opval.op == BLOCK) {
5433                 symbol *decls = tree->values.sym;
5434                 INDENT(indent,outfile);
5435                 fprintf(outfile,"{\n");
5436                 while (decls) {
5437                         INDENT(indent+2,outfile);
5438                         fprintf(outfile,"DECLARE SYMBOL (%s=%p) type (",
5439                                 decls->name, decls);
5440                         printTypeChain(decls->type,outfile);
5441                         fprintf(outfile,")\n");
5442
5443                         decls = decls->next;
5444                 }
5445                 ast_print(tree->right,outfile,indent+2);
5446                 INDENT(indent,outfile);
5447                 fprintf(outfile,"}\n");
5448                 return;
5449         }
5450         if (tree->opval.op == NULLOP) {
5451                 ast_print(tree->left,outfile,indent);
5452                 ast_print(tree->right,outfile,indent);
5453                 return ;
5454         }
5455         INDENT(indent,outfile);
5456
5457         /*------------------------------------------------------------------*/
5458         /*----------------------------*/
5459         /*   leaf has been reached    */
5460         /*----------------------------*/
5461         /* if this is of type value */
5462         /* just get the type        */
5463         if (tree->type == EX_VALUE) {
5464
5465                 if (IS_LITERAL (tree->opval.val->etype)) {
5466                         fprintf(outfile,"CONSTANT (%p) value = ", tree);
5467                         if (SPEC_USIGN (tree->opval.val->etype))
5468                                 fprintf(outfile,"%u", (TYPE_UDWORD) floatFromVal(tree->opval.val));
5469                         else
5470                                 fprintf(outfile,"%d", (TYPE_DWORD) floatFromVal(tree->opval.val));
5471                         fprintf(outfile,", 0x%x, %f", (TYPE_UDWORD) floatFromVal(tree->opval.val),
5472                                                       floatFromVal(tree->opval.val));
5473                 } else if (tree->opval.val->sym) {
5474                         /* if the undefined flag is set then give error message */
5475                         if (tree->opval.val->sym->undefined) {
5476                                 fprintf(outfile,"UNDEFINED SYMBOL ");
5477                         } else {
5478                                 fprintf(outfile,"SYMBOL ");
5479                         }
5480                         fprintf(outfile,"(%s=%p)",
5481                                 tree->opval.val->sym->name,tree);
5482                 }
5483                 if (tree->ftype) {
5484                         fprintf(outfile," type (");
5485                         printTypeChain(tree->ftype,outfile);
5486                         fprintf(outfile,")\n");
5487                 } else {
5488                         fprintf(outfile,"\n");
5489                 }
5490                 return ;
5491         }
5492
5493         /* if type link for the case of cast */
5494         if (tree->type == EX_LINK) {
5495                 fprintf(outfile,"TYPENODE (%p) type = (",tree);
5496                 printTypeChain(tree->opval.lnk,outfile);
5497                 fprintf(outfile,")\n");
5498                 return ;
5499         }
5500
5501
5502         /* depending on type of operator do */
5503
5504         switch (tree->opval.op) {
5505                 /*------------------------------------------------------------------*/
5506                 /*----------------------------*/
5507                 /*        array node          */
5508                 /*----------------------------*/
5509         case '[':
5510                 fprintf(outfile,"ARRAY_OP (%p) type (",tree);
5511                 printTypeChain(tree->ftype,outfile);
5512                 fprintf(outfile,")\n");
5513                 ast_print(tree->left,outfile,indent+2);
5514                 ast_print(tree->right,outfile,indent+2);
5515                 return;
5516
5517                 /*------------------------------------------------------------------*/
5518                 /*----------------------------*/
5519                 /*      struct/union          */
5520                 /*----------------------------*/
5521         case '.':
5522                 fprintf(outfile,"STRUCT_ACCESS (%p) type (",tree);
5523                 printTypeChain(tree->ftype,outfile);
5524                 fprintf(outfile,")\n");
5525                 ast_print(tree->left,outfile,indent+2);
5526                 ast_print(tree->right,outfile,indent+2);
5527                 return ;
5528
5529                 /*------------------------------------------------------------------*/
5530                 /*----------------------------*/
5531                 /*    struct/union pointer    */
5532                 /*----------------------------*/
5533         case PTR_OP:
5534                 fprintf(outfile,"PTR_ACCESS (%p) type (",tree);
5535                 printTypeChain(tree->ftype,outfile);
5536                 fprintf(outfile,")\n");
5537                 ast_print(tree->left,outfile,indent+2);
5538                 ast_print(tree->right,outfile,indent+2);
5539                 return ;
5540
5541                 /*------------------------------------------------------------------*/
5542                 /*----------------------------*/
5543                 /*  ++/-- operation           */
5544                 /*----------------------------*/
5545         case INC_OP:
5546                 if (tree->left)
5547                   fprintf(outfile,"post-");
5548                 else
5549                   fprintf(outfile,"pre-");
5550                 fprintf(outfile,"INC_OP (%p) type (",tree);
5551                 printTypeChain(tree->ftype,outfile);
5552                 fprintf(outfile,")\n");
5553                 ast_print(tree->left,outfile,indent+2); /* postincrement case */
5554                 ast_print(tree->right,outfile,indent+2); /* preincrement case */
5555                 return ;
5556
5557         case DEC_OP:
5558                 if (tree->left)
5559                   fprintf(outfile,"post-");
5560                 else
5561                   fprintf(outfile,"pre-");
5562                 fprintf(outfile,"DEC_OP (%p) type (",tree);
5563                 printTypeChain(tree->ftype,outfile);
5564                 fprintf(outfile,")\n");
5565                 ast_print(tree->left,outfile,indent+2); /* postdecrement case */
5566                 ast_print(tree->right,outfile,indent+2); /* predecrement case */
5567                 return ;
5568
5569                 /*------------------------------------------------------------------*/
5570                 /*----------------------------*/
5571                 /*  bitwise and               */
5572                 /*----------------------------*/
5573         case '&':
5574                 if (tree->right) {
5575                         fprintf(outfile,"& (%p) type (",tree);
5576                         printTypeChain(tree->ftype,outfile);
5577                         fprintf(outfile,")\n");
5578                         ast_print(tree->left,outfile,indent+2);
5579                         ast_print(tree->right,outfile,indent+2);
5580                 } else {
5581                         fprintf(outfile,"ADDRESS_OF (%p) type (",tree);
5582                         printTypeChain(tree->ftype,outfile);
5583                         fprintf(outfile,")\n");
5584                         ast_print(tree->left,outfile,indent+2);
5585                         ast_print(tree->right,outfile,indent+2);
5586                 }
5587                 return ;
5588                 /*----------------------------*/
5589                 /*  bitwise or                */
5590                 /*----------------------------*/
5591         case '|':
5592                 fprintf(outfile,"OR (%p) type (",tree);
5593                 printTypeChain(tree->ftype,outfile);
5594                 fprintf(outfile,")\n");
5595                 ast_print(tree->left,outfile,indent+2);
5596                 ast_print(tree->right,outfile,indent+2);
5597                 return ;
5598                 /*------------------------------------------------------------------*/
5599                 /*----------------------------*/
5600                 /*  bitwise xor               */
5601                 /*----------------------------*/
5602         case '^':
5603                 fprintf(outfile,"XOR (%p) type (",tree);
5604                 printTypeChain(tree->ftype,outfile);
5605                 fprintf(outfile,")\n");
5606                 ast_print(tree->left,outfile,indent+2);
5607                 ast_print(tree->right,outfile,indent+2);
5608                 return ;
5609
5610                 /*------------------------------------------------------------------*/
5611                 /*----------------------------*/
5612                 /*  division                  */
5613                 /*----------------------------*/
5614         case '/':
5615                 fprintf(outfile,"DIV (%p) type (",tree);
5616                 printTypeChain(tree->ftype,outfile);
5617                 fprintf(outfile,")\n");
5618                 ast_print(tree->left,outfile,indent+2);
5619                 ast_print(tree->right,outfile,indent+2);
5620                 return ;
5621                 /*------------------------------------------------------------------*/
5622                 /*----------------------------*/
5623                 /*            modulus         */
5624                 /*----------------------------*/
5625         case '%':
5626                 fprintf(outfile,"MOD (%p) type (",tree);
5627                 printTypeChain(tree->ftype,outfile);
5628                 fprintf(outfile,")\n");
5629                 ast_print(tree->left,outfile,indent+2);
5630                 ast_print(tree->right,outfile,indent+2);
5631                 return ;
5632
5633                 /*------------------------------------------------------------------*/
5634                 /*----------------------------*/
5635                 /*  address dereference       */
5636                 /*----------------------------*/
5637         case '*':                       /* can be unary  : if right is null then unary operation */
5638                 if (!tree->right) {
5639                         fprintf(outfile,"DEREF (%p) type (",tree);
5640                         printTypeChain(tree->ftype,outfile);
5641                         fprintf(outfile,")\n");
5642                         ast_print(tree->left,outfile,indent+2);
5643                         return ;
5644                 }                       
5645                 /*------------------------------------------------------------------*/
5646                 /*----------------------------*/
5647                 /*      multiplication        */
5648                 /*----------------------------*/                
5649                 fprintf(outfile,"MULT (%p) type (",tree);
5650                 printTypeChain(tree->ftype,outfile);
5651                 fprintf(outfile,")\n");
5652                 ast_print(tree->left,outfile,indent+2);
5653                 ast_print(tree->right,outfile,indent+2);
5654                 return ;
5655
5656
5657                 /*------------------------------------------------------------------*/
5658                 /*----------------------------*/
5659                 /*    unary '+' operator      */
5660                 /*----------------------------*/
5661         case '+':
5662                 /* if unary plus */
5663                 if (!tree->right) {
5664                         fprintf(outfile,"UPLUS (%p) type (",tree);
5665                         printTypeChain(tree->ftype,outfile);
5666                         fprintf(outfile,")\n");
5667                         ast_print(tree->left,outfile,indent+2);
5668                 } else {
5669                         /*------------------------------------------------------------------*/
5670                         /*----------------------------*/
5671                         /*      addition              */
5672                         /*----------------------------*/
5673                         fprintf(outfile,"ADD (%p) type (",tree);
5674                         printTypeChain(tree->ftype,outfile);
5675                         fprintf(outfile,")\n");
5676                         ast_print(tree->left,outfile,indent+2);
5677                         ast_print(tree->right,outfile,indent+2);
5678                 }
5679                 return;
5680                 /*------------------------------------------------------------------*/
5681                 /*----------------------------*/
5682                 /*      unary '-'             */
5683                 /*----------------------------*/
5684         case '-':                       /* can be unary   */
5685                 if (!tree->right) {
5686                         fprintf(outfile,"UMINUS (%p) type (",tree);
5687                         printTypeChain(tree->ftype,outfile);
5688                         fprintf(outfile,")\n");
5689                         ast_print(tree->left,outfile,indent+2);
5690                 } else {
5691                         /*------------------------------------------------------------------*/
5692                         /*----------------------------*/
5693                         /*      subtraction           */
5694                         /*----------------------------*/
5695                         fprintf(outfile,"SUB (%p) type (",tree);
5696                         printTypeChain(tree->ftype,outfile);
5697                         fprintf(outfile,")\n");
5698                         ast_print(tree->left,outfile,indent+2);
5699                         ast_print(tree->right,outfile,indent+2);
5700                 }
5701                 return;
5702                 /*------------------------------------------------------------------*/
5703                 /*----------------------------*/
5704                 /*    compliment              */
5705                 /*----------------------------*/
5706         case '~':
5707                 fprintf(outfile,"COMPL (%p) type (",tree);
5708                 printTypeChain(tree->ftype,outfile);
5709                 fprintf(outfile,")\n");
5710                 ast_print(tree->left,outfile,indent+2);
5711                 return ;
5712                 /*------------------------------------------------------------------*/
5713                 /*----------------------------*/
5714                 /*           not              */
5715                 /*----------------------------*/
5716         case '!':
5717                 fprintf(outfile,"NOT (%p) type (",tree);
5718                 printTypeChain(tree->ftype,outfile);
5719                 fprintf(outfile,")\n");
5720                 ast_print(tree->left,outfile,indent+2);
5721                 return ;
5722                 /*------------------------------------------------------------------*/
5723                 /*----------------------------*/
5724                 /*           shift            */
5725                 /*----------------------------*/
5726         case RRC:
5727                 fprintf(outfile,"RRC (%p) type (",tree);
5728                 printTypeChain(tree->ftype,outfile);
5729                 fprintf(outfile,")\n");
5730                 ast_print(tree->left,outfile,indent+2);
5731                 return ;
5732
5733         case RLC:
5734                 fprintf(outfile,"RLC (%p) type (",tree);
5735                 printTypeChain(tree->ftype,outfile);
5736                 fprintf(outfile,")\n");
5737                 ast_print(tree->left,outfile,indent+2);
5738                 return ;
5739         case SWAP:
5740                 fprintf(outfile,"SWAP (%p) type (",tree);
5741                 printTypeChain(tree->ftype,outfile);
5742                 fprintf(outfile,")\n");
5743                 ast_print(tree->left,outfile,indent+2);
5744                 return ;
5745         case GETHBIT:
5746                 fprintf(outfile,"GETHBIT (%p) type (",tree);
5747                 printTypeChain(tree->ftype,outfile);
5748                 fprintf(outfile,")\n");
5749                 ast_print(tree->left,outfile,indent+2);
5750                 return ;
5751         case LEFT_OP:
5752                 fprintf(outfile,"LEFT_SHIFT (%p) type (",tree);
5753                 printTypeChain(tree->ftype,outfile);
5754                 fprintf(outfile,")\n");
5755                 ast_print(tree->left,outfile,indent+2);
5756                 ast_print(tree->right,outfile,indent+2);
5757                 return ;
5758         case RIGHT_OP:
5759                 fprintf(outfile,"RIGHT_SHIFT (%p) type (",tree);
5760                 printTypeChain(tree->ftype,outfile);
5761                 fprintf(outfile,")\n");
5762                 ast_print(tree->left,outfile,indent+2);
5763                 ast_print(tree->right,outfile,indent+2);
5764                 return ;
5765                 /*------------------------------------------------------------------*/
5766                 /*----------------------------*/
5767                 /*         casting            */
5768                 /*----------------------------*/
5769         case CAST:                      /* change the type   */
5770                 fprintf(outfile,"CAST (%p) from type (",tree);
5771                 printTypeChain(tree->right->ftype,outfile);
5772                 fprintf(outfile,") to type (");
5773                 printTypeChain(tree->ftype,outfile);
5774                 fprintf(outfile,")\n");
5775                 ast_print(tree->right,outfile,indent+2);
5776                 return ;
5777                 
5778         case AND_OP:
5779                 fprintf(outfile,"ANDAND (%p) type (",tree);
5780                 printTypeChain(tree->ftype,outfile);
5781                 fprintf(outfile,")\n");
5782                 ast_print(tree->left,outfile,indent+2);
5783                 ast_print(tree->right,outfile,indent+2);
5784                 return ;
5785         case OR_OP:
5786                 fprintf(outfile,"OROR (%p) type (",tree);
5787                 printTypeChain(tree->ftype,outfile);
5788                 fprintf(outfile,")\n");
5789                 ast_print(tree->left,outfile,indent+2);
5790                 ast_print(tree->right,outfile,indent+2);
5791                 return ;
5792                 
5793                 /*------------------------------------------------------------------*/
5794                 /*----------------------------*/
5795                 /*     comparison operators   */
5796                 /*----------------------------*/
5797         case '>':
5798                 fprintf(outfile,"GT(>) (%p) type (",tree);
5799                 printTypeChain(tree->ftype,outfile);
5800                 fprintf(outfile,")\n");
5801                 ast_print(tree->left,outfile,indent+2);
5802                 ast_print(tree->right,outfile,indent+2);
5803                 return ;
5804         case '<':
5805                 fprintf(outfile,"LT(<) (%p) type (",tree);
5806                 printTypeChain(tree->ftype,outfile);
5807                 fprintf(outfile,")\n");
5808                 ast_print(tree->left,outfile,indent+2);
5809                 ast_print(tree->right,outfile,indent+2);
5810                 return ;
5811         case LE_OP:
5812                 fprintf(outfile,"LE(<=) (%p) type (",tree);
5813                 printTypeChain(tree->ftype,outfile);
5814                 fprintf(outfile,")\n");
5815                 ast_print(tree->left,outfile,indent+2);
5816                 ast_print(tree->right,outfile,indent+2);
5817                 return ;
5818         case GE_OP:
5819                 fprintf(outfile,"GE(>=) (%p) type (",tree);
5820                 printTypeChain(tree->ftype,outfile);
5821                 fprintf(outfile,")\n");
5822                 ast_print(tree->left,outfile,indent+2);
5823                 ast_print(tree->right,outfile,indent+2);
5824                 return ;
5825         case EQ_OP:
5826                 fprintf(outfile,"EQ(==) (%p) type (",tree);
5827                 printTypeChain(tree->ftype,outfile);
5828                 fprintf(outfile,")\n");
5829                 ast_print(tree->left,outfile,indent+2);
5830                 ast_print(tree->right,outfile,indent+2);
5831                 return ;
5832         case NE_OP:
5833                 fprintf(outfile,"NE(!=) (%p) type (",tree);
5834                 printTypeChain(tree->ftype,outfile);
5835                 fprintf(outfile,")\n");
5836                 ast_print(tree->left,outfile,indent+2);
5837                 ast_print(tree->right,outfile,indent+2);
5838                 /*------------------------------------------------------------------*/
5839                 /*----------------------------*/
5840                 /*             sizeof         */
5841                 /*----------------------------*/
5842         case SIZEOF:            /* evaluate wihout code generation */
5843                 fprintf(outfile,"SIZEOF %d\n",(getSize (tree->right->ftype)));
5844                 return ;
5845
5846                 /*------------------------------------------------------------------*/
5847                 /*----------------------------*/
5848                 /* conditional operator  '?'  */
5849                 /*----------------------------*/
5850         case '?':
5851                 fprintf(outfile,"QUEST(?) (%p) type (",tree);
5852                 printTypeChain(tree->ftype,outfile);
5853                 fprintf(outfile,")\n");
5854                 ast_print(tree->left,outfile,indent+2);
5855                 ast_print(tree->right,outfile,indent+2);
5856                 return;
5857
5858         case ':':
5859                 fprintf(outfile,"COLON(:) (%p) type (",tree);
5860                 printTypeChain(tree->ftype,outfile);
5861                 fprintf(outfile,")\n");
5862                 ast_print(tree->left,outfile,indent+2);
5863                 ast_print(tree->right,outfile,indent+2);
5864                 return ;
5865
5866                 /*------------------------------------------------------------------*/
5867                 /*----------------------------*/
5868                 /*    assignment operators    */
5869                 /*----------------------------*/
5870         case MUL_ASSIGN:
5871                 fprintf(outfile,"MULASS(*=) (%p) type (",tree);
5872                 printTypeChain(tree->ftype,outfile);
5873                 fprintf(outfile,")\n");
5874                 ast_print(tree->left,outfile,indent+2);
5875                 ast_print(tree->right,outfile,indent+2);
5876                 return;
5877         case DIV_ASSIGN:
5878                 fprintf(outfile,"DIVASS(/=) (%p) type (",tree);
5879                 printTypeChain(tree->ftype,outfile);
5880                 fprintf(outfile,")\n");
5881                 ast_print(tree->left,outfile,indent+2);
5882                 ast_print(tree->right,outfile,indent+2);
5883                 return;
5884         case AND_ASSIGN:
5885                 fprintf(outfile,"ANDASS(&=) (%p) type (",tree);
5886                 printTypeChain(tree->ftype,outfile);
5887                 fprintf(outfile,")\n");
5888                 ast_print(tree->left,outfile,indent+2);
5889                 ast_print(tree->right,outfile,indent+2);
5890                 return;
5891         case OR_ASSIGN:
5892                 fprintf(outfile,"ORASS(|=) (%p) type (",tree);
5893                 printTypeChain(tree->ftype,outfile);
5894                 fprintf(outfile,")\n");
5895                 ast_print(tree->left,outfile,indent+2);
5896                 ast_print(tree->right,outfile,indent+2);
5897                 return;
5898         case XOR_ASSIGN:
5899                 fprintf(outfile,"XORASS(^=) (%p) type (",tree);
5900                 printTypeChain(tree->ftype,outfile);
5901                 fprintf(outfile,")\n");
5902                 ast_print(tree->left,outfile,indent+2);
5903                 ast_print(tree->right,outfile,indent+2);
5904                 return;
5905         case RIGHT_ASSIGN:
5906                 fprintf(outfile,"RSHFTASS(>>=) (%p) type (",tree);
5907                 printTypeChain(tree->ftype,outfile);
5908                 fprintf(outfile,")\n");
5909                 ast_print(tree->left,outfile,indent+2);
5910                 ast_print(tree->right,outfile,indent+2);
5911                 return;
5912         case LEFT_ASSIGN:
5913                 fprintf(outfile,"LSHFTASS(<<=) (%p) type (",tree);
5914                 printTypeChain(tree->ftype,outfile);
5915                 fprintf(outfile,")\n");
5916                 ast_print(tree->left,outfile,indent+2);
5917                 ast_print(tree->right,outfile,indent+2);
5918                 return;
5919                 /*------------------------------------------------------------------*/
5920                 /*----------------------------*/
5921                 /*    -= operator             */
5922                 /*----------------------------*/
5923         case SUB_ASSIGN:
5924                 fprintf(outfile,"SUBASS(-=) (%p) type (",tree);
5925                 printTypeChain(tree->ftype,outfile);
5926                 fprintf(outfile,")\n");
5927                 ast_print(tree->left,outfile,indent+2);
5928                 ast_print(tree->right,outfile,indent+2);
5929                 return;
5930                 /*------------------------------------------------------------------*/
5931                 /*----------------------------*/
5932                 /*          += operator       */
5933                 /*----------------------------*/
5934         case ADD_ASSIGN:
5935                 fprintf(outfile,"ADDASS(+=) (%p) type (",tree);
5936                 printTypeChain(tree->ftype,outfile);
5937                 fprintf(outfile,")\n");
5938                 ast_print(tree->left,outfile,indent+2);
5939                 ast_print(tree->right,outfile,indent+2);
5940                 return;
5941                 /*------------------------------------------------------------------*/
5942                 /*----------------------------*/
5943                 /*      straight assignemnt   */
5944                 /*----------------------------*/
5945         case '=':
5946                 fprintf(outfile,"ASSIGN(=) (%p) type (",tree);
5947                 printTypeChain(tree->ftype,outfile);
5948                 fprintf(outfile,")\n");
5949                 ast_print(tree->left,outfile,indent+2);
5950                 ast_print(tree->right,outfile,indent+2);
5951                 return;     
5952                 /*------------------------------------------------------------------*/
5953                 /*----------------------------*/
5954                 /*      comma operator        */
5955                 /*----------------------------*/
5956         case ',':
5957                 fprintf(outfile,"COMMA(,) (%p) type (",tree);
5958                 printTypeChain(tree->ftype,outfile);
5959                 fprintf(outfile,")\n");
5960                 ast_print(tree->left,outfile,indent+2);
5961                 ast_print(tree->right,outfile,indent+2);
5962                 return;
5963                 /*------------------------------------------------------------------*/
5964                 /*----------------------------*/
5965                 /*       function call        */
5966                 /*----------------------------*/
5967         case CALL:
5968         case PCALL:
5969                 fprintf(outfile,"CALL (%p) type (",tree);
5970                 printTypeChain(tree->ftype,outfile);
5971                 fprintf(outfile,")\n");
5972                 ast_print(tree->left,outfile,indent+2);
5973                 ast_print(tree->right,outfile,indent+2);
5974                 return;
5975         case PARAM:
5976                 fprintf(outfile,"PARMS\n");
5977                 ast_print(tree->left,outfile,indent+2);
5978                 if (tree->right /*&& !IS_AST_PARAM(tree->right)*/) {
5979                         ast_print(tree->right,outfile,indent+2);
5980                 }
5981                 return ;
5982                 /*------------------------------------------------------------------*/
5983                 /*----------------------------*/
5984                 /*     return statement       */
5985                 /*----------------------------*/
5986         case RETURN:
5987                 fprintf(outfile,"RETURN (%p) type (",tree);
5988                 if (tree->right) {
5989                     printTypeChain(tree->right->ftype,outfile);
5990                 }
5991                 fprintf(outfile,")\n");
5992                 ast_print(tree->right,outfile,indent+2);
5993                 return ;
5994                 /*------------------------------------------------------------------*/
5995                 /*----------------------------*/
5996                 /*     label statement        */
5997                 /*----------------------------*/
5998         case LABEL :
5999                 fprintf(outfile,"LABEL (%p)\n",tree);
6000                 ast_print(tree->left,outfile,indent+2);
6001                 ast_print(tree->right,outfile,indent);
6002                 return;
6003                 /*------------------------------------------------------------------*/
6004                 /*----------------------------*/
6005                 /*     switch statement       */
6006                 /*----------------------------*/
6007         case SWITCH:
6008                 {
6009                         value *val;
6010                         fprintf(outfile,"SWITCH (%p) ",tree);
6011                         ast_print(tree->left,outfile,0);
6012                         for (val = tree->values.switchVals.swVals; val ; val = val->next) {
6013                                 INDENT(indent+2,outfile);
6014                                 fprintf(outfile,"CASE 0x%x GOTO _case_%d_%d\n",
6015                                         (int) floatFromVal(val),
6016                                         tree->values.switchVals.swNum,
6017                                         (int) floatFromVal(val));
6018                         }
6019                         ast_print(tree->right,outfile,indent);
6020                 }
6021                 return ;
6022                 /*------------------------------------------------------------------*/
6023                 /*----------------------------*/
6024                 /* ifx Statement              */
6025                 /*----------------------------*/
6026         case IFX:
6027                 fprintf(outfile,"IF (%p) \n",tree);
6028                 ast_print(tree->left,outfile,indent+2);
6029                 if (tree->trueLabel) {
6030                         INDENT(indent+2,outfile);
6031                         fprintf(outfile,"NE(!=) 0 goto %s\n",tree->trueLabel->name);
6032                 }
6033                 if (tree->falseLabel) {
6034                         INDENT(indent+2,outfile);
6035                         fprintf(outfile,"EQ(==) 0 goto %s\n",tree->falseLabel->name);
6036                 }
6037                 ast_print(tree->right,outfile,indent+2);
6038                 return ;
6039                 /*----------------------------*/
6040                 /* goto Statement              */
6041                 /*----------------------------*/
6042         case GOTO:
6043                 fprintf(outfile,"GOTO (%p) \n",tree);
6044                 ast_print(tree->left,outfile,indent+2);
6045                 fprintf(outfile,"\n");
6046                 return ;
6047                 /*------------------------------------------------------------------*/
6048                 /*----------------------------*/
6049                 /* for Statement              */
6050                 /*----------------------------*/
6051         case FOR:
6052                 fprintf(outfile,"FOR (%p) \n",tree);
6053                 if (AST_FOR( tree, initExpr)) {
6054                         INDENT(indent+2,outfile);
6055                         fprintf(outfile,"INIT EXPR ");
6056                         ast_print(AST_FOR(tree, initExpr),outfile,indent+2);
6057                 }
6058                 if (AST_FOR( tree, condExpr)) {
6059                         INDENT(indent+2,outfile);
6060                         fprintf(outfile,"COND EXPR ");
6061                         ast_print(AST_FOR(tree, condExpr),outfile,indent+2);
6062                 }
6063                 if (AST_FOR( tree, loopExpr)) {
6064                         INDENT(indent+2,outfile);
6065                         fprintf(outfile,"LOOP EXPR ");
6066                         ast_print(AST_FOR(tree, loopExpr),outfile,indent+2);
6067                 }
6068                 fprintf(outfile,"FOR LOOP BODY \n");
6069                 ast_print(tree->left,outfile,indent+2);
6070                 return ;
6071         case CRITICAL:
6072                 fprintf(outfile,"CRITICAL (%p) \n",tree);
6073                 ast_print(tree->left,outfile,indent+2);
6074         default:
6075             return ;
6076         }
6077 }
6078
6079 void PA(ast *t)
6080 {
6081         ast_print(t,stdout,0);
6082 }
6083
6084
6085
6086 /*-----------------------------------------------------------------*/
6087 /* astErrors : returns non-zero if errors present in tree          */
6088 /*-----------------------------------------------------------------*/
6089 int astErrors(ast *t)
6090 {
6091   int errors=0;
6092   
6093   if (t)
6094     {
6095       if (t->isError)
6096         errors++;
6097   
6098       if (t->type == EX_VALUE
6099           && t->opval.val->sym
6100           && t->opval.val->sym->undefined)
6101         errors++;
6102
6103       errors += astErrors(t->left);
6104       errors += astErrors(t->right);
6105     }
6106     
6107   return errors;
6108 }