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