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