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