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