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