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