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