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