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