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