d917e84ff3d9a606c43daca66c1cc0ec1a7330f1
[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 extern char *currFname ;
31 ast *staticAutos = NULL;
32 int labelKey = 1 ;
33
34 #define LRVAL(x) x->left->rvalue
35 #define RRVAL(x) x->right->rvalue
36 #define TRVAL(x) x->rvalue
37 #define LLVAL(x) x->left->lvalue
38 #define RLVAL(x) x->right->lvalue
39 #define TLVAL(x) x->lvalue
40 #define RTYPE(x) x->right->ftype
41 #define RETYPE(x) x->right->etype
42 #define LTYPE(x) x->left->ftype
43 #define LETYPE(x) x->left->etype
44 #define TTYPE(x) x->ftype
45 #define TETYPE(x) x->etype
46 #define ALLOCATE 1
47 #define DEALLOCATE 2
48
49 char  buffer[1024];
50 int noLineno = 0;
51 int noAlloc = 0 ;
52 symbol *currFunc ;
53 extern int fatalError ;
54 extern int lineno;
55 extern char *filename ;
56 extern set *publics;
57 extern ast  *createIval  (ast *, link *, initList *, ast *);
58 extern ast *createIvalCharPtr (ast *, link *, ast *);
59 ast *optimizeRRCRLC ( ast * );
60 ast *optimizeGetHbit(ast *);
61 ast *backPatchLabels (ast *,symbol *,symbol *);
62 int  inInitMode = 0;
63 FILE *codeOutFile ;
64 int ptt(ast *tree) {
65     printTypeChain(tree->ftype,stdout);
66     return 0;
67 }
68      
69
70 /*-----------------------------------------------------------------*/
71 /* newAst - creates a fresh node for an expression tree           */
72 /*-----------------------------------------------------------------*/
73 ast  *newAst (int  type, void *op )
74 {
75     ast  *ex ;
76     static int oldLineno = 0 ;
77
78     ALLOC(ex,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
87     /* depending on the type */
88     switch (type)   {
89     case  EX_VALUE :
90         ex->opval.val = (value *) op;
91         break ;
92     case EX_OP     :
93         ex->opval.op   = (int) op ;
94         break ;
95     case EX_LINK   :
96         ex->opval.lnk  = (link *) op;
97         break ;
98     case EX_STMNT  :
99         ex->opval.stmnt= (unsigned) op;
100     }
101     
102     return ex;
103 }
104
105 /*-----------------------------------------------------------------*/
106 /* newNode - creates a new node                                    */
107 /*-----------------------------------------------------------------*/
108 ast  *newNode ( int op,   ast  *left, ast *right   )
109 {
110     ast  *ex ;
111     
112     ex = newAst (EX_OP,(void *) op) ;
113     ex->left    = left ;
114     ex->right   = right;
115         
116     return ex ;
117 }
118
119 /*-----------------------------------------------------------------*/
120 /* newIfxNode - creates a new Ifx Node                             */
121 /*-----------------------------------------------------------------*/
122 ast *newIfxNode (ast *condAst, symbol *trueLabel, symbol *falseLabel)
123 {
124     ast *ifxNode ;
125     
126     /* if this is a literal then we already know the result */
127     if (condAst->etype && IS_LITERAL(condAst->etype)) {
128         
129         /* then depending on the expression value */
130         if ( floatFromVal(condAst->opval.val) )
131             ifxNode = newNode(GOTO, newAst(EX_VALUE,
132                                            symbolVal (trueLabel )),NULL);
133         else
134             ifxNode = newNode(GOTO, newAst(EX_VALUE,
135                                            symbolVal (falseLabel )),NULL);
136     }
137     else {
138         ifxNode = newNode(IFX,condAst,NULL);
139         ifxNode->trueLabel = trueLabel;
140         ifxNode->falseLabel= falseLabel;
141     }
142     
143     return ifxNode ;
144 }
145
146 /*-----------------------------------------------------------------*/
147 /* copyAstValues - copies value portion of ast if needed           */
148 /*-----------------------------------------------------------------*/
149 void copyAstValues (ast *dest,ast *src)
150 {
151     switch (src->opval.op) {
152     case BLOCK:
153         dest->values.sym     = copySymbolChain(src->values.sym);
154         break;
155         
156     case SWITCH:
157         dest->values.switchVals.swVals = 
158             copyValue(src->values.switchVals.swVals);
159         dest->values.switchVals.swDefault =
160             src->values.switchVals.swDefault ;
161         dest->values.switchVals.swNum  =
162             src->values.switchVals.swNum ;
163         break ;
164         
165     case INLINEASM:
166         ALLOC_ATOMIC(dest->values.inlineasm,strlen(src->values.inlineasm));
167         strcpy(dest->values.inlineasm,src->values.inlineasm);
168
169     case FOR:
170          AST_FOR(dest,trueLabel) = copySymbol(AST_FOR(src,trueLabel));
171          AST_FOR(dest,continueLabel) = copySymbol(AST_FOR(src,continueLabel));
172          AST_FOR(dest,falseLabel) =  copySymbol(AST_FOR(src,falseLabel));
173          AST_FOR(dest,condLabel)  =  copySymbol(AST_FOR(src,condLabel));
174          AST_FOR(dest,initExpr)   =  copyAst (AST_FOR(src,initExpr)) ;
175          AST_FOR(dest,condExpr)   =  copyAst (AST_FOR(src,condExpr)) ;
176          AST_FOR(dest,loopExpr)   =  copyAst (AST_FOR(src,loopExpr)) ;
177     }
178     
179 }
180
181 /*-----------------------------------------------------------------*/
182 /* copyAst - makes a copy of a given astession                     */
183 /*-----------------------------------------------------------------*/
184 ast  *copyAst (ast   *src)
185 {
186     ast  *dest;
187     
188     if (!src)  return NULL ;
189    
190     ALLOC(dest,sizeof(ast));
191     
192     dest->type = src->type  ;
193     dest->lineno = src->lineno ;
194     dest->level  = src->level  ;
195     dest->funcName = src->funcName;
196     dest->argSym = src->argSym;
197     
198     /* if this is a leaf */   
199     /* if value */
200     if (src->type == EX_VALUE)   {
201         dest->opval.val = copyValue(src->opval.val);
202         goto exit;
203     }
204     
205     /* if link */
206     if (src->type == EX_LINK)   {
207         dest->opval.lnk = copyLinkChain(src->opval.lnk);
208         goto exit ;
209     }
210     
211     dest->opval.op = src->opval.op ;
212     
213     /* if this is a node that has special values */
214     copyAstValues (dest,src);
215     
216     if ( src->ftype ) 
217         dest->etype = getSpec(dest->ftype = copyLinkChain(src->ftype)) ;
218     
219     dest->trueLabel = copySymbol (src->trueLabel);
220     dest->falseLabel= copySymbol (src->falseLabel);
221     dest->left = copyAst(src->left);
222     dest->right= copyAst(src->right);
223  exit:
224     return dest ;
225     
226 }
227
228 /*-----------------------------------------------------------------*/
229 /* hasSEFcalls - returns TRUE if tree has a function call          */
230 /*-----------------------------------------------------------------*/
231 bool hasSEFcalls ( ast *tree)
232 {
233     if (!tree)
234         return FALSE ;
235
236     if (tree->type == EX_OP && 
237         ( tree->opval.op == CALL  ||
238           tree->opval.op == PCALL ||
239           tree->opval.op == '='   ||
240           tree->opval.op == INC_OP ||
241           tree->opval.op == DEC_OP ))
242         return TRUE;
243
244     return ( hasSEFcalls(tree->left) |
245              hasSEFcalls(tree->right));
246 }
247
248 /*-----------------------------------------------------------------*/
249 /* isAstEqual - compares two asts & returns 1 if they are equal    */
250 /*-----------------------------------------------------------------*/
251 int isAstEqual (ast *t1, ast *t2)
252 {
253     if (!t1 && !t2)
254         return 1;
255
256     if (!t1 || !t2)
257         return 0;
258
259     /* match type */
260     if (t1->type != t2->type)
261         return 0;
262
263     switch (t1->type) {
264     case EX_OP:
265         if (t1->opval.op != t2->opval.op)
266             return 0;
267         return ( isAstEqual(t1->left,t2->left) &&
268                  isAstEqual(t1->right,t2->right));
269         break;
270
271     case EX_VALUE:
272         if (t1->opval.val->sym) {
273             if (!t2->opval.val->sym)
274                 return 0;
275             else
276                 return isSymbolEqual(t1->opval.val->sym,
277                                      t2->opval.val->sym);
278         }
279         else {
280             if (t2->opval.val->sym)
281                 return 0;
282             else
283                 return (floatFromVal(t1->opval.val) ==
284                         floatFromVal(t2->opval.val));
285         }
286         break;
287
288         /* only compare these two types */
289     default :
290         return 0;
291     }
292
293     return 0;
294 }
295
296 /*-----------------------------------------------------------------*/
297 /* resolveSymbols - resolve symbols from the symbol table          */
298 /*-----------------------------------------------------------------*/
299 ast *resolveSymbols (ast *tree)
300 {
301     /* walk the entire tree and check for values */
302     /* with symbols if we find one then replace  */
303     /* symbol with that from the symbol table    */
304     
305     if ( tree == NULL )
306         return tree ;
307
308     /* print the line          */
309     /* if not block & function */
310     if ( tree->type == EX_OP && 
311          ( tree->opval.op != FUNCTION  &&
312            tree->opval.op != BLOCK     &&
313            tree->opval.op != NULLOP    )) {
314         filename = tree->filename ;
315         lineno = tree->lineno ;
316     }
317
318     /* make sure we resolve the true & false labels for ifx */
319     if (tree->type == EX_OP && tree->opval.op == IFX ) {
320         symbol *csym ;
321
322         if (tree->trueLabel) {
323             if (( csym = findSym(LabelTab,tree->trueLabel,
324                                  tree->trueLabel->name)))
325                 tree->trueLabel = csym ;
326             else
327                 werror(E_LABEL_UNDEF,tree->trueLabel->name);
328         }
329
330         if (tree->falseLabel) {
331             if (( csym = findSym(LabelTab,
332                                  tree->falseLabel,
333                                  tree->falseLabel->name)))
334                 tree->falseLabel = csym ;
335             else
336                 werror(E_LABEL_UNDEF,tree->falseLabel->name);       
337         }
338
339     }
340
341     /* if this is a label resolve it from the labelTab*/
342     if (IS_AST_VALUE(tree)   &&      
343         tree->opval.val->sym &&
344         tree->opval.val->sym->islbl) {
345         
346         symbol *csym = findSym (LabelTab, tree->opval.val->sym , 
347                                 tree->opval.val->sym->name);
348
349         if (!csym) 
350             werror (E_LABEL_UNDEF,tree->opval.val->sym->name);
351         else        
352             tree->opval.val->sym = csym ;       
353
354         goto resolveChildren ;
355     }
356
357     /* do only for leafs */
358     if (IS_AST_VALUE(tree)   && 
359         tree->opval.val->sym && 
360         ! tree->opval.val->sym->implicit ) {
361
362         symbol *csym = findSymWithLevel (SymbolTab,tree->opval.val->sym);
363         
364         /* if found in the symbol table & they r not the same */
365         if (csym && tree->opval.val->sym != csym ) {      
366             tree->opval.val->sym = csym ;          
367             tree->opval.val->type = csym->type;
368             tree->opval.val->etype = csym->etype;
369         }
370         
371         /* if not found in the symbol table */
372         /* mark it as undefined assume it is*/
373         /* an integer in data space         */
374         if (!csym && !tree->opval.val->sym->implicit) {
375             
376             /* if this is a function name then */
377             /* mark it as returning an int     */
378             if (tree->funcName) {
379                 tree->opval.val->sym->type = newLink();
380                 DCL_TYPE(tree->opval.val->sym->type) = FUNCTION;
381                 tree->opval.val->sym->type->next = 
382                     tree->opval.val->sym->etype = newIntLink();
383                 tree->opval.val->etype = tree->opval.val->etype;
384                 tree->opval.val->type = tree->opval.val->sym->type;
385                 werror(W_IMPLICIT_FUNC,tree->opval.val->sym->name);
386             } else {
387                 tree->opval.val->sym->undefined =1 ;
388                 tree->opval.val->type = 
389                     tree->opval.val->etype = newIntLink();
390                 tree->opval.val->sym->type = 
391                     tree->opval.val->sym->etype = newIntLink();
392             }
393         }       
394     }  
395
396  resolveChildren:    
397     resolveSymbols (tree->left);
398     resolveSymbols (tree->right);
399     
400     return tree;
401 }
402
403 /*-----------------------------------------------------------------*/
404 /* setAstLineno - walks a ast tree & sets the line number          */
405 /*-----------------------------------------------------------------*/
406 int setAstLineno ( ast *tree, int lineno)
407 {
408     if (!tree)
409         return 0;
410
411     tree->lineno = lineno ;
412     setAstLineno ( tree->left, lineno);
413     setAstLineno ( tree->right, lineno);
414     return 0;
415 }
416
417 /*-----------------------------------------------------------------*/
418 /* resolveFromTable - will return the symbal table value           */
419 /*-----------------------------------------------------------------*/
420 value *resolveFromTable (value *val)
421 {
422     symbol *csym ;
423
424     if (!val->sym)
425         return val;
426
427     csym = findSymWithLevel (SymbolTab,val->sym);
428             
429     /* if found in the symbol table & they r not the same */
430     if (csym && val->sym != csym && 
431         csym->level == val->sym->level &&
432         csym->_isparm &&
433         !csym->ismyparm) {
434       
435         val->sym = csym ;      
436         val->type = csym->type;
437         val->etype = csym->etype;
438     }  
439
440     return val;
441 }
442
443 /*-----------------------------------------------------------------*/
444 /* funcOfType :- function of type with name                        */
445 /*-----------------------------------------------------------------*/
446 symbol *funcOfType (char *name, link *type, link *argType, 
447                     int nArgs , int rent)
448 {
449     symbol *sym;    
450     int argStack = 0;   
451     /* create the symbol */
452     sym = newSymbol (name,0);
453         
454     /* if arguments required */
455     if (nArgs) {
456
457         value *args ;
458         args = sym->args = newValue();
459
460         while (nArgs--) {
461             argStack += getSize(type);
462             args->type = copyLinkChain(argType);
463             args->etype = getSpec(args->type);
464             if (!nArgs)
465                 break;
466             args = args->next = newValue();
467         }
468     }
469     
470     /* setup return value       */
471     sym->type = newLink();
472     DCL_TYPE(sym->type) = FUNCTION;
473     sym->type->next = copyLinkChain(type);
474     sym->etype = getSpec(sym->type);   
475     SPEC_RENT(sym->etype) = rent;
476     
477     /* save it */
478     addSymChain(sym);
479     sym->cdef = 1;
480     sym->argStack = (rent ? argStack : 0);
481     allocVariables (sym);
482     return sym;
483     
484 }
485
486 /*-----------------------------------------------------------------*/
487 /* reverseParms - will reverse a parameter tree                    */
488 /*-----------------------------------------------------------------*/
489 void reverseParms (ast *ptree)
490 {
491     ast *ttree;
492     if (!ptree)
493         return ;
494
495     /* top down if we find a nonParm tree then quit */
496     if (ptree->type == EX_OP && ptree->opval.op == PARAM ) {
497         ttree = ptree->left;
498         ptree->left = ptree->right;
499         ptree->right = ttree;
500         reverseParms(ptree->left);
501         reverseParms(ptree->right);
502     }
503
504     return ;
505 }
506
507 /*-----------------------------------------------------------------*/
508 /* processParms  - makes sure the parameters are okay and do some  */
509 /*                 processing with them                            */
510 /*-----------------------------------------------------------------*/
511 int processParms (ast *func, value *defParm, 
512                   ast *actParm, 
513                   int *parmNumber)
514 {
515     link *fetype = func->etype;
516     
517     /* if none of them exist */
518     if ( !defParm && !actParm)
519         return 0;
520      
521     /* if the function is being called via a pointer &   */
522     /* it has not been defined a reentrant then we cannot*/
523     /* have parameters                                   */
524     if (func->type != EX_VALUE && !IS_RENT(fetype) && !options.stackAuto) {
525         werror (E_NONRENT_ARGS);  
526         return 1;
527     }
528     
529     /* if defined parameters ended but actual parameters */
530     /* exist and this is not defined as a variable arg   */
531     /* also check if statckAuto option is specified      */
532     if ((! defParm) && actParm && (!func->hasVargs ) && 
533         !options.stackAuto && !IS_RENT(fetype)) {
534         werror(E_TOO_MANY_PARMS);
535         return 1;
536     }
537     
538     /* if defined parameters present and actual paramters ended */
539     if ( defParm && ! actParm) {
540         werror(E_TO_FEW_PARMS);
541         return 1;
542     }
543         
544     /* if defined parameters ended but actual has not & */
545     /* has a variable argument list or statckAuto       */
546     if (! defParm && actParm && 
547         (func->hasVargs || options.stackAuto || IS_RENT(fetype)))
548         return 0;
549     
550     resolveSymbols(actParm);
551     /* if this is a PARAM node then match left & right */
552     if ( actParm->type == EX_OP && actParm->opval.op == PARAM) {
553         
554         return (processParms (func,defParm,actParm->left,parmNumber) ||
555                 processParms (func,defParm->next, actParm->right,parmNumber) );
556     }
557        
558     /* the parameter type must be atleast castable */
559     if (checkType(defParm->type,actParm->ftype) == 0) {
560         werror(E_TYPE_MISMATCH_PARM,*parmNumber);
561         werror(E_CONTINUE,"defined type ");
562         printTypeChain(defParm->type,stderr);fprintf(stderr,"\n");
563         werror(E_CONTINUE,"actual type ");
564         printTypeChain(actParm->ftype,stderr);fprintf(stderr,"\n");
565     }
566     
567     /* if the parameter is castable then add the cast */
568     if ( checkType (defParm->type,actParm->ftype) < 0) {
569         ast *pTree = resolveSymbols(copyAst(actParm));
570
571         /* now change the current one to a cast */      
572         actParm->type = EX_OP ;
573         actParm->opval.op = CAST ;
574         actParm->left = newAst(EX_LINK,defParm->type);
575         actParm->right= pTree ;
576         actParm->etype= defParm->etype;
577         actParm->ftype= defParm->type;
578     }
579     
580     actParm->argSym = resolveFromTable(defParm)->sym ;
581     /* make a copy and change the regparm type to the defined parm */
582     actParm->etype = getSpec(actParm->ftype = copyLinkChain(actParm->ftype));
583     SPEC_REGPARM(actParm->etype) = SPEC_REGPARM(defParm->etype);
584     return 0;
585 }
586 /*-----------------------------------------------------------------*/
587 /* createIvalType - generates ival for basic types                 */
588 /*-----------------------------------------------------------------*/
589 ast *createIvalType ( ast *sym,link  *type, initList *ilist)
590 {
591     ast *iExpr;
592
593     /* if initList is deep */
594     if ( ilist->type == INIT_DEEP )
595         ilist =  ilist->init.deep  ;
596     
597     iExpr = decorateType(resolveSymbols(list2expr(ilist)));
598     return newNode('=',sym,iExpr);
599 }
600
601 /*-----------------------------------------------------------------*/
602 /* createIvalStruct - generates initial value for structures       */
603 /*-----------------------------------------------------------------*/
604 ast *createIvalStruct (ast *sym,link *type,initList *ilist)
605 {
606     ast *rast = NULL ;
607     symbol   *sflds  ;
608     initList *iloop  ;
609     
610     sflds = SPEC_STRUCT(type)->fields  ;
611     if (ilist->type != INIT_DEEP) {
612         werror(E_INIT_STRUCT,"");
613         return NULL ;
614     }
615     
616     iloop = ilist->init.deep;
617     
618     for ( ; sflds ; sflds = sflds->next, iloop = (iloop ? iloop->next : NULL )) {
619         ast *lAst ;
620         
621         /* if we have come to end */
622         if (!iloop)
623             break;
624         sflds->implicit = 1;
625         lAst = decorateType(resolveSymbols(newNode('.',sym,
626                                                    newAst(EX_VALUE,symbolVal(sflds)))));
627         rast = createIval (lAst, sflds->type, iloop,rast);
628     }
629     return rast ;
630 }
631
632
633 /*-----------------------------------------------------------------*/
634 /* createIvalArray - generates code for array initialization       */
635 /*-----------------------------------------------------------------*/
636 ast *createIvalArray (ast  *sym, link *type, initList *ilist)
637 {
638     ast *rast = NULL;
639     initList *iloop ;
640     int lcnt = 0, size =0 ;
641     
642     /* take care of the special   case  */
643     /* array of characters can be init  */
644     /* by a string                      */
645     if ( IS_CHAR(type->next) )
646         if ( (rast = createIvalCharPtr(sym,
647                                        type,
648                                        decorateType(resolveSymbols(list2expr(ilist))))))
649             
650             return rast;
651     
652     /* not the special case             */
653     if (ilist->type != INIT_DEEP) {
654         werror(E_INIT_STRUCT,"");
655         return NULL;
656     }
657     
658     iloop = ilist->init.deep   ;
659     lcnt = DCL_ELEM(type);
660     
661     for (;;)  {
662         ast *aSym ;
663         size++ ;
664
665         aSym = newNode('[',sym,newAst(EX_VALUE,valueFromLit(size-1)));
666         aSym = decorateType(resolveSymbols(aSym));
667         rast = createIval (aSym,type->next,iloop,rast)   ;
668         iloop = (iloop ? iloop->next : NULL) ;
669         if (!iloop)
670             break;
671         /* if not array limits given & we */
672         /* are out of initialisers then   */
673         if (!DCL_ELEM(type) && !iloop)
674             break ;
675         
676         /* no of elements given and we    */
677         /* have generated for all of them */
678         if (!--lcnt)
679             break ;
680     }
681     
682     /* if we have not been given a size  */
683     if (!DCL_ELEM(type))
684         DCL_ELEM(type) = size;
685     
686     return rast;
687 }
688
689
690 /*-----------------------------------------------------------------*/
691 /* createIvalCharPtr - generates initial values for char pointers  */
692 /*-----------------------------------------------------------------*/
693 ast *createIvalCharPtr (ast *sym, link *type, ast *iexpr)
694 {      
695     ast *rast = NULL ;
696
697     /* if this is a pointer & right is a literal array then */
698     /* just assignment will do                              */
699     if ( IS_PTR(type) && (( IS_LITERAL(iexpr->etype) || 
700           SPEC_SCLS(iexpr->etype) == S_CODE )
701                           && IS_ARRAY(iexpr->ftype))) 
702         return newNode('=',sym,iexpr);
703
704     /* left side is an array so we have to assign each */
705     /* element                                         */
706     if (( IS_LITERAL(iexpr->etype) || 
707           SPEC_SCLS(iexpr->etype) == S_CODE )
708         && IS_ARRAY(iexpr->ftype))  {
709
710         /* for each character generate an assignment */
711         /* to the array element */
712         char *s = SPEC_CVAL(iexpr->etype).v_char ;
713         int i = 0 ;
714         
715         while (*s) {        
716             rast = newNode(NULLOP,
717                            rast,
718                            newNode('=',
719                                    newNode('[', sym,
720                                            newAst(EX_VALUE,valueFromLit(i))),
721                                    newAst(EX_VALUE,valueFromLit(*s))));
722             i++;
723             s++;
724         }
725         rast = newNode(NULLOP,
726                            rast,
727                            newNode('=',
728                                    newNode('[', sym,
729                                            newAst(EX_VALUE,valueFromLit(i))),
730                                    newAst(EX_VALUE,valueFromLit(*s))));
731         return rast;
732     }
733
734     return NULL ;
735 }
736
737 /*-----------------------------------------------------------------*/
738 /* createIvalPtr - generates initial value for pointers            */
739 /*-----------------------------------------------------------------*/
740 ast *createIvalPtr (ast *sym,link *type,initList *ilist)
741 {    
742     ast *rast;
743     ast *iexpr ;
744
745     /* if deep then   */
746     if ( ilist->type == INIT_DEEP )
747         ilist = ilist->init.deep   ;
748            
749     iexpr = decorateType(resolveSymbols(list2expr(ilist)));
750
751     /* if character pointer */
752     if (IS_CHAR(type->next))
753         if ((rast = createIvalCharPtr (sym,type,iexpr)))
754             return rast;   
755
756     return newNode('=',sym,iexpr);          
757 }
758
759 /*-----------------------------------------------------------------*/
760 /* createIval - generates code for initial value                   */
761 /*-----------------------------------------------------------------*/
762 ast  *createIval  (ast *sym, link *type, initList *ilist, ast *wid)
763 {
764     ast *rast = NULL;  
765
766     if (!ilist)
767         return NULL ;   
768     
769     /* if structure then    */
770     if (IS_STRUCT(type)) 
771         rast =  createIvalStruct(sym, type,ilist);
772     else
773         /* if this is a pointer */
774         if (IS_PTR(type)) 
775             rast = createIvalPtr(sym, type,ilist);
776         else
777             /* if this is an array   */
778             if (IS_ARRAY(type))  
779                 rast = createIvalArray(sym, type,ilist); 
780             else
781                 /* if type is SPECIFIER */
782                 if (IS_SPEC(type))
783                     rast =  createIvalType (sym,type,ilist);
784     if ( wid )
785         return newNode(NULLOP,wid,rast);
786     else
787         return rast ;
788 }
789
790 /*-----------------------------------------------------------------*/
791 /* initAggregates - initialises aggregate variables with initv */
792 /*-----------------------------------------------------------------*/
793 ast *initAggregates ( symbol *sym, initList *ival, ast *wid)
794 {
795     return createIval (newAst(EX_VALUE,symbolVal(sym)),sym->type,ival,wid);
796 }
797
798 /*-----------------------------------------------------------------*/
799 /* gatherAutoInit - creates assignment expressions for initial     */
800 /*      values                                                     */
801 /*-----------------------------------------------------------------*/
802 ast     *gatherAutoInit ( symbol *autoChain )
803 {
804     ast *init = NULL ;
805     ast *work ;
806     symbol      *sym;
807     
808     inInitMode =1;
809     for ( sym = autoChain ; sym ; sym = sym->next ) {
810         
811         /* resolve the symbols in the ival */
812         if (sym->ival)
813             resolveIvalSym(sym->ival);
814
815         /* if this is a static variable & has an */
816         /* initial value the code needs to be lifted */
817         /* here to the main portion since they can be */
818         /* initialised only once at the start    */
819         if ( IS_STATIC(sym->etype) && sym->ival &&
820              SPEC_SCLS(sym->etype) != S_CODE) {
821             symbol *newSym ;
822
823             /* insert the symbol into the symbol table */
824             /* with level = 0 & name = rname               */
825             newSym = copySymbol (sym);                      
826             addSym (SymbolTab,newSym,newSym->name,0,0);
827             
828             /* now lift the code to main */
829             if (IS_AGGREGATE(sym->type))
830                 work = initAggregates (sym, sym->ival,NULL);
831             else
832                 work = newNode('=' ,newAst(EX_VALUE,symbolVal(newSym)),
833                                list2expr(sym->ival));
834             
835             setAstLineno(work,sym->lineDef);
836
837             sym->ival = NULL ;
838             if ( staticAutos )
839                 staticAutos = newNode(NULLOP,staticAutos,work);
840             else
841                 staticAutos = work ;
842             
843             continue;
844         }
845         
846         /* if there is an initial value */
847         if ( sym->ival && SPEC_SCLS(sym->etype)!=S_CODE) {
848             if (IS_AGGREGATE(sym->type)) 
849                 work = initAggregates (sym,sym->ival,NULL);
850             else
851                 work = newNode('=' ,newAst(EX_VALUE,symbolVal(sym)),
852                                list2expr(sym->ival));
853             
854             setAstLineno (work,sym->lineDef);
855             sym->ival = NULL ;
856             if ( init )
857                 init = newNode(NULLOP,init,work);
858             else
859                 init = work ;
860         }
861     }
862     inInitMode = 0;
863     return init ;
864 }
865
866 /*-----------------------------------------------------------------*/
867 /* stringToSymbol - creates a symbol from a literal string         */
868 /*-----------------------------------------------------------------*/
869 static value *stringToSymbol (value *val)
870 {
871     char name[SDCC_NAME_MAX+1];
872     static int charLbl = 0;
873     symbol *sym ;
874     
875     sprintf(name,"_str_%d",charLbl++);
876     sym = newSymbol(name,0); /* make it @ level 0 */
877     strcpy(sym->rname,name);
878     
879     /* copy the type from the value passed */   
880     sym->type = copyLinkChain(val->type);
881     sym->etype = getSpec(sym->type);
882     /* change to storage class & output class */
883     SPEC_SCLS(sym->etype) = S_CODE ;
884     SPEC_CVAL(sym->etype).v_char = SPEC_CVAL(val->etype).v_char ;
885     SPEC_STAT(sym->etype) = 1;
886     /* make the level & block = 0 */
887     sym->block = sym->level = 0;
888     sym->isstrlit = 1;
889     /* create an ival */
890     sym->ival = newiList(INIT_NODE,newAst(EX_VALUE,val));
891     if (noAlloc == 0) {
892         /* allocate it */
893         addSymChain(sym);
894         allocVariables(sym);
895     }
896     sym->ival = NULL;
897     return symbolVal(sym);
898     
899 }
900
901 /*-----------------------------------------------------------------*/
902 /* processBlockVars - will go thru the ast looking for block if    */
903 /*                    a block is found then will allocate the syms */
904 /*                    will also gather the auto inits present      */
905 /*-----------------------------------------------------------------*/
906 ast *processBlockVars ( ast *tree , int *stack, int action)
907 {
908     if (! tree)
909         return NULL ;
910     
911     /* if this is a block */
912     if (tree->type == EX_OP && tree->opval.op == BLOCK ) {
913         ast *autoInit ;
914         
915         if (action == ALLOCATE) {
916             autoInit = gatherAutoInit (tree->values.sym);
917             *stack += allocVariables (tree->values.sym);
918             
919             /* if there are auto inits then do them */
920             if (autoInit)
921                 tree->left = newNode(NULLOP,autoInit,tree->left);
922         } else /* action is deallocate */
923             deallocLocal (tree->values.sym) ;
924     }
925     
926     processBlockVars (tree->left, stack, action);
927     processBlockVars (tree->right, stack, action);
928     return tree ;
929 }
930
931 /*-----------------------------------------------------------------*/
932 /* constExprValue - returns the value of a constant expression     */
933 /*-----------------------------------------------------------------*/
934 value *constExprValue (ast *cexpr, int check)
935 {
936     cexpr = decorateType(resolveSymbols(cexpr));
937
938     /* if this is not a constant then */
939     if (!IS_LITERAL(cexpr->ftype)) {
940         /* then check if this is a literal array
941            in code segment */
942         if (SPEC_SCLS(cexpr->etype) == S_CODE &&
943             SPEC_CVAL(cexpr->etype).v_char    &&
944             IS_ARRAY(cexpr->ftype)) {
945             value *val = valFromType(cexpr->ftype);
946             SPEC_SCLS(val->etype) = S_LITERAL;
947             val->sym =cexpr->opval.val->sym ; 
948             val->sym->type = copyLinkChain(cexpr->ftype);
949             val->sym->etype = getSpec(val->sym->type);
950             strcpy(val->name,cexpr->opval.val->sym->rname);
951             return val;
952         }
953         
954         /* if we are casting a literal value then */
955         if (IS_AST_OP(cexpr)        &&
956             cexpr->opval.op == CAST &&
957             IS_LITERAL(cexpr->left->ftype))
958             return valCastLiteral(cexpr->ftype,
959                                   floatFromVal(cexpr->left->opval.val));
960
961         if (IS_AST_VALUE(cexpr))
962             return cexpr->opval.val;
963         
964         if (check)         
965             werror(E_CONST_EXPECTED,"found expression");
966
967         return NULL ;
968     }
969     
970     /* return the value */
971     return cexpr->opval.val ;
972     
973 }
974
975 /*-----------------------------------------------------------------*/
976 /* isLabelInAst - will return true if a given label is found       */
977 /*-----------------------------------------------------------------*/
978 bool isLabelInAst (symbol *label, ast *tree)
979 {
980     if (!tree  || IS_AST_VALUE(tree) || IS_AST_LINK(tree))
981         return FALSE ;
982
983     if (IS_AST_OP(tree) &&
984         tree->opval.op == LABEL &&
985         isSymbolEqual(AST_SYMBOL(tree->left),label))
986         return TRUE;
987
988     return isLabelInAst(label,tree->right) &&
989         isLabelInAst(label,tree->left);
990         
991 }
992
993 /*-----------------------------------------------------------------*/
994 /* isLoopCountable - return true if the loop count can be determi- */
995 /* -ned at compile time .                                          */
996 /*-----------------------------------------------------------------*/
997 bool isLoopCountable (ast *initExpr, ast *condExpr, ast *loopExpr,
998                       symbol **sym,ast **init, ast **end) 
999 {
1000     
1001     /* the loop is considered countable if the following
1002        conditions are true :-
1003
1004        a) initExpr :- <sym> = <const>
1005        b) condExpr :- <sym> < <const1>
1006        c) loopExpr :- <sym> ++ 
1007     */
1008
1009     /* first check the initExpr */
1010     if ( IS_AST_OP(initExpr)       &&
1011          initExpr->opval.op == '=' && /* is assignment */
1012          IS_AST_SYM_VALUE(initExpr->left)) { /* left is a symbol */     
1013         
1014         *sym = AST_SYMBOL(initExpr->left);
1015         *init= initExpr->right;
1016     }
1017     else
1018         return FALSE;
1019     
1020     /* for now the symbol has to be of
1021        integral type */
1022     if (!IS_INTEGRAL((*sym)->type))
1023         return FALSE;
1024
1025     /* now check condExpr */
1026     if (IS_AST_OP(condExpr)) {
1027
1028         switch (condExpr->opval.op) {
1029         case '<':
1030             if (IS_AST_SYM_VALUE(condExpr->left) &&
1031                 isSymbolEqual (*sym,AST_SYMBOL(condExpr->left)) &&
1032                 IS_AST_LIT_VALUE(condExpr->right)) {
1033                 *end = condExpr->right;
1034                 break;
1035             }
1036             return FALSE;
1037             
1038         case '!':
1039             if (IS_AST_OP(condExpr->left) &&
1040                 condExpr->left->opval.op == '>' &&
1041                 IS_AST_LIT_VALUE(condExpr->left->right) &&
1042                 IS_AST_SYM_VALUE(condExpr->left->left)&&
1043                 isSymbolEqual (*sym,AST_SYMBOL(condExpr->left->left))) {
1044                 
1045                 *end = newNode('+', condExpr->left->right,
1046                                newAst(EX_VALUE,constVal("1")));
1047                 break;
1048             }
1049             return FALSE ;
1050             
1051         default:
1052             return FALSE ;
1053         }       
1054         
1055     }          
1056
1057     /* check loop expression is of the form <sym>++ */
1058     if (!IS_AST_OP(loopExpr))
1059         return FALSE ;
1060
1061     /* check if <sym> ++ */
1062     if (loopExpr->opval.op == INC_OP) {
1063                 
1064         if (loopExpr->left) {
1065             /* pre */
1066             if (IS_AST_SYM_VALUE(loopExpr->left) &&
1067                 isSymbolEqual(*sym,AST_SYMBOL(loopExpr->left)))
1068                 return TRUE ;      
1069                 
1070         } else {
1071             /* post */
1072             if (IS_AST_SYM_VALUE(loopExpr->right) &&
1073                 isSymbolEqual(*sym,AST_SYMBOL(loopExpr->right)))
1074                 return TRUE ; 
1075         }
1076             
1077     } 
1078     else {
1079         /* check for += */
1080         if ( loopExpr->opval.op == ADD_ASSIGN ) {
1081
1082             if (IS_AST_SYM_VALUE(loopExpr->left) &&
1083                 isSymbolEqual(*sym,AST_SYMBOL(loopExpr->left)) &&
1084                 IS_AST_LIT_VALUE(loopExpr->right) &&
1085                 (int)AST_LIT_VALUE(loopExpr->right) != 1)
1086                 return TRUE ;
1087         }               
1088     }
1089     
1090     return FALSE;
1091 }
1092
1093 /*-----------------------------------------------------------------*/
1094 /* astHasVolatile - returns true if ast contains any volatile      */
1095 /*-----------------------------------------------------------------*/
1096 bool astHasVolatile (ast *tree)
1097 {
1098     if (!tree)
1099         return FALSE ;
1100
1101     if (TETYPE(tree) && IS_VOLATILE(TETYPE(tree)))
1102         return TRUE;
1103
1104     if (IS_AST_OP(tree))
1105         return astHasVolatile(tree->left) ||
1106             astHasVolatile(tree->right);
1107     else
1108         return FALSE ;
1109 }
1110
1111 /*-----------------------------------------------------------------*/
1112 /* astHasPointer - return true if the ast contains any ptr variable*/
1113 /*-----------------------------------------------------------------*/
1114 bool astHasPointer (ast *tree)
1115 {
1116     if (!tree)
1117         return FALSE ;
1118
1119     if (IS_AST_LINK(tree))
1120         return TRUE;
1121
1122     /* if we hit an array expression then check
1123        only the left side */
1124     if (IS_AST_OP(tree) && tree->opval.op == '[')
1125         return astHasPointer(tree->left);
1126
1127     if (IS_AST_VALUE(tree))
1128             return IS_PTR(tree->ftype) || IS_ARRAY(tree->ftype);
1129
1130     return astHasPointer(tree->left) ||
1131         astHasPointer(tree->right);
1132         
1133 }
1134
1135 /*-----------------------------------------------------------------*/
1136 /* astHasSymbol - return true if the ast has the given symbol      */
1137 /*-----------------------------------------------------------------*/
1138 bool astHasSymbol (ast *tree, symbol *sym)
1139 {
1140     if (!tree || IS_AST_LINK(tree))
1141         return FALSE ;   
1142
1143     if (IS_AST_VALUE(tree)) {
1144         if (IS_AST_SYM_VALUE(tree)) 
1145             return isSymbolEqual(AST_SYMBOL(tree),sym);
1146         else
1147             return FALSE;
1148     }
1149     
1150     return astHasSymbol(tree->left,sym) ||
1151         astHasSymbol(tree->right,sym);
1152 }
1153
1154 /*-----------------------------------------------------------------*/
1155 /* isConformingBody - the loop body has to conform to a set of rules */
1156 /* for the loop to be considered reversible read on for rules      */
1157 /*-----------------------------------------------------------------*/
1158 bool isConformingBody (ast *pbody, symbol *sym, ast *body)
1159 {
1160     
1161     /* we are going to do a pre-order traversal of the
1162        tree && check for the following conditions. (essentially
1163        a set of very shallow tests )
1164        a) the sym passed does not participate in
1165           any arithmetic operation
1166        b) There are no function calls
1167        c) all jumps are within the body 
1168        d) address of loop control variable not taken 
1169        e) if an assignment has a pointer on the
1170           left hand side make sure right does not have
1171           loop control variable */
1172
1173     /* if we reach the end or a leaf then true */
1174     if (!pbody ||  IS_AST_LINK(pbody) || IS_AST_VALUE(pbody))
1175         return TRUE ;
1176
1177
1178     /* if anything else is "volatile" */
1179     if (IS_VOLATILE(TETYPE(pbody)))
1180         return FALSE;
1181
1182     /* we will walk the body in a pre-order traversal for
1183        efficiency sake */
1184     switch (pbody->opval.op) {
1185         /*------------------------------------------------------------------*/
1186     case  '['   :       
1187         return isConformingBody (pbody->right,sym,body);
1188
1189         /*------------------------------------------------------------------*/
1190     case  PTR_OP:  
1191     case  '.'   :  
1192         return TRUE;
1193
1194         /*------------------------------------------------------------------*/
1195     case  INC_OP:  /* incerement operator unary so left only */
1196     case  DEC_OP:
1197         
1198         /* sure we are not sym is not modified */
1199         if (pbody->left                &&
1200             IS_AST_SYM_VALUE(pbody->left) &&
1201             isSymbolEqual(AST_SYMBOL(pbody->left),sym))
1202             return FALSE;
1203
1204         if (pbody->right                &&
1205             IS_AST_SYM_VALUE(pbody->right) &&
1206             isSymbolEqual(AST_SYMBOL(pbody->right),sym))
1207             return FALSE;
1208
1209         return TRUE;
1210
1211         /*------------------------------------------------------------------*/
1212
1213     case '*' :  /* can be unary  : if right is null then unary operation */
1214     case '+' :  
1215     case '-' :  
1216     case  '&':     
1217         
1218         /* if right is NULL then unary operation  */
1219         /*------------------------------------------------------------------*/
1220         /*----------------------------*/
1221         /*  address of                */
1222         /*----------------------------*/    
1223         if ( ! pbody->right ) { 
1224             if (IS_AST_SYM_VALUE(pbody->left) &&
1225                 isSymbolEqual(AST_SYMBOL(pbody->left),sym))
1226                 return FALSE;
1227             else
1228                 return isConformingBody(pbody->left,sym,body) ;
1229         } 
1230         
1231         /*------------------------------------------------------------------*/
1232     case  '|':
1233     case  '^':
1234     case  '/':
1235     case  '%':
1236     case LEFT_OP:
1237     case RIGHT_OP:
1238         
1239         if (IS_AST_SYM_VALUE(pbody->left) &&
1240             isSymbolEqual(AST_SYMBOL(pbody->left),sym))
1241             return FALSE ;
1242
1243         if (IS_AST_SYM_VALUE(pbody->right) &&
1244             isSymbolEqual(AST_SYMBOL(pbody->right),sym))
1245             return FALSE ;
1246         
1247         return isConformingBody(pbody->left,sym,body) &&
1248             isConformingBody(pbody->right,sym,body);
1249         
1250     case '~' :
1251     case '!' :
1252     case RRC:
1253     case RLC:
1254     case GETHBIT:
1255         if (IS_AST_SYM_VALUE(pbody->left) &&
1256             isSymbolEqual(AST_SYMBOL(pbody->left),sym))
1257             return FALSE;
1258         return isConformingBody (pbody->left,sym,body);
1259         
1260         /*------------------------------------------------------------------*/
1261
1262     case AND_OP:
1263     case OR_OP:
1264     case '>' :
1265     case '<' :
1266     case LE_OP:
1267     case GE_OP:
1268     case EQ_OP:
1269     case NE_OP:
1270     case '?' :
1271     case ':' :
1272     case SIZEOF:  /* evaluate wihout code generation */
1273
1274         return isConformingBody(pbody->left,sym,body) &&
1275             isConformingBody(pbody->right,sym,body);    
1276
1277         /*------------------------------------------------------------------*/
1278     case '=' :
1279
1280         /* if left has a pointer & right has loop
1281            control variable then we cannot */
1282         if (astHasPointer(pbody->left) &&
1283             astHasSymbol (pbody->right,sym))
1284             return FALSE ;
1285         if (astHasVolatile(pbody->left))
1286             return FALSE ;
1287
1288         if (IS_AST_SYM_VALUE(pbody->left) &&
1289             isSymbolEqual(AST_SYMBOL(pbody->left),sym))
1290             return FALSE ;
1291         
1292         if (astHasVolatile(pbody->left))
1293             return FALSE;
1294
1295         return isConformingBody(pbody->left,sym,body) &&
1296             isConformingBody(pbody->right,sym,body);    
1297
1298     case MUL_ASSIGN:
1299     case DIV_ASSIGN:
1300     case AND_ASSIGN:
1301     case OR_ASSIGN:
1302     case XOR_ASSIGN:
1303     case RIGHT_ASSIGN:
1304     case LEFT_ASSIGN:
1305     case SUB_ASSIGN:
1306     case ADD_ASSIGN:
1307             assert("Parser should not have generated this\n");
1308         
1309         /*------------------------------------------------------------------*/
1310         /*----------------------------*/
1311         /*      comma operator        */
1312         /*----------------------------*/        
1313     case ',' :
1314         return isConformingBody(pbody->left,sym,body) &&
1315             isConformingBody(pbody->right,sym,body);    
1316         
1317         /*------------------------------------------------------------------*/
1318         /*----------------------------*/
1319         /*       function call        */
1320         /*----------------------------*/        
1321     case CALL:
1322         return FALSE;
1323
1324         /*------------------------------------------------------------------*/
1325         /*----------------------------*/
1326         /*     return statement       */
1327         /*----------------------------*/        
1328     case RETURN:
1329         return FALSE ;
1330
1331     case GOTO:
1332         if (isLabelInAst (AST_SYMBOL(pbody->left),body))
1333             return TRUE ;
1334         else
1335             return FALSE;
1336     case SWITCH:
1337         if (astHasSymbol(pbody->left,sym))
1338             return FALSE ;
1339
1340     default:
1341         break;
1342     }
1343
1344     return isConformingBody(pbody->left,sym,body) &&
1345         isConformingBody(pbody->right,sym,body);        
1346         
1347     
1348
1349 }
1350
1351 /*-----------------------------------------------------------------*/
1352 /* isLoopReversible - takes a for loop as input && returns true    */
1353 /* if the for loop is reversible. If yes will set the value of     */
1354 /* the loop control var & init value & termination value           */
1355 /*-----------------------------------------------------------------*/
1356 bool isLoopReversible (ast *loop, symbol **loopCntrl, 
1357                        ast **init, ast **end )
1358 {
1359     /* if option says don't do it then don't */
1360     if (optimize.noLoopReverse)
1361         return 0;
1362     /* there are several tests to determine this */
1363        
1364     /* for loop has to be of the form 
1365        for ( <sym> = <const1> ; 
1366              [<sym> < <const2>]  ;
1367              [<sym>++] | [<sym> += 1] | [<sym> = <sym> + 1] )
1368              forBody */
1369     if (! isLoopCountable (AST_FOR(loop,initExpr),
1370                            AST_FOR(loop,condExpr),
1371                            AST_FOR(loop,loopExpr),
1372                            loopCntrl,init,end))
1373         return 0;
1374
1375     /* now do some serious checking on the body of the loop
1376      */
1377     
1378     return isConformingBody(loop->left,*loopCntrl,loop->left);
1379
1380 }
1381
1382 /*-----------------------------------------------------------------*/
1383 /* replLoopSym - replace the loop sym by loop sym -1               */
1384 /*-----------------------------------------------------------------*/
1385 static void replLoopSym ( ast *body, symbol *sym)
1386 {
1387     /* reached end */
1388     if (!body || IS_AST_LINK(body))
1389         return ;
1390
1391     if (IS_AST_SYM_VALUE(body)) {
1392         
1393         if (isSymbolEqual(AST_SYMBOL(body),sym)) {
1394             
1395             body->type = EX_OP;
1396             body->opval.op = '-';
1397             body->left = newAst(EX_VALUE,symbolVal(sym));
1398             body->right= newAst(EX_VALUE,constVal("1"));
1399
1400         }
1401             
1402         return;
1403         
1404     }
1405         
1406     replLoopSym(body->left,sym);
1407     replLoopSym(body->right,sym);
1408         
1409 }
1410
1411 /*-----------------------------------------------------------------*/
1412 /* reverseLoop - do the actual loop reversal                       */
1413 /*-----------------------------------------------------------------*/
1414 ast *reverseLoop (ast *loop, symbol *sym, ast *init, ast *end)
1415 {    
1416     ast *rloop ;  
1417         
1418     /* create the following tree 
1419                 <sym> = loopCount ;
1420          for_continue:
1421                 forbody
1422                 <sym> -= 1;
1423                 if (sym) goto for_continue ; 
1424                 <sym> = end - 1; */
1425     
1426     /* put it together piece by piece */
1427     rloop = newNode (NULLOP,
1428                      createIf(newAst(EX_VALUE,symbolVal(sym)),
1429                               newNode(GOTO,
1430                                       newAst(EX_VALUE,
1431                                              symbolVal(AST_FOR(loop,continueLabel))),
1432                                       NULL),NULL),
1433                      newNode('=',
1434                              newAst(EX_VALUE,symbolVal(sym)),
1435                              newNode('-', end,
1436                                      newAst(EX_VALUE,
1437                                             constVal("1")))));
1438
1439     replLoopSym(loop->left, sym);
1440
1441     rloop = newNode(NULLOP,
1442                     newNode('=',
1443                             newAst(EX_VALUE,symbolVal(sym)),
1444                             newNode('-',end,init)),
1445                     createLabel(AST_FOR(loop,continueLabel),
1446                                 newNode(NULLOP,
1447                                         loop->left,
1448                                         newNode(NULLOP,
1449                                                 newNode(SUB_ASSIGN,
1450                                                         newAst(EX_VALUE,symbolVal(sym)),
1451                                                         newAst(EX_VALUE,constVal("1"))),
1452                                                 rloop ))));
1453     
1454     return decorateType(rloop);
1455
1456 }
1457
1458 /*-----------------------------------------------------------------*/
1459 /* decorateType - compute type for this tree also does type cheking*/
1460 /*          this is done bottom up, since type have to flow upwards*/
1461 /*          it also does constant folding, and paramater checking  */
1462 /*-----------------------------------------------------------------*/
1463 ast *decorateType (ast *tree)
1464 {         
1465     int parmNumber ;
1466     link *p;
1467     
1468     if ( ! tree )
1469         return tree ;
1470     
1471     /* if already has type then do nothing */
1472     if ( tree->decorated )
1473         return tree ;
1474     
1475     tree->decorated = 1;
1476     
1477     /* print the line          */
1478     /* if not block & function */
1479     if ( tree->type == EX_OP && 
1480          ( tree->opval.op != FUNCTION  &&
1481            tree->opval.op != BLOCK     &&
1482            tree->opval.op != NULLOP    )) {
1483         filename = tree->filename ;
1484         lineno = tree->lineno ;
1485     }
1486
1487     /* if any child is an error | this one is an error do nothing */
1488     if ( tree->isError ||
1489          ( tree->left && tree->left->isError) ||
1490          ( tree->right && tree->right->isError ))
1491         return tree ;
1492
1493     /*------------------------------------------------------------------*/
1494     /*----------------------------*/
1495     /*   leaf has been reached    */
1496     /*----------------------------*/        
1497     /* if this is of type value */
1498     /* just get the type        */
1499     if ( tree->type == EX_VALUE ) {
1500         
1501         if ( IS_LITERAL(tree->opval.val->etype) ) {
1502             
1503             /* if this is a character array then declare it */
1504             if (IS_ARRAY(tree->opval.val->type))
1505                 tree->opval.val = stringToSymbol(tree->opval.val);
1506             
1507             /* otherwise just copy the type information */
1508             COPYTYPE(TTYPE(tree),TETYPE(tree),tree->opval.val->type);
1509             return tree ;
1510         }
1511         
1512         if ( tree->opval.val->sym ) {
1513             /* if the undefined flag is set then give error message */
1514                 if (tree->opval.val->sym->undefined ) {
1515                   werror(E_ID_UNDEF,tree->opval.val->sym->name) ;
1516                   /* assume int */
1517                   TTYPE(tree) = TETYPE(tree) =
1518                     tree->opval.val->type = tree->opval.val->sym->type = 
1519                     tree->opval.val->etype = tree->opval.val->sym->etype = 
1520                     copyLinkChain(intType);
1521                 }
1522                 else {
1523                   
1524                   /* if impilicit i.e. struct/union member then no type */
1525                   if (tree->opval.val->sym->implicit )
1526                     TTYPE(tree) = TETYPE(tree) = NULL ;
1527                   
1528                   else { 
1529                     
1530                                 /* else copy the type */
1531                     COPYTYPE(TTYPE(tree),TETYPE(tree),tree->opval.val->type); 
1532                     
1533                                 /* and mark it as referenced */
1534                     tree->opval.val->sym->isref = 1;
1535                                 /* if this is of type function or function pointer */
1536                     if (funcInChain(tree->opval.val->type)) {
1537                       tree->hasVargs = tree->opval.val->sym->hasVargs;
1538                       tree->args = copyValueChain(tree->opval.val->sym->args) ;
1539                       
1540                     }
1541                   }
1542                 }
1543         }
1544         
1545         return tree ;
1546     }
1547     
1548     /* if type link for the case of cast */
1549     if ( tree->type == EX_LINK ) {
1550         COPYTYPE(TTYPE(tree),TETYPE(tree),tree->opval.lnk);
1551         return tree ;
1552     } 
1553     
1554     {
1555         ast *dtl, *dtr;
1556         
1557         dtl = decorateType (tree->left);
1558         dtr = decorateType (tree->right);  
1559
1560         /* this is to take care of situations
1561            when the tree gets rewritten */
1562         if (dtl != tree->left)
1563             tree->left = dtl;
1564         if (dtr != tree->right)
1565             tree->right = dtr;
1566     }
1567     
1568     /* depending on type of operator do */
1569     
1570     switch   (tree->opval.op) {
1571         /*------------------------------------------------------------------*/
1572         /*----------------------------*/
1573         /*        array node          */
1574         /*----------------------------*/
1575     case  '['   :  
1576         
1577         /* determine which is the array & which the index */
1578         if ((IS_ARRAY(RTYPE(tree)) || IS_PTR(RTYPE(tree))) && IS_INTEGRAL(LTYPE(tree))) {
1579             
1580             ast *tempTree = tree->left ;
1581             tree->left = tree->right ;
1582             tree->right= tempTree ;
1583         }
1584
1585         /* first check if this is a array or a pointer */
1586         if ( (!IS_ARRAY(LTYPE(tree)))  && (!IS_PTR(LTYPE(tree)))) {
1587             werror(E_NEED_ARRAY_PTR,"[]");
1588             goto errorTreeReturn ;
1589         }       
1590         
1591         /* check if the type of the idx */
1592         if (!IS_INTEGRAL(RTYPE(tree))) {
1593             werror(E_IDX_NOT_INT);
1594             goto errorTreeReturn ;
1595         }
1596         
1597         /* if the left is an rvalue then error */
1598         if (LRVAL(tree)) {
1599             werror(E_LVALUE_REQUIRED,"array access");
1600             goto errorTreeReturn ;
1601         }
1602         RRVAL(tree) = 1;
1603         COPYTYPE(TTYPE(tree),TETYPE(tree),LTYPE(tree)->next);
1604         return tree;
1605         
1606         /*------------------------------------------------------------------*/
1607         /*----------------------------*/
1608         /*      struct/union          */
1609         /*----------------------------*/   
1610     case  '.'   :  
1611         /* if this is not a structure */
1612         if (!IS_STRUCT(LTYPE(tree))) {
1613             werror(E_STRUCT_UNION,".");
1614             goto errorTreeReturn ;
1615         }
1616         TTYPE(tree) = structElemType (LTYPE(tree), 
1617                                       (tree->right->type == EX_VALUE ?
1618                                        tree->right->opval.val : NULL ),&tree->args);
1619         TETYPE(tree) = getSpec(TTYPE(tree));
1620         return tree ;
1621         
1622         /*------------------------------------------------------------------*/
1623         /*----------------------------*/
1624         /*    struct/union pointer    */
1625         /*----------------------------*/
1626     case  PTR_OP:  
1627         /* if not pointer to a structure */
1628         if (!IS_PTR(LTYPE(tree)))  {
1629             werror(E_PTR_REQD);
1630             goto errorTreeReturn ;
1631         }
1632         
1633         if (!IS_STRUCT(LTYPE(tree)->next))  {
1634             werror(E_STRUCT_UNION,"->");
1635             goto errorTreeReturn ;
1636         }
1637         
1638         TTYPE(tree) = structElemType (LTYPE(tree)->next, 
1639                                       (tree->right->type == EX_VALUE ?
1640                                        tree->right->opval.val : NULL ),&tree->args);
1641         TETYPE(tree) = getSpec(TTYPE(tree));
1642         return tree ;
1643         
1644         /*------------------------------------------------------------------*/
1645         /*----------------------------*/
1646         /*  ++/-- operation           */
1647         /*----------------------------*/
1648     case  INC_OP:  /* incerement operator unary so left only */
1649     case  DEC_OP:
1650         {
1651             link *ltc = (tree->right ? RTYPE(tree) : LTYPE(tree) );
1652             COPYTYPE(TTYPE(tree),TETYPE(tree),ltc);
1653             if (!tree->initMode && IS_CONSTANT(TETYPE(tree)))
1654                 werror(E_CODE_WRITE,"++/--");
1655             
1656             if (tree->right)
1657                 RLVAL(tree) = 1;
1658             else
1659                 LLVAL(tree) = 1;
1660             return tree ;
1661         }
1662         
1663         /*------------------------------------------------------------------*/
1664         /*----------------------------*/
1665         /*  bitwise and               */
1666         /*----------------------------*/
1667     case  '&':     /* can be unary   */
1668         /* if right is NULL then unary operation  */
1669         if ( tree->right ) /* not an unary operation */ {
1670             
1671             if (!IS_INTEGRAL(LTYPE(tree)) || !IS_INTEGRAL(RTYPE(tree))) {
1672                 werror(E_BITWISE_OP);
1673                 werror(E_CONTINUE,"left & right types are ");
1674                 printTypeChain(LTYPE(tree),stderr);
1675                 fprintf(stderr,",");
1676                 printTypeChain(RTYPE(tree),stderr);
1677                 fprintf(stderr,"\n");
1678                 goto errorTreeReturn ;
1679             }
1680             
1681             /* if they are both literal */
1682             if (IS_LITERAL(RTYPE(tree)) && IS_LITERAL(LTYPE(tree))) {
1683                 tree->type = EX_VALUE ;
1684                 tree->opval.val = valBitwise (valFromType(LETYPE(tree)),
1685                                               valFromType(RETYPE(tree)),'&');
1686                                        
1687                 tree->right = tree->left = NULL;
1688                 TETYPE(tree) = tree->opval.val->etype ;
1689                 TTYPE(tree) =  tree->opval.val->type;
1690                 return tree ;
1691             }
1692             
1693             /* see if this is a GETHBIT operation if yes
1694                then return that */
1695             {
1696                 ast *otree = optimizeGetHbit(tree);
1697                 
1698                 if (otree != tree)
1699                     return decorateType(otree);
1700             }
1701             
1702             /* if right or left is literal then result of that type*/
1703             if (IS_LITERAL(RTYPE(tree))) {
1704                 
1705                 TTYPE(tree) = copyLinkChain(RTYPE(tree));
1706                 TETYPE(tree) = getSpec(TTYPE(tree));
1707                 SPEC_SCLS(TETYPE(tree)) = S_AUTO;
1708             }
1709             else {
1710                 if (IS_LITERAL(LTYPE(tree))) {              
1711                     TTYPE(tree) = copyLinkChain(LTYPE(tree));
1712                     TETYPE(tree) = getSpec(TTYPE(tree));
1713                     SPEC_SCLS(TETYPE(tree)) = S_AUTO;
1714                     
1715                 }
1716                 else {
1717                     TTYPE(tree) = 
1718                         computeType (LTYPE(tree), RTYPE(tree));
1719                     TETYPE(tree) = getSpec(TTYPE(tree));
1720                 }
1721             }
1722             LRVAL(tree) = RRVAL(tree) = 1;
1723             return tree ;
1724         } 
1725         
1726         /*------------------------------------------------------------------*/
1727         /*----------------------------*/
1728         /*  address of                */
1729         /*----------------------------*/    
1730         p = newLink();
1731         p->class = DECLARATOR;
1732         /* if bit field then error */
1733         if (IS_BITVAR(tree->left->etype)) {
1734             werror (E_ILLEGAL_ADDR,"addrress of bit variable");
1735             goto errorTreeReturn ;
1736         }
1737         
1738         if (SPEC_SCLS(tree->left->etype)== S_REGISTER ) {
1739             werror (E_ILLEGAL_ADDR,"address of register variable");
1740             goto errorTreeReturn;
1741         }
1742         
1743         if (IS_FUNC(LTYPE(tree))) {
1744             werror(E_ILLEGAL_ADDR,"address of function");
1745             goto errorTreeReturn ;
1746         }
1747         
1748         if (LRVAL(tree)) {
1749             werror(E_LVALUE_REQUIRED,"address of");
1750             goto errorTreeReturn ;      
1751         }
1752         if (SPEC_SCLS(tree->left->etype) == S_CODE) {
1753             DCL_TYPE(p) = CPOINTER ;
1754             DCL_PTR_CONST(p) = 1;
1755         }
1756         else
1757             if (SPEC_SCLS(tree->left->etype) == S_XDATA)
1758                 DCL_TYPE(p) = FPOINTER;
1759             else
1760                 if (SPEC_SCLS(tree->left->etype) == S_XSTACK )
1761                     DCL_TYPE(p) = PPOINTER ;
1762                 else
1763                     if (SPEC_SCLS(tree->left->etype) == S_IDATA)
1764                         DCL_TYPE(p) = IPOINTER ;
1765                     else
1766                         DCL_TYPE(p) = POINTER ;
1767
1768         if (IS_AST_SYM_VALUE(tree->left)) {
1769             AST_SYMBOL(tree->left)->addrtaken = 1;
1770             AST_SYMBOL(tree->left)->allocreq = 1;
1771         }
1772
1773         p->next = LTYPE(tree);
1774         TTYPE(tree) = p;
1775         TETYPE(tree) = getSpec(TTYPE(tree));
1776         DCL_PTR_CONST(p) = SPEC_CONST(TETYPE(tree));
1777         DCL_PTR_VOLATILE(p) = SPEC_VOLATILE(TETYPE(tree));
1778         LLVAL(tree) = 1;
1779         TLVAL(tree) = 1;
1780         return tree ;
1781         
1782         /*------------------------------------------------------------------*/
1783         /*----------------------------*/
1784         /*  bitwise or                */
1785         /*----------------------------*/
1786     case  '|':
1787         /* if the rewrite succeeds then don't go any furthur */
1788         {
1789             ast *wtree = optimizeRRCRLC ( tree );
1790             if (wtree != tree) 
1791                 return decorateType(wtree) ;
1792         }
1793         /*------------------------------------------------------------------*/
1794         /*----------------------------*/
1795         /*  bitwise xor               */
1796         /*----------------------------*/
1797     case  '^':
1798         if (!IS_INTEGRAL(LTYPE(tree)) || !IS_INTEGRAL(RTYPE(tree))) {
1799             werror(E_BITWISE_OP);
1800             werror(E_CONTINUE,"left & right types are ");
1801             printTypeChain(LTYPE(tree),stderr);
1802             fprintf(stderr,",");
1803             printTypeChain(RTYPE(tree),stderr);
1804             fprintf(stderr,"\n");
1805             goto errorTreeReturn ;
1806         }
1807         
1808         /* if they are both literal then */
1809         /* rewrite the tree */
1810         if (IS_LITERAL(RTYPE(tree)) && IS_LITERAL(LTYPE(tree))) {
1811             tree->type = EX_VALUE ;
1812             tree->opval.val = valBitwise (valFromType(LETYPE(tree)),
1813                                           valFromType(RETYPE(tree)),
1814                                           tree->opval.op);                 
1815             tree->right = tree->left = NULL;
1816             TETYPE(tree) = tree->opval.val->etype;
1817             TTYPE(tree) = tree->opval.val->type;
1818             return tree ;
1819         }
1820         LRVAL(tree) = RRVAL(tree) = 1;
1821         TETYPE(tree) = getSpec (TTYPE(tree) = 
1822                                 computeType(LTYPE(tree),
1823                                             RTYPE(tree)));
1824         
1825         /*------------------------------------------------------------------*/
1826         /*----------------------------*/
1827         /*  division                  */
1828         /*----------------------------*/
1829     case  '/':
1830         if (!IS_ARITHMETIC(LTYPE(tree)) || !IS_ARITHMETIC(RTYPE(tree))) {
1831             werror(E_INVALID_OP,"divide");
1832             goto errorTreeReturn ;
1833         }
1834         /* if they are both literal then */
1835         /* rewrite the tree */
1836         if (IS_LITERAL(RTYPE(tree)) && IS_LITERAL(LTYPE(tree))) {
1837             tree->type = EX_VALUE ;
1838             tree->opval.val = valDiv (valFromType(LETYPE(tree)),
1839                                       valFromType(RETYPE(tree)));
1840             tree->right = tree->left = NULL;
1841             TETYPE(tree) = getSpec(TTYPE(tree) = 
1842                                    tree->opval.val->type);
1843             return tree ;
1844         }
1845         LRVAL(tree) = RRVAL(tree) = 1;
1846         TETYPE(tree) = getSpec (TTYPE(tree) = 
1847                                 computeType(LTYPE(tree),
1848                                             RTYPE(tree)));
1849         return tree;
1850         
1851         /*------------------------------------------------------------------*/
1852         /*----------------------------*/
1853         /*            modulus         */
1854         /*----------------------------*/
1855     case  '%':
1856         if (!IS_INTEGRAL(LTYPE(tree)) || !IS_INTEGRAL(RTYPE(tree))) {
1857             werror(E_BITWISE_OP);
1858             werror(E_CONTINUE,"left & right types are ");
1859             printTypeChain(LTYPE(tree),stderr);
1860             fprintf(stderr,",");
1861             printTypeChain(RTYPE(tree),stderr);
1862             fprintf(stderr,"\n");
1863             goto errorTreeReturn ;
1864         }
1865         /* if they are both literal then */
1866         /* rewrite the tree */
1867         if (IS_LITERAL(RTYPE(tree)) && IS_LITERAL(LTYPE(tree))) {
1868             tree->type = EX_VALUE ;
1869             tree->opval.val = valMod (valFromType(LETYPE(tree)),
1870                                       valFromType(RETYPE(tree)));                 
1871             tree->right = tree->left = NULL;
1872             TETYPE(tree) = getSpec(TTYPE(tree) = 
1873                                    tree->opval.val->type);
1874             return tree ;
1875         }
1876         LRVAL(tree) = RRVAL(tree) = 1;
1877         TETYPE(tree) = getSpec (TTYPE(tree) = 
1878                                 computeType(LTYPE(tree),
1879                                             RTYPE(tree)));
1880         return tree;
1881         
1882         /*------------------------------------------------------------------*/
1883         /*----------------------------*/
1884         /*  address dereference       */
1885         /*----------------------------*/
1886     case  '*':     /* can be unary  : if right is null then unary operation */
1887         if ( ! tree->right ) {
1888             if (!IS_PTR(LTYPE(tree)) && !IS_ARRAY(LTYPE(tree))) {
1889                 werror(E_PTR_REQD);
1890                 goto errorTreeReturn ;
1891             }
1892             
1893             if (LRVAL(tree)) {
1894                 werror(E_LVALUE_REQUIRED,"pointer deref");
1895                 goto errorTreeReturn ;  
1896             }
1897             TTYPE(tree) = copyLinkChain ((IS_PTR(LTYPE(tree)) || IS_ARRAY(LTYPE(tree))) ? 
1898                                          LTYPE(tree)->next : NULL );
1899             TETYPE(tree) = getSpec(TTYPE(tree));
1900             tree->args = tree->left->args ;
1901             tree->hasVargs = tree->left->hasVargs ;
1902             SPEC_CONST(TETYPE(tree)) = DCL_PTR_CONST(LTYPE(tree));
1903             return tree ;
1904         }
1905         
1906         /*------------------------------------------------------------------*/
1907         /*----------------------------*/
1908         /*      multiplication        */
1909         /*----------------------------*/
1910         if (!IS_ARITHMETIC(LTYPE(tree)) || !IS_ARITHMETIC(RTYPE(tree))) {
1911             werror(E_INVALID_OP,"multiplication");
1912             goto errorTreeReturn ;
1913         }
1914         
1915         /* if they are both literal then */
1916         /* rewrite the tree */
1917         if (IS_LITERAL(RTYPE(tree)) && IS_LITERAL(LTYPE(tree))) {
1918             tree->type = EX_VALUE ;
1919             tree->opval.val = valMult (valFromType(LETYPE(tree)),
1920                                        valFromType(RETYPE(tree)));                 
1921             tree->right = tree->left = NULL;
1922             TETYPE(tree) = getSpec(TTYPE(tree) = 
1923                                    tree->opval.val->type);
1924             return tree ;
1925         }
1926
1927         /* if left is a literal exchange left & right */
1928         if (IS_LITERAL(LTYPE(tree))) {
1929             ast *tTree = tree->left ;
1930             tree->left = tree->right ;
1931             tree->right= tTree ;
1932         }
1933                 
1934         LRVAL(tree) = RRVAL(tree) = 1;
1935         TETYPE(tree) = getSpec (TTYPE(tree) = 
1936                                 computeType(LTYPE(tree),
1937                                             RTYPE(tree)));                        
1938         return tree ;
1939         
1940         /*------------------------------------------------------------------*/
1941         /*----------------------------*/
1942         /*    unary '+' operator      */
1943         /*----------------------------*/
1944     case '+' :  
1945         /* if unary plus */
1946         if ( ! tree->right ) {
1947             if (!IS_INTEGRAL(LTYPE(tree))) {
1948                 werror(E_UNARY_OP,'+');
1949                 goto errorTreeReturn ;
1950             }
1951             
1952             /* if left is a literal then do it */
1953             if (IS_LITERAL(LTYPE(tree))) {
1954                 tree->type = EX_VALUE ;
1955                 tree->opval.val = valFromType(LETYPE(tree));          
1956                 tree->left = NULL ;
1957                 TETYPE(tree) = TTYPE(tree) = tree->opval.val->type;
1958                 return tree ;
1959             }
1960             LRVAL(tree) = 1;
1961             COPYTYPE(TTYPE(tree),TETYPE(tree),LTYPE(tree)); 
1962             return tree ;
1963         }
1964         
1965         /*------------------------------------------------------------------*/
1966         /*----------------------------*/
1967         /*      addition              */
1968         /*----------------------------*/
1969         
1970         /* this is not a unary operation */
1971         /* if both pointers then problem */
1972         if ((IS_PTR(LTYPE(tree)) || IS_ARRAY(LTYPE(tree))) &&
1973             (IS_PTR(RTYPE(tree)) || IS_ARRAY(RTYPE(tree)))) {
1974             werror(E_PTR_PLUS_PTR);
1975             goto errorTreeReturn ;
1976         }       
1977
1978         if (!IS_ARITHMETIC(LTYPE(tree)) && 
1979             !IS_PTR(LTYPE(tree)) && !IS_ARRAY(LTYPE(tree))) {
1980             werror(E_PLUS_INVALID,"+");
1981             goto errorTreeReturn ;
1982         }
1983         
1984         if (!IS_ARITHMETIC(RTYPE(tree)) && 
1985             !IS_PTR(RTYPE(tree)) && !IS_ARRAY(RTYPE(tree))) {
1986             werror(E_PLUS_INVALID,"+");
1987             goto errorTreeReturn;
1988         }
1989         /* if they are both literal then */
1990         /* rewrite the tree */
1991         if (IS_LITERAL(RTYPE(tree)) && IS_LITERAL(LTYPE(tree))) {
1992             tree->type = EX_VALUE ;
1993             tree->opval.val = valPlus (valFromType(LETYPE(tree)),
1994                                        valFromType(RETYPE(tree))); 
1995             tree->right = tree->left = NULL;
1996             TETYPE(tree) = getSpec(TTYPE(tree) = 
1997                                    tree->opval.val->type);
1998             return tree ;
1999         }
2000         
2001         /* if the right is a pointer or left is a literal 
2002            xchange left & right */
2003         if (IS_ARRAY(RTYPE(tree)) || 
2004             IS_PTR(RTYPE(tree))   || 
2005             IS_LITERAL(LTYPE(tree))) {
2006             ast *tTree = tree->left ;
2007             tree->left = tree->right ;
2008             tree->right= tTree ;
2009         }
2010
2011         LRVAL(tree) = RRVAL(tree) = 1;  
2012         /* if the left is a pointer */
2013         if (IS_PTR(LTYPE(tree)))      
2014             TETYPE(tree) = getSpec(TTYPE(tree) =
2015                                    LTYPE(tree));
2016         else
2017             TETYPE(tree) = getSpec(TTYPE(tree) = 
2018                                    computeType(LTYPE(tree),
2019                                                RTYPE(tree)));
2020         return tree ;
2021         
2022         /*------------------------------------------------------------------*/
2023         /*----------------------------*/
2024         /*      unary '-'             */
2025         /*----------------------------*/
2026     case '-' :  /* can be unary   */
2027         /* if right is null then unary */
2028         if ( ! tree->right ) {
2029             
2030             if (!IS_ARITHMETIC(LTYPE(tree))) {
2031                 werror(E_UNARY_OP,tree->opval.op);
2032                 goto errorTreeReturn ;
2033             }
2034             
2035             /* if left is a literal then do it */
2036             if (IS_LITERAL(LTYPE(tree))) {
2037                 tree->type = EX_VALUE ;
2038                 tree->opval.val = valUnaryPM(valFromType(LETYPE(tree)));
2039                 tree->left = NULL ;
2040                 TETYPE(tree) = TTYPE(tree) = tree->opval.val->type;
2041                 return tree ;
2042             }
2043             LRVAL(tree) = 1;
2044             TTYPE(tree) =  LTYPE(tree); 
2045             return tree ;
2046         }
2047         
2048         /*------------------------------------------------------------------*/
2049         /*----------------------------*/
2050         /*    subtraction             */
2051         /*----------------------------*/
2052         
2053         if (!(IS_PTR(LTYPE(tree)) || 
2054               IS_ARRAY(LTYPE(tree)) || 
2055               IS_ARITHMETIC(LTYPE(tree)))) {
2056             werror(E_PLUS_INVALID,"-");
2057             goto errorTreeReturn ;
2058         }
2059         
2060         if (!(IS_PTR(RTYPE(tree)) || 
2061               IS_ARRAY(RTYPE(tree)) || 
2062               IS_ARITHMETIC(RTYPE(tree)))) {
2063             werror(E_PLUS_INVALID,"-");
2064             goto errorTreeReturn ;
2065         }
2066         
2067         if ( (IS_PTR(LTYPE(tree)) || IS_ARRAY(LTYPE(tree))) &&
2068             ! (IS_PTR(RTYPE(tree)) || IS_ARRAY(RTYPE(tree)) || 
2069                IS_INTEGRAL(RTYPE(tree)))   ) {
2070             werror(E_PLUS_INVALID,"-");
2071             goto errorTreeReturn ;
2072         }
2073
2074         /* if they are both literal then */
2075         /* rewrite the tree */
2076         if (IS_LITERAL(RTYPE(tree)) &&  IS_LITERAL(LTYPE(tree))) {
2077             tree->type = EX_VALUE ;
2078             tree->opval.val = valMinus (valFromType(LETYPE(tree)),
2079                                         valFromType(RETYPE(tree)));  
2080             tree->right = tree->left = NULL;
2081             TETYPE(tree) = getSpec(TTYPE(tree) = 
2082                                    tree->opval.val->type);
2083             return tree ;
2084         }
2085         
2086         /* if the left & right are equal then zero */
2087         if (isAstEqual(tree->left,tree->right)) {
2088             tree->type = EX_VALUE;
2089             tree->left = tree->right = NULL;
2090             tree->opval.val = constVal("0");
2091             TETYPE(tree) = TTYPE(tree) = tree->opval.val->type;
2092             return tree;
2093         }
2094
2095         /* if both of them are pointers or arrays then */
2096         /* the result is going to be an integer        */
2097         if (( IS_ARRAY(LTYPE(tree)) || IS_PTR(LTYPE(tree))) &&
2098             ( IS_ARRAY(RTYPE(tree)) || IS_PTR(RTYPE(tree)))) 
2099             TETYPE(tree) = TTYPE(tree) = newIntLink();
2100         else 
2101             /* if only the left is a pointer */
2102             /* then result is a pointer      */
2103             if (IS_PTR(LTYPE(tree)) || IS_ARRAY(LTYPE(tree))) 
2104                 TETYPE(tree) = getSpec(TTYPE(tree) =
2105                                        LTYPE(tree));
2106             else
2107                 TETYPE(tree) = getSpec (TTYPE(tree) = 
2108                                         computeType(LTYPE(tree),
2109                                                     RTYPE(tree))); 
2110         LRVAL(tree) = RRVAL(tree) = 1;
2111         return tree ;  
2112         
2113         /*------------------------------------------------------------------*/
2114         /*----------------------------*/
2115         /*    compliment              */
2116         /*----------------------------*/
2117     case '~' :
2118         /* can be only integral type */
2119         if (!IS_INTEGRAL(LTYPE(tree))) {
2120             werror(E_UNARY_OP,tree->opval.op);
2121             goto errorTreeReturn ;
2122         } 
2123         
2124         /* if left is a literal then do it */
2125         if (IS_LITERAL(LTYPE(tree))) {
2126             tree->type = EX_VALUE ;
2127             tree->opval.val = valComplement(valFromType(LETYPE(tree)));     
2128             tree->left = NULL ;
2129             TETYPE(tree) = TTYPE(tree) = tree->opval.val->type;
2130             return tree ;
2131         }
2132         LRVAL(tree) = 1;
2133         COPYTYPE(TTYPE(tree),TETYPE(tree),LTYPE(tree));
2134         return tree ;
2135         
2136         /*------------------------------------------------------------------*/
2137         /*----------------------------*/
2138         /*           not              */
2139         /*----------------------------*/
2140     case '!' :
2141         /* can be pointer */
2142         if (!IS_ARITHMETIC(LTYPE(tree)) && 
2143             !IS_PTR(LTYPE(tree))        && 
2144             !IS_ARRAY(LTYPE(tree))) {
2145             werror(E_UNARY_OP,tree->opval.op);
2146             goto errorTreeReturn ;
2147         }
2148         
2149         /* if left is a literal then do it */
2150         if (IS_LITERAL(LTYPE(tree))) {
2151             tree->type = EX_VALUE ;
2152             tree->opval.val = valNot(valFromType(LETYPE(tree)));           
2153             tree->left = NULL ;
2154             TETYPE(tree) = TTYPE(tree) = tree->opval.val->type;
2155             return tree ;
2156         }
2157         LRVAL(tree) = 1;
2158         TTYPE(tree) = TETYPE(tree) = newCharLink();
2159         return tree ;
2160         
2161         /*------------------------------------------------------------------*/
2162         /*----------------------------*/
2163         /*           shift            */
2164         /*----------------------------*/
2165     case RRC:
2166     case RLC:
2167         TTYPE(tree) = LTYPE(tree);
2168         TETYPE(tree) = LETYPE(tree);
2169         return tree ;
2170         
2171     case GETHBIT:
2172         TTYPE(tree) = TETYPE(tree) = newCharLink();       
2173         return tree;
2174
2175     case LEFT_OP:
2176     case RIGHT_OP:
2177         if (!IS_INTEGRAL(LTYPE(tree)) || !IS_INTEGRAL(tree->left->etype)) {  
2178             werror(E_SHIFT_OP_INVALID);
2179             werror(E_CONTINUE,"left & right types are ");
2180             printTypeChain(LTYPE(tree),stderr);
2181             fprintf(stderr,",");
2182             printTypeChain(RTYPE(tree),stderr);
2183             fprintf(stderr,"\n");
2184             goto errorTreeReturn ;
2185         }
2186
2187         /* if they are both literal then */
2188         /* rewrite the tree */
2189         if (IS_LITERAL(RTYPE(tree)) && IS_LITERAL(LTYPE(tree))) {
2190             tree->type = EX_VALUE ;
2191             tree->opval.val = valShift (valFromType(LETYPE(tree)),
2192                                         valFromType(RETYPE(tree)),
2193                                         (tree->opval.op == LEFT_OP ? 1 : 0));             
2194             tree->right = tree->left = NULL;
2195             TETYPE(tree) = getSpec(TTYPE(tree) = 
2196                                    tree->opval.val->type);
2197             return tree ;
2198         }
2199         /* if only the right side is a literal & we are
2200            shifting more than size of the left operand then zero */
2201         if (IS_LITERAL(RTYPE(tree)) && 
2202             ((int)floatFromVal( valFromType(RETYPE(tree)))) >=
2203             (getSize(LTYPE(tree))*8)) {
2204             werror(W_SHIFT_CHANGED, 
2205                    (tree->opval.op == LEFT_OP ? "left" : "right"));
2206             tree->type = EX_VALUE;
2207             tree->left = tree->right = NULL;
2208             tree->opval.val = constVal("0");
2209             TETYPE(tree) = TTYPE(tree) = tree->opval.val->type;
2210             return tree;
2211         }
2212         LRVAL(tree) = RRVAL(tree) = 1;
2213         COPYTYPE(TTYPE(tree),TETYPE(tree),LTYPE(tree));
2214         return tree ;
2215         
2216         /*------------------------------------------------------------------*/
2217         /*----------------------------*/
2218         /*         casting            */
2219         /*----------------------------*/
2220     case CAST   :  /* change the type   */
2221         /* cannot cast to an aggregate type */
2222         if (IS_AGGREGATE(LTYPE(tree))) {
2223             werror(E_CAST_ILLEGAL);
2224             goto errorTreeReturn ;
2225         }
2226         
2227         /* if the right is a literal replace the tree */
2228         if (IS_LITERAL(RETYPE(tree)) && !IS_PTR(LTYPE(tree))) {
2229             tree->type = EX_VALUE ;
2230             tree->opval.val = 
2231                 valCastLiteral(LTYPE(tree),
2232                                floatFromVal(valFromType(RETYPE(tree))));
2233             tree->left = NULL;
2234             tree->right = NULL;
2235             TTYPE(tree) = tree->opval.val->type;            
2236         }
2237         else {
2238             TTYPE(tree) = LTYPE(tree);
2239             LRVAL(tree) = 1;
2240         }
2241
2242         TETYPE(tree) = getSpec(TTYPE(tree)); 
2243         
2244         return tree;
2245         
2246         /*------------------------------------------------------------------*/
2247         /*----------------------------*/
2248         /*       logical &&, ||       */
2249         /*----------------------------*/
2250     case AND_OP:
2251     case OR_OP :
2252         /* each must me arithmetic type or be a pointer */
2253         if (!IS_PTR(LTYPE(tree)) && 
2254             !IS_ARRAY(LTYPE(tree)) && 
2255             !IS_INTEGRAL(LTYPE(tree))) {
2256             werror(E_COMPARE_OP);
2257             goto errorTreeReturn ;
2258         }
2259         
2260         if (!IS_PTR(RTYPE(tree)) &&     
2261             !IS_ARRAY(RTYPE(tree)) && 
2262             !IS_INTEGRAL(RTYPE(tree))) {
2263             werror(E_COMPARE_OP);
2264             goto errorTreeReturn ;
2265         }
2266         /* if they are both literal then */
2267         /* rewrite the tree */
2268         if (IS_LITERAL(RTYPE(tree)) &&
2269             IS_LITERAL(LTYPE(tree))) {
2270             tree->type = EX_VALUE ;
2271             tree->opval.val = valLogicAndOr (valFromType(LETYPE(tree)),
2272                                              valFromType(RETYPE(tree)),
2273                                              tree->opval.op);               
2274             tree->right = tree->left = NULL;
2275             TETYPE(tree) = getSpec(TTYPE(tree) = 
2276                                    tree->opval.val->type);
2277             return tree ;
2278         }
2279         LRVAL(tree) = RRVAL(tree) = 1;
2280         TTYPE(tree) = TETYPE(tree) = newCharLink();
2281         return tree ;
2282         
2283         /*------------------------------------------------------------------*/
2284         /*----------------------------*/
2285         /*     comparison operators   */
2286         /*----------------------------*/    
2287     case '>' :
2288     case '<' :
2289     case LE_OP :
2290     case GE_OP :
2291     case EQ_OP :
2292     case NE_OP :
2293         {
2294             ast *lt = optimizeCompare(tree);
2295             
2296             if ( tree != lt )
2297                 return lt;
2298         }
2299
2300         /* if they are pointers they must be castable */
2301         if ( IS_PTR(LTYPE(tree)) && IS_PTR(RTYPE(tree))) {
2302             if (checkType(LTYPE(tree),RTYPE(tree)) == 0) {
2303                 werror(E_COMPARE_OP);
2304                 fprintf(stderr,"comparing type ");
2305                 printTypeChain(LTYPE(tree),stderr);
2306                 fprintf(stderr,"to type ");
2307                 printTypeChain(RTYPE(tree),stderr);
2308                 fprintf(stderr,"\n");
2309                 goto errorTreeReturn ;
2310             }
2311         } 
2312         /* else they should be promotable to one another */
2313         else {
2314             if (!(  ( IS_PTR(LTYPE(tree)) && IS_LITERAL(RTYPE(tree))) ||
2315                     ( IS_PTR(RTYPE(tree)) && IS_LITERAL(LTYPE(tree))))) 
2316                 
2317                 if (checkType (LTYPE(tree),RTYPE(tree)) == 0 ) {
2318                     werror(E_COMPARE_OP);
2319                     fprintf(stderr,"comparing type ");
2320                     printTypeChain(LTYPE(tree),stderr);
2321                     fprintf(stderr,"to type ");
2322                     printTypeChain(RTYPE(tree),stderr);
2323                     fprintf(stderr,"\n");
2324                     goto errorTreeReturn ;
2325                 }
2326         }
2327         
2328         /* if they are both literal then */
2329         /* rewrite the tree */
2330         if (IS_LITERAL(RTYPE(tree)) &&
2331             IS_LITERAL(LTYPE(tree))) {
2332             tree->type = EX_VALUE ;
2333             tree->opval.val = valCompare (valFromType(LETYPE(tree)),
2334                                           valFromType(RETYPE(tree)),
2335                                           tree->opval.op);                 
2336             tree->right = tree->left = NULL;
2337             TETYPE(tree) = getSpec(TTYPE(tree) = 
2338                                    tree->opval.val->type);
2339             return tree ;
2340         }
2341         LRVAL(tree) = RRVAL(tree) = 1;
2342         TTYPE(tree) = TETYPE(tree) = newCharLink();
2343         return tree ;
2344         
2345         /*------------------------------------------------------------------*/
2346         /*----------------------------*/
2347         /*             sizeof         */
2348         /*----------------------------*/    
2349     case SIZEOF :  /* evaluate wihout code generation */
2350         /* change the type to a integer */
2351         tree->type = EX_VALUE;
2352         sprintf(buffer,"%d",(getSize(tree->right->ftype)));
2353         tree->opval.val = constVal(buffer);
2354         tree->right = tree->left = NULL;
2355         TETYPE(tree) = getSpec(TTYPE(tree) = 
2356                                tree->opval.val->type);
2357         return tree;     
2358         
2359         /*------------------------------------------------------------------*/
2360         /*----------------------------*/
2361         /* conditional operator  '?'  */
2362         /*----------------------------*/    
2363     case '?' :
2364         /* the type is one on the left */
2365         TTYPE(tree) = LTYPE(tree);
2366         TETYPE(tree)= getSpec (TTYPE(tree));
2367         return tree ;
2368         
2369     case ':' :
2370         /* if they don't match we have a problem */
2371         if (checkType( LTYPE(tree), RTYPE(tree)) == 0) {
2372             werror(E_TYPE_MISMATCH,"conditional operator"," ");
2373             goto errorTreeReturn ;
2374         }
2375         
2376         TTYPE(tree) = computeType(LTYPE(tree),RTYPE(tree));
2377         TETYPE(tree)= getSpec(TTYPE(tree));
2378         return tree ;
2379         
2380         
2381         /*------------------------------------------------------------------*/
2382         /*----------------------------*/
2383         /*    assignment operators    */
2384         /*----------------------------*/    
2385     case MUL_ASSIGN:
2386     case DIV_ASSIGN:
2387         /* for these it must be both must be integral */
2388         if (!IS_ARITHMETIC(LTYPE(tree)) ||
2389             !IS_ARITHMETIC(RTYPE(tree))) {
2390             werror (E_OPS_INTEGRAL);
2391             goto errorTreeReturn ;
2392         }
2393         RRVAL(tree) = 1;
2394         TETYPE(tree) = getSpec(TTYPE(tree) = LTYPE(tree));
2395
2396         if (!tree->initMode && IS_CONSTANT(LETYPE(tree)))
2397             werror(E_CODE_WRITE," ");
2398
2399         if (LRVAL(tree)) {
2400             werror(E_LVALUE_REQUIRED,"*= or /=");
2401             goto errorTreeReturn ;      
2402         }
2403         LLVAL(tree) = 1;
2404         return tree ;
2405
2406     case AND_ASSIGN:
2407     case OR_ASSIGN:
2408     case XOR_ASSIGN:
2409     case RIGHT_ASSIGN:
2410     case LEFT_ASSIGN:
2411         /* for these it must be both must be integral */
2412         if (!IS_INTEGRAL(LTYPE(tree)) ||
2413             !IS_INTEGRAL(RTYPE(tree))) {
2414             werror (E_OPS_INTEGRAL);
2415             goto errorTreeReturn ;
2416         }
2417         RRVAL(tree) = 1;
2418         TETYPE(tree) = getSpec(TTYPE(tree) = LTYPE(tree));
2419
2420         if (!tree->initMode && IS_CONSTANT(LETYPE(tree)))
2421             werror(E_CODE_WRITE," ");
2422
2423         if (LRVAL(tree)) {
2424             werror(E_LVALUE_REQUIRED,"&= or |= or ^= or >>= or <<=");
2425             goto errorTreeReturn ;      
2426         }
2427         LLVAL(tree) = 1;
2428         return tree ;
2429         
2430         /*------------------------------------------------------------------*/
2431         /*----------------------------*/
2432         /*    -= operator             */
2433         /*----------------------------*/    
2434     case SUB_ASSIGN:
2435         if (!(IS_PTR(LTYPE(tree))   ||
2436               IS_ARITHMETIC(LTYPE(tree)))) {
2437             werror(E_PLUS_INVALID,"-=");
2438             goto errorTreeReturn ;
2439         }
2440         
2441         if (!(IS_PTR(RTYPE(tree))   ||
2442               IS_ARITHMETIC(RTYPE(tree)))) {
2443             werror(E_PLUS_INVALID,"-=");
2444             goto errorTreeReturn ;
2445         }
2446         RRVAL(tree) = 1;
2447         TETYPE(tree) = getSpec (TTYPE(tree) = 
2448                                 computeType(LTYPE(tree),
2449                                             RTYPE(tree)));  
2450
2451         if (!tree->initMode && IS_CONSTANT(LETYPE(tree)))
2452             werror(E_CODE_WRITE," ");
2453
2454         if (LRVAL(tree)) {
2455             werror(E_LVALUE_REQUIRED,"-=");
2456             goto errorTreeReturn ;      
2457         }
2458         LLVAL(tree) = 1;
2459         return tree;
2460         
2461         /*------------------------------------------------------------------*/
2462         /*----------------------------*/
2463         /*          += operator       */
2464         /*----------------------------*/    
2465     case ADD_ASSIGN:
2466         /* this is not a unary operation */
2467         /* if both pointers then problem */
2468         if (IS_PTR(LTYPE(tree)) && IS_PTR(RTYPE(tree)) ) {
2469             werror(E_PTR_PLUS_PTR);
2470             goto errorTreeReturn ;
2471         }
2472         
2473         if (!IS_ARITHMETIC(LTYPE(tree)) && !IS_PTR(LTYPE(tree)))  {
2474             werror(E_PLUS_INVALID,"+=");
2475             goto errorTreeReturn ;
2476         }
2477         
2478         if (!IS_ARITHMETIC(RTYPE(tree)) && !IS_PTR(RTYPE(tree)))  {
2479             werror(E_PLUS_INVALID,"+=");
2480             goto errorTreeReturn;
2481         }
2482         RRVAL(tree) = 1;
2483         TETYPE(tree) = getSpec (TTYPE(tree) = 
2484                                 computeType(LTYPE(tree),
2485                                             RTYPE(tree)));  
2486
2487         if (!tree->initMode && IS_CONSTANT(LETYPE(tree)))
2488             werror(E_CODE_WRITE," ");
2489
2490         if (LRVAL(tree)) {
2491             werror(E_LVALUE_REQUIRED,"+=");
2492             goto errorTreeReturn ;      
2493         }
2494
2495         tree->right = decorateType(newNode('+',copyAst(tree->left),tree->right));
2496         tree->opval.op = '=';       
2497         return tree;
2498         
2499         /*------------------------------------------------------------------*/
2500         /*----------------------------*/
2501         /*      straight assignemnt   */
2502         /*----------------------------*/    
2503     case '=' :
2504         /* cannot be an aggregate */
2505         if (IS_AGGREGATE(LTYPE(tree))) {
2506             werror(E_AGGR_ASSIGN);
2507             goto errorTreeReturn;
2508         }
2509             
2510         /* they should either match or be castable */
2511         if (checkType (LTYPE(tree),RTYPE(tree)) == 0) {
2512             werror(E_TYPE_MISMATCH,"assignment"," ");
2513             fprintf(stderr,"type --> '"); 
2514             printTypeChain (RTYPE(tree),stderr); fprintf(stderr,"' ");
2515             fprintf(stderr,"assigned to type --> '"); 
2516             printTypeChain (LTYPE(tree),stderr); fprintf(stderr,"'\n");
2517             goto errorTreeReturn ;
2518         }
2519
2520         /* if the left side of the tree is of type void
2521            then report error */
2522         if (IS_VOID(LTYPE(tree))) {
2523             werror(E_CAST_ZERO);
2524             fprintf(stderr,"type --> '"); 
2525             printTypeChain (RTYPE(tree),stderr); fprintf(stderr,"' ");
2526             fprintf(stderr,"assigned to type --> '"); 
2527             printTypeChain (LTYPE(tree),stderr); fprintf(stderr,"'\n");
2528         }
2529
2530         /* extra checks for pointer types */
2531         if (IS_PTR(LTYPE(tree)) && IS_PTR(RTYPE(tree)) &&
2532             !IS_GENPTR(LTYPE(tree))) {
2533           if (DCL_TYPE(LTYPE(tree)) != DCL_TYPE(RTYPE(tree)))
2534             werror(W_PTR_ASSIGN);
2535         }
2536
2537         TETYPE(tree) = getSpec(TTYPE(tree) = 
2538                                LTYPE(tree));
2539         RRVAL(tree) = 1;
2540         LLVAL(tree) = 1;
2541         if (!tree->initMode && IS_CONSTANT(LETYPE(tree)))
2542             werror(E_CODE_WRITE," ");
2543
2544         if (LRVAL(tree)) {
2545             werror(E_LVALUE_REQUIRED,"=");
2546             goto errorTreeReturn ;      
2547         }
2548
2549         return tree ;
2550         
2551         /*------------------------------------------------------------------*/
2552         /*----------------------------*/
2553         /*      comma operator        */
2554         /*----------------------------*/        
2555     case ',' :
2556         TETYPE(tree) = getSpec(TTYPE(tree) =  RTYPE(tree));
2557         return tree ;    
2558         
2559         /*------------------------------------------------------------------*/
2560         /*----------------------------*/
2561         /*       function call        */
2562         /*----------------------------*/        
2563     case CALL   :
2564         parmNumber = 1;
2565
2566
2567         if (processParms (tree->left,
2568                           tree->left->args,
2569                           tree->right,&parmNumber)) 
2570             goto errorTreeReturn ;    
2571
2572         if (options.stackAuto || IS_RENT(LETYPE(tree))) {
2573                 tree->left->args = reverseVal(tree->left->args); 
2574                 reverseParms(tree->right);
2575         }
2576
2577         tree->args = tree->left->args ;
2578         TETYPE(tree) = getSpec (TTYPE(tree) = LTYPE(tree)->next);
2579         return tree;
2580
2581         /*------------------------------------------------------------------*/
2582         /*----------------------------*/
2583         /*     return statement       */
2584         /*----------------------------*/        
2585     case RETURN :
2586         if (!tree->right)
2587             goto voidcheck ;
2588
2589         if (checkType(currFunc->type->next,RTYPE(tree)) == 0) {
2590             werror(E_RETURN_MISMATCH);
2591             goto errorTreeReturn ;
2592         }
2593
2594         if (IS_VOID(currFunc->type->next) 
2595             && tree->right && 
2596             !IS_VOID(RTYPE(tree))) {
2597             werror(E_FUNC_VOID);
2598             goto errorTreeReturn ;
2599         }
2600         
2601         /* if there is going to be a casing required then add it */
2602         if (checkType(currFunc->type->next,RTYPE(tree)) < 0 ) {
2603             tree->right = 
2604                 decorateType(newNode(CAST,
2605                                      newAst(EX_LINK,
2606                                             copyLinkChain(currFunc->type->next)),
2607                                      tree->right));
2608         }
2609         
2610         RRVAL(tree) = 1;
2611         return tree;
2612
2613         voidcheck :
2614
2615         if (!IS_VOID(currFunc->type->next) && tree->right == NULL ) {
2616             werror(E_VOID_FUNC,currFunc->name);
2617             goto errorTreeReturn ;
2618         }               
2619
2620         TTYPE(tree) = TETYPE(tree) = NULL ;
2621         return tree ;    
2622
2623         /*------------------------------------------------------------------*/
2624         /*----------------------------*/
2625         /*     switch statement       */
2626         /*----------------------------*/        
2627     case SWITCH:
2628         /* the switch value must be an integer */
2629         if (!IS_INTEGRAL(LTYPE(tree))) {
2630             werror (E_SWITCH_NON_INTEGER);
2631             goto errorTreeReturn ;
2632         }
2633         LRVAL(tree) = 1;
2634         TTYPE(tree) = TETYPE(tree) = NULL ;
2635         return tree ;
2636
2637         /*------------------------------------------------------------------*/
2638         /*----------------------------*/
2639         /* ifx Statement              */
2640         /*----------------------------*/
2641     case IFX:
2642         tree->left = backPatchLabels(tree->left,
2643                                      tree->trueLabel,
2644                                      tree->falseLabel);
2645         TTYPE(tree) = TETYPE(tree) = NULL;
2646         return tree;
2647
2648         /*------------------------------------------------------------------*/
2649         /*----------------------------*/
2650         /* for Statement              */
2651         /*----------------------------*/
2652     case FOR:              
2653
2654         decorateType(resolveSymbols(AST_FOR(tree,initExpr)));
2655         decorateType(resolveSymbols(AST_FOR(tree,condExpr)));
2656         decorateType(resolveSymbols(AST_FOR(tree,loopExpr)));
2657         
2658         /* if the for loop is reversible then 
2659            reverse it otherwise do what we normally
2660            do */
2661         {
2662             symbol *sym ;
2663             ast *init, *end;
2664
2665             if (isLoopReversible (tree,&sym,&init,&end))
2666                 return reverseLoop (tree,sym,init,end);
2667             else
2668                 return decorateType(createFor ( AST_FOR(tree,trueLabel), 
2669                                                 AST_FOR(tree,continueLabel) ,
2670                                                 AST_FOR(tree,falseLabel) ,
2671                                                 AST_FOR(tree,condLabel)  ,
2672                                                 AST_FOR(tree,initExpr)   , 
2673                                                 AST_FOR(tree,condExpr)   , 
2674                                                 AST_FOR(tree,loopExpr),
2675                                                 tree->left ) );
2676         }
2677     default :
2678         TTYPE(tree) = TETYPE(tree) = NULL ;
2679         return tree ;    
2680     }
2681     
2682     /* some error found this tree will be killed */
2683     errorTreeReturn :     
2684         TTYPE(tree) = TETYPE(tree) = newCharLink();
2685     tree->opval.op = NULLOP ;
2686     tree->isError = 1;
2687     
2688     return tree ;
2689 }
2690
2691 /*-----------------------------------------------------------------*/
2692 /* sizeofOp - processes size of operation                          */
2693 /*-----------------------------------------------------------------*/
2694 value  *sizeofOp( link  *type)
2695 {
2696         char buff[10];
2697
2698         /* get the size and convert it to character  */
2699         sprintf (buff,"%d", getSize(type));
2700
2701         /* now convert into value  */
2702         return  constVal (buff);      
2703 }
2704
2705
2706 #define IS_AND(ex) (ex->type == EX_OP && ex->opval.op == AND_OP )
2707 #define IS_OR(ex)  (ex->type == EX_OP && ex->opval.op == OR_OP )
2708 #define IS_NOT(ex) (ex->type == EX_OP && ex->opval.op == '!' )
2709 #define IS_ANDORNOT(ex) (IS_AND(ex) || IS_OR(ex) || IS_NOT(ex))
2710 #define IS_IFX(ex) (ex->type == EX_OP && ex->opval.op == IFX )
2711 #define IS_LT(ex)  (ex->type == EX_OP && ex->opval.op == '<' )
2712 #define IS_GT(ex)  (ex->type == EX_OP && ex->opval.op == '>')
2713
2714 /*-----------------------------------------------------------------*/
2715 /* backPatchLabels - change and or not operators to flow control    */
2716 /*-----------------------------------------------------------------*/
2717 ast *backPatchLabels (ast *tree, symbol *trueLabel, symbol *falseLabel )
2718 {  
2719     
2720     if ( ! tree )
2721         return NULL ;
2722     
2723     if ( ! (IS_ANDORNOT(tree)))
2724         return tree ;
2725     
2726     /* if this an and */
2727     if (IS_AND(tree)) {
2728         static int localLbl = 0 ;
2729         symbol *localLabel ;
2730         
2731         sprintf (buffer,"_and_%d",localLbl++);
2732         localLabel = newSymbol(buffer,NestLevel);
2733         
2734         tree->left = backPatchLabels (tree->left, localLabel,falseLabel);    
2735         
2736         /* if left is already a IFX then just change the if true label in that */
2737         if (!IS_IFX(tree->left)) 
2738             tree->left = newIfxNode(tree->left,localLabel,falseLabel);
2739         
2740         tree->right = backPatchLabels(tree->right,trueLabel,falseLabel);    
2741         /* right is a IFX then just join */
2742         if (IS_IFX(tree->right))
2743             return newNode(NULLOP,tree->left,createLabel(localLabel,tree->right));
2744         
2745         tree->right = createLabel(localLabel,tree->right);
2746         tree->right = newIfxNode(tree->right,trueLabel,falseLabel);
2747         
2748         return newNode(NULLOP,tree->left,tree->right);
2749     }
2750     
2751     /* if this is an or operation */
2752     if (IS_OR(tree)) {
2753         static int localLbl = 0 ;
2754         symbol *localLabel ;
2755         
2756         sprintf (buffer,"_or_%d",localLbl++);
2757         localLabel = newSymbol(buffer,NestLevel);
2758         
2759         tree->left = backPatchLabels (tree->left, trueLabel,localLabel);    
2760         
2761         /* if left is already a IFX then just change the if true label in that */
2762         if (!IS_IFX(tree->left))                
2763             tree->left = newIfxNode(tree->left,trueLabel,localLabel);
2764         
2765         tree->right = backPatchLabels(tree->right,trueLabel,falseLabel);    
2766         /* right is a IFX then just join */
2767         if (IS_IFX(tree->right))
2768             return newNode(NULLOP,tree->left,createLabel(localLabel,tree->right));
2769         
2770         tree->right = createLabel(localLabel,tree->right);
2771         tree->right = newIfxNode(tree->right,trueLabel,falseLabel);
2772         
2773         return newNode(NULLOP,tree->left,tree->right);
2774     }
2775     
2776     /* change not */
2777     if (IS_NOT(tree)) {
2778         tree->left = backPatchLabels (tree->left,falseLabel,trueLabel);
2779         
2780         /* if the left is already a IFX */
2781         if ( ! IS_IFX(tree->left) ) 
2782             tree->left = newNode (IFX,tree->left,NULL);
2783         
2784         tree->left->trueLabel = falseLabel ;
2785         tree->left->falseLabel= trueLabel ;
2786         return tree->left ;
2787     }
2788     
2789     if (IS_IFX(tree)) {
2790         tree->trueLabel = trueLabel ;
2791         tree->falseLabel= falseLabel;
2792     }
2793     
2794     return tree ;    
2795 }
2796
2797
2798 /*-----------------------------------------------------------------*/
2799 /* createBlock - create expression tree for block                  */
2800 /*-----------------------------------------------------------------*/
2801 ast  *createBlock   ( symbol *decl,   ast  *body )
2802 {
2803     ast *ex ;
2804     
2805     /* if the block has nothing */
2806     if (!body)
2807         return NULL;
2808
2809     ex = newNode(BLOCK,NULL,body);
2810     ex->values.sym = decl ;
2811     
2812     ex->right = ex->right ;
2813     ex->level++ ;
2814     ex->lineno = 0 ;
2815     return ex;
2816 }
2817
2818 /*-----------------------------------------------------------------*/
2819 /* createLabel - creates the expression tree for labels            */
2820 /*-----------------------------------------------------------------*/
2821 ast  *createLabel  ( symbol  *label,  ast  *stmnt  )
2822 {
2823     symbol *csym;
2824     char        name[SDCC_NAME_MAX+1];
2825     ast   *rValue ;
2826     
2827     /* must create fresh symbol if the symbol name  */
2828     /* exists in the symbol table, since there can  */
2829     /* be a variable with the same name as the labl */
2830     if ((csym = findSym (SymbolTab,NULL,label->name)) &&
2831         (csym->level == label->level))
2832         label = newSymbol(label->name,label->level);
2833     
2834     /* change the name before putting it in add _*/
2835     sprintf (name,"%s",label->name);
2836     
2837     /* put the label in the LabelSymbol table    */
2838     /* but first check if a label of the same    */
2839     /* name exists                               */
2840     if ( (csym = findSym(LabelTab,NULL,name)))
2841         werror(E_DUPLICATE_LABEL,label->name);
2842     else
2843         addSym (LabelTab, label, name,label->level,0);
2844     
2845     label->islbl = 1;
2846     label->key = labelKey++ ;
2847     rValue =  newNode (LABEL,newAst(EX_VALUE,symbolVal(label)),stmnt);  
2848     rValue->lineno = 0;
2849     
2850     return rValue ;
2851 }
2852
2853 /*-----------------------------------------------------------------*/
2854 /* createCase - generates the parsetree for a case statement       */
2855 /*-----------------------------------------------------------------*/
2856 ast  *createCase (ast *swStat, ast *caseVal, ast *stmnt   )
2857 {
2858     char caseLbl[SDCC_NAME_MAX+1];
2859     ast *rexpr;
2860     value *val;
2861     
2862     /* if the switch statement does not exist */
2863     /* then case is out of context            */
2864     if (!swStat) {
2865         werror(E_CASE_CONTEXT);
2866         return NULL ;
2867     }
2868     
2869     caseVal = decorateType(resolveSymbols(caseVal));
2870     /* if not a constant then error  */
2871     if (!IS_LITERAL(caseVal->ftype)) {
2872         werror(E_CASE_CONSTANT);
2873         return NULL ;
2874     }
2875     
2876     /* if not a integer than error */
2877     if (!IS_INTEGRAL(caseVal->ftype)) {
2878         werror(E_CASE_NON_INTEGER);
2879         return NULL;
2880     }
2881
2882     /* find the end of the switch values chain   */
2883     if (!(val = swStat->values.switchVals.swVals))
2884         swStat->values.switchVals.swVals = caseVal->opval.val ;
2885     else {
2886         /* also order the cases according to value */
2887         value *pval = NULL;
2888         int cVal = (int) floatFromVal(caseVal->opval.val);
2889         while (val && (int) floatFromVal(val) < cVal) {
2890             pval = val;
2891             val = val->next ;
2892         }
2893        
2894         /* if we reached the end then */
2895         if (!val) {
2896             pval->next =  caseVal->opval.val;
2897         } else {
2898             /* we found a value greater than */
2899             /* the current value we must add this */
2900             /* before the value */
2901             caseVal->opval.val->next = val;
2902
2903             /* if this was the first in chain */
2904             if (swStat->values.switchVals.swVals == val)
2905                 swStat->values.switchVals.swVals = 
2906                     caseVal->opval.val;
2907             else
2908                 pval->next =  caseVal->opval.val;
2909         }
2910             
2911     }
2912     
2913     /* create the case label   */
2914     sprintf(caseLbl,"_case_%d_%d",
2915             swStat->values.switchVals.swNum,
2916             (int) floatFromVal(caseVal->opval.val));
2917     
2918     rexpr = createLabel(newSymbol(caseLbl,0),stmnt);
2919     rexpr->lineno = 0;
2920     return rexpr;
2921 }
2922
2923 /*-----------------------------------------------------------------*/
2924 /* createDefault - creates the parse tree for the default statement*/
2925 /*-----------------------------------------------------------------*/
2926 ast  *createDefault (ast *swStat, ast *stmnt)
2927 {
2928     char  defLbl[SDCC_NAME_MAX+1];
2929     
2930     /* if the switch statement does not exist */
2931     /* then case is out of context            */
2932     if (!swStat) {
2933         werror(E_CASE_CONTEXT);
2934         return NULL ;
2935     }
2936     
2937     /* turn on the default flag   */
2938     swStat->values.switchVals.swDefault = 1   ;
2939     
2940     /* create the label  */
2941     sprintf (defLbl,"_default_%d",swStat->values.switchVals.swNum);
2942     return createLabel(newSymbol(defLbl,0),stmnt);   
2943 }
2944
2945 /*-----------------------------------------------------------------*/
2946 /* createIf - creates the parsetree for the if statement           */
2947 /*-----------------------------------------------------------------*/
2948 ast *createIf ( ast *condAst, ast *ifBody, ast *elseBody )
2949 {
2950     static int Lblnum = 0 ;
2951     ast *ifTree ;
2952     symbol *ifTrue , *ifFalse, *ifEnd ;
2953     
2954     /* if neither exists */
2955     if (! elseBody && !ifBody)
2956         return condAst ;
2957     
2958     /* create the labels */
2959     sprintf (buffer,"_iffalse_%d",Lblnum);
2960     ifFalse = newSymbol (buffer,NestLevel);
2961     /* if no else body then end == false */
2962     if ( ! elseBody ) 
2963         ifEnd = ifFalse ;
2964     else {
2965         sprintf (buffer,"_ifend_%d",Lblnum);
2966         ifEnd = newSymbol (buffer,NestLevel);
2967     }
2968
2969     sprintf (buffer,"_iftrue_%d",Lblnum);
2970     ifTrue = newSymbol (buffer,NestLevel);
2971         
2972     Lblnum++ ;
2973
2974     /* attach the ifTrue label to the top of it body */
2975     ifBody = createLabel(ifTrue,ifBody);
2976     /* attach a goto end to the ifBody if else is present */
2977     if ( elseBody ) {
2978         ifBody = newNode(NULLOP,ifBody,
2979                          newNode(GOTO,
2980                                  newAst(EX_VALUE,symbolVal(ifEnd)),             
2981                                  NULL));
2982         /* put the elseLabel on the else body */
2983         elseBody = createLabel (ifFalse,elseBody);
2984         /* out the end at the end of the body */
2985         elseBody = newNode(NULLOP,
2986                            elseBody,
2987                            createLabel(ifEnd,NULL));
2988     }
2989     else {
2990         ifBody = newNode(NULLOP,ifBody,
2991                          createLabel(ifFalse,NULL));
2992     }
2993     condAst = backPatchLabels (condAst,ifTrue,ifFalse);
2994     if (IS_IFX(condAst))
2995         ifTree = condAst;
2996     else 
2997         ifTree = newIfxNode(condAst,ifTrue,ifFalse);
2998     
2999     return newNode(NULLOP,ifTree,
3000                    newNode(NULLOP,ifBody,elseBody));
3001     
3002 }
3003
3004 /*-----------------------------------------------------------------*/
3005 /* createDo - creates parse tree for do                            */
3006 /*        _dobody_n:                                               */
3007 /*            statements                                           */
3008 /*        _docontinue_n:                                           */
3009 /*            condition_expression +-> trueLabel -> _dobody_n      */
3010 /*                                 |                               */
3011 /*                                 +-> falseLabel-> _dobreak_n     */
3012 /*        _dobreak_n:                                              */
3013 /*-----------------------------------------------------------------*/
3014 ast *createDo ( symbol *trueLabel, symbol *continueLabel,
3015                 symbol *falseLabel, ast *condAst, ast *doBody )
3016 {
3017     ast *doTree ;
3018     
3019     
3020     /* if the body does not exist then it is simple */
3021     if ( ! doBody ) {
3022         condAst = backPatchLabels(condAst,continueLabel,NULL);
3023         doTree = (IS_IFX(condAst) ? createLabel(continueLabel,condAst) 
3024                   : newNode(IFX,createLabel(continueLabel,condAst),NULL));
3025         doTree->trueLabel = continueLabel ;
3026         doTree->falseLabel= NULL ;
3027         return doTree ;
3028     }
3029     
3030     /* otherwise we have a body */
3031     condAst = backPatchLabels(condAst,trueLabel,falseLabel);
3032     
3033     /* attach the body label to the top */
3034     doBody = createLabel(trueLabel,doBody);
3035     /* attach the continue label to end of body */
3036     doBody = newNode(NULLOP, doBody, 
3037                      createLabel(continueLabel,NULL));
3038     
3039     /* now put the break label at the end */
3040     if (IS_IFX(condAst))
3041         doTree = condAst;
3042     else 
3043         doTree = newIfxNode(condAst,trueLabel,falseLabel);
3044     
3045     doTree = newNode(NULLOP,doTree,createLabel(falseLabel,NULL));
3046     
3047     /* putting it together */
3048     return newNode(NULLOP,doBody,doTree);
3049 }
3050
3051 /*-----------------------------------------------------------------*/
3052 /* createFor - creates parse tree for 'for' statement              */
3053 /*        initExpr                                                 */
3054 /*   _forcond_n:                                                   */
3055 /*        condExpr  +-> trueLabel -> _forbody_n                    */
3056 /*                  |                                              */
3057 /*                  +-> falseLabel-> _forbreak_n                   */
3058 /*   _forbody_n:                                                   */
3059 /*        statements                                               */
3060 /*   _forcontinue_n:                                               */
3061 /*        loopExpr                                                 */
3062 /*        goto _forcond_n ;                                        */
3063 /*   _forbreak_n:                                                  */
3064 /*-----------------------------------------------------------------*/
3065 ast *createFor ( symbol *trueLabel, symbol *continueLabel ,
3066                  symbol *falseLabel,symbol *condLabel     ,
3067                  ast *initExpr, ast *condExpr, ast *loopExpr,
3068                  ast *forBody )
3069 {
3070     ast *forTree ;      
3071
3072     /* if loopexpression not present then we can generate it */
3073     /* the same way as a while */
3074     if ( ! loopExpr ) 
3075         return newNode(NULLOP,initExpr,
3076                        createWhile (trueLabel, continueLabel, 
3077                                     falseLabel,condExpr, forBody ));
3078     /* vanilla for statement */
3079     condExpr = backPatchLabels(condExpr,trueLabel,falseLabel);
3080     
3081     if (condExpr && !IS_IFX(condExpr)) 
3082         condExpr = newIfxNode(condExpr,trueLabel,falseLabel);
3083     
3084     
3085     /* attach condition label to condition */
3086     condExpr = createLabel(condLabel,condExpr);
3087     
3088     /* attach body label to body */
3089     forBody = createLabel(trueLabel,forBody);
3090     
3091     /* attach continue to forLoop expression & attach */
3092     /* goto the forcond @ and of loopExpression       */
3093     loopExpr = createLabel(continueLabel,
3094                            newNode(NULLOP,
3095                                    loopExpr,
3096                                    newNode(GOTO,
3097                                            newAst(EX_VALUE,symbolVal(condLabel)),
3098                                            NULL)));
3099     /* now start putting them together */
3100     forTree = newNode(NULLOP,initExpr,condExpr);
3101     forTree = newNode(NULLOP,forTree,forBody);
3102     forTree = newNode(NULLOP,forTree,loopExpr);
3103     /* finally add the break label */
3104     forTree = newNode(NULLOP,forTree,
3105                       createLabel(falseLabel,NULL));
3106     return forTree ;
3107 }
3108
3109 /*-----------------------------------------------------------------*/
3110 /* createWhile - creates parse tree for while statement            */
3111 /*               the while statement will be created as follows    */
3112 /*                                                                 */
3113 /*      _while_continue_n:                                         */
3114 /*            condition_expression +-> trueLabel -> _while_boby_n  */
3115 /*                                 |                               */
3116 /*                                 +-> falseLabel -> _while_break_n*/
3117 /*      _while_body_n:                                             */
3118 /*            statements                                           */
3119 /*            goto _while_continue_n                               */
3120 /*      _while_break_n:                                            */
3121 /*-----------------------------------------------------------------*/
3122 ast *createWhile (symbol *trueLabel, symbol *continueLabel, 
3123                    symbol *falseLabel,ast *condExpr, ast *whileBody )
3124 {
3125     ast *whileTree ;
3126         
3127     /* put the continue label */
3128     condExpr = backPatchLabels (condExpr,trueLabel,falseLabel);
3129     condExpr = createLabel(continueLabel,condExpr);
3130     condExpr->lineno = 0;
3131     
3132     /* put the body label in front of the body */
3133     whileBody = createLabel(trueLabel,whileBody);
3134     whileBody->lineno = 0;
3135     /* put a jump to continue at the end of the body */
3136     /* and put break label at the end of the body */
3137     whileBody = newNode(NULLOP,
3138                         whileBody,
3139                         newNode(GOTO,
3140                                 newAst(EX_VALUE,
3141                                        symbolVal(continueLabel)),
3142                                 createLabel(falseLabel,NULL)));
3143     
3144     /* put it all together */
3145     if ( IS_IFX(condExpr) )
3146         whileTree = condExpr ;
3147     else {
3148         whileTree = newNode (IFX, condExpr,NULL );      
3149         /* put the true & false labels in place */
3150         whileTree->trueLabel = trueLabel ;
3151         whileTree->falseLabel= falseLabel;
3152     }
3153     
3154     return newNode(NULLOP,whileTree,whileBody );
3155 }
3156
3157 /*-----------------------------------------------------------------*/
3158 /* optimizeGetHbit - get highest order bit of the expression       */
3159 /*-----------------------------------------------------------------*/
3160 ast *optimizeGetHbit (ast *tree)
3161 {
3162     int i,j;
3163     /* if this is not a bit and */
3164     if (!IS_BITAND(tree))
3165         return tree;
3166     
3167     /* will look for tree of the form
3168        ( expr >> ((sizeof expr) -1) ) & 1 */
3169     if (!IS_AST_LIT_VALUE(tree->right))
3170         return tree;
3171
3172     if (AST_LIT_VALUE(tree->right) != 1)
3173         return tree;
3174
3175     if (!IS_RIGHT_OP(tree->left))
3176         return tree;
3177
3178     if (!IS_AST_LIT_VALUE(tree->left->right))
3179         return tree;
3180
3181     if ((i = AST_LIT_VALUE(tree->left->right)) !=
3182         ( j = (getSize(TTYPE(tree->left->left))*8 - 1)))
3183         return tree;
3184
3185     return decorateType(newNode(GETHBIT,tree->left->left,NULL));
3186         
3187 }
3188
3189 /*-----------------------------------------------------------------*/
3190 /* optimizeRRCRLC :- optimize for Rotate Left/Right with carry     */
3191 /*-----------------------------------------------------------------*/
3192 ast *optimizeRRCRLC ( ast *root )
3193 {
3194     /* will look for trees of the form
3195        (?expr << 1) | (?expr >> 7) or
3196        (?expr >> 7) | (?expr << 1) will make that
3197        into a RLC : operation ..
3198        Will also look for 
3199        (?expr >> 1) | (?expr << 7) or
3200        (?expr << 7) | (?expr >> 1) will make that
3201        into a RRC operation 
3202        note : by 7 I mean (number of bits required to hold the
3203        variable -1 ) */
3204     /* if the root operations is not a | operation the not */
3205     if (!IS_BITOR(root))
3206         return root ;
3207
3208     /* I have to think of a better way to match patterns this sucks */
3209     /* that aside let start looking for the first case : I use a the
3210        negative check a lot to improve the efficiency */
3211     /* (?expr << 1) | (?expr >> 7) */
3212     if (IS_LEFT_OP(root->left)    && 
3213         IS_RIGHT_OP(root->right)  ) {   
3214         
3215         if (!SPEC_USIGN(TETYPE(root->left->left)))
3216             return root;
3217
3218         if (!IS_AST_LIT_VALUE(root->left->right) ||
3219             !IS_AST_LIT_VALUE(root->right->right))
3220             goto tryNext0;
3221
3222         /* make sure it is the same expression */
3223         if (!isAstEqual(root->left->left,
3224                         root->right->left))
3225             goto tryNext0;
3226         
3227         if (AST_LIT_VALUE(root->left->right) != 1 )
3228             goto tryNext0 ;
3229         
3230         if (AST_LIT_VALUE(root->right->right) !=
3231             (getSize(TTYPE(root->left->left))*8 - 1))
3232             goto tryNext0 ;
3233
3234         /* whew got the first case : create the AST */
3235         return  newNode(RLC,root->left->left,NULL);     
3236     }
3237
3238  tryNext0:
3239     /* check for second case */
3240     /* (?expr >> 7) | (?expr << 1) */
3241     if (IS_LEFT_OP(root->right)    && 
3242         IS_RIGHT_OP(root->left)  ) {     
3243
3244         if (!SPEC_USIGN(TETYPE(root->left->left)))
3245             return root;
3246         
3247         if (!IS_AST_LIT_VALUE(root->left->right) ||
3248             !IS_AST_LIT_VALUE(root->right->right))
3249             goto tryNext1 ;
3250         
3251         /* make sure it is the same symbol */
3252         if (!isAstEqual(root->left->left,
3253                         root->right->left))
3254             goto tryNext1 ;
3255         
3256         if (AST_LIT_VALUE(root->right->right) != 1 )
3257             goto tryNext1 ;
3258         
3259         if (AST_LIT_VALUE(root->left->right) !=
3260             (getSize(TTYPE(root->left->left))*8 - 1))
3261             goto tryNext1 ;
3262
3263         /* whew got the first case : create the AST */
3264         return  newNode(RLC,root->left->left,NULL);
3265         
3266     }
3267
3268  tryNext1:
3269     /* third case for RRC */
3270     /*  (?symbol >> 1) | (?symbol << 7) */
3271     if (IS_LEFT_OP(root->right)    && 
3272         IS_RIGHT_OP(root->left)  ) {    
3273
3274         if (!SPEC_USIGN(TETYPE(root->left->left)))
3275             return root;
3276         
3277         if (!IS_AST_LIT_VALUE(root->left->right) ||
3278             !IS_AST_LIT_VALUE(root->right->right))
3279             goto tryNext2;
3280         
3281         /* make sure it is the same symbol */
3282         if (!isAstEqual(root->left->left,
3283                         root->right->left))
3284             goto tryNext2;
3285         
3286         if (AST_LIT_VALUE(root->left->right) != 1 )
3287             goto tryNext2;
3288         
3289         if (AST_LIT_VALUE(root->right->right) !=
3290             (getSize(TTYPE(root->left->left))*8 - 1))
3291             goto tryNext2;
3292
3293         /* whew got the first case : create the AST */
3294         return newNode(RRC,root->left->left,NULL);
3295         
3296     }
3297  tryNext2:
3298     /* fourth and last case for now */
3299     /* (?symbol << 7) | (?symbol >> 1) */
3300     if (IS_RIGHT_OP(root->right)    && 
3301         IS_LEFT_OP(root->left)  ) {     
3302
3303         if (!SPEC_USIGN(TETYPE(root->left->left)))
3304             return root;
3305         
3306         if (!IS_AST_LIT_VALUE(root->left->right) ||
3307             !IS_AST_LIT_VALUE(root->right->right))
3308             return root;
3309
3310         /* make sure it is the same symbol */
3311         if (!isAstEqual(root->left->left,
3312                         root->right->left))
3313             return root;
3314         
3315         if (AST_LIT_VALUE(root->right->right) != 1 )
3316             return root ;
3317         
3318         if (AST_LIT_VALUE(root->left->right) !=
3319             (getSize(TTYPE(root->left->left))*8 - 1))
3320             return root ;
3321
3322         /* whew got the first case : create the AST */
3323         return  newNode(RRC,root->left->left,NULL);
3324         
3325     }
3326
3327     /* not found return root */
3328     return root;
3329 }
3330
3331 /*-----------------------------------------------------------------*/
3332 /* optimizeCompare - otimizes compares for bit variables           */
3333 /*-----------------------------------------------------------------*/
3334 ast  *optimizeCompare ( ast *root )
3335 {
3336     ast *optExpr = NULL;
3337     value       *vleft;
3338     value       *vright;
3339     unsigned int litValue ;
3340     
3341     /* if nothing then return nothing */
3342     if (!root)
3343         return NULL ;
3344     
3345     /* if not a compare op then do leaves */
3346     if (!IS_COMPARE_OP(root)) {
3347         root->left = optimizeCompare (root->left);
3348         root->right= optimizeCompare (root->right);
3349         return root ;
3350     }
3351     
3352     /* if left & right are the same then depending 
3353        of the operation do */
3354     if (isAstEqual(root->left,root->right)) {
3355         switch (root->opval.op) {
3356         case '>' :
3357         case '<' :
3358         case NE_OP :
3359             optExpr = newAst(EX_VALUE,constVal("0"));
3360             break;
3361         case GE_OP :
3362         case LE_OP :
3363         case EQ_OP :
3364             optExpr = newAst(EX_VALUE,constVal("1"));
3365             break;
3366         }
3367
3368         return decorateType(optExpr);
3369     }
3370
3371     vleft = (root->left->type == EX_VALUE ?
3372              root->left->opval.val : NULL );
3373     
3374     vright = (root->right->type == EX_VALUE ?
3375               root->right->opval.val : NULL);
3376     
3377     /* if left is a BITVAR in BITSPACE */
3378     /* and right is a LITERAL then opt-*/
3379     /* imize else do nothing               */
3380     if (vleft && vright                   &&
3381         IS_BITVAR(vleft->etype)           && 
3382         IN_BITSPACE(SPEC_OCLS(vleft->etype))  &&
3383         IS_LITERAL(vright->etype)) {
3384         
3385         /* if right side > 1 then comparison may never succeed */
3386         if ( (litValue = (int) floatFromVal(vright)) > 1 ) {
3387             werror(W_BAD_COMPARE);
3388             goto noOptimize ;
3389         }
3390         
3391         if ( litValue ) {
3392             switch (root->opval.op) {
3393             case '>' :  /* bit value greater than 1 cannot be */
3394                 werror(W_BAD_COMPARE);
3395                 goto noOptimize ;
3396                 break;
3397                 
3398             case '<' : /* bit value < 1 means 0 */
3399             case NE_OP :
3400                 optExpr = newNode('!',newAst(EX_VALUE,vleft),NULL);
3401                 break;
3402                 
3403             case LE_OP : /* bit value <= 1 means no check */
3404                 optExpr = newAst(EX_VALUE,vright);              
3405                 break;
3406                 
3407             case GE_OP : /* bit value >= 1 means only check for = */
3408             case EQ_OP :
3409                 optExpr = newAst(EX_VALUE,vleft);               
3410                 break;
3411             }
3412         } else { /* literal is zero */
3413             switch (root->opval.op) {
3414             case '<' :  /* bit value < 0 cannot be */
3415                 werror(W_BAD_COMPARE);
3416                 goto noOptimize ;
3417                 break;
3418                 
3419             case '>' : /* bit value > 0 means 1 */
3420             case NE_OP :
3421                 optExpr = newAst(EX_VALUE,vleft);            
3422                 break;
3423                 
3424             case LE_OP : /* bit value <= 0 means no check */
3425             case GE_OP : /* bit value >= 0 means no check */
3426                 werror(W_BAD_COMPARE);
3427                 goto noOptimize ;
3428                 break;
3429                 
3430             case EQ_OP : /* bit == 0 means ! of bit */
3431                 optExpr = newNode('!',newAst(EX_VALUE,vleft),NULL);           
3432                 break;
3433             }
3434         }                      
3435         return decorateType(resolveSymbols(optExpr)); 
3436     }   /* end-of-if of BITVAR */
3437     
3438     noOptimize :
3439         return root;
3440 }
3441 /*-----------------------------------------------------------------*/
3442 /* addSymToBlock : adds the symbol to the first block we find      */
3443 /*-----------------------------------------------------------------*/
3444 void addSymToBlock (symbol *sym, ast *tree)
3445 {
3446     /* reached end of tree or a leaf */
3447     if (!tree || IS_AST_LINK(tree) || IS_AST_VALUE(tree))
3448         return ;
3449
3450     /* found a block */
3451     if (IS_AST_OP(tree) &&
3452         tree->opval.op == BLOCK ) {
3453         
3454         symbol *lsym = copySymbol(sym);
3455         
3456         lsym->next = AST_VALUES(tree,sym);
3457         AST_VALUES(tree,sym) = lsym ;
3458         return ;
3459     }
3460     
3461     addSymToBlock(sym,tree->left);
3462     addSymToBlock(sym,tree->right);
3463 }
3464
3465 /*-----------------------------------------------------------------*/
3466 /* processRegParms - do processing for register parameters         */
3467 /*-----------------------------------------------------------------*/
3468 static void processRegParms (value *args, ast *body)
3469 {
3470     while (args) {
3471         if (IS_REGPARM(args->etype))
3472             addSymToBlock(args->sym,body);
3473         args = args->next;
3474     }
3475 }
3476
3477 /*-----------------------------------------------------------------*/
3478 /* resetParmKey - resets the operandkeys for the symbols           */
3479 /*-----------------------------------------------------------------*/
3480 DEFSETFUNC(resetParmKey)
3481 {
3482     symbol *sym = item;
3483
3484     sym->key = 0 ;
3485     sym->defs = NULL ;
3486     sym->uses = NULL ;
3487     sym->remat= 0;
3488     return 1;
3489 }
3490
3491 /*-----------------------------------------------------------------*/
3492 /* createFunction - This is the key node that calls the iCode for  */
3493 /*                  generating the code for a function. Note code  */
3494 /*                  is generated function by function, later when  */
3495 /*                  add inter-procedural analysis this will change */
3496 /*-----------------------------------------------------------------*/
3497 ast  *createFunction   (symbol  *name,   ast  *body )
3498 {
3499     ast  *ex ;
3500     symbol *csym;
3501     int stack = 0 ;
3502     link *fetype;       
3503     iCode *piCode = NULL;
3504     
3505     /* if check function return 0 then some problem */
3506     if (checkFunction (name) == 0)
3507         return NULL;
3508     
3509     /* create a dummy block if none exists */
3510     if (!body)
3511         body = newNode(BLOCK,NULL,NULL);
3512
3513     noLineno++ ;
3514    
3515     /* check if the function name already in the symbol table */
3516     if ((csym = findSym (SymbolTab,NULL,name->name))) {
3517         name = csym ;     
3518         /* special case for compiler defined functions
3519            we need to add the name to the publics list : this
3520            actually means we are now compiling the compiler
3521            support routine */
3522         if (name->cdef)
3523             addSet(&publics,name);
3524     }
3525     else {
3526         addSymChain(name);
3527         allocVariables(name);
3528     }
3529     name->lastLine = yylineno;
3530     currFunc = name ;
3531     processFuncArgs(currFunc,0);
3532     
3533     /* set the stack pointer */
3534     /* PENDING: check this for the mcs51 */
3535     stackPtr = -port->stack.direction * port->stack.call_overhead;
3536     if (IS_ISR(name->etype))
3537         stackPtr -= port->stack.direction * port->stack.isr_overhead;
3538     if (IS_RENT(name->etype) || options.stackAuto)
3539         stackPtr -= port->stack.direction * port->stack.reent_overhead;
3540
3541     xstackPtr = -port->stack.direction * port->stack.call_overhead;
3542     
3543     fetype = getSpec(name->type); /* get the specifier for the function */
3544     /* if this is a reentrant function then */
3545     if (IS_RENT(fetype))
3546         reentrant++ ;
3547         
3548     allocParms (name->args);           /* allocate the parameters */
3549
3550     /* do processing for parameters that are passed in registers */
3551     processRegParms (name->args,body); 
3552
3553    /* set the stack pointer */
3554     stackPtr = 0;
3555     xstackPtr= -1;
3556     
3557     /* allocate & autoinit the block variables */
3558     processBlockVars (body, &stack,ALLOCATE); 
3559     
3560     /* save the stack information */
3561     if (options.useXstack)
3562         name->xstack = SPEC_STAK(fetype) = stack;
3563     else
3564         name->stack = SPEC_STAK(fetype) = stack;
3565     
3566     /* name needs to be mangled */
3567     sprintf (name->rname,"_%s",name->name);
3568     
3569     body = resolveSymbols(body); /* resolve the symbols */
3570     body = decorateType (body);  /* propagateType & do semantic checks */
3571     
3572     ex = newAst (EX_VALUE, symbolVal(name));    /* create name       */
3573     ex = newNode (FUNCTION,ex,body);
3574     ex->values.args = name->args ;
3575     
3576     if (fatalError) {
3577         werror(E_FUNC_NO_CODE,name->name);
3578         goto skipall ;
3579     }
3580         
3581     /* create the node & generate intermediate code */  
3582     codeOutFile = code->oFile;
3583     piCode = iCodeFromAst(ex);
3584
3585      if (fatalError) {
3586          werror(E_FUNC_NO_CODE,name->name);
3587          goto skipall ;
3588      }
3589      
3590      eBBlockFromiCode(piCode);
3591                     
3592     /* if there are any statics then do them */
3593     if (staticAutos) {
3594         codeOutFile = statsg->oFile;
3595         eBBlockFromiCode (iCodeFromAst (decorateType(resolveSymbols(staticAutos))));
3596         staticAutos = NULL;
3597     }
3598     
3599  skipall:
3600     
3601     /* dealloc the block variables */
3602     processBlockVars(body, &stack,DEALLOCATE);
3603     /* deallocate paramaters */
3604     deallocParms(name->args);
3605     
3606     if (IS_RENT(fetype))
3607         reentrant-- ;
3608     
3609     /* we are done freeup memory & cleanup */
3610     noLineno-- ;
3611     labelKey = 1 ;
3612     name->key = 0;
3613     name->fbody = 1;
3614     addSet(&operKeyReset,name);
3615     applyToSet(operKeyReset,resetParmKey);
3616        
3617     if (options.debug)
3618         cdbStructBlock(1,cdbFile);
3619
3620     cleanUpLevel(LabelTab,0);
3621     cleanUpBlock(StructTab,1);
3622     cleanUpBlock(TypedefTab,1);
3623
3624     xstack->syms = NULL;
3625     istack->syms = NULL;
3626     return NULL ;
3627 }
3628
3629