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