Fixed left shift. Will promote the left side of a left shift
[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 left shift operation : cast up right->left if type of left
1963        has greater size than right */
1964     if (tree->left && tree->right && tree->right->opval.op == LEFT_OP) {
1965         int lsize = getSize(LTYPE(tree));
1966         int rsize = getSize(RTYPE(tree));
1967
1968         if (lsize > rsize) {
1969             tree->right->decorated = 0;
1970             tree->right->left = newNode( CAST, (lsize == 2 ? 
1971                                                newAst_LINK(newIntLink()) : 
1972                                                newAst_LINK(newLongLink())),
1973                                         tree->right->left);
1974             tree->right = decorateType(tree->right);
1975         }
1976     }
1977   }
1978
1979   /* depending on type of operator do */
1980
1981   switch (tree->opval.op)
1982     {
1983         /*------------------------------------------------------------------*/
1984         /*----------------------------*/
1985         /*        array node          */
1986         /*----------------------------*/
1987     case '[':
1988
1989       /* determine which is the array & which the index */
1990       if ((IS_ARRAY (RTYPE (tree)) || IS_PTR (RTYPE (tree))) && IS_INTEGRAL (LTYPE (tree)))
1991         {
1992
1993           ast *tempTree = tree->left;
1994           tree->left = tree->right;
1995           tree->right = tempTree;
1996         }
1997
1998       /* first check if this is a array or a pointer */
1999       if ((!IS_ARRAY (LTYPE (tree))) && (!IS_PTR (LTYPE (tree))))
2000         {
2001           werror (E_NEED_ARRAY_PTR, "[]");
2002           goto errorTreeReturn;
2003         }
2004
2005       /* check if the type of the idx */
2006       if (!IS_INTEGRAL (RTYPE (tree)))
2007         {
2008           werror (E_IDX_NOT_INT);
2009           goto errorTreeReturn;
2010         }
2011
2012       /* if the left is an rvalue then error */
2013       if (LRVAL (tree))
2014         {
2015           werror (E_LVALUE_REQUIRED, "array access");
2016           goto errorTreeReturn;
2017         }
2018       RRVAL (tree) = 1;
2019       COPYTYPE (TTYPE (tree), TETYPE (tree), LTYPE (tree)->next);
2020       if (IS_PTR(LTYPE(tree))) {
2021               SPEC_CONST (TETYPE (tree)) = DCL_PTR_CONST (LTYPE(tree));
2022       }
2023       return tree;
2024
2025       /*------------------------------------------------------------------*/
2026       /*----------------------------*/
2027       /*      struct/union          */
2028       /*----------------------------*/
2029     case '.':
2030       /* if this is not a structure */
2031       if (!IS_STRUCT (LTYPE (tree)))
2032         {
2033           werror (E_STRUCT_UNION, ".");
2034           goto errorTreeReturn;
2035         }
2036       TTYPE (tree) = structElemType (LTYPE (tree),
2037                                      (tree->right->type == EX_VALUE ?
2038                                tree->right->opval.val : NULL));
2039       TETYPE (tree) = getSpec (TTYPE (tree));
2040       return tree;
2041
2042       /*------------------------------------------------------------------*/
2043       /*----------------------------*/
2044       /*    struct/union pointer    */
2045       /*----------------------------*/
2046     case PTR_OP:
2047       /* if not pointer to a structure */
2048       if (!IS_PTR (LTYPE (tree)))
2049         {
2050           werror (E_PTR_REQD);
2051           goto errorTreeReturn;
2052         }
2053
2054       if (!IS_STRUCT (LTYPE (tree)->next))
2055         {
2056           werror (E_STRUCT_UNION, "->");
2057           goto errorTreeReturn;
2058         }
2059
2060       TTYPE (tree) = structElemType (LTYPE (tree)->next,
2061                                      (tree->right->type == EX_VALUE ?
2062                                tree->right->opval.val : NULL));
2063       TETYPE (tree) = getSpec (TTYPE (tree));
2064
2065       /* adjust the storage class */
2066       switch (DCL_TYPE(tree->left->ftype)) {
2067       case POINTER:
2068         break;
2069       case FPOINTER:
2070         SPEC_SCLS(TETYPE(tree)) = S_XDATA; 
2071         break;
2072       case CPOINTER:
2073         SPEC_SCLS(TETYPE(tree)) = S_CODE; 
2074         break;
2075       case GPOINTER:
2076         break;
2077       case PPOINTER:
2078         SPEC_SCLS(TETYPE(tree)) = S_XSTACK; 
2079         break;
2080       case IPOINTER:
2081         SPEC_SCLS(TETYPE(tree)) = S_IDATA;
2082         break;
2083       case EEPPOINTER:
2084         SPEC_SCLS(TETYPE(tree)) = S_EEPROM;
2085         break;
2086       case UPOINTER:
2087       case ARRAY:
2088       case FUNCTION:
2089       }
2090
2091       return tree;
2092
2093       /*------------------------------------------------------------------*/
2094       /*----------------------------*/
2095       /*  ++/-- operation           */
2096       /*----------------------------*/
2097     case INC_OP:                /* incerement operator unary so left only */
2098     case DEC_OP:
2099       {
2100         sym_link *ltc = (tree->right ? RTYPE (tree) : LTYPE (tree));
2101         COPYTYPE (TTYPE (tree), TETYPE (tree), ltc);
2102         if (!tree->initMode && IS_CONSTANT(TETYPE(tree)))
2103           werror (E_CODE_WRITE, "++/--");
2104
2105         if (tree->right)
2106           RLVAL (tree) = 1;
2107         else
2108           LLVAL (tree) = 1;
2109         return tree;
2110       }
2111
2112       /*------------------------------------------------------------------*/
2113       /*----------------------------*/
2114       /*  bitwise and               */
2115       /*----------------------------*/
2116     case '&':                   /* can be unary   */
2117       /* if right is NULL then unary operation  */
2118       if (tree->right)          /* not an unary operation */
2119         {
2120
2121           if (!IS_INTEGRAL (LTYPE (tree)) || !IS_INTEGRAL (RTYPE (tree)))
2122             {
2123               werror (E_BITWISE_OP);
2124               werror (W_CONTINUE, "left & right types are ");
2125               printTypeChain (LTYPE (tree), stderr);
2126               fprintf (stderr, ",");
2127               printTypeChain (RTYPE (tree), stderr);
2128               fprintf (stderr, "\n");
2129               goto errorTreeReturn;
2130             }
2131
2132           /* if they are both literal */
2133           if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2134             {
2135               tree->type = EX_VALUE;
2136               tree->opval.val = valBitwise (valFromType (LETYPE (tree)),
2137                                           valFromType (RETYPE (tree)), '&');
2138
2139               tree->right = tree->left = NULL;
2140               TETYPE (tree) = tree->opval.val->etype;
2141               TTYPE (tree) = tree->opval.val->type;
2142               return tree;
2143             }
2144
2145           /* see if this is a GETHBIT operation if yes
2146              then return that */
2147           {
2148             ast *otree = optimizeGetHbit (tree);
2149
2150             if (otree != tree)
2151               return decorateType (otree);
2152           }
2153
2154           TTYPE (tree) =
2155             computeType (LTYPE (tree), RTYPE (tree));
2156           TETYPE (tree) = getSpec (TTYPE (tree));
2157
2158           LRVAL (tree) = RRVAL (tree) = 1;
2159           return tree;
2160         }
2161
2162       /*------------------------------------------------------------------*/
2163       /*----------------------------*/
2164       /*  address of                */
2165       /*----------------------------*/
2166       p = newLink ();
2167       p->class = DECLARATOR;
2168       /* if bit field then error */
2169       if (IS_BITVAR (tree->left->etype))
2170         {
2171           werror (E_ILLEGAL_ADDR, "address of bit variable");
2172           goto errorTreeReturn;
2173         }
2174
2175       if (SPEC_SCLS (tree->left->etype) == S_REGISTER)
2176         {
2177           werror (E_ILLEGAL_ADDR, "address of register variable");
2178           goto errorTreeReturn;
2179         }
2180
2181       if (IS_FUNC (LTYPE (tree)))
2182         {
2183           // this ought to be ignored
2184           return (tree->left);
2185         }
2186
2187       if (IS_LITERAL(LTYPE(tree)))
2188         {
2189           werror (E_ILLEGAL_ADDR, "address of literal");
2190           goto errorTreeReturn;
2191         }
2192
2193      if (LRVAL (tree))
2194         {
2195           werror (E_LVALUE_REQUIRED, "address of");
2196           goto errorTreeReturn;
2197         }
2198       if (SPEC_SCLS (tree->left->etype) == S_CODE)
2199         {
2200           DCL_TYPE (p) = CPOINTER;
2201           DCL_PTR_CONST (p) = port->mem.code_ro;
2202         }
2203       else if (SPEC_SCLS (tree->left->etype) == S_XDATA)
2204         DCL_TYPE (p) = FPOINTER;
2205       else if (SPEC_SCLS (tree->left->etype) == S_XSTACK)
2206         DCL_TYPE (p) = PPOINTER;
2207       else if (SPEC_SCLS (tree->left->etype) == S_IDATA)
2208         DCL_TYPE (p) = IPOINTER;
2209       else if (SPEC_SCLS (tree->left->etype) == S_EEPROM)
2210         DCL_TYPE (p) = EEPPOINTER;
2211       else if (SPEC_OCLS(tree->left->etype))
2212           DCL_TYPE (p) = PTR_TYPE(SPEC_OCLS(tree->left->etype));
2213       else
2214           DCL_TYPE (p) = POINTER;
2215
2216       if (IS_AST_SYM_VALUE (tree->left))
2217         {
2218           AST_SYMBOL (tree->left)->addrtaken = 1;
2219           AST_SYMBOL (tree->left)->allocreq = 1;
2220         }
2221
2222       p->next = LTYPE (tree);
2223       TTYPE (tree) = p;
2224       TETYPE (tree) = getSpec (TTYPE (tree));
2225       DCL_PTR_CONST (p) = SPEC_CONST (TETYPE (tree));
2226       DCL_PTR_VOLATILE (p) = SPEC_VOLATILE (TETYPE (tree));
2227       LLVAL (tree) = 1;
2228       TLVAL (tree) = 1;
2229       return tree;
2230
2231       /*------------------------------------------------------------------*/
2232       /*----------------------------*/
2233       /*  bitwise or                */
2234       /*----------------------------*/
2235     case '|':
2236       /* if the rewrite succeeds then don't go any furthur */
2237       {
2238         ast *wtree = optimizeRRCRLC (tree);
2239         if (wtree != tree)
2240           return decorateType (wtree);
2241       }
2242       /*------------------------------------------------------------------*/
2243       /*----------------------------*/
2244       /*  bitwise xor               */
2245       /*----------------------------*/
2246     case '^':
2247       if (!IS_INTEGRAL (LTYPE (tree)) || !IS_INTEGRAL (RTYPE (tree)))
2248         {
2249           werror (E_BITWISE_OP);
2250           werror (W_CONTINUE, "left & right types are ");
2251           printTypeChain (LTYPE (tree), stderr);
2252           fprintf (stderr, ",");
2253           printTypeChain (RTYPE (tree), stderr);
2254           fprintf (stderr, "\n");
2255           goto errorTreeReturn;
2256         }
2257
2258       /* if they are both literal then */
2259       /* rewrite the tree */
2260       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2261         {
2262           tree->type = EX_VALUE;
2263           tree->opval.val = valBitwise (valFromType (LETYPE (tree)),
2264                                         valFromType (RETYPE (tree)),
2265                                         tree->opval.op);
2266           tree->right = tree->left = NULL;
2267           TETYPE (tree) = tree->opval.val->etype;
2268           TTYPE (tree) = tree->opval.val->type;
2269           return tree;
2270         }
2271       LRVAL (tree) = RRVAL (tree) = 1;
2272       TETYPE (tree) = getSpec (TTYPE (tree) =
2273                                computeType (LTYPE (tree),
2274                                             RTYPE (tree)));
2275
2276       /*------------------------------------------------------------------*/
2277       /*----------------------------*/
2278       /*  division                  */
2279       /*----------------------------*/
2280     case '/':
2281       if (!IS_ARITHMETIC (LTYPE (tree)) || !IS_ARITHMETIC (RTYPE (tree)))
2282         {
2283           werror (E_INVALID_OP, "divide");
2284           goto errorTreeReturn;
2285         }
2286       /* if they are both literal then */
2287       /* rewrite the tree */
2288       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2289         {
2290           tree->type = EX_VALUE;
2291           tree->opval.val = valDiv (valFromType (LETYPE (tree)),
2292                                     valFromType (RETYPE (tree)));
2293           tree->right = tree->left = NULL;
2294           TETYPE (tree) = getSpec (TTYPE (tree) =
2295                                    tree->opval.val->type);
2296           return tree;
2297         }
2298       LRVAL (tree) = RRVAL (tree) = 1;
2299       TETYPE (tree) = getSpec (TTYPE (tree) =
2300                                computeType (LTYPE (tree),
2301                                             RTYPE (tree)));
2302       return tree;
2303
2304       /*------------------------------------------------------------------*/
2305       /*----------------------------*/
2306       /*            modulus         */
2307       /*----------------------------*/
2308     case '%':
2309       if (!IS_INTEGRAL (LTYPE (tree)) || !IS_INTEGRAL (RTYPE (tree)))
2310         {
2311           werror (E_BITWISE_OP);
2312           werror (W_CONTINUE, "left & right types are ");
2313           printTypeChain (LTYPE (tree), stderr);
2314           fprintf (stderr, ",");
2315           printTypeChain (RTYPE (tree), stderr);
2316           fprintf (stderr, "\n");
2317           goto errorTreeReturn;
2318         }
2319       /* if they are both literal then */
2320       /* rewrite the tree */
2321       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2322         {
2323           tree->type = EX_VALUE;
2324           tree->opval.val = valMod (valFromType (LETYPE (tree)),
2325                                     valFromType (RETYPE (tree)));
2326           tree->right = tree->left = NULL;
2327           TETYPE (tree) = getSpec (TTYPE (tree) =
2328                                    tree->opval.val->type);
2329           return tree;
2330         }
2331       LRVAL (tree) = RRVAL (tree) = 1;
2332       TETYPE (tree) = getSpec (TTYPE (tree) =
2333                                computeType (LTYPE (tree),
2334                                             RTYPE (tree)));
2335       return tree;
2336
2337       /*------------------------------------------------------------------*/
2338       /*----------------------------*/
2339       /*  address dereference       */
2340       /*----------------------------*/
2341     case '*':                   /* can be unary  : if right is null then unary operation */
2342       if (!tree->right)
2343         {
2344           if (!IS_PTR (LTYPE (tree)) && !IS_ARRAY (LTYPE (tree)))
2345             {
2346               werror (E_PTR_REQD);
2347               goto errorTreeReturn;
2348             }
2349
2350           if (LRVAL (tree))
2351             {
2352               werror (E_LVALUE_REQUIRED, "pointer deref");
2353               goto errorTreeReturn;
2354             }
2355           TTYPE (tree) = copyLinkChain ((IS_PTR (LTYPE (tree)) || IS_ARRAY (LTYPE (tree))) ?
2356                                         LTYPE (tree)->next : NULL);
2357           TETYPE (tree) = getSpec (TTYPE (tree));
2358           SPEC_CONST (TETYPE (tree)) = DCL_PTR_CONST (LTYPE(tree));
2359           return tree;
2360         }
2361
2362       /*------------------------------------------------------------------*/
2363       /*----------------------------*/
2364       /*      multiplication        */
2365       /*----------------------------*/
2366       if (!IS_ARITHMETIC (LTYPE (tree)) || !IS_ARITHMETIC (RTYPE (tree)))
2367         {
2368           werror (E_INVALID_OP, "multiplication");
2369           goto errorTreeReturn;
2370         }
2371
2372       /* if they are both literal then */
2373       /* rewrite the tree */
2374       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2375         {
2376           tree->type = EX_VALUE;
2377           tree->opval.val = valMult (valFromType (LETYPE (tree)),
2378                                      valFromType (RETYPE (tree)));
2379           tree->right = tree->left = NULL;
2380           TETYPE (tree) = getSpec (TTYPE (tree) =
2381                                    tree->opval.val->type);
2382           return tree;
2383         }
2384
2385       /* if left is a literal exchange left & right */
2386       if (IS_LITERAL (LTYPE (tree)))
2387         {
2388           ast *tTree = tree->left;
2389           tree->left = tree->right;
2390           tree->right = tTree;
2391         }
2392
2393       LRVAL (tree) = RRVAL (tree) = 1;
2394       /* promote result to int if left & right are char
2395          this will facilitate hardware multiplies 8bit x 8bit = 16bit */
2396       if (IS_CHAR(LETYPE(tree)) && IS_CHAR(RETYPE(tree))) {
2397         TETYPE (tree) = getSpec (TTYPE (tree) =
2398                                  computeType (LTYPE (tree),
2399                                               RTYPE (tree)));
2400         SPEC_NOUN(TETYPE(tree)) = V_INT;
2401       } else {
2402         TETYPE (tree) = getSpec (TTYPE (tree) =
2403                                  computeType (LTYPE (tree),
2404                                               RTYPE (tree)));
2405       }
2406       return tree;
2407
2408       /*------------------------------------------------------------------*/
2409       /*----------------------------*/
2410       /*    unary '+' operator      */
2411       /*----------------------------*/
2412     case '+':
2413       /* if unary plus */
2414       if (!tree->right)
2415         {
2416           if (!IS_INTEGRAL (LTYPE (tree)))
2417             {
2418               werror (E_UNARY_OP, '+');
2419               goto errorTreeReturn;
2420             }
2421
2422           /* if left is a literal then do it */
2423           if (IS_LITERAL (LTYPE (tree)))
2424             {
2425               tree->type = EX_VALUE;
2426               tree->opval.val = valFromType (LETYPE (tree));
2427               tree->left = NULL;
2428               TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
2429               return tree;
2430             }
2431           LRVAL (tree) = 1;
2432           COPYTYPE (TTYPE (tree), TETYPE (tree), LTYPE (tree));
2433           return tree;
2434         }
2435
2436       /*------------------------------------------------------------------*/
2437       /*----------------------------*/
2438       /*      addition              */
2439       /*----------------------------*/
2440
2441       /* this is not a unary operation */
2442       /* if both pointers then problem */
2443       if ((IS_PTR (LTYPE (tree)) || IS_ARRAY (LTYPE (tree))) &&
2444           (IS_PTR (RTYPE (tree)) || IS_ARRAY (RTYPE (tree))))
2445         {
2446           werror (E_PTR_PLUS_PTR);
2447           goto errorTreeReturn;
2448         }
2449
2450       if (!IS_ARITHMETIC (LTYPE (tree)) &&
2451           !IS_PTR (LTYPE (tree)) && !IS_ARRAY (LTYPE (tree)))
2452         {
2453           werror (E_PLUS_INVALID, "+");
2454           goto errorTreeReturn;
2455         }
2456
2457       if (!IS_ARITHMETIC (RTYPE (tree)) &&
2458           !IS_PTR (RTYPE (tree)) && !IS_ARRAY (RTYPE (tree)))
2459         {
2460           werror (E_PLUS_INVALID, "+");
2461           goto errorTreeReturn;
2462         }
2463       /* if they are both literal then */
2464       /* rewrite the tree */
2465       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2466         {
2467           tree->type = EX_VALUE;
2468           tree->opval.val = valPlus (valFromType (LETYPE (tree)),
2469                                      valFromType (RETYPE (tree)));
2470           tree->right = tree->left = NULL;
2471           TETYPE (tree) = getSpec (TTYPE (tree) =
2472                                    tree->opval.val->type);
2473           return tree;
2474         }
2475
2476       /* if the right is a pointer or left is a literal
2477          xchange left & right */
2478       if (IS_ARRAY (RTYPE (tree)) ||
2479           IS_PTR (RTYPE (tree)) ||
2480           IS_LITERAL (LTYPE (tree)))
2481         {
2482           ast *tTree = tree->left;
2483           tree->left = tree->right;
2484           tree->right = tTree;
2485         }
2486
2487       LRVAL (tree) = RRVAL (tree) = 1;
2488       /* if the left is a pointer */
2489       if (IS_PTR (LTYPE (tree)) || IS_ARRAY (LTYPE (tree)))
2490         TETYPE (tree) = getSpec (TTYPE (tree) =
2491                                  LTYPE (tree));
2492       else
2493         TETYPE (tree) = getSpec (TTYPE (tree) =
2494                                  computeType (LTYPE (tree),
2495                                               RTYPE (tree)));
2496       return tree;
2497
2498       /*------------------------------------------------------------------*/
2499       /*----------------------------*/
2500       /*      unary '-'             */
2501       /*----------------------------*/
2502     case '-':                   /* can be unary   */
2503       /* if right is null then unary */
2504       if (!tree->right)
2505         {
2506
2507           if (!IS_ARITHMETIC (LTYPE (tree)))
2508             {
2509               werror (E_UNARY_OP, tree->opval.op);
2510               goto errorTreeReturn;
2511             }
2512
2513           /* if left is a literal then do it */
2514           if (IS_LITERAL (LTYPE (tree)))
2515             {
2516               tree->type = EX_VALUE;
2517               tree->opval.val = valUnaryPM (valFromType (LETYPE (tree)));
2518               tree->left = NULL;
2519               TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
2520               SPEC_USIGN(TETYPE(tree)) = 0;
2521               return tree;
2522             }
2523           LRVAL (tree) = 1;
2524           TTYPE (tree) = LTYPE (tree);
2525           return tree;
2526         }
2527
2528       /*------------------------------------------------------------------*/
2529       /*----------------------------*/
2530       /*    subtraction             */
2531       /*----------------------------*/
2532
2533       if (!(IS_PTR (LTYPE (tree)) ||
2534             IS_ARRAY (LTYPE (tree)) ||
2535             IS_ARITHMETIC (LTYPE (tree))))
2536         {
2537           werror (E_PLUS_INVALID, "-");
2538           goto errorTreeReturn;
2539         }
2540
2541       if (!(IS_PTR (RTYPE (tree)) ||
2542             IS_ARRAY (RTYPE (tree)) ||
2543             IS_ARITHMETIC (RTYPE (tree))))
2544         {
2545           werror (E_PLUS_INVALID, "-");
2546           goto errorTreeReturn;
2547         }
2548
2549       if ((IS_PTR (LTYPE (tree)) || IS_ARRAY (LTYPE (tree))) &&
2550           !(IS_PTR (RTYPE (tree)) || IS_ARRAY (RTYPE (tree)) ||
2551             IS_INTEGRAL (RTYPE (tree))))
2552         {
2553           werror (E_PLUS_INVALID, "-");
2554           goto errorTreeReturn;
2555         }
2556
2557       /* if they are both literal then */
2558       /* rewrite the tree */
2559       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2560         {
2561           tree->type = EX_VALUE;
2562           tree->opval.val = valMinus (valFromType (LETYPE (tree)),
2563                                       valFromType (RETYPE (tree)));
2564           tree->right = tree->left = NULL;
2565           TETYPE (tree) = getSpec (TTYPE (tree) =
2566                                    tree->opval.val->type);
2567           return tree;
2568         }
2569
2570       /* if the left & right are equal then zero */
2571       if (isAstEqual (tree->left, tree->right))
2572         {
2573           tree->type = EX_VALUE;
2574           tree->left = tree->right = NULL;
2575           tree->opval.val = constVal ("0");
2576           TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
2577           return tree;
2578         }
2579
2580       /* if both of them are pointers or arrays then */
2581       /* the result is going to be an integer        */
2582       if ((IS_ARRAY (LTYPE (tree)) || IS_PTR (LTYPE (tree))) &&
2583           (IS_ARRAY (RTYPE (tree)) || IS_PTR (RTYPE (tree))))
2584         TETYPE (tree) = TTYPE (tree) = newIntLink ();
2585       else
2586         /* if only the left is a pointer */
2587         /* then result is a pointer      */
2588       if (IS_PTR (LTYPE (tree)) || IS_ARRAY (LTYPE (tree)))
2589         TETYPE (tree) = getSpec (TTYPE (tree) =
2590                                  LTYPE (tree));
2591       else
2592         TETYPE (tree) = getSpec (TTYPE (tree) =
2593                                  computeType (LTYPE (tree),
2594                                               RTYPE (tree)));
2595       LRVAL (tree) = RRVAL (tree) = 1;
2596       return tree;
2597
2598       /*------------------------------------------------------------------*/
2599       /*----------------------------*/
2600       /*    compliment              */
2601       /*----------------------------*/
2602     case '~':
2603       /* can be only integral type */
2604       if (!IS_INTEGRAL (LTYPE (tree)))
2605         {
2606           werror (E_UNARY_OP, tree->opval.op);
2607           goto errorTreeReturn;
2608         }
2609
2610       /* if left is a literal then do it */
2611       if (IS_LITERAL (LTYPE (tree)))
2612         {
2613           tree->type = EX_VALUE;
2614           tree->opval.val = valComplement (valFromType (LETYPE (tree)));
2615           tree->left = NULL;
2616           TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
2617           return tree;
2618         }
2619       LRVAL (tree) = 1;
2620       COPYTYPE (TTYPE (tree), TETYPE (tree), LTYPE (tree));
2621       return tree;
2622
2623       /*------------------------------------------------------------------*/
2624       /*----------------------------*/
2625       /*           not              */
2626       /*----------------------------*/
2627     case '!':
2628       /* can be pointer */
2629       if (!IS_ARITHMETIC (LTYPE (tree)) &&
2630           !IS_PTR (LTYPE (tree)) &&
2631           !IS_ARRAY (LTYPE (tree)))
2632         {
2633           werror (E_UNARY_OP, tree->opval.op);
2634           goto errorTreeReturn;
2635         }
2636
2637       /* if left is a literal then do it */
2638       if (IS_LITERAL (LTYPE (tree)))
2639         {
2640           tree->type = EX_VALUE;
2641           tree->opval.val = valNot (valFromType (LETYPE (tree)));
2642           tree->left = NULL;
2643           TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
2644           return tree;
2645         }
2646       LRVAL (tree) = 1;
2647       TTYPE (tree) = TETYPE (tree) = newCharLink ();
2648       return tree;
2649
2650       /*------------------------------------------------------------------*/
2651       /*----------------------------*/
2652       /*           shift            */
2653       /*----------------------------*/
2654     case RRC:
2655     case RLC:
2656       TTYPE (tree) = LTYPE (tree);
2657       TETYPE (tree) = LETYPE (tree);
2658       return tree;
2659
2660     case GETHBIT:
2661       TTYPE (tree) = TETYPE (tree) = newCharLink ();
2662       return tree;
2663
2664     case LEFT_OP:
2665     case RIGHT_OP:
2666       if (!IS_INTEGRAL (LTYPE (tree)) || !IS_INTEGRAL (tree->left->etype))
2667         {
2668           werror (E_SHIFT_OP_INVALID);
2669           werror (W_CONTINUE, "left & right types are ");
2670           printTypeChain (LTYPE (tree), stderr);
2671           fprintf (stderr, ",");
2672           printTypeChain (RTYPE (tree), stderr);
2673           fprintf (stderr, "\n");
2674           goto errorTreeReturn;
2675         }
2676
2677       /* if they are both literal then */
2678       /* rewrite the tree */
2679       if (IS_LITERAL (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))
2680         {
2681           tree->type = EX_VALUE;
2682           tree->opval.val = valShift (valFromType (LETYPE (tree)),
2683                                       valFromType (RETYPE (tree)),
2684                                       (tree->opval.op == LEFT_OP ? 1 : 0));
2685           tree->right = tree->left = NULL;
2686           TETYPE (tree) = getSpec (TTYPE (tree) =
2687                                    tree->opval.val->type);
2688           return tree;
2689         }
2690 #if 0
2691       /* a left shift must be done with at least 16bits */
2692       if ((tree->opval.op==LEFT_OP) && (getSize(LTYPE(tree))<2)) {
2693         // insert a cast
2694         if (IS_AST_SYM_VALUE(tree->left) || IS_AST_OP(tree->left)) {
2695           tree->left = 
2696             decorateType (newNode (CAST,
2697                                    newAst_LINK(copyLinkChain(LTYPE(tree))),
2698                                    tree->left));
2699           SPEC_NOUN(tree->left->left->ftype)=V_INT;
2700         } else {
2701           // must be a literal, we can do it right away
2702           SPEC_NOUN(tree->left->opval.val->type)=V_INT;
2703         }
2704       }
2705 #endif
2706       /* if only the right side is a literal & we are
2707          shifting more than size of the left operand then zero */
2708       if (IS_LITERAL (RTYPE (tree)) &&
2709           ((unsigned) floatFromVal (valFromType (RETYPE (tree)))) >=
2710           (getSize (LTYPE (tree)) * 8))
2711         {
2712             /* if left shift then cast up */
2713             if (tree->opval.op==LEFT_OP) {
2714                 int size = getSize(LTYPE(tree));
2715                 tree->left = 
2716                     decorateType (newNode (CAST,
2717                                            (size == 1 ? newAst_LINK(newIntLink()) : 
2718                                             (size == 2 ? newAst_LINK(newLongLink()) : 
2719                                              newAst_LINK(newIntLink()))),
2720                                            tree->left));
2721             } else {
2722                 werror (W_SHIFT_CHANGED,
2723                         (tree->opval.op == LEFT_OP ? "left" : "right"));
2724                 tree->type = EX_VALUE;
2725                 tree->left = tree->right = NULL;
2726                 tree->opval.val = constVal ("0");
2727                 TETYPE (tree) = TTYPE (tree) = tree->opval.val->type;
2728                 return tree;
2729             }
2730         }
2731       LRVAL (tree) = RRVAL (tree) = 1;
2732       if (IS_LITERAL (LTYPE (tree)) && !IS_LITERAL (RTYPE (tree)))
2733         {
2734           COPYTYPE (TTYPE (tree), TETYPE (tree), RTYPE (tree));
2735         }
2736       else
2737         {
2738           COPYTYPE (TTYPE (tree), TETYPE (tree), LTYPE (tree));
2739         }
2740       return tree;
2741
2742       /*------------------------------------------------------------------*/
2743       /*----------------------------*/
2744       /*         casting            */
2745       /*----------------------------*/
2746     case CAST:                  /* change the type   */
2747       /* cannot cast to an aggregate type */
2748       if (IS_AGGREGATE (LTYPE (tree)))
2749         {
2750           werror (E_CAST_ILLEGAL);
2751           goto errorTreeReturn;
2752         }
2753       
2754       /* make sure the type is complete and sane */
2755       checkTypeSanity(LETYPE(tree), "(cast)");
2756
2757 #if 0
2758       /* if the right is a literal replace the tree */
2759       if (IS_LITERAL (RETYPE (tree))) {
2760               if (!IS_PTR (LTYPE (tree))) {
2761                       tree->type = EX_VALUE;
2762                       tree->opval.val =
2763                               valCastLiteral (LTYPE (tree),
2764                                               floatFromVal (valFromType (RETYPE (tree))));
2765                       tree->left = NULL;
2766                       tree->right = NULL;
2767                       TTYPE (tree) = tree->opval.val->type;
2768                       tree->values.literalFromCast = 1;
2769               } else if (IS_GENPTR(LTYPE(tree)) && !IS_PTR(RTYPE(tree)) && 
2770                          ((int)floatFromVal(valFromType(RETYPE(tree)))) !=0 ) /* special case of NULL */  {
2771                       sym_link *rest = LTYPE(tree)->next;
2772                       werror(W_LITERAL_GENERIC);                      
2773                       TTYPE(tree) = newLink();
2774                       DCL_TYPE(TTYPE(tree)) = FPOINTER;
2775                       TTYPE(tree)->next = rest;
2776                       tree->left->opval.lnk = TTYPE(tree);
2777                       LRVAL (tree) = 1;
2778               } else {
2779                       TTYPE (tree) = LTYPE (tree);
2780                       LRVAL (tree) = 1;
2781               }
2782       } else {
2783               TTYPE (tree) = LTYPE (tree);
2784               LRVAL (tree) = 1;
2785       }
2786 #else
2787 #if 0 // this is already checked, now this could be explicit
2788       /* if pointer to struct then check names */
2789       if (IS_PTR(LTYPE(tree)) && IS_STRUCT(LTYPE(tree)->next) &&
2790           IS_PTR(RTYPE(tree)) && IS_STRUCT(RTYPE(tree)->next) &&
2791           strcmp(SPEC_STRUCT(LETYPE(tree))->tag,SPEC_STRUCT(RETYPE(tree))->tag)) 
2792         {
2793           werror(W_CAST_STRUCT_PTR,SPEC_STRUCT(RETYPE(tree))->tag,
2794                  SPEC_STRUCT(LETYPE(tree))->tag);
2795         }
2796 #endif
2797       /* if the right is a literal replace the tree */
2798       if (IS_LITERAL (RETYPE (tree)) && !IS_PTR (LTYPE (tree))) {
2799         tree->type = EX_VALUE;
2800         tree->opval.val =
2801           valCastLiteral (LTYPE (tree),
2802                           floatFromVal (valFromType (RETYPE (tree))));
2803         tree->left = NULL;
2804         tree->right = NULL;
2805         TTYPE (tree) = tree->opval.val->type;
2806         tree->values.literalFromCast = 1;
2807       } else {
2808         TTYPE (tree) = LTYPE (tree);
2809         LRVAL (tree) = 1;
2810       }
2811 #endif      
2812       TETYPE (tree) = getSpec (TTYPE (tree));
2813
2814       return tree;
2815
2816       /*------------------------------------------------------------------*/
2817       /*----------------------------*/
2818       /*       logical &&, ||       */
2819       /*----------------------------*/
2820     case AND_OP:
2821     case OR_OP:
2822       /* each must me arithmetic type or be a pointer */
2823       if (!IS_PTR (LTYPE (tree)) &&
2824           !IS_ARRAY (LTYPE (tree)) &&
2825           !IS_INTEGRAL (LTYPE (tree)))
2826         {
2827           werror (E_COMPARE_OP);
2828           goto errorTreeReturn;
2829         }
2830
2831       if (!IS_PTR (RTYPE (tree)) &&
2832           !IS_ARRAY (RTYPE (tree)) &&
2833           !IS_INTEGRAL (RTYPE (tree)))
2834         {
2835           werror (E_COMPARE_OP);
2836           goto errorTreeReturn;
2837         }
2838       /* if they are both literal then */
2839       /* rewrite the tree */
2840       if (IS_LITERAL (RTYPE (tree)) &&
2841           IS_LITERAL (LTYPE (tree)))
2842         {
2843           tree->type = EX_VALUE;
2844           tree->opval.val = valLogicAndOr (valFromType (LETYPE (tree)),
2845                                            valFromType (RETYPE (tree)),
2846                                            tree->opval.op);
2847           tree->right = tree->left = NULL;
2848           TETYPE (tree) = getSpec (TTYPE (tree) =
2849                                    tree->opval.val->type);
2850           return tree;
2851         }
2852       LRVAL (tree) = RRVAL (tree) = 1;
2853       TTYPE (tree) = TETYPE (tree) = newCharLink ();
2854       return tree;
2855
2856       /*------------------------------------------------------------------*/
2857       /*----------------------------*/
2858       /*     comparison operators   */
2859       /*----------------------------*/
2860     case '>':
2861     case '<':
2862     case LE_OP:
2863     case GE_OP:
2864     case EQ_OP:
2865     case NE_OP:
2866       {
2867         ast *lt = optimizeCompare (tree);
2868
2869         if (tree != lt)
2870           return lt;
2871       }
2872
2873       /* if they are pointers they must be castable */
2874       if (IS_PTR (LTYPE (tree)) && IS_PTR (RTYPE (tree)))
2875         {
2876           if (compareType (LTYPE (tree), RTYPE (tree)) == 0)
2877             {
2878               werror (E_COMPARE_OP);
2879               fprintf (stderr, "comparing type ");
2880               printTypeChain (LTYPE (tree), stderr);
2881               fprintf (stderr, "to type ");
2882               printTypeChain (RTYPE (tree), stderr);
2883               fprintf (stderr, "\n");
2884               goto errorTreeReturn;
2885             }
2886         }
2887       /* else they should be promotable to one another */
2888       else
2889         {
2890           if (!((IS_PTR (LTYPE (tree)) && IS_LITERAL (RTYPE (tree))) ||
2891                 (IS_PTR (RTYPE (tree)) && IS_LITERAL (LTYPE (tree)))))
2892
2893             if (compareType (LTYPE (tree), RTYPE (tree)) == 0)
2894               {
2895                 werror (E_COMPARE_OP);
2896                 fprintf (stderr, "comparing type ");
2897                 printTypeChain (LTYPE (tree), stderr);
2898                 fprintf (stderr, "to type ");
2899                 printTypeChain (RTYPE (tree), stderr);
2900                 fprintf (stderr, "\n");
2901                 goto errorTreeReturn;
2902               }
2903         }
2904       /* if unsigned value < 0  then always false */
2905       /* if (unsigned value) > 0 then (unsigned value) */
2906       if (SPEC_USIGN(LETYPE(tree)) && IS_LITERAL(RTYPE(tree)) && 
2907           ((int) floatFromVal (valFromType (RETYPE (tree)))) == 0) {
2908
2909           if (tree->opval.op == '<') {
2910               return tree->right;
2911           }
2912           if (tree->opval.op == '>') {
2913               return tree->left;
2914           }
2915       }
2916       /* if they are both literal then */
2917       /* rewrite the tree */
2918       if (IS_LITERAL (RTYPE (tree)) &&
2919           IS_LITERAL (LTYPE (tree)))
2920         {
2921           tree->type = EX_VALUE;
2922           tree->opval.val = valCompare (valFromType (LETYPE (tree)),
2923                                         valFromType (RETYPE (tree)),
2924                                         tree->opval.op);
2925           tree->right = tree->left = NULL;
2926           TETYPE (tree) = getSpec (TTYPE (tree) =
2927                                    tree->opval.val->type);
2928           return tree;
2929         }
2930       LRVAL (tree) = RRVAL (tree) = 1;
2931       TTYPE (tree) = TETYPE (tree) = newCharLink ();
2932       return tree;
2933
2934       /*------------------------------------------------------------------*/
2935       /*----------------------------*/
2936       /*             sizeof         */
2937       /*----------------------------*/
2938     case SIZEOF:                /* evaluate wihout code generation */
2939       /* change the type to a integer */
2940       tree->type = EX_VALUE;
2941       sprintf (buffer, "%d", (getSize (tree->right->ftype)));
2942       tree->opval.val = constVal (buffer);
2943       tree->right = tree->left = NULL;
2944       TETYPE (tree) = getSpec (TTYPE (tree) =
2945                                tree->opval.val->type);
2946       return tree;
2947
2948       /*------------------------------------------------------------------*/
2949       /*----------------------------*/
2950       /*             typeof         */
2951       /*----------------------------*/
2952     case TYPEOF:
2953         /* return typeof enum value */
2954         tree->type = EX_VALUE;
2955         {
2956             int typeofv = 0;
2957             if (IS_SPEC(tree->right->ftype)) {
2958                 switch (SPEC_NOUN(tree->right->ftype)) {
2959                 case V_INT:
2960                     if (SPEC_LONG(tree->right->ftype)) typeofv = TYPEOF_LONG;
2961                     else typeofv = TYPEOF_INT;
2962                     break;
2963                 case V_FLOAT:
2964                     typeofv = TYPEOF_FLOAT;
2965                     break;
2966                 case V_CHAR:
2967                     typeofv = TYPEOF_CHAR;
2968                     break;
2969                 case V_VOID:
2970                     typeofv = TYPEOF_VOID;
2971                     break;
2972                 case V_STRUCT:
2973                     typeofv = TYPEOF_STRUCT;
2974                     break;
2975                 case V_BIT:
2976                     typeofv = TYPEOF_BIT;
2977                     break;
2978                 case V_SBIT:
2979                     typeofv = TYPEOF_SBIT;
2980                     break;
2981                 default:
2982                     break;
2983                 }
2984             } else {
2985                 switch (DCL_TYPE(tree->right->ftype)) {
2986                 case POINTER:
2987                     typeofv = TYPEOF_POINTER;
2988                     break;
2989                 case FPOINTER:
2990                     typeofv = TYPEOF_FPOINTER;
2991                     break;
2992                 case CPOINTER:
2993                     typeofv = TYPEOF_CPOINTER;
2994                     break;
2995                 case GPOINTER:
2996                     typeofv = TYPEOF_GPOINTER;
2997                     break;
2998                 case PPOINTER:
2999                     typeofv = TYPEOF_PPOINTER;
3000                     break;
3001                 case IPOINTER:
3002                     typeofv = TYPEOF_IPOINTER;
3003                     break;
3004                 case ARRAY:
3005                     typeofv = TYPEOF_ARRAY;
3006                     break;
3007                 case FUNCTION:
3008                     typeofv = TYPEOF_FUNCTION;
3009                     break;
3010                 default:
3011                     break;
3012                 }
3013             }
3014             sprintf (buffer, "%d", typeofv);
3015             tree->opval.val = constVal (buffer);
3016             tree->right = tree->left = NULL;
3017             TETYPE (tree) = getSpec (TTYPE (tree) =
3018                                      tree->opval.val->type);
3019         }
3020         return tree;
3021       /*------------------------------------------------------------------*/
3022       /*----------------------------*/
3023       /* conditional operator  '?'  */
3024       /*----------------------------*/
3025     case '?':
3026       /* the type is value of the colon operator (on the right) */
3027       assert(IS_COLON_OP(tree->right));
3028       /* if already known then replace the tree : optimizer will do it
3029          but faster to do it here */
3030       if (IS_LITERAL (LTYPE(tree))) {     
3031           if ( ((int) floatFromVal (valFromType (LETYPE (tree)))) != 0) {
3032               return decorateType(tree->right->left) ;
3033           } else {
3034               return decorateType(tree->right->right) ;
3035           }
3036       } else {
3037           tree->right = decorateType(tree->right);
3038           TTYPE (tree) = RTYPE(tree);
3039           TETYPE (tree) = getSpec (TTYPE (tree));
3040       }
3041       return tree;
3042
3043     case ':':
3044       /* if they don't match we have a problem */
3045       if (compareType (LTYPE (tree), RTYPE (tree)) == 0)
3046         {
3047           werror (E_TYPE_MISMATCH, "conditional operator", " ");
3048           goto errorTreeReturn;
3049         }
3050
3051       TTYPE (tree) = computeType (LTYPE (tree), RTYPE (tree));
3052       TETYPE (tree) = getSpec (TTYPE (tree));
3053       return tree;
3054
3055
3056 #if 0 // assignment operators are converted by the parser
3057       /*------------------------------------------------------------------*/
3058       /*----------------------------*/
3059       /*    assignment operators    */
3060       /*----------------------------*/
3061     case MUL_ASSIGN:
3062     case DIV_ASSIGN:
3063       /* for these it must be both must be integral */
3064       if (!IS_ARITHMETIC (LTYPE (tree)) ||
3065           !IS_ARITHMETIC (RTYPE (tree)))
3066         {
3067           werror (E_OPS_INTEGRAL);
3068           goto errorTreeReturn;
3069         }
3070       RRVAL (tree) = 1;
3071       TETYPE (tree) = getSpec (TTYPE (tree) = LTYPE (tree));
3072
3073       if (!tree->initMode && IS_CONSTANT (LETYPE (tree)))
3074         werror (E_CODE_WRITE, " ");
3075
3076       if (LRVAL (tree))
3077         {
3078           werror (E_LVALUE_REQUIRED, "*= or /=");
3079           goto errorTreeReturn;
3080         }
3081       LLVAL (tree) = 1;
3082
3083       return tree;
3084
3085     case AND_ASSIGN:
3086     case OR_ASSIGN:
3087     case XOR_ASSIGN:
3088     case RIGHT_ASSIGN:
3089     case LEFT_ASSIGN:
3090       /* for these it must be both must be integral */
3091       if (!IS_INTEGRAL (LTYPE (tree)) ||
3092           !IS_INTEGRAL (RTYPE (tree)))
3093         {
3094           werror (E_OPS_INTEGRAL);
3095           goto errorTreeReturn;
3096         }
3097       RRVAL (tree) = 1;
3098       TETYPE (tree) = getSpec (TTYPE (tree) = LTYPE (tree));
3099
3100       if (!tree->initMode && IS_CONSTANT (LETYPE (tree)))
3101         werror (E_CODE_WRITE, " ");
3102
3103       if (LRVAL (tree))
3104         {
3105           werror (E_LVALUE_REQUIRED, "&= or |= or ^= or >>= or <<=");
3106           goto errorTreeReturn;
3107         }
3108       LLVAL (tree) = 1;
3109
3110       return tree;
3111
3112       /*------------------------------------------------------------------*/
3113       /*----------------------------*/
3114       /*    -= operator             */
3115       /*----------------------------*/
3116     case SUB_ASSIGN:
3117       if (!(IS_PTR (LTYPE (tree)) ||
3118             IS_ARITHMETIC (LTYPE (tree))))
3119         {
3120           werror (E_PLUS_INVALID, "-=");
3121           goto errorTreeReturn;
3122         }
3123
3124       if (!(IS_PTR (RTYPE (tree)) ||
3125             IS_ARITHMETIC (RTYPE (tree))))
3126         {
3127           werror (E_PLUS_INVALID, "-=");
3128           goto errorTreeReturn;
3129         }
3130       RRVAL (tree) = 1;
3131       TETYPE (tree) = getSpec (TTYPE (tree) =
3132                                computeType (LTYPE (tree),
3133                                             RTYPE (tree)));
3134
3135       if (!tree->initMode && IS_CONSTANT (LETYPE (tree)))
3136         werror (E_CODE_WRITE, " ");
3137
3138       if (LRVAL (tree))
3139         {
3140           werror (E_LVALUE_REQUIRED, "-=");
3141           goto errorTreeReturn;
3142         }
3143       LLVAL (tree) = 1;
3144
3145       return tree;
3146
3147       /*------------------------------------------------------------------*/
3148       /*----------------------------*/
3149       /*          += operator       */
3150       /*----------------------------*/
3151     case ADD_ASSIGN:
3152       /* this is not a unary operation */
3153       /* if both pointers then problem */
3154       if (IS_PTR (LTYPE (tree)) && IS_PTR (RTYPE (tree)))
3155         {
3156           werror (E_PTR_PLUS_PTR);
3157           goto errorTreeReturn;
3158         }
3159
3160       if (!IS_ARITHMETIC (LTYPE (tree)) && !IS_PTR (LTYPE (tree)))
3161         {
3162           werror (E_PLUS_INVALID, "+=");
3163           goto errorTreeReturn;
3164         }
3165
3166       if (!IS_ARITHMETIC (RTYPE (tree)) && !IS_PTR (RTYPE (tree)))
3167         {
3168           werror (E_PLUS_INVALID, "+=");
3169           goto errorTreeReturn;
3170         }
3171       RRVAL (tree) = 1;
3172       TETYPE (tree) = getSpec (TTYPE (tree) =
3173                                computeType (LTYPE (tree),
3174                                             RTYPE (tree)));
3175
3176       if (!tree->initMode && IS_CONSTANT (LETYPE (tree)))
3177         werror (E_CODE_WRITE, " ");
3178
3179       if (LRVAL (tree))
3180         {
3181           werror (E_LVALUE_REQUIRED, "+=");
3182           goto errorTreeReturn;
3183         }
3184
3185       tree->right = decorateType (newNode ('+', copyAst (tree->left), tree->right));
3186       tree->opval.op = '=';
3187
3188       return tree;
3189 #endif
3190
3191       /*------------------------------------------------------------------*/
3192       /*----------------------------*/
3193       /*      straight assignemnt   */
3194       /*----------------------------*/
3195     case '=':
3196       /* cannot be an aggregate */
3197       if (IS_AGGREGATE (LTYPE (tree)))
3198         {
3199           werror (E_AGGR_ASSIGN);
3200           goto errorTreeReturn;
3201         }
3202
3203       /* they should either match or be castable */
3204       if (compareType (LTYPE (tree), RTYPE (tree)) == 0)
3205         {
3206           werror (E_TYPE_MISMATCH, "assignment", " ");
3207           printFromToType(RTYPE(tree),LTYPE(tree));
3208           //goto errorTreeReturn;
3209         }
3210
3211       /* if the left side of the tree is of type void
3212          then report error */
3213       if (IS_VOID (LTYPE (tree)))
3214         {
3215           werror (E_CAST_ZERO);
3216           printFromToType(RTYPE(tree), LTYPE(tree));
3217         }
3218
3219       TETYPE (tree) = getSpec (TTYPE (tree) =
3220                                LTYPE (tree));
3221       RRVAL (tree) = 1;
3222       LLVAL (tree) = 1;
3223       if (!tree->initMode ) {
3224         if ((IS_SPEC(LETYPE(tree)) && IS_CONSTANT (LETYPE (tree))))
3225           werror (E_CODE_WRITE, " ");
3226       }
3227       if (LRVAL (tree))
3228         {
3229           werror (E_LVALUE_REQUIRED, "=");
3230           goto errorTreeReturn;
3231         }
3232
3233       return tree;
3234
3235       /*------------------------------------------------------------------*/
3236       /*----------------------------*/
3237       /*      comma operator        */
3238       /*----------------------------*/
3239     case ',':
3240       TETYPE (tree) = getSpec (TTYPE (tree) = RTYPE (tree));
3241       return tree;
3242
3243       /*------------------------------------------------------------------*/
3244       /*----------------------------*/
3245       /*       function call        */
3246       /*----------------------------*/
3247     case CALL:
3248       parmNumber = 1;
3249
3250       if (processParms (tree->left,
3251                         FUNC_ARGS(tree->left->ftype),
3252                         tree->right, &parmNumber, TRUE)) {
3253         goto errorTreeReturn;
3254       }
3255
3256       if ((options.stackAuto || IFFUNC_ISREENT (LTYPE (tree))) && 
3257           !IFFUNC_ISBUILTIN(LTYPE(tree)))
3258         {
3259           //FUNC_ARGS(tree->left->ftype) = 
3260           //reverseVal (FUNC_ARGS(tree->left->ftype));
3261           reverseParms (tree->right);
3262         }
3263
3264       TETYPE (tree) = getSpec (TTYPE (tree) = LTYPE (tree)->next);
3265       return tree;
3266
3267       /*------------------------------------------------------------------*/
3268       /*----------------------------*/
3269       /*     return statement       */
3270       /*----------------------------*/
3271     case RETURN:
3272       if (!tree->right)
3273         goto voidcheck;
3274
3275       if (compareType (currFunc->type->next, RTYPE (tree)) == 0)
3276         {
3277           werror (W_RETURN_MISMATCH);
3278           printFromToType (RTYPE(tree), currFunc->type->next);
3279           goto errorTreeReturn;
3280         }
3281
3282       if (IS_VOID (currFunc->type->next)
3283           && tree->right &&
3284           !IS_VOID (RTYPE (tree)))
3285         {
3286           werror (E_FUNC_VOID);
3287           goto errorTreeReturn;
3288         }
3289
3290       /* if there is going to be a casing required then add it */
3291       if (compareType (currFunc->type->next, RTYPE (tree)) < 0)
3292         {
3293           tree->right =
3294             decorateType (newNode (CAST,
3295                            newAst_LINK (copyLinkChain (currFunc->type->next)),
3296                                    tree->right));
3297         }
3298
3299       RRVAL (tree) = 1;
3300       return tree;
3301
3302     voidcheck:
3303
3304       if (!IS_VOID (currFunc->type->next) && tree->right == NULL)
3305         {
3306           werror (E_VOID_FUNC, currFunc->name);
3307           goto errorTreeReturn;
3308         }
3309
3310       TTYPE (tree) = TETYPE (tree) = NULL;
3311       return tree;
3312
3313       /*------------------------------------------------------------------*/
3314       /*----------------------------*/
3315       /*     switch statement       */
3316       /*----------------------------*/
3317     case SWITCH:
3318       /* the switch value must be an integer */
3319       if (!IS_INTEGRAL (LTYPE (tree)))
3320         {
3321           werror (E_SWITCH_NON_INTEGER);
3322           goto errorTreeReturn;
3323         }
3324       LRVAL (tree) = 1;
3325       TTYPE (tree) = TETYPE (tree) = NULL;
3326       return tree;
3327
3328       /*------------------------------------------------------------------*/
3329       /*----------------------------*/
3330       /* ifx Statement              */
3331       /*----------------------------*/
3332     case IFX:
3333       tree->left = backPatchLabels (tree->left,
3334                                     tree->trueLabel,
3335                                     tree->falseLabel);
3336       TTYPE (tree) = TETYPE (tree) = NULL;
3337       return tree;
3338
3339       /*------------------------------------------------------------------*/
3340       /*----------------------------*/
3341       /* for Statement              */
3342       /*----------------------------*/
3343     case FOR:
3344
3345       decorateType (resolveSymbols (AST_FOR (tree, initExpr)));
3346       decorateType (resolveSymbols (AST_FOR (tree, condExpr)));
3347       decorateType (resolveSymbols (AST_FOR (tree, loopExpr)));
3348
3349       /* if the for loop is reversible then
3350          reverse it otherwise do what we normally
3351          do */
3352       {
3353         symbol *sym;
3354         ast *init, *end;
3355
3356         if (isLoopReversible (tree, &sym, &init, &end))
3357           return reverseLoop (tree, sym, init, end);
3358         else
3359           return decorateType (createFor (AST_FOR (tree, trueLabel),
3360                                           AST_FOR (tree, continueLabel),
3361                                           AST_FOR (tree, falseLabel),
3362                                           AST_FOR (tree, condLabel),
3363                                           AST_FOR (tree, initExpr),
3364                                           AST_FOR (tree, condExpr),
3365                                           AST_FOR (tree, loopExpr),
3366                                           tree->left));
3367       }
3368     default:
3369       TTYPE (tree) = TETYPE (tree) = NULL;
3370       return tree;
3371     }
3372
3373   /* some error found this tree will be killed */
3374 errorTreeReturn:
3375   TTYPE (tree) = TETYPE (tree) = newCharLink ();
3376   tree->opval.op = NULLOP;
3377   tree->isError = 1;
3378
3379   return tree;
3380 }
3381
3382 /*-----------------------------------------------------------------*/
3383 /* sizeofOp - processes size of operation                          */
3384 /*-----------------------------------------------------------------*/
3385 value *
3386 sizeofOp (sym_link * type)
3387 {
3388   char buff[10];
3389
3390   /* make sure the type is complete and sane */
3391   checkTypeSanity(type, "(sizeof)");
3392
3393   /* get the size and convert it to character  */
3394   sprintf (buff, "%d", getSize (type));
3395
3396   /* now convert into value  */
3397   return constVal (buff);
3398 }
3399
3400
3401 #define IS_AND(ex) (ex->type == EX_OP && ex->opval.op == AND_OP )
3402 #define IS_OR(ex)  (ex->type == EX_OP && ex->opval.op == OR_OP )
3403 #define IS_NOT(ex) (ex->type == EX_OP && ex->opval.op == '!' )
3404 #define IS_ANDORNOT(ex) (IS_AND(ex) || IS_OR(ex) || IS_NOT(ex))
3405 #define IS_IFX(ex) (ex->type == EX_OP && ex->opval.op == IFX )
3406 #define IS_LT(ex)  (ex->type == EX_OP && ex->opval.op == '<' )
3407 #define IS_GT(ex)  (ex->type == EX_OP && ex->opval.op == '>')
3408
3409 /*-----------------------------------------------------------------*/
3410 /* backPatchLabels - change and or not operators to flow control    */
3411 /*-----------------------------------------------------------------*/
3412 ast *
3413 backPatchLabels (ast * tree, symbol * trueLabel, symbol * falseLabel)
3414 {
3415
3416   if (!tree)
3417     return NULL;
3418
3419   if (!(IS_ANDORNOT (tree)))
3420     return tree;
3421
3422   /* if this an and */
3423   if (IS_AND (tree))
3424     {
3425       static int localLbl = 0;
3426       symbol *localLabel;
3427
3428       sprintf (buffer, "_and_%d", localLbl++);
3429       localLabel = newSymbol (buffer, NestLevel);
3430
3431       tree->left = backPatchLabels (tree->left, localLabel, falseLabel);
3432
3433       /* if left is already a IFX then just change the if true label in that */
3434       if (!IS_IFX (tree->left))
3435         tree->left = newIfxNode (tree->left, localLabel, falseLabel);
3436
3437       tree->right = backPatchLabels (tree->right, trueLabel, falseLabel);
3438       /* right is a IFX then just join */
3439       if (IS_IFX (tree->right))
3440         return newNode (NULLOP, tree->left, createLabel (localLabel, tree->right));
3441
3442       tree->right = createLabel (localLabel, tree->right);
3443       tree->right = newIfxNode (tree->right, trueLabel, falseLabel);
3444
3445       return newNode (NULLOP, tree->left, tree->right);
3446     }
3447
3448   /* if this is an or operation */
3449   if (IS_OR (tree))
3450     {
3451       static int localLbl = 0;
3452       symbol *localLabel;
3453
3454       sprintf (buffer, "_or_%d", localLbl++);
3455       localLabel = newSymbol (buffer, NestLevel);
3456
3457       tree->left = backPatchLabels (tree->left, trueLabel, localLabel);
3458
3459       /* if left is already a IFX then just change the if true label in that */
3460       if (!IS_IFX (tree->left))
3461         tree->left = newIfxNode (tree->left, trueLabel, localLabel);
3462
3463       tree->right = backPatchLabels (tree->right, trueLabel, falseLabel);
3464       /* right is a IFX then just join */
3465       if (IS_IFX (tree->right))
3466         return newNode (NULLOP, tree->left, createLabel (localLabel, tree->right));
3467
3468       tree->right = createLabel (localLabel, tree->right);
3469       tree->right = newIfxNode (tree->right, trueLabel, falseLabel);
3470
3471       return newNode (NULLOP, tree->left, tree->right);
3472     }
3473
3474   /* change not */
3475   if (IS_NOT (tree))
3476     {
3477       int wasnot = IS_NOT (tree->left);
3478       tree->left = backPatchLabels (tree->left, falseLabel, trueLabel);
3479
3480       /* if the left is already a IFX */
3481       if (!IS_IFX (tree->left))
3482         tree->left = newNode (IFX, tree->left, NULL);
3483
3484       if (wasnot)
3485         {
3486           tree->left->trueLabel = trueLabel;
3487           tree->left->falseLabel = falseLabel;
3488         }
3489       else
3490         {
3491           tree->left->trueLabel = falseLabel;
3492           tree->left->falseLabel = trueLabel;
3493         }
3494       return tree->left;
3495     }
3496
3497   if (IS_IFX (tree))
3498     {
3499       tree->trueLabel = trueLabel;
3500       tree->falseLabel = falseLabel;
3501     }
3502
3503   return tree;
3504 }
3505
3506
3507 /*-----------------------------------------------------------------*/
3508 /* createBlock - create expression tree for block                  */
3509 /*-----------------------------------------------------------------*/
3510 ast *
3511 createBlock (symbol * decl, ast * body)
3512 {
3513   ast *ex;
3514
3515   /* if the block has nothing */
3516   if (!body)
3517     return NULL;
3518
3519   ex = newNode (BLOCK, NULL, body);
3520   ex->values.sym = decl;
3521
3522   ex->right = ex->right;
3523   ex->level++;
3524   ex->lineno = 0;
3525   return ex;
3526 }
3527
3528 /*-----------------------------------------------------------------*/
3529 /* createLabel - creates the expression tree for labels            */
3530 /*-----------------------------------------------------------------*/
3531 ast *
3532 createLabel (symbol * label, ast * stmnt)
3533 {
3534   symbol *csym;
3535   char name[SDCC_NAME_MAX + 1];
3536   ast *rValue;
3537
3538   /* must create fresh symbol if the symbol name  */
3539   /* exists in the symbol table, since there can  */
3540   /* be a variable with the same name as the labl */
3541   if ((csym = findSym (SymbolTab, NULL, label->name)) &&
3542       (csym->level == label->level))
3543     label = newSymbol (label->name, label->level);
3544
3545   /* change the name before putting it in add _ */
3546   sprintf (name, "%s", label->name);
3547
3548   /* put the label in the LabelSymbol table    */
3549   /* but first check if a label of the same    */
3550   /* name exists                               */
3551   if ((csym = findSym (LabelTab, NULL, name)))
3552     werror (E_DUPLICATE_LABEL, label->name);
3553   else
3554     addSym (LabelTab, label, name, label->level, 0, 0);
3555
3556   label->islbl = 1;
3557   label->key = labelKey++;
3558   rValue = newNode (LABEL, newAst_VALUE (symbolVal (label)), stmnt);
3559   rValue->lineno = 0;
3560
3561   return rValue;
3562 }
3563
3564 /*-----------------------------------------------------------------*/
3565 /* createCase - generates the parsetree for a case statement       */
3566 /*-----------------------------------------------------------------*/
3567 ast *
3568 createCase (ast * swStat, ast * caseVal, ast * stmnt)
3569 {
3570   char caseLbl[SDCC_NAME_MAX + 1];
3571   ast *rexpr;
3572   value *val;
3573
3574   /* if the switch statement does not exist */
3575   /* then case is out of context            */
3576   if (!swStat)
3577     {
3578       werror (E_CASE_CONTEXT);
3579       return NULL;
3580     }
3581
3582   caseVal = decorateType (resolveSymbols (caseVal));
3583   /* if not a constant then error  */
3584   if (!IS_LITERAL (caseVal->ftype))
3585     {
3586       werror (E_CASE_CONSTANT);
3587       return NULL;
3588     }
3589
3590   /* if not a integer than error */
3591   if (!IS_INTEGRAL (caseVal->ftype))
3592     {
3593       werror (E_CASE_NON_INTEGER);
3594       return NULL;
3595     }
3596
3597   /* find the end of the switch values chain   */
3598   if (!(val = swStat->values.switchVals.swVals))
3599     swStat->values.switchVals.swVals = caseVal->opval.val;
3600   else
3601     {
3602       /* also order the cases according to value */
3603       value *pval = NULL;
3604       int cVal = (int) floatFromVal (caseVal->opval.val);
3605       while (val && (int) floatFromVal (val) < cVal)
3606         {
3607           pval = val;
3608           val = val->next;
3609         }
3610
3611       /* if we reached the end then */
3612       if (!val)
3613         {
3614           pval->next = caseVal->opval.val;
3615         }
3616       else
3617         {
3618           /* we found a value greater than */
3619           /* the current value we must add this */
3620           /* before the value */
3621           caseVal->opval.val->next = val;
3622
3623           /* if this was the first in chain */
3624           if (swStat->values.switchVals.swVals == val)
3625             swStat->values.switchVals.swVals =
3626               caseVal->opval.val;
3627           else
3628             pval->next = caseVal->opval.val;
3629         }
3630
3631     }
3632
3633   /* create the case label   */
3634   sprintf (caseLbl, "_case_%d_%d",
3635            swStat->values.switchVals.swNum,
3636            (int) floatFromVal (caseVal->opval.val));
3637
3638   rexpr = createLabel (newSymbol (caseLbl, 0), stmnt);
3639   rexpr->lineno = 0;
3640   return rexpr;
3641 }
3642
3643 /*-----------------------------------------------------------------*/
3644 /* createDefault - creates the parse tree for the default statement */
3645 /*-----------------------------------------------------------------*/
3646 ast *
3647 createDefault (ast * swStat, ast * stmnt)
3648 {
3649   char defLbl[SDCC_NAME_MAX + 1];
3650
3651   /* if the switch statement does not exist */
3652   /* then case is out of context            */
3653   if (!swStat)
3654     {
3655       werror (E_CASE_CONTEXT);
3656       return NULL;
3657     }
3658
3659   /* turn on the default flag   */
3660   swStat->values.switchVals.swDefault = 1;
3661
3662   /* create the label  */
3663   sprintf (defLbl, "_default_%d", swStat->values.switchVals.swNum);
3664   return createLabel (newSymbol (defLbl, 0), stmnt);
3665 }
3666
3667 /*-----------------------------------------------------------------*/
3668 /* createIf - creates the parsetree for the if statement           */
3669 /*-----------------------------------------------------------------*/
3670 ast *
3671 createIf (ast * condAst, ast * ifBody, ast * elseBody)
3672 {
3673   static int Lblnum = 0;
3674   ast *ifTree;
3675   symbol *ifTrue, *ifFalse, *ifEnd;
3676
3677   /* if neither exists */
3678   if (!elseBody && !ifBody) {
3679     // if there are no side effects (i++, j() etc)
3680     if (!hasSEFcalls(condAst)) {
3681       return condAst;
3682     }
3683   }
3684
3685   /* create the labels */
3686   sprintf (buffer, "_iffalse_%d", Lblnum);
3687   ifFalse = newSymbol (buffer, NestLevel);
3688   /* if no else body then end == false */
3689   if (!elseBody)
3690     ifEnd = ifFalse;
3691   else
3692     {
3693       sprintf (buffer, "_ifend_%d", Lblnum);
3694       ifEnd = newSymbol (buffer, NestLevel);
3695     }
3696
3697   sprintf (buffer, "_iftrue_%d", Lblnum);
3698   ifTrue = newSymbol (buffer, NestLevel);
3699
3700   Lblnum++;
3701
3702   /* attach the ifTrue label to the top of it body */
3703   ifBody = createLabel (ifTrue, ifBody);
3704   /* attach a goto end to the ifBody if else is present */
3705   if (elseBody)
3706     {
3707       ifBody = newNode (NULLOP, ifBody,
3708                         newNode (GOTO,
3709                                  newAst_VALUE (symbolVal (ifEnd)),
3710                                  NULL));
3711       /* put the elseLabel on the else body */
3712       elseBody = createLabel (ifFalse, elseBody);
3713       /* out the end at the end of the body */
3714       elseBody = newNode (NULLOP,
3715                           elseBody,
3716                           createLabel (ifEnd, NULL));
3717     }
3718   else
3719     {
3720       ifBody = newNode (NULLOP, ifBody,
3721                         createLabel (ifFalse, NULL));
3722     }
3723   condAst = backPatchLabels (condAst, ifTrue, ifFalse);
3724   if (IS_IFX (condAst))
3725     ifTree = condAst;
3726   else
3727     ifTree = newIfxNode (condAst, ifTrue, ifFalse);
3728
3729   return newNode (NULLOP, ifTree,
3730                   newNode (NULLOP, ifBody, elseBody));
3731
3732 }
3733
3734 /*-----------------------------------------------------------------*/
3735 /* createDo - creates parse tree for do                            */
3736 /*        _dobody_n:                                               */
3737 /*            statements                                           */
3738 /*        _docontinue_n:                                           */
3739 /*            condition_expression +-> trueLabel -> _dobody_n      */
3740 /*                                 |                               */
3741 /*                                 +-> falseLabel-> _dobreak_n     */
3742 /*        _dobreak_n:                                              */
3743 /*-----------------------------------------------------------------*/
3744 ast *
3745 createDo (symbol * trueLabel, symbol * continueLabel,
3746           symbol * falseLabel, ast * condAst, ast * doBody)
3747 {
3748   ast *doTree;
3749
3750
3751   /* if the body does not exist then it is simple */
3752   if (!doBody)
3753     {
3754       condAst = backPatchLabels (condAst, continueLabel, NULL);
3755       doTree = (IS_IFX (condAst) ? createLabel (continueLabel, condAst)
3756                 : newNode (IFX, createLabel (continueLabel, condAst), NULL));
3757       doTree->trueLabel = continueLabel;
3758       doTree->falseLabel = NULL;
3759       return doTree;
3760     }
3761
3762   /* otherwise we have a body */
3763   condAst = backPatchLabels (condAst, trueLabel, falseLabel);
3764
3765   /* attach the body label to the top */
3766   doBody = createLabel (trueLabel, doBody);
3767   /* attach the continue label to end of body */
3768   doBody = newNode (NULLOP, doBody,
3769                     createLabel (continueLabel, NULL));
3770
3771   /* now put the break label at the end */
3772   if (IS_IFX (condAst))
3773     doTree = condAst;
3774   else
3775     doTree = newIfxNode (condAst, trueLabel, falseLabel);
3776
3777   doTree = newNode (NULLOP, doTree, createLabel (falseLabel, NULL));
3778
3779   /* putting it together */
3780   return newNode (NULLOP, doBody, doTree);
3781 }
3782
3783 /*-----------------------------------------------------------------*/
3784 /* createFor - creates parse tree for 'for' statement              */
3785 /*        initExpr                                                 */
3786 /*   _forcond_n:                                                   */
3787 /*        condExpr  +-> trueLabel -> _forbody_n                    */
3788 /*                  |                                              */
3789 /*                  +-> falseLabel-> _forbreak_n                   */
3790 /*   _forbody_n:                                                   */
3791 /*        statements                                               */
3792 /*   _forcontinue_n:                                               */
3793 /*        loopExpr                                                 */
3794 /*        goto _forcond_n ;                                        */
3795 /*   _forbreak_n:                                                  */
3796 /*-----------------------------------------------------------------*/
3797 ast *
3798 createFor (symbol * trueLabel, symbol * continueLabel,
3799            symbol * falseLabel, symbol * condLabel,
3800            ast * initExpr, ast * condExpr, ast * loopExpr,
3801            ast * forBody)
3802 {
3803   ast *forTree;
3804
3805   /* if loopexpression not present then we can generate it */
3806   /* the same way as a while */
3807   if (!loopExpr)
3808     return newNode (NULLOP, initExpr,
3809                     createWhile (trueLabel, continueLabel,
3810                                  falseLabel, condExpr, forBody));
3811   /* vanilla for statement */
3812   condExpr = backPatchLabels (condExpr, trueLabel, falseLabel);
3813
3814   if (condExpr && !IS_IFX (condExpr))
3815     condExpr = newIfxNode (condExpr, trueLabel, falseLabel);
3816
3817
3818   /* attach condition label to condition */
3819   condExpr = createLabel (condLabel, condExpr);
3820
3821   /* attach body label to body */
3822   forBody = createLabel (trueLabel, forBody);
3823
3824   /* attach continue to forLoop expression & attach */
3825   /* goto the forcond @ and of loopExpression       */
3826   loopExpr = createLabel (continueLabel,
3827                           newNode (NULLOP,
3828                                    loopExpr,
3829                                    newNode (GOTO,
3830                                        newAst_VALUE (symbolVal (condLabel)),
3831                                             NULL)));
3832   /* now start putting them together */
3833   forTree = newNode (NULLOP, initExpr, condExpr);
3834   forTree = newNode (NULLOP, forTree, forBody);
3835   forTree = newNode (NULLOP, forTree, loopExpr);
3836   /* finally add the break label */
3837   forTree = newNode (NULLOP, forTree,
3838                      createLabel (falseLabel, NULL));
3839   return forTree;
3840 }
3841
3842 /*-----------------------------------------------------------------*/
3843 /* createWhile - creates parse tree for while statement            */
3844 /*               the while statement will be created as follows    */
3845 /*                                                                 */
3846 /*      _while_continue_n:                                         */
3847 /*            condition_expression +-> trueLabel -> _while_boby_n  */
3848 /*                                 |                               */
3849 /*                                 +-> falseLabel -> _while_break_n */
3850 /*      _while_body_n:                                             */
3851 /*            statements                                           */
3852 /*            goto _while_continue_n                               */
3853 /*      _while_break_n:                                            */
3854 /*-----------------------------------------------------------------*/
3855 ast *
3856 createWhile (symbol * trueLabel, symbol * continueLabel,
3857              symbol * falseLabel, ast * condExpr, ast * whileBody)
3858 {
3859   ast *whileTree;
3860
3861   /* put the continue label */
3862   condExpr = backPatchLabels (condExpr, trueLabel, falseLabel);
3863   condExpr = createLabel (continueLabel, condExpr);
3864   condExpr->lineno = 0;
3865
3866   /* put the body label in front of the body */
3867   whileBody = createLabel (trueLabel, whileBody);
3868   whileBody->lineno = 0;
3869   /* put a jump to continue at the end of the body */
3870   /* and put break label at the end of the body */
3871   whileBody = newNode (NULLOP,
3872                        whileBody,
3873                        newNode (GOTO,
3874                                 newAst_VALUE (symbolVal (continueLabel)),
3875                                 createLabel (falseLabel, NULL)));
3876
3877   /* put it all together */
3878   if (IS_IFX (condExpr))
3879     whileTree = condExpr;
3880   else
3881     {
3882       whileTree = newNode (IFX, condExpr, NULL);
3883       /* put the true & false labels in place */
3884       whileTree->trueLabel = trueLabel;
3885       whileTree->falseLabel = falseLabel;
3886     }
3887
3888   return newNode (NULLOP, whileTree, whileBody);
3889 }
3890
3891 /*-----------------------------------------------------------------*/
3892 /* optimizeGetHbit - get highest order bit of the expression       */
3893 /*-----------------------------------------------------------------*/
3894 ast *
3895 optimizeGetHbit (ast * tree)
3896 {
3897   int i, j;
3898   /* if this is not a bit and */
3899   if (!IS_BITAND (tree))
3900     return tree;
3901
3902   /* will look for tree of the form
3903      ( expr >> ((sizeof expr) -1) ) & 1 */
3904   if (!IS_AST_LIT_VALUE (tree->right))
3905     return tree;
3906
3907   if (AST_LIT_VALUE (tree->right) != 1)
3908     return tree;
3909
3910   if (!IS_RIGHT_OP (tree->left))
3911     return tree;
3912
3913   if (!IS_AST_LIT_VALUE (tree->left->right))
3914     return tree;
3915
3916   if ((i = (int) AST_LIT_VALUE (tree->left->right)) !=
3917       (j = (getSize (TTYPE (tree->left->left)) * 8 - 1)))
3918     return tree;
3919
3920   return decorateType (newNode (GETHBIT, tree->left->left, NULL));
3921
3922 }
3923
3924 /*-----------------------------------------------------------------*/
3925 /* optimizeRRCRLC :- optimize for Rotate Left/Right with carry     */
3926 /*-----------------------------------------------------------------*/
3927 ast *
3928 optimizeRRCRLC (ast * root)
3929 {
3930   /* will look for trees of the form
3931      (?expr << 1) | (?expr >> 7) or
3932      (?expr >> 7) | (?expr << 1) will make that
3933      into a RLC : operation ..
3934      Will also look for
3935      (?expr >> 1) | (?expr << 7) or
3936      (?expr << 7) | (?expr >> 1) will make that
3937      into a RRC operation
3938      note : by 7 I mean (number of bits required to hold the
3939      variable -1 ) */
3940   /* if the root operations is not a | operation the not */
3941   if (!IS_BITOR (root))
3942     return root;
3943
3944   /* I have to think of a better way to match patterns this sucks */
3945   /* that aside let start looking for the first case : I use a the
3946      negative check a lot to improve the efficiency */
3947   /* (?expr << 1) | (?expr >> 7) */
3948   if (IS_LEFT_OP (root->left) &&
3949       IS_RIGHT_OP (root->right))
3950     {
3951
3952       if (!SPEC_USIGN (TETYPE (root->left->left)))
3953         return root;
3954
3955       if (!IS_AST_LIT_VALUE (root->left->right) ||
3956           !IS_AST_LIT_VALUE (root->right->right))
3957         goto tryNext0;
3958
3959       /* make sure it is the same expression */
3960       if (!isAstEqual (root->left->left,
3961                        root->right->left))
3962         goto tryNext0;
3963
3964       if (AST_LIT_VALUE (root->left->right) != 1)
3965         goto tryNext0;
3966
3967       if (AST_LIT_VALUE (root->right->right) !=
3968           (getSize (TTYPE (root->left->left)) * 8 - 1))
3969         goto tryNext0;
3970
3971       /* whew got the first case : create the AST */
3972       return newNode (RLC, root->left->left, NULL);
3973     }
3974
3975 tryNext0:
3976   /* check for second case */
3977   /* (?expr >> 7) | (?expr << 1) */
3978   if (IS_LEFT_OP (root->right) &&
3979       IS_RIGHT_OP (root->left))
3980     {
3981
3982       if (!SPEC_USIGN (TETYPE (root->left->left)))
3983         return root;
3984
3985       if (!IS_AST_LIT_VALUE (root->left->right) ||
3986           !IS_AST_LIT_VALUE (root->right->right))
3987         goto tryNext1;
3988
3989       /* make sure it is the same symbol */
3990       if (!isAstEqual (root->left->left,
3991                        root->right->left))
3992         goto tryNext1;
3993
3994       if (AST_LIT_VALUE (root->right->right) != 1)
3995         goto tryNext1;
3996
3997       if (AST_LIT_VALUE (root->left->right) !=
3998           (getSize (TTYPE (root->left->left)) * 8 - 1))
3999         goto tryNext1;
4000
4001       /* whew got the first case : create the AST */
4002       return newNode (RLC, root->left->left, NULL);
4003
4004     }
4005
4006 tryNext1:
4007   /* third case for RRC */
4008   /*  (?symbol >> 1) | (?symbol << 7) */
4009   if (IS_LEFT_OP (root->right) &&
4010       IS_RIGHT_OP (root->left))
4011     {
4012
4013       if (!SPEC_USIGN (TETYPE (root->left->left)))
4014         return root;
4015
4016       if (!IS_AST_LIT_VALUE (root->left->right) ||
4017           !IS_AST_LIT_VALUE (root->right->right))
4018         goto tryNext2;
4019
4020       /* make sure it is the same symbol */
4021       if (!isAstEqual (root->left->left,
4022                        root->right->left))
4023         goto tryNext2;
4024
4025       if (AST_LIT_VALUE (root->left->right) != 1)
4026         goto tryNext2;
4027
4028       if (AST_LIT_VALUE (root->right->right) !=
4029           (getSize (TTYPE (root->left->left)) * 8 - 1))
4030         goto tryNext2;
4031
4032       /* whew got the first case : create the AST */
4033       return newNode (RRC, root->left->left, NULL);
4034
4035     }
4036 tryNext2:
4037   /* fourth and last case for now */
4038   /* (?symbol << 7) | (?symbol >> 1) */
4039   if (IS_RIGHT_OP (root->right) &&
4040       IS_LEFT_OP (root->left))
4041     {
4042
4043       if (!SPEC_USIGN (TETYPE (root->left->left)))
4044         return root;
4045
4046       if (!IS_AST_LIT_VALUE (root->left->right) ||
4047           !IS_AST_LIT_VALUE (root->right->right))
4048         return root;
4049
4050       /* make sure it is the same symbol */
4051       if (!isAstEqual (root->left->left,
4052                        root->right->left))
4053         return root;
4054
4055       if (AST_LIT_VALUE (root->right->right) != 1)
4056         return root;
4057
4058       if (AST_LIT_VALUE (root->left->right) !=
4059           (getSize (TTYPE (root->left->left)) * 8 - 1))
4060         return root;
4061
4062       /* whew got the first case : create the AST */
4063       return newNode (RRC, root->left->left, NULL);
4064
4065     }
4066
4067   /* not found return root */
4068   return root;
4069 }
4070
4071 /*-----------------------------------------------------------------*/
4072 /* optimizeCompare - otimizes compares for bit variables     */
4073 /*-----------------------------------------------------------------*/
4074 static ast *
4075 optimizeCompare (ast * root)
4076 {
4077   ast *optExpr = NULL;
4078   value *vleft;
4079   value *vright;
4080   unsigned int litValue;
4081
4082   /* if nothing then return nothing */
4083   if (!root)
4084     return NULL;
4085
4086   /* if not a compare op then do leaves */
4087   if (!IS_COMPARE_OP (root))
4088     {
4089       root->left = optimizeCompare (root->left);
4090       root->right = optimizeCompare (root->right);
4091       return root;
4092     }
4093
4094   /* if left & right are the same then depending
4095      of the operation do */
4096   if (isAstEqual (root->left, root->right))
4097     {
4098       switch (root->opval.op)
4099         {
4100         case '>':
4101         case '<':
4102         case NE_OP:
4103           optExpr = newAst_VALUE (constVal ("0"));
4104           break;
4105         case GE_OP:
4106         case LE_OP:
4107         case EQ_OP:
4108           optExpr = newAst_VALUE (constVal ("1"));
4109           break;
4110         }
4111
4112       return decorateType (optExpr);
4113     }
4114
4115   vleft = (root->left->type == EX_VALUE ?
4116            root->left->opval.val : NULL);
4117
4118   vright = (root->right->type == EX_VALUE ?
4119             root->right->opval.val : NULL);
4120
4121   /* if left is a BITVAR in BITSPACE */
4122   /* and right is a LITERAL then opt- */
4123   /* imize else do nothing       */
4124   if (vleft && vright &&
4125       IS_BITVAR (vleft->etype) &&
4126       IN_BITSPACE (SPEC_OCLS (vleft->etype)) &&
4127       IS_LITERAL (vright->etype))
4128     {
4129
4130       /* if right side > 1 then comparison may never succeed */
4131       if ((litValue = (int) floatFromVal (vright)) > 1)
4132         {
4133           werror (W_BAD_COMPARE);
4134           goto noOptimize;
4135         }
4136
4137       if (litValue)
4138         {
4139           switch (root->opval.op)
4140             {
4141             case '>':           /* bit value greater than 1 cannot be */
4142               werror (W_BAD_COMPARE);
4143               goto noOptimize;
4144               break;
4145
4146             case '<':           /* bit value < 1 means 0 */
4147             case NE_OP:
4148               optExpr = newNode ('!', newAst_VALUE (vleft), NULL);
4149               break;
4150
4151             case LE_OP: /* bit value <= 1 means no check */
4152               optExpr = newAst_VALUE (vright);
4153               break;
4154
4155             case GE_OP: /* bit value >= 1 means only check for = */
4156             case EQ_OP:
4157               optExpr = newAst_VALUE (vleft);
4158               break;
4159             }
4160         }
4161       else
4162         {                       /* literal is zero */
4163           switch (root->opval.op)
4164             {
4165             case '<':           /* bit value < 0 cannot be */
4166               werror (W_BAD_COMPARE);
4167               goto noOptimize;
4168               break;
4169
4170             case '>':           /* bit value > 0 means 1 */
4171             case NE_OP:
4172               optExpr = newAst_VALUE (vleft);
4173               break;
4174
4175             case LE_OP: /* bit value <= 0 means no check */
4176             case GE_OP: /* bit value >= 0 means no check */
4177               werror (W_BAD_COMPARE);
4178               goto noOptimize;
4179               break;
4180
4181             case EQ_OP: /* bit == 0 means ! of bit */
4182               optExpr = newNode ('!', newAst_VALUE (vleft), NULL);
4183               break;
4184             }
4185         }
4186       return decorateType (resolveSymbols (optExpr));
4187     }                           /* end-of-if of BITVAR */
4188
4189 noOptimize:
4190   return root;
4191 }
4192 /*-----------------------------------------------------------------*/
4193 /* addSymToBlock : adds the symbol to the first block we find      */
4194 /*-----------------------------------------------------------------*/
4195 void 
4196 addSymToBlock (symbol * sym, ast * tree)
4197 {
4198   /* reached end of tree or a leaf */
4199   if (!tree || IS_AST_LINK (tree) || IS_AST_VALUE (tree))
4200     return;
4201
4202   /* found a block */
4203   if (IS_AST_OP (tree) &&
4204       tree->opval.op == BLOCK)
4205     {
4206
4207       symbol *lsym = copySymbol (sym);
4208
4209       lsym->next = AST_VALUES (tree, sym);
4210       AST_VALUES (tree, sym) = lsym;
4211       return;
4212     }
4213
4214   addSymToBlock (sym, tree->left);
4215   addSymToBlock (sym, tree->right);
4216 }
4217
4218 /*-----------------------------------------------------------------*/
4219 /* processRegParms - do processing for register parameters         */
4220 /*-----------------------------------------------------------------*/
4221 static void 
4222 processRegParms (value * args, ast * body)
4223 {
4224   while (args)
4225     {
4226       if (IS_REGPARM (args->etype))
4227         addSymToBlock (args->sym, body);
4228       args = args->next;
4229     }
4230 }
4231
4232 /*-----------------------------------------------------------------*/
4233 /* resetParmKey - resets the operandkeys for the symbols           */
4234 /*-----------------------------------------------------------------*/
4235 DEFSETFUNC (resetParmKey)
4236 {
4237   symbol *sym = item;
4238
4239   sym->key = 0;
4240   sym->defs = NULL;
4241   sym->uses = NULL;
4242   sym->remat = 0;
4243   return 1;
4244 }
4245
4246 /*-----------------------------------------------------------------*/
4247 /* createFunction - This is the key node that calls the iCode for  */
4248 /*                  generating the code for a function. Note code  */
4249 /*                  is generated function by function, later when  */
4250 /*                  add inter-procedural analysis this will change */
4251 /*-----------------------------------------------------------------*/
4252 ast *
4253 createFunction (symbol * name, ast * body)
4254 {
4255   ast *ex;
4256   symbol *csym;
4257   int stack = 0;
4258   sym_link *fetype;
4259   iCode *piCode = NULL;
4260
4261   if (getenv("SDCC_DEBUG_FUNCTION_POINTERS"))
4262     fprintf (stderr, "SDCCast.c:createFunction(%s)\n", name->name);
4263
4264   /* if check function return 0 then some problem */
4265   if (checkFunction (name, NULL) == 0)
4266     return NULL;
4267
4268   /* create a dummy block if none exists */
4269   if (!body)
4270     body = newNode (BLOCK, NULL, NULL);
4271
4272   noLineno++;
4273
4274   /* check if the function name already in the symbol table */
4275   if ((csym = findSym (SymbolTab, NULL, name->name)))
4276     {
4277       name = csym;
4278       /* special case for compiler defined functions
4279          we need to add the name to the publics list : this
4280          actually means we are now compiling the compiler
4281          support routine */
4282       if (name->cdef)
4283         {
4284           addSet (&publics, name);
4285         }
4286     }
4287   else
4288     {
4289       addSymChain (name);
4290       allocVariables (name);
4291     }
4292   name->lastLine = yylineno;
4293   currFunc = name;
4294
4295   /* set the stack pointer */
4296   /* PENDING: check this for the mcs51 */
4297   stackPtr = -port->stack.direction * port->stack.call_overhead;
4298   if (IFFUNC_ISISR (name->type))
4299     stackPtr -= port->stack.direction * port->stack.isr_overhead;
4300   if (IFFUNC_ISREENT (name->type) || options.stackAuto)
4301     stackPtr -= port->stack.direction * port->stack.reent_overhead;
4302
4303   xstackPtr = -port->stack.direction * port->stack.call_overhead;
4304
4305   fetype = getSpec (name->type);        /* get the specifier for the function */
4306   /* if this is a reentrant function then */
4307   if (IFFUNC_ISREENT (name->type))
4308     reentrant++;
4309
4310   allocParms (FUNC_ARGS(name->type));   /* allocate the parameters */
4311
4312   /* do processing for parameters that are passed in registers */
4313   processRegParms (FUNC_ARGS(name->type), body);
4314
4315   /* set the stack pointer */
4316   stackPtr = 0;
4317   xstackPtr = -1;
4318
4319   /* allocate & autoinit the block variables */
4320   processBlockVars (body, &stack, ALLOCATE);
4321
4322   /* save the stack information */
4323   if (options.useXstack)
4324     name->xstack = SPEC_STAK (fetype) = stack;
4325   else
4326     name->stack = SPEC_STAK (fetype) = stack;
4327
4328   /* name needs to be mangled */
4329   sprintf (name->rname, "%s%s", port->fun_prefix, name->name);
4330
4331   body = resolveSymbols (body); /* resolve the symbols */
4332   body = decorateType (body);   /* propagateType & do semantic checks */
4333
4334   ex = newAst_VALUE (symbolVal (name)); /* create name */
4335   ex = newNode (FUNCTION, ex, body);
4336   ex->values.args = FUNC_ARGS(name->type);
4337   ex->decorated=1;
4338   if (options.dump_tree) PA(ex);
4339   if (fatalError)
4340     {
4341       werror (E_FUNC_NO_CODE, name->name);
4342       goto skipall;
4343     }
4344
4345   /* create the node & generate intermediate code */
4346   GcurMemmap = code;
4347   codeOutFile = code->oFile;
4348   piCode = iCodeFromAst (ex);
4349
4350   if (fatalError)
4351     {
4352       werror (E_FUNC_NO_CODE, name->name);
4353       goto skipall;
4354     }
4355
4356   eBBlockFromiCode (piCode);
4357
4358   /* if there are any statics then do them */
4359   if (staticAutos)
4360     {
4361       GcurMemmap = statsg;
4362       codeOutFile = statsg->oFile;
4363       eBBlockFromiCode (iCodeFromAst (decorateType (resolveSymbols (staticAutos))));
4364       staticAutos = NULL;
4365     }
4366
4367 skipall:
4368
4369   /* dealloc the block variables */
4370   processBlockVars (body, &stack, DEALLOCATE);
4371   /* deallocate paramaters */
4372   deallocParms (FUNC_ARGS(name->type));
4373
4374   if (IFFUNC_ISREENT (name->type))
4375     reentrant--;
4376
4377   /* we are done freeup memory & cleanup */
4378   noLineno--;
4379   if (port->reset_labelKey) labelKey = 1;
4380   name->key = 0;
4381   FUNC_HASBODY(name->type) = 1;
4382   addSet (&operKeyReset, name);
4383   applyToSet (operKeyReset, resetParmKey);
4384
4385   if (options.debug)
4386     cdbStructBlock (1, cdbFile);
4387
4388   cleanUpLevel (LabelTab, 0);
4389   cleanUpBlock (StructTab, 1);
4390   cleanUpBlock (TypedefTab, 1);
4391
4392   xstack->syms = NULL;
4393   istack->syms = NULL;
4394   return NULL;
4395 }
4396
4397
4398 #define INDENT(x,f) { int i ; for (i=0;i < x; i++) fprintf(f," "); }
4399 /*-----------------------------------------------------------------*/
4400 /* ast_print : prints the ast (for debugging purposes)             */
4401 /*-----------------------------------------------------------------*/
4402
4403 void ast_print (ast * tree, FILE *outfile, int indent)
4404 {
4405         
4406         if (!tree) return ;
4407
4408         /* can print only decorated trees */
4409         if (!tree->decorated) return;
4410
4411         /* if any child is an error | this one is an error do nothing */
4412         if (tree->isError ||
4413             (tree->left && tree->left->isError) ||
4414             (tree->right && tree->right->isError)) {
4415                 fprintf(outfile,"ERROR_NODE(%p)\n",tree);
4416         }
4417
4418         
4419         /* print the line          */
4420         /* if not block & function */
4421         if (tree->type == EX_OP &&
4422             (tree->opval.op != FUNCTION &&
4423              tree->opval.op != BLOCK &&
4424              tree->opval.op != NULLOP)) {
4425         }
4426         
4427         if (tree->opval.op == FUNCTION) {
4428                 int arg=0;
4429                 value *args=FUNC_ARGS(tree->left->opval.val->type);
4430                 fprintf(outfile,"FUNCTION (%s=%p) type (", 
4431                         tree->left->opval.val->name, tree);
4432                 printTypeChain (tree->ftype,outfile);
4433                 fprintf(outfile,") args (");
4434                 do {
4435                   if (arg) {
4436                     fprintf (outfile, ", ");
4437                   }
4438                   printTypeChain (args ? args->type : NULL, outfile);
4439                   arg++;
4440                   args= args ? args->next : NULL;
4441                 } while (args);
4442                 fprintf(outfile,")\n");
4443                 ast_print(tree->left,outfile,indent);
4444                 ast_print(tree->right,outfile,indent);
4445                 return ;
4446         }
4447         if (tree->opval.op == BLOCK) {
4448                 symbol *decls = tree->values.sym;
4449                 INDENT(indent,outfile);
4450                 fprintf(outfile,"{\n");
4451                 while (decls) {
4452                         INDENT(indent+2,outfile);
4453                         fprintf(outfile,"DECLARE SYMBOL (%s=%p) type (",
4454                                 decls->name, decls);
4455                         printTypeChain(decls->type,outfile);
4456                         fprintf(outfile,")\n");
4457                         
4458                         decls = decls->next;                    
4459                 }
4460                 ast_print(tree->right,outfile,indent+2);
4461                 INDENT(indent,outfile);
4462                 fprintf(outfile,"}\n");
4463                 return;
4464         }
4465         if (tree->opval.op == NULLOP) {
4466                 fprintf(outfile,"\n");
4467                 ast_print(tree->left,outfile,indent);
4468                 fprintf(outfile,"\n");
4469                 ast_print(tree->right,outfile,indent);
4470                 return ;
4471         }
4472         INDENT(indent,outfile);
4473
4474         /*------------------------------------------------------------------*/
4475         /*----------------------------*/
4476         /*   leaf has been reached    */
4477         /*----------------------------*/
4478         /* if this is of type value */
4479         /* just get the type        */
4480         if (tree->type == EX_VALUE) {
4481
4482                 if (IS_LITERAL (tree->opval.val->etype)) {                      
4483                         fprintf(outfile,"CONSTANT (%p) value = %d, 0x%x, %g", tree,
4484                                 (int) floatFromVal(tree->opval.val),
4485                                 (int) floatFromVal(tree->opval.val),
4486                                 floatFromVal(tree->opval.val));
4487                 } else if (tree->opval.val->sym) {
4488                         /* if the undefined flag is set then give error message */
4489                         if (tree->opval.val->sym->undefined) {
4490                                 fprintf(outfile,"UNDEFINED SYMBOL ");
4491                         } else {
4492                                 fprintf(outfile,"SYMBOL ");
4493                         }
4494                         fprintf(outfile,"(%s=%p)",
4495                                 tree->opval.val->sym->name,tree);
4496                 }
4497                 if (tree->ftype) {
4498                         fprintf(outfile," type (");
4499                         printTypeChain(tree->ftype,outfile);
4500                         fprintf(outfile,")\n");
4501                 } else {
4502                         fprintf(outfile,"\n");
4503                 }
4504                 return ;
4505         }
4506
4507         /* if type link for the case of cast */
4508         if (tree->type == EX_LINK) {
4509                 fprintf(outfile,"TYPENODE (%p) type = (",tree);
4510                 printTypeChain(tree->opval.lnk,outfile);
4511                 fprintf(outfile,")\n");
4512                 return ;
4513         }
4514
4515
4516         /* depending on type of operator do */
4517         
4518         switch (tree->opval.op) {
4519                 /*------------------------------------------------------------------*/
4520                 /*----------------------------*/
4521                 /*        array node          */
4522                 /*----------------------------*/
4523         case '[':
4524                 fprintf(outfile,"ARRAY_OP (%p) type (",tree);
4525                 printTypeChain(tree->ftype,outfile);
4526                 fprintf(outfile,")\n");
4527                 ast_print(tree->left,outfile,indent+2);
4528                 ast_print(tree->right,outfile,indent+2);
4529                 return;
4530
4531                 /*------------------------------------------------------------------*/
4532                 /*----------------------------*/
4533                 /*      struct/union          */
4534                 /*----------------------------*/
4535         case '.':
4536                 fprintf(outfile,"STRUCT_ACCESS (%p) type (",tree);
4537                 printTypeChain(tree->ftype,outfile);
4538                 fprintf(outfile,")\n");
4539                 ast_print(tree->left,outfile,indent+2);
4540                 ast_print(tree->right,outfile,indent+2);
4541                 return ;
4542
4543                 /*------------------------------------------------------------------*/
4544                 /*----------------------------*/
4545                 /*    struct/union pointer    */
4546                 /*----------------------------*/
4547         case PTR_OP:
4548                 fprintf(outfile,"PTR_ACCESS (%p) type (",tree);
4549                 printTypeChain(tree->ftype,outfile);
4550                 fprintf(outfile,")\n");
4551                 ast_print(tree->left,outfile,indent+2);
4552                 ast_print(tree->right,outfile,indent+2);
4553                 return ;
4554
4555                 /*------------------------------------------------------------------*/
4556                 /*----------------------------*/
4557                 /*  ++/-- operation           */
4558                 /*----------------------------*/
4559         case INC_OP:            /* incerement operator unary so left only */
4560                 fprintf(outfile,"INC_OP (%p) type (",tree);
4561                 printTypeChain(tree->ftype,outfile);
4562                 fprintf(outfile,")\n");
4563                 ast_print(tree->left,outfile,indent+2);
4564                 return ;
4565
4566         case DEC_OP:
4567                 fprintf(outfile,"DEC_OP (%p) type (",tree);
4568                 printTypeChain(tree->ftype,outfile);
4569                 fprintf(outfile,")\n");
4570                 ast_print(tree->left,outfile,indent+2);
4571                 return ;
4572
4573                 /*------------------------------------------------------------------*/
4574                 /*----------------------------*/
4575                 /*  bitwise and               */
4576                 /*----------------------------*/
4577         case '&':                       
4578                 if (tree->right) {
4579                         fprintf(outfile,"& (%p) type (",tree);
4580                         printTypeChain(tree->ftype,outfile);
4581                         fprintf(outfile,")\n");
4582                         ast_print(tree->left,outfile,indent+2);
4583                         ast_print(tree->right,outfile,indent+2);
4584                 } else {
4585                         fprintf(outfile,"ADDRESS_OF (%p) type (",tree);
4586                         printTypeChain(tree->ftype,outfile);
4587                         fprintf(outfile,")\n");
4588                         ast_print(tree->left,outfile,indent+2);
4589                         ast_print(tree->right,outfile,indent+2);
4590                 }
4591                 return ;
4592                 /*----------------------------*/
4593                 /*  bitwise or                */
4594                 /*----------------------------*/
4595         case '|':
4596                 fprintf(outfile,"OR (%p) type (",tree);
4597                 printTypeChain(tree->ftype,outfile);
4598                 fprintf(outfile,")\n");
4599                 ast_print(tree->left,outfile,indent+2);
4600                 ast_print(tree->right,outfile,indent+2);
4601                 return ;
4602                 /*------------------------------------------------------------------*/
4603                 /*----------------------------*/
4604                 /*  bitwise xor               */
4605                 /*----------------------------*/
4606         case '^':
4607                 fprintf(outfile,"XOR (%p) type (",tree);
4608                 printTypeChain(tree->ftype,outfile);
4609                 fprintf(outfile,")\n");
4610                 ast_print(tree->left,outfile,indent+2);
4611                 ast_print(tree->right,outfile,indent+2);
4612                 return ;
4613                 
4614                 /*------------------------------------------------------------------*/
4615                 /*----------------------------*/
4616                 /*  division                  */
4617                 /*----------------------------*/
4618         case '/':
4619                 fprintf(outfile,"DIV (%p) type (",tree);
4620                 printTypeChain(tree->ftype,outfile);
4621                 fprintf(outfile,")\n");
4622                 ast_print(tree->left,outfile,indent+2);
4623                 ast_print(tree->right,outfile,indent+2);
4624                 return ;
4625                 /*------------------------------------------------------------------*/
4626                 /*----------------------------*/
4627                 /*            modulus         */
4628                 /*----------------------------*/
4629         case '%':
4630                 fprintf(outfile,"MOD (%p) type (",tree);
4631                 printTypeChain(tree->ftype,outfile);
4632                 fprintf(outfile,")\n");
4633                 ast_print(tree->left,outfile,indent+2);
4634                 ast_print(tree->right,outfile,indent+2);
4635                 return ;
4636
4637                 /*------------------------------------------------------------------*/
4638                 /*----------------------------*/
4639                 /*  address dereference       */
4640                 /*----------------------------*/
4641         case '*':                       /* can be unary  : if right is null then unary operation */
4642                 if (!tree->right) {
4643                         fprintf(outfile,"DEREF (%p) type (",tree);
4644                         printTypeChain(tree->ftype,outfile);
4645                         fprintf(outfile,")\n");
4646                         ast_print(tree->left,outfile,indent+2);
4647                         return ;
4648                 }                       
4649                 /*------------------------------------------------------------------*/
4650                 /*----------------------------*/
4651                 /*      multiplication        */
4652                 /*----------------------------*/                
4653                 fprintf(outfile,"MULT (%p) type (",tree);
4654                 printTypeChain(tree->ftype,outfile);
4655                 fprintf(outfile,")\n");
4656                 ast_print(tree->left,outfile,indent+2);
4657                 ast_print(tree->right,outfile,indent+2);
4658                 return ;
4659
4660
4661                 /*------------------------------------------------------------------*/
4662                 /*----------------------------*/
4663                 /*    unary '+' operator      */
4664                 /*----------------------------*/
4665         case '+':
4666                 /* if unary plus */
4667                 if (!tree->right) {
4668                         fprintf(outfile,"UPLUS (%p) type (",tree);
4669                         printTypeChain(tree->ftype,outfile);
4670                         fprintf(outfile,")\n");
4671                         ast_print(tree->left,outfile,indent+2);
4672                 } else {
4673                         /*------------------------------------------------------------------*/
4674                         /*----------------------------*/
4675                         /*      addition              */
4676                         /*----------------------------*/
4677                         fprintf(outfile,"ADD (%p) type (",tree);
4678                         printTypeChain(tree->ftype,outfile);
4679                         fprintf(outfile,")\n");
4680                         ast_print(tree->left,outfile,indent+2);
4681                         ast_print(tree->right,outfile,indent+2);
4682                 }
4683                 return;
4684                 /*------------------------------------------------------------------*/
4685                 /*----------------------------*/
4686                 /*      unary '-'             */
4687                 /*----------------------------*/
4688         case '-':                       /* can be unary   */
4689                 if (!tree->right) {
4690                         fprintf(outfile,"UMINUS (%p) type (",tree);
4691                         printTypeChain(tree->ftype,outfile);
4692                         fprintf(outfile,")\n");
4693                         ast_print(tree->left,outfile,indent+2);
4694                 } else {
4695                         /*------------------------------------------------------------------*/
4696                         /*----------------------------*/
4697                         /*      subtraction           */
4698                         /*----------------------------*/
4699                         fprintf(outfile,"SUB (%p) type (",tree);
4700                         printTypeChain(tree->ftype,outfile);
4701                         fprintf(outfile,")\n");
4702                         ast_print(tree->left,outfile,indent+2);
4703                         ast_print(tree->right,outfile,indent+2);
4704                 }
4705                 return;
4706                 /*------------------------------------------------------------------*/
4707                 /*----------------------------*/
4708                 /*    compliment              */
4709                 /*----------------------------*/
4710         case '~':
4711                 fprintf(outfile,"COMPL (%p) type (",tree);
4712                 printTypeChain(tree->ftype,outfile);
4713                 fprintf(outfile,")\n");
4714                 ast_print(tree->left,outfile,indent+2);
4715                 return ;
4716                 /*------------------------------------------------------------------*/
4717                 /*----------------------------*/
4718                 /*           not              */
4719                 /*----------------------------*/
4720         case '!':
4721                 fprintf(outfile,"NOT (%p) type (",tree);
4722                 printTypeChain(tree->ftype,outfile);
4723                 fprintf(outfile,")\n");
4724                 ast_print(tree->left,outfile,indent+2);
4725                 return ;
4726                 /*------------------------------------------------------------------*/
4727                 /*----------------------------*/
4728                 /*           shift            */
4729                 /*----------------------------*/
4730         case RRC:
4731                 fprintf(outfile,"RRC (%p) type (",tree);
4732                 printTypeChain(tree->ftype,outfile);
4733                 fprintf(outfile,")\n");
4734                 ast_print(tree->left,outfile,indent+2);
4735                 return ;
4736
4737         case RLC:
4738                 fprintf(outfile,"RLC (%p) type (",tree);
4739                 printTypeChain(tree->ftype,outfile);
4740                 fprintf(outfile,")\n");
4741                 ast_print(tree->left,outfile,indent+2);
4742                 return ;
4743         case GETHBIT:
4744                 fprintf(outfile,"GETHBIT (%p) type (",tree);
4745                 printTypeChain(tree->ftype,outfile);
4746                 fprintf(outfile,")\n");
4747                 ast_print(tree->left,outfile,indent+2);
4748                 return ;
4749         case LEFT_OP:
4750                 fprintf(outfile,"LEFT_SHIFT (%p) type (",tree);
4751                 printTypeChain(tree->ftype,outfile);
4752                 fprintf(outfile,")\n");
4753                 ast_print(tree->left,outfile,indent+2);
4754                 ast_print(tree->right,outfile,indent+2);
4755                 return ;
4756         case RIGHT_OP:
4757                 fprintf(outfile,"RIGHT_SHIFT (%p) type (",tree);
4758                 printTypeChain(tree->ftype,outfile);
4759                 fprintf(outfile,")\n");
4760                 ast_print(tree->left,outfile,indent+2);
4761                 ast_print(tree->right,outfile,indent+2);
4762                 return ;
4763                 /*------------------------------------------------------------------*/
4764                 /*----------------------------*/
4765                 /*         casting            */
4766                 /*----------------------------*/
4767         case CAST:                      /* change the type   */
4768                 fprintf(outfile,"CAST (%p) from type (",tree);
4769                 printTypeChain(tree->right->ftype,outfile);
4770                 fprintf(outfile,") to type (");
4771                 printTypeChain(tree->ftype,outfile);
4772                 fprintf(outfile,")\n");
4773                 ast_print(tree->right,outfile,indent+2);
4774                 return ;
4775                 
4776         case AND_OP:
4777                 fprintf(outfile,"ANDAND (%p) type (",tree);
4778                 printTypeChain(tree->ftype,outfile);
4779                 fprintf(outfile,")\n");
4780                 ast_print(tree->left,outfile,indent+2);
4781                 ast_print(tree->right,outfile,indent+2);
4782                 return ;
4783         case OR_OP:
4784                 fprintf(outfile,"OROR (%p) type (",tree);
4785                 printTypeChain(tree->ftype,outfile);
4786                 fprintf(outfile,")\n");
4787                 ast_print(tree->left,outfile,indent+2);
4788                 ast_print(tree->right,outfile,indent+2);
4789                 return ;
4790                 
4791                 /*------------------------------------------------------------------*/
4792                 /*----------------------------*/
4793                 /*     comparison operators   */
4794                 /*----------------------------*/
4795         case '>':
4796                 fprintf(outfile,"GT(>) (%p) type (",tree);
4797                 printTypeChain(tree->ftype,outfile);
4798                 fprintf(outfile,")\n");
4799                 ast_print(tree->left,outfile,indent+2);
4800                 ast_print(tree->right,outfile,indent+2);
4801                 return ;
4802         case '<':
4803                 fprintf(outfile,"LT(<) (%p) type (",tree);
4804                 printTypeChain(tree->ftype,outfile);
4805                 fprintf(outfile,")\n");
4806                 ast_print(tree->left,outfile,indent+2);
4807                 ast_print(tree->right,outfile,indent+2);
4808                 return ;
4809         case LE_OP:
4810                 fprintf(outfile,"LE(<=) (%p) type (",tree);
4811                 printTypeChain(tree->ftype,outfile);
4812                 fprintf(outfile,")\n");
4813                 ast_print(tree->left,outfile,indent+2);
4814                 ast_print(tree->right,outfile,indent+2);
4815                 return ;
4816         case GE_OP:
4817                 fprintf(outfile,"GE(>=) (%p) type (",tree);
4818                 printTypeChain(tree->ftype,outfile);
4819                 fprintf(outfile,")\n");
4820                 ast_print(tree->left,outfile,indent+2);
4821                 ast_print(tree->right,outfile,indent+2);
4822                 return ;
4823         case EQ_OP:
4824                 fprintf(outfile,"EQ(==) (%p) type (",tree);
4825                 printTypeChain(tree->ftype,outfile);
4826                 fprintf(outfile,")\n");
4827                 ast_print(tree->left,outfile,indent+2);
4828                 ast_print(tree->right,outfile,indent+2);
4829                 return ;
4830         case NE_OP:
4831                 fprintf(outfile,"NE(!=) (%p) type (",tree);
4832                 printTypeChain(tree->ftype,outfile);
4833                 fprintf(outfile,")\n");
4834                 ast_print(tree->left,outfile,indent+2);
4835                 ast_print(tree->right,outfile,indent+2);
4836                 /*------------------------------------------------------------------*/
4837                 /*----------------------------*/
4838                 /*             sizeof         */
4839                 /*----------------------------*/
4840         case SIZEOF:            /* evaluate wihout code generation */
4841                 fprintf(outfile,"SIZEOF %d\n",(getSize (tree->right->ftype)));
4842                 return ;
4843
4844                 /*------------------------------------------------------------------*/
4845                 /*----------------------------*/
4846                 /* conditional operator  '?'  */
4847                 /*----------------------------*/
4848         case '?':
4849                 fprintf(outfile,"QUEST(?) (%p) type (",tree);
4850                 printTypeChain(tree->ftype,outfile);
4851                 fprintf(outfile,")\n");
4852                 ast_print(tree->left,outfile,indent+2);
4853                 ast_print(tree->right,outfile,indent+2);
4854                 return;
4855
4856         case ':':
4857                 fprintf(outfile,"COLON(:) (%p) type (",tree);
4858                 printTypeChain(tree->ftype,outfile);
4859                 fprintf(outfile,")\n");
4860                 ast_print(tree->left,outfile,indent+2);
4861                 ast_print(tree->right,outfile,indent+2);
4862                 return ;
4863                 
4864                 /*------------------------------------------------------------------*/
4865                 /*----------------------------*/
4866                 /*    assignment operators    */
4867                 /*----------------------------*/
4868         case MUL_ASSIGN:
4869                 fprintf(outfile,"MULASS(*=) (%p) type (",tree);
4870                 printTypeChain(tree->ftype,outfile);
4871                 fprintf(outfile,")\n");
4872                 ast_print(tree->left,outfile,indent+2);
4873                 ast_print(tree->right,outfile,indent+2);
4874                 return;
4875         case DIV_ASSIGN:
4876                 fprintf(outfile,"DIVASS(/=) (%p) type (",tree);
4877                 printTypeChain(tree->ftype,outfile);
4878                 fprintf(outfile,")\n");
4879                 ast_print(tree->left,outfile,indent+2);
4880                 ast_print(tree->right,outfile,indent+2);
4881                 return;
4882         case AND_ASSIGN:
4883                 fprintf(outfile,"ANDASS(&=) (%p) type (",tree);
4884                 printTypeChain(tree->ftype,outfile);
4885                 fprintf(outfile,")\n");
4886                 ast_print(tree->left,outfile,indent+2);
4887                 ast_print(tree->right,outfile,indent+2);
4888                 return;
4889         case OR_ASSIGN:
4890                 fprintf(outfile,"ORASS(*=) (%p) type (",tree);
4891                 printTypeChain(tree->ftype,outfile);
4892                 fprintf(outfile,")\n");
4893                 ast_print(tree->left,outfile,indent+2);
4894                 ast_print(tree->right,outfile,indent+2);
4895                 return;
4896         case XOR_ASSIGN:
4897                 fprintf(outfile,"XORASS(*=) (%p) type (",tree);
4898                 printTypeChain(tree->ftype,outfile);
4899                 fprintf(outfile,")\n");
4900                 ast_print(tree->left,outfile,indent+2);
4901                 ast_print(tree->right,outfile,indent+2);
4902                 return;
4903         case RIGHT_ASSIGN:
4904                 fprintf(outfile,"RSHFTASS(>>=) (%p) type (",tree);
4905                 printTypeChain(tree->ftype,outfile);
4906                 fprintf(outfile,")\n");
4907                 ast_print(tree->left,outfile,indent+2);
4908                 ast_print(tree->right,outfile,indent+2);
4909                 return;
4910         case LEFT_ASSIGN:
4911                 fprintf(outfile,"LSHFTASS(*=) (%p) type (",tree);
4912                 printTypeChain(tree->ftype,outfile);
4913                 fprintf(outfile,")\n");
4914                 ast_print(tree->left,outfile,indent+2);
4915                 ast_print(tree->right,outfile,indent+2);
4916                 return;
4917                 /*------------------------------------------------------------------*/
4918                 /*----------------------------*/
4919                 /*    -= operator             */
4920                 /*----------------------------*/
4921         case SUB_ASSIGN:
4922                 fprintf(outfile,"SUBASS(-=) (%p) type (",tree);
4923                 printTypeChain(tree->ftype,outfile);
4924                 fprintf(outfile,")\n");
4925                 ast_print(tree->left,outfile,indent+2);
4926                 ast_print(tree->right,outfile,indent+2);
4927                 return;
4928                 /*------------------------------------------------------------------*/
4929                 /*----------------------------*/
4930                 /*          += operator       */
4931                 /*----------------------------*/
4932         case ADD_ASSIGN:
4933                 fprintf(outfile,"ADDASS(+=) (%p) type (",tree);
4934                 printTypeChain(tree->ftype,outfile);
4935                 fprintf(outfile,")\n");
4936                 ast_print(tree->left,outfile,indent+2);
4937                 ast_print(tree->right,outfile,indent+2);
4938                 return;
4939                 /*------------------------------------------------------------------*/
4940                 /*----------------------------*/
4941                 /*      straight assignemnt   */
4942                 /*----------------------------*/
4943         case '=':
4944                 fprintf(outfile,"ASSIGN(=) (%p) type (",tree);
4945                 printTypeChain(tree->ftype,outfile);
4946                 fprintf(outfile,")\n");
4947                 ast_print(tree->left,outfile,indent+2);
4948                 ast_print(tree->right,outfile,indent+2);
4949                 return;     
4950                 /*------------------------------------------------------------------*/
4951                 /*----------------------------*/
4952                 /*      comma operator        */
4953                 /*----------------------------*/
4954         case ',':
4955                 fprintf(outfile,"COMMA(,) (%p) type (",tree);
4956                 printTypeChain(tree->ftype,outfile);
4957                 fprintf(outfile,")\n");
4958                 ast_print(tree->left,outfile,indent+2);
4959                 ast_print(tree->right,outfile,indent+2);
4960                 return;
4961                 /*------------------------------------------------------------------*/
4962                 /*----------------------------*/
4963                 /*       function call        */
4964                 /*----------------------------*/
4965         case CALL:
4966         case PCALL:
4967                 fprintf(outfile,"CALL (%p) type (",tree);
4968                 printTypeChain(tree->ftype,outfile);
4969                 fprintf(outfile,")\n");
4970                 ast_print(tree->left,outfile,indent+2);
4971                 ast_print(tree->right,outfile,indent+2);
4972                 return;
4973         case PARAM:
4974                 fprintf(outfile,"PARMS\n");
4975                 ast_print(tree->left,outfile,indent+2);
4976                 if (tree->right /*&& !IS_AST_PARAM(tree->right)*/) {
4977                         ast_print(tree->right,outfile,indent+2);
4978                 }
4979                 return ;
4980                 /*------------------------------------------------------------------*/
4981                 /*----------------------------*/
4982                 /*     return statement       */
4983                 /*----------------------------*/
4984         case RETURN:
4985                 fprintf(outfile,"RETURN (%p) type (",tree);
4986                 if (tree->right) {
4987                     printTypeChain(tree->right->ftype,outfile);
4988                 }
4989                 fprintf(outfile,")\n");
4990                 ast_print(tree->right,outfile,indent+2);
4991                 return ;
4992                 /*------------------------------------------------------------------*/
4993                 /*----------------------------*/
4994                 /*     label statement        */
4995                 /*----------------------------*/
4996         case LABEL :
4997                 fprintf(outfile,"LABEL (%p)\n",tree);
4998                 ast_print(tree->left,outfile,indent+2);
4999                 ast_print(tree->right,outfile,indent);
5000                 return;
5001                 /*------------------------------------------------------------------*/
5002                 /*----------------------------*/
5003                 /*     switch statement       */
5004                 /*----------------------------*/
5005         case SWITCH:
5006                 {
5007                         value *val;
5008                         fprintf(outfile,"SWITCH (%p) ",tree);
5009                         ast_print(tree->left,outfile,0);
5010                         for (val = tree->values.switchVals.swVals; val ; val = val->next) {
5011                                 INDENT(indent+2,outfile);
5012                                 fprintf(outfile,"CASE 0x%x GOTO _case_%d_%d\n",
5013                                         (int) floatFromVal(val),
5014                                         tree->values.switchVals.swNum,
5015                                         (int) floatFromVal(val));
5016                         }
5017                         ast_print(tree->right,outfile,indent);
5018                 }
5019                 return ;
5020                 /*------------------------------------------------------------------*/
5021                 /*----------------------------*/
5022                 /* ifx Statement              */
5023                 /*----------------------------*/
5024         case IFX:
5025                 fprintf(outfile,"IF (%p) \n",tree);
5026                 ast_print(tree->left,outfile,indent+2);
5027                 if (tree->trueLabel) {
5028                         INDENT(indent,outfile);
5029                         fprintf(outfile,"NE(!=) 0 goto %s\n",tree->trueLabel->name);
5030                 }
5031                 if (tree->falseLabel) {
5032                         INDENT(indent,outfile);
5033                         fprintf(outfile,"EQ(==) 0 goto %s\n",tree->falseLabel->name);
5034                 }
5035                 ast_print(tree->right,outfile,indent+2);
5036                 return ;
5037                 /*------------------------------------------------------------------*/
5038                 /*----------------------------*/
5039                 /* for Statement              */
5040                 /*----------------------------*/
5041         case FOR:
5042                 fprintf(outfile,"FOR (%p) \n",tree);
5043                 if (AST_FOR( tree, initExpr)) {
5044                         INDENT(indent+2,outfile);
5045                         fprintf(outfile,"INIT EXPR ");
5046                         ast_print(AST_FOR(tree, initExpr),outfile,indent+2);
5047                 }
5048                 if (AST_FOR( tree, condExpr)) {
5049                         INDENT(indent+2,outfile);
5050                         fprintf(outfile,"COND EXPR ");
5051                         ast_print(AST_FOR(tree, condExpr),outfile,indent+2);
5052                 }
5053                 if (AST_FOR( tree, loopExpr)) {
5054                         INDENT(indent+2,outfile);
5055                         fprintf(outfile,"LOOP EXPR ");
5056                         ast_print(AST_FOR(tree, loopExpr),outfile,indent+2);
5057                 }
5058                 fprintf(outfile,"FOR LOOP BODY \n");
5059                 ast_print(tree->left,outfile,indent+2);
5060                 return ;
5061         default:
5062             return ;
5063         }
5064 }
5065
5066 void PA(ast *t)
5067 {
5068         ast_print(t,stdout,0);
5069 }