Clean up Borland C++ makefiles and add (lousy) documentation
[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         } else {
1230             if (astHasSymbol(pbody->left,sym) ||
1231                 astHasSymbol(pbody->right,sym))
1232                 return FALSE;
1233         }
1234
1235         
1236         /*------------------------------------------------------------------*/
1237     case  '|':
1238     case  '^':
1239     case  '/':
1240     case  '%':
1241     case LEFT_OP:
1242     case RIGHT_OP:
1243         
1244         if (IS_AST_SYM_VALUE(pbody->left) &&
1245             isSymbolEqual(AST_SYMBOL(pbody->left),sym))
1246             return FALSE ;
1247
1248         if (IS_AST_SYM_VALUE(pbody->right) &&
1249             isSymbolEqual(AST_SYMBOL(pbody->right),sym))
1250             return FALSE ;
1251         
1252         return isConformingBody(pbody->left,sym,body) &&
1253             isConformingBody(pbody->right,sym,body);
1254         
1255     case '~' :
1256     case '!' :
1257     case RRC:
1258     case RLC:
1259     case GETHBIT:
1260         if (IS_AST_SYM_VALUE(pbody->left) &&
1261             isSymbolEqual(AST_SYMBOL(pbody->left),sym))
1262             return FALSE;
1263         return isConformingBody (pbody->left,sym,body);
1264         
1265         /*------------------------------------------------------------------*/
1266
1267     case AND_OP:
1268     case OR_OP:
1269     case '>' :
1270     case '<' :
1271     case LE_OP:
1272     case GE_OP:
1273     case EQ_OP:
1274     case NE_OP:
1275     case '?' :
1276     case ':' :
1277     case SIZEOF:  /* evaluate wihout code generation */
1278
1279         return isConformingBody(pbody->left,sym,body) &&
1280             isConformingBody(pbody->right,sym,body);    
1281
1282         /*------------------------------------------------------------------*/
1283     case '=' :
1284
1285         /* if left has a pointer & right has loop
1286            control variable then we cannot */
1287         if (astHasPointer(pbody->left) &&
1288             astHasSymbol (pbody->right,sym))
1289             return FALSE ;
1290         if (astHasVolatile(pbody->left))
1291             return FALSE ;
1292
1293         if (IS_AST_SYM_VALUE(pbody->left) &&
1294             isSymbolEqual(AST_SYMBOL(pbody->left),sym))
1295             return FALSE ;
1296         
1297         if (astHasVolatile(pbody->left))
1298             return FALSE;
1299
1300         return isConformingBody(pbody->left,sym,body) &&
1301             isConformingBody(pbody->right,sym,body);    
1302
1303     case MUL_ASSIGN:
1304     case DIV_ASSIGN:
1305     case AND_ASSIGN:
1306     case OR_ASSIGN:
1307     case XOR_ASSIGN:
1308     case RIGHT_ASSIGN:
1309     case LEFT_ASSIGN:
1310     case SUB_ASSIGN:
1311     case ADD_ASSIGN:
1312             assert("Parser should not have generated this\n");
1313         
1314         /*------------------------------------------------------------------*/
1315         /*----------------------------*/
1316         /*      comma operator        */
1317         /*----------------------------*/        
1318     case ',' :
1319         return isConformingBody(pbody->left,sym,body) &&
1320             isConformingBody(pbody->right,sym,body);    
1321         
1322         /*------------------------------------------------------------------*/
1323         /*----------------------------*/
1324         /*       function call        */
1325         /*----------------------------*/        
1326     case CALL:
1327         return FALSE;
1328
1329         /*------------------------------------------------------------------*/
1330         /*----------------------------*/
1331         /*     return statement       */
1332         /*----------------------------*/        
1333     case RETURN:
1334         return FALSE ;
1335
1336     case GOTO:
1337         if (isLabelInAst (AST_SYMBOL(pbody->left),body))
1338             return TRUE ;
1339         else
1340             return FALSE;
1341     case SWITCH:
1342         if (astHasSymbol(pbody->left,sym))
1343             return FALSE ;
1344
1345     default:
1346         break;
1347     }
1348
1349     return isConformingBody(pbody->left,sym,body) &&
1350         isConformingBody(pbody->right,sym,body);        
1351         
1352     
1353
1354 }
1355
1356 /*-----------------------------------------------------------------*/
1357 /* isLoopReversible - takes a for loop as input && returns true    */
1358 /* if the for loop is reversible. If yes will set the value of     */
1359 /* the loop control var & init value & termination value           */
1360 /*-----------------------------------------------------------------*/
1361 bool isLoopReversible (ast *loop, symbol **loopCntrl, 
1362                        ast **init, ast **end )
1363 {
1364     /* if option says don't do it then don't */
1365     if (optimize.noLoopReverse)
1366         return 0;
1367     /* there are several tests to determine this */
1368        
1369     /* for loop has to be of the form 
1370        for ( <sym> = <const1> ; 
1371              [<sym> < <const2>]  ;
1372              [<sym>++] | [<sym> += 1] | [<sym> = <sym> + 1] )
1373              forBody */
1374     if (! isLoopCountable (AST_FOR(loop,initExpr),
1375                            AST_FOR(loop,condExpr),
1376                            AST_FOR(loop,loopExpr),
1377                            loopCntrl,init,end))
1378         return 0;
1379
1380     /* now do some serious checking on the body of the loop
1381      */
1382     
1383     return isConformingBody(loop->left,*loopCntrl,loop->left);
1384
1385 }
1386
1387 /*-----------------------------------------------------------------*/
1388 /* replLoopSym - replace the loop sym by loop sym -1               */
1389 /*-----------------------------------------------------------------*/
1390 static void replLoopSym ( ast *body, symbol *sym)
1391 {
1392     /* reached end */
1393     if (!body || IS_AST_LINK(body))
1394         return ;
1395
1396     if (IS_AST_SYM_VALUE(body)) {
1397         
1398         if (isSymbolEqual(AST_SYMBOL(body),sym)) {
1399             
1400             body->type = EX_OP;
1401             body->opval.op = '-';
1402             body->left = newAst(EX_VALUE,symbolVal(sym));
1403             body->right= newAst(EX_VALUE,constVal("1"));
1404
1405         }
1406             
1407         return;
1408         
1409     }
1410         
1411     replLoopSym(body->left,sym);
1412     replLoopSym(body->right,sym);
1413         
1414 }
1415
1416 /*-----------------------------------------------------------------*/
1417 /* reverseLoop - do the actual loop reversal                       */
1418 /*-----------------------------------------------------------------*/
1419 ast *reverseLoop (ast *loop, symbol *sym, ast *init, ast *end)
1420 {    
1421     ast *rloop ;  
1422         
1423     /* create the following tree 
1424                 <sym> = loopCount ;
1425          for_continue:
1426                 forbody
1427                 <sym> -= 1;
1428                 if (sym) goto for_continue ; 
1429                 <sym> = end - 1; */
1430     
1431     /* put it together piece by piece */
1432     rloop = newNode (NULLOP,
1433                      createIf(newAst(EX_VALUE,symbolVal(sym)),
1434                               newNode(GOTO,
1435                                       newAst(EX_VALUE,
1436                                              symbolVal(AST_FOR(loop,continueLabel))),
1437                                       NULL),NULL),
1438                      newNode('=',
1439                              newAst(EX_VALUE,symbolVal(sym)),
1440                              newNode('-', end,
1441                                      newAst(EX_VALUE,
1442                                             constVal("1")))));
1443
1444     replLoopSym(loop->left, sym);
1445
1446     rloop = newNode(NULLOP,
1447                     newNode('=',
1448                             newAst(EX_VALUE,symbolVal(sym)),
1449                             newNode('-',end,init)),
1450                     createLabel(AST_FOR(loop,continueLabel),
1451                                 newNode(NULLOP,
1452                                         loop->left,
1453                                         newNode(NULLOP,
1454                                                 newNode(SUB_ASSIGN,
1455                                                         newAst(EX_VALUE,symbolVal(sym)),
1456                                                         newAst(EX_VALUE,constVal("1"))),
1457                                                 rloop ))));
1458     
1459     return decorateType(rloop);
1460
1461 }
1462
1463 /*-----------------------------------------------------------------*/
1464 /* decorateType - compute type for this tree also does type cheking*/
1465 /*          this is done bottom up, since type have to flow upwards*/
1466 /*          it also does constant folding, and paramater checking  */
1467 /*-----------------------------------------------------------------*/
1468 ast *decorateType (ast *tree)
1469 {         
1470     int parmNumber ;
1471     link *p;
1472     
1473     if ( ! tree )
1474         return tree ;
1475     
1476     /* if already has type then do nothing */
1477     if ( tree->decorated )
1478         return tree ;
1479     
1480     tree->decorated = 1;
1481     
1482     /* print the line          */
1483     /* if not block & function */
1484     if ( tree->type == EX_OP && 
1485          ( tree->opval.op != FUNCTION  &&
1486            tree->opval.op != BLOCK     &&
1487            tree->opval.op != NULLOP    )) {
1488         filename = tree->filename ;
1489         lineno = tree->lineno ;
1490     }
1491
1492     /* if any child is an error | this one is an error do nothing */
1493     if ( tree->isError ||
1494          ( tree->left && tree->left->isError) ||
1495          ( tree->right && tree->right->isError ))
1496         return tree ;
1497
1498     /*------------------------------------------------------------------*/
1499     /*----------------------------*/
1500     /*   leaf has been reached    */
1501     /*----------------------------*/        
1502     /* if this is of type value */
1503     /* just get the type        */
1504     if ( tree->type == EX_VALUE ) {
1505         
1506         if ( IS_LITERAL(tree->opval.val->etype) ) {
1507             
1508             /* if this is a character array then declare it */
1509             if (IS_ARRAY(tree->opval.val->type))
1510                 tree->opval.val = stringToSymbol(tree->opval.val);
1511             
1512             /* otherwise just copy the type information */
1513             COPYTYPE(TTYPE(tree),TETYPE(tree),tree->opval.val->type);
1514             return tree ;
1515         }
1516         
1517         if ( tree->opval.val->sym ) {
1518             /* if the undefined flag is set then give error message */
1519                 if (tree->opval.val->sym->undefined ) {
1520                   werror(E_ID_UNDEF,tree->opval.val->sym->name) ;
1521                   /* assume int */
1522                   TTYPE(tree) = TETYPE(tree) =
1523                     tree->opval.val->type = tree->opval.val->sym->type = 
1524                     tree->opval.val->etype = tree->opval.val->sym->etype = 
1525                     copyLinkChain(INTTYPE);
1526                 }
1527                 else {
1528                   
1529                   /* if impilicit i.e. struct/union member then no type */
1530                   if (tree->opval.val->sym->implicit )
1531                     TTYPE(tree) = TETYPE(tree) = NULL ;
1532                   
1533                   else { 
1534                     
1535                                 /* else copy the type */
1536                     COPYTYPE(TTYPE(tree),TETYPE(tree),tree->opval.val->type); 
1537                     
1538                                 /* and mark it as referenced */
1539                     tree->opval.val->sym->isref = 1;
1540                                 /* if this is of type function or function pointer */
1541                     if (funcInChain(tree->opval.val->type)) {
1542                       tree->hasVargs = tree->opval.val->sym->hasVargs;
1543                       tree->args = copyValueChain(tree->opval.val->sym->args) ;
1544                       
1545                     }
1546                   }
1547                 }
1548         }
1549         
1550         return tree ;
1551     }
1552     
1553     /* if type link for the case of cast */
1554     if ( tree->type == EX_LINK ) {
1555         COPYTYPE(TTYPE(tree),TETYPE(tree),tree->opval.lnk);
1556         return tree ;
1557     } 
1558     
1559     {
1560         ast *dtl, *dtr;
1561         
1562         dtl = decorateType (tree->left);
1563         dtr = decorateType (tree->right);  
1564
1565         /* this is to take care of situations
1566            when the tree gets rewritten */
1567         if (dtl != tree->left)
1568             tree->left = dtl;
1569         if (dtr != tree->right)
1570             tree->right = dtr;
1571     }
1572     
1573     /* depending on type of operator do */
1574     
1575     switch   (tree->opval.op) {
1576         /*------------------------------------------------------------------*/
1577         /*----------------------------*/
1578         /*        array node          */
1579         /*----------------------------*/
1580     case  '['   :  
1581         
1582         /* determine which is the array & which the index */
1583         if ((IS_ARRAY(RTYPE(tree)) || IS_PTR(RTYPE(tree))) && IS_INTEGRAL(LTYPE(tree))) {
1584             
1585             ast *tempTree = tree->left ;
1586             tree->left = tree->right ;
1587             tree->right= tempTree ;
1588         }
1589
1590         /* first check if this is a array or a pointer */
1591         if ( (!IS_ARRAY(LTYPE(tree)))  && (!IS_PTR(LTYPE(tree)))) {
1592             werror(E_NEED_ARRAY_PTR,"[]");
1593             goto errorTreeReturn ;
1594         }       
1595         
1596         /* check if the type of the idx */
1597         if (!IS_INTEGRAL(RTYPE(tree))) {
1598             werror(E_IDX_NOT_INT);
1599             goto errorTreeReturn ;
1600         }
1601         
1602         /* if the left is an rvalue then error */
1603         if (LRVAL(tree)) {
1604             werror(E_LVALUE_REQUIRED,"array access");
1605             goto errorTreeReturn ;
1606         }
1607         RRVAL(tree) = 1;
1608         COPYTYPE(TTYPE(tree),TETYPE(tree),LTYPE(tree)->next);
1609         return tree;
1610         
1611         /*------------------------------------------------------------------*/
1612         /*----------------------------*/
1613         /*      struct/union          */
1614         /*----------------------------*/   
1615     case  '.'   :  
1616         /* if this is not a structure */
1617         if (!IS_STRUCT(LTYPE(tree))) {
1618             werror(E_STRUCT_UNION,".");
1619             goto errorTreeReturn ;
1620         }
1621         TTYPE(tree) = structElemType (LTYPE(tree), 
1622                                       (tree->right->type == EX_VALUE ?
1623                                        tree->right->opval.val : NULL ),&tree->args);
1624         TETYPE(tree) = getSpec(TTYPE(tree));
1625         return tree ;
1626         
1627         /*------------------------------------------------------------------*/
1628         /*----------------------------*/
1629         /*    struct/union pointer    */
1630         /*----------------------------*/
1631     case  PTR_OP:  
1632         /* if not pointer to a structure */
1633         if (!IS_PTR(LTYPE(tree)))  {
1634             werror(E_PTR_REQD);
1635             goto errorTreeReturn ;
1636         }
1637         
1638         if (!IS_STRUCT(LTYPE(tree)->next))  {
1639             werror(E_STRUCT_UNION,"->");
1640             goto errorTreeReturn ;
1641         }
1642         
1643         TTYPE(tree) = structElemType (LTYPE(tree)->next, 
1644                                       (tree->right->type == EX_VALUE ?
1645                                        tree->right->opval.val : NULL ),&tree->args);
1646         TETYPE(tree) = getSpec(TTYPE(tree));
1647         return tree ;
1648         
1649         /*------------------------------------------------------------------*/
1650         /*----------------------------*/
1651         /*  ++/-- operation           */
1652         /*----------------------------*/
1653     case  INC_OP:  /* incerement operator unary so left only */
1654     case  DEC_OP:
1655         {
1656             link *ltc = (tree->right ? RTYPE(tree) : LTYPE(tree) );
1657             COPYTYPE(TTYPE(tree),TETYPE(tree),ltc);
1658             if (!tree->initMode && IS_CONSTANT(TETYPE(tree)))
1659                 werror(E_CODE_WRITE,"++/--");
1660             
1661             if (tree->right)
1662                 RLVAL(tree) = 1;
1663             else
1664                 LLVAL(tree) = 1;
1665             return tree ;
1666         }
1667         
1668         /*------------------------------------------------------------------*/
1669         /*----------------------------*/
1670         /*  bitwise and               */
1671         /*----------------------------*/
1672     case  '&':     /* can be unary   */
1673         /* if right is NULL then unary operation  */
1674         if ( tree->right ) /* not an unary operation */ {
1675             
1676             if (!IS_INTEGRAL(LTYPE(tree)) || !IS_INTEGRAL(RTYPE(tree))) {
1677                 werror(E_BITWISE_OP);
1678                 werror(E_CONTINUE,"left & right types are ");
1679                 printTypeChain(LTYPE(tree),stderr);
1680                 fprintf(stderr,",");
1681                 printTypeChain(RTYPE(tree),stderr);
1682                 fprintf(stderr,"\n");
1683                 goto errorTreeReturn ;
1684             }
1685             
1686             /* if they are both literal */
1687             if (IS_LITERAL(RTYPE(tree)) && IS_LITERAL(LTYPE(tree))) {
1688                 tree->type = EX_VALUE ;
1689                 tree->opval.val = valBitwise (valFromType(LETYPE(tree)),
1690                                               valFromType(RETYPE(tree)),'&');
1691                                        
1692                 tree->right = tree->left = NULL;
1693                 TETYPE(tree) = tree->opval.val->etype ;
1694                 TTYPE(tree) =  tree->opval.val->type;
1695                 return tree ;
1696             }
1697             
1698             /* see if this is a GETHBIT operation if yes
1699                then return that */
1700             {
1701                 ast *otree = optimizeGetHbit(tree);
1702                 
1703                 if (otree != tree)
1704                     return decorateType(otree);
1705             }
1706             
1707             /* if right or left is literal then result of that type*/
1708             if (IS_LITERAL(RTYPE(tree))) {
1709                 
1710                 TTYPE(tree) = copyLinkChain(RTYPE(tree));
1711                 TETYPE(tree) = getSpec(TTYPE(tree));
1712                 SPEC_SCLS(TETYPE(tree)) = S_AUTO;
1713             }
1714             else {
1715                 if (IS_LITERAL(LTYPE(tree))) {              
1716                     TTYPE(tree) = copyLinkChain(LTYPE(tree));
1717                     TETYPE(tree) = getSpec(TTYPE(tree));
1718                     SPEC_SCLS(TETYPE(tree)) = S_AUTO;
1719                     
1720                 }
1721                 else {
1722                     TTYPE(tree) = 
1723                         computeType (LTYPE(tree), RTYPE(tree));
1724                     TETYPE(tree) = getSpec(TTYPE(tree));
1725                 }
1726             }
1727             LRVAL(tree) = RRVAL(tree) = 1;
1728             return tree ;
1729         } 
1730         
1731         /*------------------------------------------------------------------*/
1732         /*----------------------------*/
1733         /*  address of                */
1734         /*----------------------------*/    
1735         p = newLink();
1736         p->class = DECLARATOR;
1737         /* if bit field then error */
1738         if (IS_BITVAR(tree->left->etype)) {
1739             werror (E_ILLEGAL_ADDR,"addrress of bit variable");
1740             goto errorTreeReturn ;
1741         }
1742         
1743         if (SPEC_SCLS(tree->left->etype)== S_REGISTER ) {
1744             werror (E_ILLEGAL_ADDR,"address of register variable");
1745             goto errorTreeReturn;
1746         }
1747         
1748         if (IS_FUNC(LTYPE(tree))) {
1749             werror(E_ILLEGAL_ADDR,"address of function");
1750             goto errorTreeReturn ;
1751         }
1752         
1753         if (LRVAL(tree)) {
1754             werror(E_LVALUE_REQUIRED,"address of");
1755             goto errorTreeReturn ;      
1756         }
1757         if (SPEC_SCLS(tree->left->etype) == S_CODE) {
1758             DCL_TYPE(p) = CPOINTER ;
1759             DCL_PTR_CONST(p) = 1;
1760         }
1761         else
1762             if (SPEC_SCLS(tree->left->etype) == S_XDATA)
1763                 DCL_TYPE(p) = FPOINTER;
1764             else
1765                 if (SPEC_SCLS(tree->left->etype) == S_XSTACK )
1766                     DCL_TYPE(p) = PPOINTER ;
1767                 else
1768                     if (SPEC_SCLS(tree->left->etype) == S_IDATA)
1769                         DCL_TYPE(p) = IPOINTER ;
1770                     else
1771                         if (SPEC_SCLS(tree->left->etype) == S_EEPROM)
1772                             DCL_TYPE(p) = EEPPOINTER ;
1773                         else
1774                             DCL_TYPE(p) = POINTER ;
1775
1776         if (IS_AST_SYM_VALUE(tree->left)) {
1777             AST_SYMBOL(tree->left)->addrtaken = 1;
1778             AST_SYMBOL(tree->left)->allocreq = 1;
1779         }
1780
1781         p->next = LTYPE(tree);
1782         TTYPE(tree) = p;
1783         TETYPE(tree) = getSpec(TTYPE(tree));
1784         DCL_PTR_CONST(p) = SPEC_CONST(TETYPE(tree));
1785         DCL_PTR_VOLATILE(p) = SPEC_VOLATILE(TETYPE(tree));
1786         LLVAL(tree) = 1;
1787         TLVAL(tree) = 1;
1788         return tree ;
1789         
1790         /*------------------------------------------------------------------*/
1791         /*----------------------------*/
1792         /*  bitwise or                */
1793         /*----------------------------*/
1794     case  '|':
1795         /* if the rewrite succeeds then don't go any furthur */
1796         {
1797             ast *wtree = optimizeRRCRLC ( tree );
1798             if (wtree != tree) 
1799                 return decorateType(wtree) ;
1800         }
1801         /*------------------------------------------------------------------*/
1802         /*----------------------------*/
1803         /*  bitwise xor               */
1804         /*----------------------------*/
1805     case  '^':
1806         if (!IS_INTEGRAL(LTYPE(tree)) || !IS_INTEGRAL(RTYPE(tree))) {
1807             werror(E_BITWISE_OP);
1808             werror(E_CONTINUE,"left & right types are ");
1809             printTypeChain(LTYPE(tree),stderr);
1810             fprintf(stderr,",");
1811             printTypeChain(RTYPE(tree),stderr);
1812             fprintf(stderr,"\n");
1813             goto errorTreeReturn ;
1814         }
1815         
1816         /* if they are both literal then */
1817         /* rewrite the tree */
1818         if (IS_LITERAL(RTYPE(tree)) && IS_LITERAL(LTYPE(tree))) {
1819             tree->type = EX_VALUE ;
1820             tree->opval.val = valBitwise (valFromType(LETYPE(tree)),
1821                                           valFromType(RETYPE(tree)),
1822                                           tree->opval.op);                 
1823             tree->right = tree->left = NULL;
1824             TETYPE(tree) = tree->opval.val->etype;
1825             TTYPE(tree) = tree->opval.val->type;
1826             return tree ;
1827         }
1828         LRVAL(tree) = RRVAL(tree) = 1;
1829         TETYPE(tree) = getSpec (TTYPE(tree) = 
1830                                 computeType(LTYPE(tree),
1831                                             RTYPE(tree)));
1832         
1833         /*------------------------------------------------------------------*/
1834         /*----------------------------*/
1835         /*  division                  */
1836         /*----------------------------*/
1837     case  '/':
1838         if (!IS_ARITHMETIC(LTYPE(tree)) || !IS_ARITHMETIC(RTYPE(tree))) {
1839             werror(E_INVALID_OP,"divide");
1840             goto errorTreeReturn ;
1841         }
1842         /* if they are both literal then */
1843         /* rewrite the tree */
1844         if (IS_LITERAL(RTYPE(tree)) && IS_LITERAL(LTYPE(tree))) {
1845             tree->type = EX_VALUE ;
1846             tree->opval.val = valDiv (valFromType(LETYPE(tree)),
1847                                       valFromType(RETYPE(tree)));
1848             tree->right = tree->left = NULL;
1849             TETYPE(tree) = getSpec(TTYPE(tree) = 
1850                                    tree->opval.val->type);
1851             return tree ;
1852         }
1853         LRVAL(tree) = RRVAL(tree) = 1;
1854         TETYPE(tree) = getSpec (TTYPE(tree) = 
1855                                 computeType(LTYPE(tree),
1856                                             RTYPE(tree)));
1857         return tree;
1858         
1859         /*------------------------------------------------------------------*/
1860         /*----------------------------*/
1861         /*            modulus         */
1862         /*----------------------------*/
1863     case  '%':
1864         if (!IS_INTEGRAL(LTYPE(tree)) || !IS_INTEGRAL(RTYPE(tree))) {
1865             werror(E_BITWISE_OP);
1866             werror(E_CONTINUE,"left & right types are ");
1867             printTypeChain(LTYPE(tree),stderr);
1868             fprintf(stderr,",");
1869             printTypeChain(RTYPE(tree),stderr);
1870             fprintf(stderr,"\n");
1871             goto errorTreeReturn ;
1872         }
1873         /* if they are both literal then */
1874         /* rewrite the tree */
1875         if (IS_LITERAL(RTYPE(tree)) && IS_LITERAL(LTYPE(tree))) {
1876             tree->type = EX_VALUE ;
1877             tree->opval.val = valMod (valFromType(LETYPE(tree)),
1878                                       valFromType(RETYPE(tree)));                 
1879             tree->right = tree->left = NULL;
1880             TETYPE(tree) = getSpec(TTYPE(tree) = 
1881                                    tree->opval.val->type);
1882             return tree ;
1883         }
1884         LRVAL(tree) = RRVAL(tree) = 1;
1885         TETYPE(tree) = getSpec (TTYPE(tree) = 
1886                                 computeType(LTYPE(tree),
1887                                             RTYPE(tree)));
1888         return tree;
1889         
1890         /*------------------------------------------------------------------*/
1891         /*----------------------------*/
1892         /*  address dereference       */
1893         /*----------------------------*/
1894     case  '*':     /* can be unary  : if right is null then unary operation */
1895         if ( ! tree->right ) {
1896             if (!IS_PTR(LTYPE(tree)) && !IS_ARRAY(LTYPE(tree))) {
1897                 werror(E_PTR_REQD);
1898                 goto errorTreeReturn ;
1899             }
1900             
1901             if (LRVAL(tree)) {
1902                 werror(E_LVALUE_REQUIRED,"pointer deref");
1903                 goto errorTreeReturn ;  
1904             }
1905             TTYPE(tree) = copyLinkChain ((IS_PTR(LTYPE(tree)) || IS_ARRAY(LTYPE(tree))) ? 
1906                                          LTYPE(tree)->next : NULL );
1907             TETYPE(tree) = getSpec(TTYPE(tree));
1908             tree->args = tree->left->args ;
1909             tree->hasVargs = tree->left->hasVargs ;
1910             SPEC_CONST(TETYPE(tree)) = DCL_PTR_CONST(LTYPE(tree));
1911             return tree ;
1912         }
1913         
1914         /*------------------------------------------------------------------*/
1915         /*----------------------------*/
1916         /*      multiplication        */
1917         /*----------------------------*/
1918         if (!IS_ARITHMETIC(LTYPE(tree)) || !IS_ARITHMETIC(RTYPE(tree))) {
1919             werror(E_INVALID_OP,"multiplication");
1920             goto errorTreeReturn ;
1921         }
1922         
1923         /* if they are both literal then */
1924         /* rewrite the tree */
1925         if (IS_LITERAL(RTYPE(tree)) && IS_LITERAL(LTYPE(tree))) {
1926             tree->type = EX_VALUE ;
1927             tree->opval.val = valMult (valFromType(LETYPE(tree)),
1928                                        valFromType(RETYPE(tree)));                 
1929             tree->right = tree->left = NULL;
1930             TETYPE(tree) = getSpec(TTYPE(tree) = 
1931                                    tree->opval.val->type);
1932             return tree ;
1933         }
1934
1935         /* if left is a literal exchange left & right */
1936         if (IS_LITERAL(LTYPE(tree))) {
1937             ast *tTree = tree->left ;
1938             tree->left = tree->right ;
1939             tree->right= tTree ;
1940         }
1941                 
1942         LRVAL(tree) = RRVAL(tree) = 1;
1943         TETYPE(tree) = getSpec (TTYPE(tree) = 
1944                                 computeType(LTYPE(tree),
1945                                             RTYPE(tree)));                        
1946         return tree ;
1947         
1948         /*------------------------------------------------------------------*/
1949         /*----------------------------*/
1950         /*    unary '+' operator      */
1951         /*----------------------------*/
1952     case '+' :  
1953         /* if unary plus */
1954         if ( ! tree->right ) {
1955             if (!IS_INTEGRAL(LTYPE(tree))) {
1956                 werror(E_UNARY_OP,'+');
1957                 goto errorTreeReturn ;
1958             }
1959             
1960             /* if left is a literal then do it */
1961             if (IS_LITERAL(LTYPE(tree))) {
1962                 tree->type = EX_VALUE ;
1963                 tree->opval.val = valFromType(LETYPE(tree));          
1964                 tree->left = NULL ;
1965                 TETYPE(tree) = TTYPE(tree) = tree->opval.val->type;
1966                 return tree ;
1967             }
1968             LRVAL(tree) = 1;
1969             COPYTYPE(TTYPE(tree),TETYPE(tree),LTYPE(tree)); 
1970             return tree ;
1971         }
1972         
1973         /*------------------------------------------------------------------*/
1974         /*----------------------------*/
1975         /*      addition              */
1976         /*----------------------------*/
1977         
1978         /* this is not a unary operation */
1979         /* if both pointers then problem */
1980         if ((IS_PTR(LTYPE(tree)) || IS_ARRAY(LTYPE(tree))) &&
1981             (IS_PTR(RTYPE(tree)) || IS_ARRAY(RTYPE(tree)))) {
1982             werror(E_PTR_PLUS_PTR);
1983             goto errorTreeReturn ;
1984         }       
1985
1986         if (!IS_ARITHMETIC(LTYPE(tree)) && 
1987             !IS_PTR(LTYPE(tree)) && !IS_ARRAY(LTYPE(tree))) {
1988             werror(E_PLUS_INVALID,"+");
1989             goto errorTreeReturn ;
1990         }
1991         
1992         if (!IS_ARITHMETIC(RTYPE(tree)) && 
1993             !IS_PTR(RTYPE(tree)) && !IS_ARRAY(RTYPE(tree))) {
1994             werror(E_PLUS_INVALID,"+");
1995             goto errorTreeReturn;
1996         }
1997         /* if they are both literal then */
1998         /* rewrite the tree */
1999         if (IS_LITERAL(RTYPE(tree)) && IS_LITERAL(LTYPE(tree))) {
2000             tree->type = EX_VALUE ;
2001             tree->opval.val = valPlus (valFromType(LETYPE(tree)),
2002                                        valFromType(RETYPE(tree))); 
2003             tree->right = tree->left = NULL;
2004             TETYPE(tree) = getSpec(TTYPE(tree) = 
2005                                    tree->opval.val->type);
2006             return tree ;
2007         }
2008         
2009         /* if the right is a pointer or left is a literal 
2010            xchange left & right */
2011         if (IS_ARRAY(RTYPE(tree)) || 
2012             IS_PTR(RTYPE(tree))   || 
2013             IS_LITERAL(LTYPE(tree))) {
2014             ast *tTree = tree->left ;
2015             tree->left = tree->right ;
2016             tree->right= tTree ;
2017         }
2018
2019         LRVAL(tree) = RRVAL(tree) = 1;  
2020         /* if the left is a pointer */
2021         if (IS_PTR(LTYPE(tree)))      
2022             TETYPE(tree) = getSpec(TTYPE(tree) =
2023                                    LTYPE(tree));
2024         else
2025             TETYPE(tree) = getSpec(TTYPE(tree) = 
2026                                    computeType(LTYPE(tree),
2027                                                RTYPE(tree)));
2028         return tree ;
2029         
2030         /*------------------------------------------------------------------*/
2031         /*----------------------------*/
2032         /*      unary '-'             */
2033         /*----------------------------*/
2034     case '-' :  /* can be unary   */
2035         /* if right is null then unary */
2036         if ( ! tree->right ) {
2037             
2038             if (!IS_ARITHMETIC(LTYPE(tree))) {
2039                 werror(E_UNARY_OP,tree->opval.op);
2040                 goto errorTreeReturn ;
2041             }
2042             
2043             /* if left is a literal then do it */
2044             if (IS_LITERAL(LTYPE(tree))) {
2045                 tree->type = EX_VALUE ;
2046                 tree->opval.val = valUnaryPM(valFromType(LETYPE(tree)));
2047                 tree->left = NULL ;
2048                 TETYPE(tree) = TTYPE(tree) = tree->opval.val->type;
2049                 return tree ;
2050             }
2051             LRVAL(tree) = 1;
2052             TTYPE(tree) =  LTYPE(tree); 
2053             return tree ;
2054         }
2055         
2056         /*------------------------------------------------------------------*/
2057         /*----------------------------*/
2058         /*    subtraction             */
2059         /*----------------------------*/
2060         
2061         if (!(IS_PTR(LTYPE(tree)) || 
2062               IS_ARRAY(LTYPE(tree)) || 
2063               IS_ARITHMETIC(LTYPE(tree)))) {
2064             werror(E_PLUS_INVALID,"-");
2065             goto errorTreeReturn ;
2066         }
2067         
2068         if (!(IS_PTR(RTYPE(tree)) || 
2069               IS_ARRAY(RTYPE(tree)) || 
2070               IS_ARITHMETIC(RTYPE(tree)))) {
2071             werror(E_PLUS_INVALID,"-");
2072             goto errorTreeReturn ;
2073         }
2074         
2075         if ( (IS_PTR(LTYPE(tree)) || IS_ARRAY(LTYPE(tree))) &&
2076             ! (IS_PTR(RTYPE(tree)) || IS_ARRAY(RTYPE(tree)) || 
2077                IS_INTEGRAL(RTYPE(tree)))   ) {
2078             werror(E_PLUS_INVALID,"-");
2079             goto errorTreeReturn ;
2080         }
2081
2082         /* if they are both literal then */
2083         /* rewrite the tree */
2084         if (IS_LITERAL(RTYPE(tree)) &&  IS_LITERAL(LTYPE(tree))) {
2085             tree->type = EX_VALUE ;
2086             tree->opval.val = valMinus (valFromType(LETYPE(tree)),
2087                                         valFromType(RETYPE(tree)));  
2088             tree->right = tree->left = NULL;
2089             TETYPE(tree) = getSpec(TTYPE(tree) = 
2090                                    tree->opval.val->type);
2091             return tree ;
2092         }
2093         
2094         /* if the left & right are equal then zero */
2095         if (isAstEqual(tree->left,tree->right)) {
2096             tree->type = EX_VALUE;
2097             tree->left = tree->right = NULL;
2098             tree->opval.val = constVal("0");
2099             TETYPE(tree) = TTYPE(tree) = tree->opval.val->type;
2100             return tree;
2101         }
2102
2103         /* if both of them are pointers or arrays then */
2104         /* the result is going to be an integer        */
2105         if (( IS_ARRAY(LTYPE(tree)) || IS_PTR(LTYPE(tree))) &&
2106             ( IS_ARRAY(RTYPE(tree)) || IS_PTR(RTYPE(tree)))) 
2107             TETYPE(tree) = TTYPE(tree) = newIntLink();
2108         else 
2109             /* if only the left is a pointer */
2110             /* then result is a pointer      */
2111             if (IS_PTR(LTYPE(tree)) || IS_ARRAY(LTYPE(tree))) 
2112                 TETYPE(tree) = getSpec(TTYPE(tree) =
2113                                        LTYPE(tree));
2114             else
2115                 TETYPE(tree) = getSpec (TTYPE(tree) = 
2116                                         computeType(LTYPE(tree),
2117                                                     RTYPE(tree))); 
2118         LRVAL(tree) = RRVAL(tree) = 1;
2119         return tree ;  
2120         
2121         /*------------------------------------------------------------------*/
2122         /*----------------------------*/
2123         /*    compliment              */
2124         /*----------------------------*/
2125     case '~' :
2126         /* can be only integral type */
2127         if (!IS_INTEGRAL(LTYPE(tree))) {
2128             werror(E_UNARY_OP,tree->opval.op);
2129             goto errorTreeReturn ;
2130         } 
2131         
2132         /* if left is a literal then do it */
2133         if (IS_LITERAL(LTYPE(tree))) {
2134             tree->type = EX_VALUE ;
2135             tree->opval.val = valComplement(valFromType(LETYPE(tree)));     
2136             tree->left = NULL ;
2137             TETYPE(tree) = TTYPE(tree) = tree->opval.val->type;
2138             return tree ;
2139         }
2140         LRVAL(tree) = 1;
2141         COPYTYPE(TTYPE(tree),TETYPE(tree),LTYPE(tree));
2142         return tree ;
2143         
2144         /*------------------------------------------------------------------*/
2145         /*----------------------------*/
2146         /*           not              */
2147         /*----------------------------*/
2148     case '!' :
2149         /* can be pointer */
2150         if (!IS_ARITHMETIC(LTYPE(tree)) && 
2151             !IS_PTR(LTYPE(tree))        && 
2152             !IS_ARRAY(LTYPE(tree))) {
2153             werror(E_UNARY_OP,tree->opval.op);
2154             goto errorTreeReturn ;
2155         }
2156         
2157         /* if left is a literal then do it */
2158         if (IS_LITERAL(LTYPE(tree))) {
2159             tree->type = EX_VALUE ;
2160             tree->opval.val = valNot(valFromType(LETYPE(tree)));           
2161             tree->left = NULL ;
2162             TETYPE(tree) = TTYPE(tree) = tree->opval.val->type;
2163             return tree ;
2164         }
2165         LRVAL(tree) = 1;
2166         TTYPE(tree) = TETYPE(tree) = newCharLink();
2167         return tree ;
2168         
2169         /*------------------------------------------------------------------*/
2170         /*----------------------------*/
2171         /*           shift            */
2172         /*----------------------------*/
2173     case RRC:
2174     case RLC:
2175         TTYPE(tree) = LTYPE(tree);
2176         TETYPE(tree) = LETYPE(tree);
2177         return tree ;
2178         
2179     case GETHBIT:
2180         TTYPE(tree) = TETYPE(tree) = newCharLink();       
2181         return tree;
2182
2183     case LEFT_OP:
2184     case RIGHT_OP:
2185         if (!IS_INTEGRAL(LTYPE(tree)) || !IS_INTEGRAL(tree->left->etype)) {  
2186             werror(E_SHIFT_OP_INVALID);
2187             werror(E_CONTINUE,"left & right types are ");
2188             printTypeChain(LTYPE(tree),stderr);
2189             fprintf(stderr,",");
2190             printTypeChain(RTYPE(tree),stderr);
2191             fprintf(stderr,"\n");
2192             goto errorTreeReturn ;
2193         }
2194
2195         /* if they are both literal then */
2196         /* rewrite the tree */
2197         if (IS_LITERAL(RTYPE(tree)) && IS_LITERAL(LTYPE(tree))) {
2198             tree->type = EX_VALUE ;
2199             tree->opval.val = valShift (valFromType(LETYPE(tree)),
2200                                         valFromType(RETYPE(tree)),
2201                                         (tree->opval.op == LEFT_OP ? 1 : 0));             
2202             tree->right = tree->left = NULL;
2203             TETYPE(tree) = getSpec(TTYPE(tree) = 
2204                                    tree->opval.val->type);
2205             return tree ;
2206         }
2207         /* if only the right side is a literal & we are
2208            shifting more than size of the left operand then zero */
2209         if (IS_LITERAL(RTYPE(tree)) && 
2210             ((int)floatFromVal( valFromType(RETYPE(tree)))) >=
2211             (getSize(LTYPE(tree))*8)) {
2212             werror(W_SHIFT_CHANGED, 
2213                    (tree->opval.op == LEFT_OP ? "left" : "right"));
2214             tree->type = EX_VALUE;
2215             tree->left = tree->right = NULL;
2216             tree->opval.val = constVal("0");
2217             TETYPE(tree) = TTYPE(tree) = tree->opval.val->type;
2218             return tree;
2219         }
2220         LRVAL(tree) = RRVAL(tree) = 1;
2221         COPYTYPE(TTYPE(tree),TETYPE(tree),LTYPE(tree));
2222         return tree ;
2223         
2224         /*------------------------------------------------------------------*/
2225         /*----------------------------*/
2226         /*         casting            */
2227         /*----------------------------*/
2228     case CAST   :  /* change the type   */
2229         /* cannot cast to an aggregate type */
2230         if (IS_AGGREGATE(LTYPE(tree))) {
2231             werror(E_CAST_ILLEGAL);
2232             goto errorTreeReturn ;
2233         }
2234         
2235         /* if the right is a literal replace the tree */
2236         if (IS_LITERAL(RETYPE(tree)) && !IS_PTR(LTYPE(tree))) {
2237             tree->type = EX_VALUE ;
2238             tree->opval.val = 
2239                 valCastLiteral(LTYPE(tree),
2240                                floatFromVal(valFromType(RETYPE(tree))));
2241             tree->left = NULL;
2242             tree->right = NULL;
2243             TTYPE(tree) = tree->opval.val->type;            
2244         }
2245         else {
2246             TTYPE(tree) = LTYPE(tree);
2247             LRVAL(tree) = 1;
2248         }
2249
2250         TETYPE(tree) = getSpec(TTYPE(tree)); 
2251         
2252         return tree;
2253         
2254         /*------------------------------------------------------------------*/
2255         /*----------------------------*/
2256         /*       logical &&, ||       */
2257         /*----------------------------*/
2258     case AND_OP:
2259     case OR_OP :
2260         /* each must me arithmetic type or be a pointer */
2261         if (!IS_PTR(LTYPE(tree)) && 
2262             !IS_ARRAY(LTYPE(tree)) && 
2263             !IS_INTEGRAL(LTYPE(tree))) {
2264             werror(E_COMPARE_OP);
2265             goto errorTreeReturn ;
2266         }
2267         
2268         if (!IS_PTR(RTYPE(tree)) &&     
2269             !IS_ARRAY(RTYPE(tree)) && 
2270             !IS_INTEGRAL(RTYPE(tree))) {
2271             werror(E_COMPARE_OP);
2272             goto errorTreeReturn ;
2273         }
2274         /* if they are both literal then */
2275         /* rewrite the tree */
2276         if (IS_LITERAL(RTYPE(tree)) &&
2277             IS_LITERAL(LTYPE(tree))) {
2278             tree->type = EX_VALUE ;
2279             tree->opval.val = valLogicAndOr (valFromType(LETYPE(tree)),
2280                                              valFromType(RETYPE(tree)),
2281                                              tree->opval.op);               
2282             tree->right = tree->left = NULL;
2283             TETYPE(tree) = getSpec(TTYPE(tree) = 
2284                                    tree->opval.val->type);
2285             return tree ;
2286         }
2287         LRVAL(tree) = RRVAL(tree) = 1;
2288         TTYPE(tree) = TETYPE(tree) = newCharLink();
2289         return tree ;
2290         
2291         /*------------------------------------------------------------------*/
2292         /*----------------------------*/
2293         /*     comparison operators   */
2294         /*----------------------------*/    
2295     case '>' :
2296     case '<' :
2297     case LE_OP :
2298     case GE_OP :
2299     case EQ_OP :
2300     case NE_OP :
2301         {
2302             ast *lt = optimizeCompare(tree);
2303             
2304             if ( tree != lt )
2305                 return lt;
2306         }
2307
2308         /* if they are pointers they must be castable */
2309         if ( IS_PTR(LTYPE(tree)) && IS_PTR(RTYPE(tree))) {
2310             if (checkType(LTYPE(tree),RTYPE(tree)) == 0) {
2311                 werror(E_COMPARE_OP);
2312                 fprintf(stderr,"comparing type ");
2313                 printTypeChain(LTYPE(tree),stderr);
2314                 fprintf(stderr,"to type ");
2315                 printTypeChain(RTYPE(tree),stderr);
2316                 fprintf(stderr,"\n");
2317                 goto errorTreeReturn ;
2318             }
2319         } 
2320         /* else they should be promotable to one another */
2321         else {
2322             if (!(  ( IS_PTR(LTYPE(tree)) && IS_LITERAL(RTYPE(tree))) ||
2323                     ( IS_PTR(RTYPE(tree)) && IS_LITERAL(LTYPE(tree))))) 
2324                 
2325                 if (checkType (LTYPE(tree),RTYPE(tree)) == 0 ) {
2326                     werror(E_COMPARE_OP);
2327                     fprintf(stderr,"comparing type ");
2328                     printTypeChain(LTYPE(tree),stderr);
2329                     fprintf(stderr,"to type ");
2330                     printTypeChain(RTYPE(tree),stderr);
2331                     fprintf(stderr,"\n");
2332                     goto errorTreeReturn ;
2333                 }
2334         }
2335         
2336         /* if they are both literal then */
2337         /* rewrite the tree */
2338         if (IS_LITERAL(RTYPE(tree)) &&
2339             IS_LITERAL(LTYPE(tree))) {
2340             tree->type = EX_VALUE ;
2341             tree->opval.val = valCompare (valFromType(LETYPE(tree)),
2342                                           valFromType(RETYPE(tree)),
2343                                           tree->opval.op);                 
2344             tree->right = tree->left = NULL;
2345             TETYPE(tree) = getSpec(TTYPE(tree) = 
2346                                    tree->opval.val->type);
2347             return tree ;
2348         }
2349         LRVAL(tree) = RRVAL(tree) = 1;
2350         TTYPE(tree) = TETYPE(tree) = newCharLink();
2351         return tree ;
2352         
2353         /*------------------------------------------------------------------*/
2354         /*----------------------------*/
2355         /*             sizeof         */
2356         /*----------------------------*/    
2357     case SIZEOF :  /* evaluate wihout code generation */
2358         /* change the type to a integer */
2359         tree->type = EX_VALUE;
2360         sprintf(buffer,"%d",(getSize(tree->right->ftype)));
2361         tree->opval.val = constVal(buffer);
2362         tree->right = tree->left = NULL;
2363         TETYPE(tree) = getSpec(TTYPE(tree) = 
2364                                tree->opval.val->type);
2365         return tree;     
2366         
2367         /*------------------------------------------------------------------*/
2368         /*----------------------------*/
2369         /* conditional operator  '?'  */
2370         /*----------------------------*/    
2371     case '?' :
2372         /* the type is one on the left */
2373         TTYPE(tree) = LTYPE(tree);
2374         TETYPE(tree)= getSpec (TTYPE(tree));
2375         return tree ;
2376         
2377     case ':' :
2378         /* if they don't match we have a problem */
2379         if (checkType( LTYPE(tree), RTYPE(tree)) == 0) {
2380             werror(E_TYPE_MISMATCH,"conditional operator"," ");
2381             goto errorTreeReturn ;
2382         }
2383         
2384         TTYPE(tree) = computeType(LTYPE(tree),RTYPE(tree));
2385         TETYPE(tree)= getSpec(TTYPE(tree));
2386         return tree ;
2387         
2388         
2389         /*------------------------------------------------------------------*/
2390         /*----------------------------*/
2391         /*    assignment operators    */
2392         /*----------------------------*/    
2393     case MUL_ASSIGN:
2394     case DIV_ASSIGN:
2395         /* for these it must be both must be integral */
2396         if (!IS_ARITHMETIC(LTYPE(tree)) ||
2397             !IS_ARITHMETIC(RTYPE(tree))) {
2398             werror (E_OPS_INTEGRAL);
2399             goto errorTreeReturn ;
2400         }
2401         RRVAL(tree) = 1;
2402         TETYPE(tree) = getSpec(TTYPE(tree) = LTYPE(tree));
2403
2404         if (!tree->initMode && IS_CONSTANT(LETYPE(tree)))
2405             werror(E_CODE_WRITE," ");
2406
2407         if (LRVAL(tree)) {
2408             werror(E_LVALUE_REQUIRED,"*= or /=");
2409             goto errorTreeReturn ;      
2410         }
2411         LLVAL(tree) = 1;
2412         return tree ;
2413
2414     case AND_ASSIGN:
2415     case OR_ASSIGN:
2416     case XOR_ASSIGN:
2417     case RIGHT_ASSIGN:
2418     case LEFT_ASSIGN:
2419         /* for these it must be both must be integral */
2420         if (!IS_INTEGRAL(LTYPE(tree)) ||
2421             !IS_INTEGRAL(RTYPE(tree))) {
2422             werror (E_OPS_INTEGRAL);
2423             goto errorTreeReturn ;
2424         }
2425         RRVAL(tree) = 1;
2426         TETYPE(tree) = getSpec(TTYPE(tree) = LTYPE(tree));
2427
2428         if (!tree->initMode && IS_CONSTANT(LETYPE(tree)))
2429             werror(E_CODE_WRITE," ");
2430
2431         if (LRVAL(tree)) {
2432             werror(E_LVALUE_REQUIRED,"&= or |= or ^= or >>= or <<=");
2433             goto errorTreeReturn ;      
2434         }
2435         LLVAL(tree) = 1;
2436         return tree ;
2437         
2438         /*------------------------------------------------------------------*/
2439         /*----------------------------*/
2440         /*    -= operator             */
2441         /*----------------------------*/    
2442     case SUB_ASSIGN:
2443         if (!(IS_PTR(LTYPE(tree))   ||
2444               IS_ARITHMETIC(LTYPE(tree)))) {
2445             werror(E_PLUS_INVALID,"-=");
2446             goto errorTreeReturn ;
2447         }
2448         
2449         if (!(IS_PTR(RTYPE(tree))   ||
2450               IS_ARITHMETIC(RTYPE(tree)))) {
2451             werror(E_PLUS_INVALID,"-=");
2452             goto errorTreeReturn ;
2453         }
2454         RRVAL(tree) = 1;
2455         TETYPE(tree) = getSpec (TTYPE(tree) = 
2456                                 computeType(LTYPE(tree),
2457                                             RTYPE(tree)));  
2458
2459         if (!tree->initMode && IS_CONSTANT(LETYPE(tree)))
2460             werror(E_CODE_WRITE," ");
2461
2462         if (LRVAL(tree)) {
2463             werror(E_LVALUE_REQUIRED,"-=");
2464             goto errorTreeReturn ;      
2465         }
2466         LLVAL(tree) = 1;
2467         return tree;
2468         
2469         /*------------------------------------------------------------------*/
2470         /*----------------------------*/
2471         /*          += operator       */
2472         /*----------------------------*/    
2473     case ADD_ASSIGN:
2474         /* this is not a unary operation */
2475         /* if both pointers then problem */
2476         if (IS_PTR(LTYPE(tree)) && IS_PTR(RTYPE(tree)) ) {
2477             werror(E_PTR_PLUS_PTR);
2478             goto errorTreeReturn ;
2479         }
2480         
2481         if (!IS_ARITHMETIC(LTYPE(tree)) && !IS_PTR(LTYPE(tree)))  {
2482             werror(E_PLUS_INVALID,"+=");
2483             goto errorTreeReturn ;
2484         }
2485         
2486         if (!IS_ARITHMETIC(RTYPE(tree)) && !IS_PTR(RTYPE(tree)))  {
2487             werror(E_PLUS_INVALID,"+=");
2488             goto errorTreeReturn;
2489         }
2490         RRVAL(tree) = 1;
2491         TETYPE(tree) = getSpec (TTYPE(tree) = 
2492                                 computeType(LTYPE(tree),
2493                                             RTYPE(tree)));  
2494
2495         if (!tree->initMode && IS_CONSTANT(LETYPE(tree)))
2496             werror(E_CODE_WRITE," ");
2497
2498         if (LRVAL(tree)) {
2499             werror(E_LVALUE_REQUIRED,"+=");
2500             goto errorTreeReturn ;      
2501         }
2502
2503         tree->right = decorateType(newNode('+',copyAst(tree->left),tree->right));
2504         tree->opval.op = '=';       
2505         return tree;
2506         
2507         /*------------------------------------------------------------------*/
2508         /*----------------------------*/
2509         /*      straight assignemnt   */
2510         /*----------------------------*/    
2511     case '=' :
2512         /* cannot be an aggregate */
2513         if (IS_AGGREGATE(LTYPE(tree))) {
2514             werror(E_AGGR_ASSIGN);
2515             goto errorTreeReturn;
2516         }
2517             
2518         /* they should either match or be castable */
2519         if (checkType (LTYPE(tree),RTYPE(tree)) == 0) {
2520             werror(E_TYPE_MISMATCH,"assignment"," ");
2521             fprintf(stderr,"type --> '"); 
2522             printTypeChain (RTYPE(tree),stderr); fprintf(stderr,"' ");
2523             fprintf(stderr,"assigned to type --> '"); 
2524             printTypeChain (LTYPE(tree),stderr); fprintf(stderr,"'\n");
2525             goto errorTreeReturn ;
2526         }
2527
2528         /* if the left side of the tree is of type void
2529            then report error */
2530         if (IS_VOID(LTYPE(tree))) {
2531             werror(E_CAST_ZERO);
2532             fprintf(stderr,"type --> '"); 
2533             printTypeChain (RTYPE(tree),stderr); fprintf(stderr,"' ");
2534             fprintf(stderr,"assigned to type --> '"); 
2535             printTypeChain (LTYPE(tree),stderr); fprintf(stderr,"'\n");
2536         }
2537
2538         /* extra checks for pointer types */
2539         if (IS_PTR(LTYPE(tree)) && IS_PTR(RTYPE(tree)) &&
2540             !IS_GENPTR(LTYPE(tree))) {
2541           if (DCL_TYPE(LTYPE(tree)) != DCL_TYPE(RTYPE(tree)))
2542             werror(W_PTR_ASSIGN);
2543         }
2544
2545         TETYPE(tree) = getSpec(TTYPE(tree) = 
2546                                LTYPE(tree));
2547         RRVAL(tree) = 1;
2548         LLVAL(tree) = 1;
2549         if (!tree->initMode && IS_CONSTANT(LETYPE(tree)))
2550             werror(E_CODE_WRITE," ");
2551
2552         if (LRVAL(tree)) {
2553             werror(E_LVALUE_REQUIRED,"=");
2554             goto errorTreeReturn ;      
2555         }
2556
2557         return tree ;
2558         
2559         /*------------------------------------------------------------------*/
2560         /*----------------------------*/
2561         /*      comma operator        */
2562         /*----------------------------*/        
2563     case ',' :
2564         TETYPE(tree) = getSpec(TTYPE(tree) =  RTYPE(tree));
2565         return tree ;    
2566         
2567         /*------------------------------------------------------------------*/
2568         /*----------------------------*/
2569         /*       function call        */
2570         /*----------------------------*/        
2571     case CALL   :
2572         parmNumber = 1;
2573
2574
2575         if (processParms (tree->left,
2576                           tree->left->args,
2577                           tree->right,&parmNumber)) 
2578             goto errorTreeReturn ;    
2579
2580         if (options.stackAuto || IS_RENT(LETYPE(tree))) {
2581                 tree->left->args = reverseVal(tree->left->args); 
2582                 reverseParms(tree->right);
2583         }
2584
2585         tree->args = tree->left->args ;
2586         TETYPE(tree) = getSpec (TTYPE(tree) = LTYPE(tree)->next);
2587         return tree;
2588
2589         /*------------------------------------------------------------------*/
2590         /*----------------------------*/
2591         /*     return statement       */
2592         /*----------------------------*/        
2593     case RETURN :
2594         if (!tree->right)
2595             goto voidcheck ;
2596
2597         if (checkType(currFunc->type->next,RTYPE(tree)) == 0) {
2598             werror(E_RETURN_MISMATCH);
2599             goto errorTreeReturn ;
2600         }
2601
2602         if (IS_VOID(currFunc->type->next) 
2603             && tree->right && 
2604             !IS_VOID(RTYPE(tree))) {
2605             werror(E_FUNC_VOID);
2606             goto errorTreeReturn ;
2607         }
2608         
2609         /* if there is going to be a casing required then add it */
2610         if (checkType(currFunc->type->next,RTYPE(tree)) < 0 ) {
2611             tree->right = 
2612                 decorateType(newNode(CAST,
2613                                      newAst(EX_LINK,
2614                                             copyLinkChain(currFunc->type->next)),
2615                                      tree->right));
2616         }
2617         
2618         RRVAL(tree) = 1;
2619         return tree;
2620
2621         voidcheck :
2622
2623         if (!IS_VOID(currFunc->type->next) && tree->right == NULL ) {
2624             werror(E_VOID_FUNC,currFunc->name);
2625             goto errorTreeReturn ;
2626         }               
2627
2628         TTYPE(tree) = TETYPE(tree) = NULL ;
2629         return tree ;    
2630
2631         /*------------------------------------------------------------------*/
2632         /*----------------------------*/
2633         /*     switch statement       */
2634         /*----------------------------*/        
2635     case SWITCH:
2636         /* the switch value must be an integer */
2637         if (!IS_INTEGRAL(LTYPE(tree))) {
2638             werror (E_SWITCH_NON_INTEGER);
2639             goto errorTreeReturn ;
2640         }
2641         LRVAL(tree) = 1;
2642         TTYPE(tree) = TETYPE(tree) = NULL ;
2643         return tree ;
2644
2645         /*------------------------------------------------------------------*/
2646         /*----------------------------*/
2647         /* ifx Statement              */
2648         /*----------------------------*/
2649     case IFX:
2650         tree->left = backPatchLabels(tree->left,
2651                                      tree->trueLabel,
2652                                      tree->falseLabel);
2653         TTYPE(tree) = TETYPE(tree) = NULL;
2654         return tree;
2655
2656         /*------------------------------------------------------------------*/
2657         /*----------------------------*/
2658         /* for Statement              */
2659         /*----------------------------*/
2660     case FOR:              
2661
2662         decorateType(resolveSymbols(AST_FOR(tree,initExpr)));
2663         decorateType(resolveSymbols(AST_FOR(tree,condExpr)));
2664         decorateType(resolveSymbols(AST_FOR(tree,loopExpr)));
2665         
2666         /* if the for loop is reversible then 
2667            reverse it otherwise do what we normally
2668            do */
2669         {
2670             symbol *sym ;
2671             ast *init, *end;
2672
2673             if (isLoopReversible (tree,&sym,&init,&end))
2674                 return reverseLoop (tree,sym,init,end);
2675             else
2676                 return decorateType(createFor ( AST_FOR(tree,trueLabel), 
2677                                                 AST_FOR(tree,continueLabel) ,
2678                                                 AST_FOR(tree,falseLabel) ,
2679                                                 AST_FOR(tree,condLabel)  ,
2680                                                 AST_FOR(tree,initExpr)   , 
2681                                                 AST_FOR(tree,condExpr)   , 
2682                                                 AST_FOR(tree,loopExpr),
2683                                                 tree->left ) );
2684         }
2685     default :
2686         TTYPE(tree) = TETYPE(tree) = NULL ;
2687         return tree ;    
2688     }
2689     
2690     /* some error found this tree will be killed */
2691     errorTreeReturn :     
2692         TTYPE(tree) = TETYPE(tree) = newCharLink();
2693     tree->opval.op = NULLOP ;
2694     tree->isError = 1;
2695     
2696     return tree ;
2697 }
2698
2699 /*-----------------------------------------------------------------*/
2700 /* sizeofOp - processes size of operation                          */
2701 /*-----------------------------------------------------------------*/
2702 value  *sizeofOp( link  *type)
2703 {
2704         char buff[10];
2705
2706         /* get the size and convert it to character  */
2707         sprintf (buff,"%d", getSize(type));
2708
2709         /* now convert into value  */
2710         return  constVal (buff);      
2711 }
2712
2713
2714 #define IS_AND(ex) (ex->type == EX_OP && ex->opval.op == AND_OP )
2715 #define IS_OR(ex)  (ex->type == EX_OP && ex->opval.op == OR_OP )
2716 #define IS_NOT(ex) (ex->type == EX_OP && ex->opval.op == '!' )
2717 #define IS_ANDORNOT(ex) (IS_AND(ex) || IS_OR(ex) || IS_NOT(ex))
2718 #define IS_IFX(ex) (ex->type == EX_OP && ex->opval.op == IFX )
2719 #define IS_LT(ex)  (ex->type == EX_OP && ex->opval.op == '<' )
2720 #define IS_GT(ex)  (ex->type == EX_OP && ex->opval.op == '>')
2721
2722 /*-----------------------------------------------------------------*/
2723 /* backPatchLabels - change and or not operators to flow control    */
2724 /*-----------------------------------------------------------------*/
2725 ast *backPatchLabels (ast *tree, symbol *trueLabel, symbol *falseLabel )
2726 {  
2727     
2728     if ( ! tree )
2729         return NULL ;
2730     
2731     if ( ! (IS_ANDORNOT(tree)))
2732         return tree ;
2733     
2734     /* if this an and */
2735     if (IS_AND(tree)) {
2736         static int localLbl = 0 ;
2737         symbol *localLabel ;
2738         
2739         sprintf (buffer,"_and_%d",localLbl++);
2740         localLabel = newSymbol(buffer,NestLevel);
2741         
2742         tree->left = backPatchLabels (tree->left, localLabel,falseLabel);    
2743         
2744         /* if left is already a IFX then just change the if true label in that */
2745         if (!IS_IFX(tree->left)) 
2746             tree->left = newIfxNode(tree->left,localLabel,falseLabel);
2747         
2748         tree->right = backPatchLabels(tree->right,trueLabel,falseLabel);    
2749         /* right is a IFX then just join */
2750         if (IS_IFX(tree->right))
2751             return newNode(NULLOP,tree->left,createLabel(localLabel,tree->right));
2752         
2753         tree->right = createLabel(localLabel,tree->right);
2754         tree->right = newIfxNode(tree->right,trueLabel,falseLabel);
2755         
2756         return newNode(NULLOP,tree->left,tree->right);
2757     }
2758     
2759     /* if this is an or operation */
2760     if (IS_OR(tree)) {
2761         static int localLbl = 0 ;
2762         symbol *localLabel ;
2763         
2764         sprintf (buffer,"_or_%d",localLbl++);
2765         localLabel = newSymbol(buffer,NestLevel);
2766         
2767         tree->left = backPatchLabels (tree->left, trueLabel,localLabel);    
2768         
2769         /* if left is already a IFX then just change the if true label in that */
2770         if (!IS_IFX(tree->left))                
2771             tree->left = newIfxNode(tree->left,trueLabel,localLabel);
2772         
2773         tree->right = backPatchLabels(tree->right,trueLabel,falseLabel);    
2774         /* right is a IFX then just join */
2775         if (IS_IFX(tree->right))
2776             return newNode(NULLOP,tree->left,createLabel(localLabel,tree->right));
2777         
2778         tree->right = createLabel(localLabel,tree->right);
2779         tree->right = newIfxNode(tree->right,trueLabel,falseLabel);
2780         
2781         return newNode(NULLOP,tree->left,tree->right);
2782     }
2783     
2784     /* change not */
2785     if (IS_NOT(tree)) {
2786         tree->left = backPatchLabels (tree->left,falseLabel,trueLabel);
2787         
2788         /* if the left is already a IFX */
2789         if ( ! IS_IFX(tree->left) ) 
2790             tree->left = newNode (IFX,tree->left,NULL);
2791         
2792         tree->left->trueLabel = falseLabel ;
2793         tree->left->falseLabel= trueLabel ;
2794         return tree->left ;
2795     }
2796     
2797     if (IS_IFX(tree)) {
2798         tree->trueLabel = trueLabel ;
2799         tree->falseLabel= falseLabel;
2800     }
2801     
2802     return tree ;    
2803 }
2804
2805
2806 /*-----------------------------------------------------------------*/
2807 /* createBlock - create expression tree for block                  */
2808 /*-----------------------------------------------------------------*/
2809 ast  *createBlock   ( symbol *decl,   ast  *body )
2810 {
2811     ast *ex ;
2812     
2813     /* if the block has nothing */
2814     if (!body)
2815         return NULL;
2816
2817     ex = newNode(BLOCK,NULL,body);
2818     ex->values.sym = decl ;
2819     
2820     ex->right = ex->right ;
2821     ex->level++ ;
2822     ex->lineno = 0 ;
2823     return ex;
2824 }
2825
2826 /*-----------------------------------------------------------------*/
2827 /* createLabel - creates the expression tree for labels            */
2828 /*-----------------------------------------------------------------*/
2829 ast  *createLabel  ( symbol  *label,  ast  *stmnt  )
2830 {
2831     symbol *csym;
2832     char        name[SDCC_NAME_MAX+1];
2833     ast   *rValue ;
2834     
2835     /* must create fresh symbol if the symbol name  */
2836     /* exists in the symbol table, since there can  */
2837     /* be a variable with the same name as the labl */
2838     if ((csym = findSym (SymbolTab,NULL,label->name)) &&
2839         (csym->level == label->level))
2840         label = newSymbol(label->name,label->level);
2841     
2842     /* change the name before putting it in add _*/
2843     sprintf (name,"%s",label->name);
2844     
2845     /* put the label in the LabelSymbol table    */
2846     /* but first check if a label of the same    */
2847     /* name exists                               */
2848     if ( (csym = findSym(LabelTab,NULL,name)))
2849         werror(E_DUPLICATE_LABEL,label->name);
2850     else
2851         addSym (LabelTab, label, name,label->level,0);
2852     
2853     label->islbl = 1;
2854     label->key = labelKey++ ;
2855     rValue =  newNode (LABEL,newAst(EX_VALUE,symbolVal(label)),stmnt);  
2856     rValue->lineno = 0;
2857     
2858     return rValue ;
2859 }
2860
2861 /*-----------------------------------------------------------------*/
2862 /* createCase - generates the parsetree for a case statement       */
2863 /*-----------------------------------------------------------------*/
2864 ast  *createCase (ast *swStat, ast *caseVal, ast *stmnt   )
2865 {
2866     char caseLbl[SDCC_NAME_MAX+1];
2867     ast *rexpr;
2868     value *val;
2869     
2870     /* if the switch statement does not exist */
2871     /* then case is out of context            */
2872     if (!swStat) {
2873         werror(E_CASE_CONTEXT);
2874         return NULL ;
2875     }
2876     
2877     caseVal = decorateType(resolveSymbols(caseVal));
2878     /* if not a constant then error  */
2879     if (!IS_LITERAL(caseVal->ftype)) {
2880         werror(E_CASE_CONSTANT);
2881         return NULL ;
2882     }
2883     
2884     /* if not a integer than error */
2885     if (!IS_INTEGRAL(caseVal->ftype)) {
2886         werror(E_CASE_NON_INTEGER);
2887         return NULL;
2888     }
2889
2890     /* find the end of the switch values chain   */
2891     if (!(val = swStat->values.switchVals.swVals))
2892         swStat->values.switchVals.swVals = caseVal->opval.val ;
2893     else {
2894         /* also order the cases according to value */
2895         value *pval = NULL;
2896         int cVal = (int) floatFromVal(caseVal->opval.val);
2897         while (val && (int) floatFromVal(val) < cVal) {
2898             pval = val;
2899             val = val->next ;
2900         }
2901        
2902         /* if we reached the end then */
2903         if (!val) {
2904             pval->next =  caseVal->opval.val;
2905         } else {
2906             /* we found a value greater than */
2907             /* the current value we must add this */
2908             /* before the value */
2909             caseVal->opval.val->next = val;
2910
2911             /* if this was the first in chain */
2912             if (swStat->values.switchVals.swVals == val)
2913                 swStat->values.switchVals.swVals = 
2914                     caseVal->opval.val;
2915             else
2916                 pval->next =  caseVal->opval.val;
2917         }
2918             
2919     }
2920     
2921     /* create the case label   */
2922     sprintf(caseLbl,"_case_%d_%d",
2923             swStat->values.switchVals.swNum,
2924             (int) floatFromVal(caseVal->opval.val));
2925     
2926     rexpr = createLabel(newSymbol(caseLbl,0),stmnt);
2927     rexpr->lineno = 0;
2928     return rexpr;
2929 }
2930
2931 /*-----------------------------------------------------------------*/
2932 /* createDefault - creates the parse tree for the default statement*/
2933 /*-----------------------------------------------------------------*/
2934 ast  *createDefault (ast *swStat, ast *stmnt)
2935 {
2936     char  defLbl[SDCC_NAME_MAX+1];
2937     
2938     /* if the switch statement does not exist */
2939     /* then case is out of context            */
2940     if (!swStat) {
2941         werror(E_CASE_CONTEXT);
2942         return NULL ;
2943     }
2944     
2945     /* turn on the default flag   */
2946     swStat->values.switchVals.swDefault = 1   ;
2947     
2948     /* create the label  */
2949     sprintf (defLbl,"_default_%d",swStat->values.switchVals.swNum);
2950     return createLabel(newSymbol(defLbl,0),stmnt);   
2951 }
2952
2953 /*-----------------------------------------------------------------*/
2954 /* createIf - creates the parsetree for the if statement           */
2955 /*-----------------------------------------------------------------*/
2956 ast *createIf ( ast *condAst, ast *ifBody, ast *elseBody )
2957 {
2958     static int Lblnum = 0 ;
2959     ast *ifTree ;
2960     symbol *ifTrue , *ifFalse, *ifEnd ;
2961     
2962     /* if neither exists */
2963     if (! elseBody && !ifBody)
2964         return condAst ;
2965     
2966     /* create the labels */
2967     sprintf (buffer,"_iffalse_%d",Lblnum);
2968     ifFalse = newSymbol (buffer,NestLevel);
2969     /* if no else body then end == false */
2970     if ( ! elseBody ) 
2971         ifEnd = ifFalse ;
2972     else {
2973         sprintf (buffer,"_ifend_%d",Lblnum);
2974         ifEnd = newSymbol (buffer,NestLevel);
2975     }
2976
2977     sprintf (buffer,"_iftrue_%d",Lblnum);
2978     ifTrue = newSymbol (buffer,NestLevel);
2979         
2980     Lblnum++ ;
2981
2982     /* attach the ifTrue label to the top of it body */
2983     ifBody = createLabel(ifTrue,ifBody);
2984     /* attach a goto end to the ifBody if else is present */
2985     if ( elseBody ) {
2986         ifBody = newNode(NULLOP,ifBody,
2987                          newNode(GOTO,
2988                                  newAst(EX_VALUE,symbolVal(ifEnd)),             
2989                                  NULL));
2990         /* put the elseLabel on the else body */
2991         elseBody = createLabel (ifFalse,elseBody);
2992         /* out the end at the end of the body */
2993         elseBody = newNode(NULLOP,
2994                            elseBody,
2995                            createLabel(ifEnd,NULL));
2996     }
2997     else {
2998         ifBody = newNode(NULLOP,ifBody,
2999                          createLabel(ifFalse,NULL));
3000     }
3001     condAst = backPatchLabels (condAst,ifTrue,ifFalse);
3002     if (IS_IFX(condAst))
3003         ifTree = condAst;
3004     else 
3005         ifTree = newIfxNode(condAst,ifTrue,ifFalse);
3006     
3007     return newNode(NULLOP,ifTree,
3008                    newNode(NULLOP,ifBody,elseBody));
3009     
3010 }
3011
3012 /*-----------------------------------------------------------------*/
3013 /* createDo - creates parse tree for do                            */
3014 /*        _dobody_n:                                               */
3015 /*            statements                                           */
3016 /*        _docontinue_n:                                           */
3017 /*            condition_expression +-> trueLabel -> _dobody_n      */
3018 /*                                 |                               */
3019 /*                                 +-> falseLabel-> _dobreak_n     */
3020 /*        _dobreak_n:                                              */
3021 /*-----------------------------------------------------------------*/
3022 ast *createDo ( symbol *trueLabel, symbol *continueLabel,
3023                 symbol *falseLabel, ast *condAst, ast *doBody )
3024 {
3025     ast *doTree ;
3026     
3027     
3028     /* if the body does not exist then it is simple */
3029     if ( ! doBody ) {
3030         condAst = backPatchLabels(condAst,continueLabel,NULL);
3031         doTree = (IS_IFX(condAst) ? createLabel(continueLabel,condAst) 
3032                   : newNode(IFX,createLabel(continueLabel,condAst),NULL));
3033         doTree->trueLabel = continueLabel ;
3034         doTree->falseLabel= NULL ;
3035         return doTree ;
3036     }
3037     
3038     /* otherwise we have a body */
3039     condAst = backPatchLabels(condAst,trueLabel,falseLabel);
3040     
3041     /* attach the body label to the top */
3042     doBody = createLabel(trueLabel,doBody);
3043     /* attach the continue label to end of body */
3044     doBody = newNode(NULLOP, doBody, 
3045                      createLabel(continueLabel,NULL));
3046     
3047     /* now put the break label at the end */
3048     if (IS_IFX(condAst))
3049         doTree = condAst;
3050     else 
3051         doTree = newIfxNode(condAst,trueLabel,falseLabel);
3052     
3053     doTree = newNode(NULLOP,doTree,createLabel(falseLabel,NULL));
3054     
3055     /* putting it together */
3056     return newNode(NULLOP,doBody,doTree);
3057 }
3058
3059 /*-----------------------------------------------------------------*/
3060 /* createFor - creates parse tree for 'for' statement              */
3061 /*        initExpr                                                 */
3062 /*   _forcond_n:                                                   */
3063 /*        condExpr  +-> trueLabel -> _forbody_n                    */
3064 /*                  |                                              */
3065 /*                  +-> falseLabel-> _forbreak_n                   */
3066 /*   _forbody_n:                                                   */
3067 /*        statements                                               */
3068 /*   _forcontinue_n:                                               */
3069 /*        loopExpr                                                 */
3070 /*        goto _forcond_n ;                                        */
3071 /*   _forbreak_n:                                                  */
3072 /*-----------------------------------------------------------------*/
3073 ast *createFor ( symbol *trueLabel, symbol *continueLabel ,
3074                  symbol *falseLabel,symbol *condLabel     ,
3075                  ast *initExpr, ast *condExpr, ast *loopExpr,
3076                  ast *forBody )
3077 {
3078     ast *forTree ;      
3079
3080     /* if loopexpression not present then we can generate it */
3081     /* the same way as a while */
3082     if ( ! loopExpr ) 
3083         return newNode(NULLOP,initExpr,
3084                        createWhile (trueLabel, continueLabel, 
3085                                     falseLabel,condExpr, forBody ));
3086     /* vanilla for statement */
3087     condExpr = backPatchLabels(condExpr,trueLabel,falseLabel);
3088     
3089     if (condExpr && !IS_IFX(condExpr)) 
3090         condExpr = newIfxNode(condExpr,trueLabel,falseLabel);
3091     
3092     
3093     /* attach condition label to condition */
3094     condExpr = createLabel(condLabel,condExpr);
3095     
3096     /* attach body label to body */
3097     forBody = createLabel(trueLabel,forBody);
3098     
3099     /* attach continue to forLoop expression & attach */
3100     /* goto the forcond @ and of loopExpression       */
3101     loopExpr = createLabel(continueLabel,
3102                            newNode(NULLOP,
3103                                    loopExpr,
3104                                    newNode(GOTO,
3105                                            newAst(EX_VALUE,symbolVal(condLabel)),
3106                                            NULL)));
3107     /* now start putting them together */
3108     forTree = newNode(NULLOP,initExpr,condExpr);
3109     forTree = newNode(NULLOP,forTree,forBody);
3110     forTree = newNode(NULLOP,forTree,loopExpr);
3111     /* finally add the break label */
3112     forTree = newNode(NULLOP,forTree,
3113                       createLabel(falseLabel,NULL));
3114     return forTree ;
3115 }
3116
3117 /*-----------------------------------------------------------------*/
3118 /* createWhile - creates parse tree for while statement            */
3119 /*               the while statement will be created as follows    */
3120 /*                                                                 */
3121 /*      _while_continue_n:                                         */
3122 /*            condition_expression +-> trueLabel -> _while_boby_n  */
3123 /*                                 |                               */
3124 /*                                 +-> falseLabel -> _while_break_n*/
3125 /*      _while_body_n:                                             */
3126 /*            statements                                           */
3127 /*            goto _while_continue_n                               */
3128 /*      _while_break_n:                                            */
3129 /*-----------------------------------------------------------------*/
3130 ast *createWhile (symbol *trueLabel, symbol *continueLabel, 
3131                    symbol *falseLabel,ast *condExpr, ast *whileBody )
3132 {
3133     ast *whileTree ;
3134         
3135     /* put the continue label */
3136     condExpr = backPatchLabels (condExpr,trueLabel,falseLabel);
3137     condExpr = createLabel(continueLabel,condExpr);
3138     condExpr->lineno = 0;
3139     
3140     /* put the body label in front of the body */
3141     whileBody = createLabel(trueLabel,whileBody);
3142     whileBody->lineno = 0;
3143     /* put a jump to continue at the end of the body */
3144     /* and put break label at the end of the body */
3145     whileBody = newNode(NULLOP,
3146                         whileBody,
3147                         newNode(GOTO,
3148                                 newAst(EX_VALUE,
3149                                        symbolVal(continueLabel)),
3150                                 createLabel(falseLabel,NULL)));
3151     
3152     /* put it all together */
3153     if ( IS_IFX(condExpr) )
3154         whileTree = condExpr ;
3155     else {
3156         whileTree = newNode (IFX, condExpr,NULL );      
3157         /* put the true & false labels in place */
3158         whileTree->trueLabel = trueLabel ;
3159         whileTree->falseLabel= falseLabel;
3160     }
3161     
3162     return newNode(NULLOP,whileTree,whileBody );
3163 }
3164
3165 /*-----------------------------------------------------------------*/
3166 /* optimizeGetHbit - get highest order bit of the expression       */
3167 /*-----------------------------------------------------------------*/
3168 ast *optimizeGetHbit (ast *tree)
3169 {
3170     int i,j;
3171     /* if this is not a bit and */
3172     if (!IS_BITAND(tree))
3173         return tree;
3174     
3175     /* will look for tree of the form
3176        ( expr >> ((sizeof expr) -1) ) & 1 */
3177     if (!IS_AST_LIT_VALUE(tree->right))
3178         return tree;
3179
3180     if (AST_LIT_VALUE(tree->right) != 1)
3181         return tree;
3182
3183     if (!IS_RIGHT_OP(tree->left))
3184         return tree;
3185
3186     if (!IS_AST_LIT_VALUE(tree->left->right))
3187         return tree;
3188
3189     if ((i = AST_LIT_VALUE(tree->left->right)) !=
3190         ( j = (getSize(TTYPE(tree->left->left))*8 - 1)))
3191         return tree;
3192
3193     return decorateType(newNode(GETHBIT,tree->left->left,NULL));
3194         
3195 }
3196
3197 /*-----------------------------------------------------------------*/
3198 /* optimizeRRCRLC :- optimize for Rotate Left/Right with carry     */
3199 /*-----------------------------------------------------------------*/
3200 ast *optimizeRRCRLC ( ast *root )
3201 {
3202     /* will look for trees of the form
3203        (?expr << 1) | (?expr >> 7) or
3204        (?expr >> 7) | (?expr << 1) will make that
3205        into a RLC : operation ..
3206        Will also look for 
3207        (?expr >> 1) | (?expr << 7) or
3208        (?expr << 7) | (?expr >> 1) will make that
3209        into a RRC operation 
3210        note : by 7 I mean (number of bits required to hold the
3211        variable -1 ) */
3212     /* if the root operations is not a | operation the not */
3213     if (!IS_BITOR(root))
3214         return root ;
3215
3216     /* I have to think of a better way to match patterns this sucks */
3217     /* that aside let start looking for the first case : I use a the
3218        negative check a lot to improve the efficiency */
3219     /* (?expr << 1) | (?expr >> 7) */
3220     if (IS_LEFT_OP(root->left)    && 
3221         IS_RIGHT_OP(root->right)  ) {   
3222         
3223         if (!SPEC_USIGN(TETYPE(root->left->left)))
3224             return root;
3225
3226         if (!IS_AST_LIT_VALUE(root->left->right) ||
3227             !IS_AST_LIT_VALUE(root->right->right))
3228             goto tryNext0;
3229
3230         /* make sure it is the same expression */
3231         if (!isAstEqual(root->left->left,
3232                         root->right->left))
3233             goto tryNext0;
3234         
3235         if (AST_LIT_VALUE(root->left->right) != 1 )
3236             goto tryNext0 ;
3237         
3238         if (AST_LIT_VALUE(root->right->right) !=
3239             (getSize(TTYPE(root->left->left))*8 - 1))
3240             goto tryNext0 ;
3241
3242         /* whew got the first case : create the AST */
3243         return  newNode(RLC,root->left->left,NULL);     
3244     }
3245
3246  tryNext0:
3247     /* check for second case */
3248     /* (?expr >> 7) | (?expr << 1) */
3249     if (IS_LEFT_OP(root->right)    && 
3250         IS_RIGHT_OP(root->left)  ) {     
3251
3252         if (!SPEC_USIGN(TETYPE(root->left->left)))
3253             return root;
3254         
3255         if (!IS_AST_LIT_VALUE(root->left->right) ||
3256             !IS_AST_LIT_VALUE(root->right->right))
3257             goto tryNext1 ;
3258         
3259         /* make sure it is the same symbol */
3260         if (!isAstEqual(root->left->left,
3261                         root->right->left))
3262             goto tryNext1 ;
3263         
3264         if (AST_LIT_VALUE(root->right->right) != 1 )
3265             goto tryNext1 ;
3266         
3267         if (AST_LIT_VALUE(root->left->right) !=
3268             (getSize(TTYPE(root->left->left))*8 - 1))
3269             goto tryNext1 ;
3270
3271         /* whew got the first case : create the AST */
3272         return  newNode(RLC,root->left->left,NULL);
3273         
3274     }
3275
3276  tryNext1:
3277     /* third case for RRC */
3278     /*  (?symbol >> 1) | (?symbol << 7) */
3279     if (IS_LEFT_OP(root->right)    && 
3280         IS_RIGHT_OP(root->left)  ) {    
3281
3282         if (!SPEC_USIGN(TETYPE(root->left->left)))
3283             return root;
3284         
3285         if (!IS_AST_LIT_VALUE(root->left->right) ||
3286             !IS_AST_LIT_VALUE(root->right->right))
3287             goto tryNext2;
3288         
3289         /* make sure it is the same symbol */
3290         if (!isAstEqual(root->left->left,
3291                         root->right->left))
3292             goto tryNext2;
3293         
3294         if (AST_LIT_VALUE(root->left->right) != 1 )
3295             goto tryNext2;
3296         
3297         if (AST_LIT_VALUE(root->right->right) !=
3298             (getSize(TTYPE(root->left->left))*8 - 1))
3299             goto tryNext2;
3300
3301         /* whew got the first case : create the AST */
3302         return newNode(RRC,root->left->left,NULL);
3303         
3304     }
3305  tryNext2:
3306     /* fourth and last case for now */
3307     /* (?symbol << 7) | (?symbol >> 1) */
3308     if (IS_RIGHT_OP(root->right)    && 
3309         IS_LEFT_OP(root->left)  ) {     
3310
3311         if (!SPEC_USIGN(TETYPE(root->left->left)))
3312             return root;
3313         
3314         if (!IS_AST_LIT_VALUE(root->left->right) ||
3315             !IS_AST_LIT_VALUE(root->right->right))
3316             return root;
3317
3318         /* make sure it is the same symbol */
3319         if (!isAstEqual(root->left->left,
3320                         root->right->left))
3321             return root;
3322         
3323         if (AST_LIT_VALUE(root->right->right) != 1 )
3324             return root ;
3325         
3326         if (AST_LIT_VALUE(root->left->right) !=
3327             (getSize(TTYPE(root->left->left))*8 - 1))
3328             return root ;
3329
3330         /* whew got the first case : create the AST */
3331         return  newNode(RRC,root->left->left,NULL);
3332         
3333     }
3334
3335     /* not found return root */
3336     return root;
3337 }
3338
3339 /*-----------------------------------------------------------------*/
3340 /* optimizeCompare - otimizes compares for bit variables           */
3341 /*-----------------------------------------------------------------*/
3342 ast  *optimizeCompare ( ast *root )
3343 {
3344     ast *optExpr = NULL;
3345     value       *vleft;
3346     value       *vright;
3347     unsigned int litValue ;
3348     
3349     /* if nothing then return nothing */
3350     if (!root)
3351         return NULL ;
3352     
3353     /* if not a compare op then do leaves */
3354     if (!IS_COMPARE_OP(root)) {
3355         root->left = optimizeCompare (root->left);
3356         root->right= optimizeCompare (root->right);
3357         return root ;
3358     }
3359     
3360     /* if left & right are the same then depending 
3361        of the operation do */
3362     if (isAstEqual(root->left,root->right)) {
3363         switch (root->opval.op) {
3364         case '>' :
3365         case '<' :
3366         case NE_OP :
3367             optExpr = newAst(EX_VALUE,constVal("0"));
3368             break;
3369         case GE_OP :
3370         case LE_OP :
3371         case EQ_OP :
3372             optExpr = newAst(EX_VALUE,constVal("1"));
3373             break;
3374         }
3375
3376         return decorateType(optExpr);
3377     }
3378
3379     vleft = (root->left->type == EX_VALUE ?
3380              root->left->opval.val : NULL );
3381     
3382     vright = (root->right->type == EX_VALUE ?
3383               root->right->opval.val : NULL);
3384     
3385     /* if left is a BITVAR in BITSPACE */
3386     /* and right is a LITERAL then opt-*/
3387     /* imize else do nothing               */
3388     if (vleft && vright                   &&
3389         IS_BITVAR(vleft->etype)           && 
3390         IN_BITSPACE(SPEC_OCLS(vleft->etype))  &&
3391         IS_LITERAL(vright->etype)) {
3392         
3393         /* if right side > 1 then comparison may never succeed */
3394         if ( (litValue = (int) floatFromVal(vright)) > 1 ) {
3395             werror(W_BAD_COMPARE);
3396             goto noOptimize ;
3397         }
3398         
3399         if ( litValue ) {
3400             switch (root->opval.op) {
3401             case '>' :  /* bit value greater than 1 cannot be */
3402                 werror(W_BAD_COMPARE);
3403                 goto noOptimize ;
3404                 break;
3405                 
3406             case '<' : /* bit value < 1 means 0 */
3407             case NE_OP :
3408                 optExpr = newNode('!',newAst(EX_VALUE,vleft),NULL);
3409                 break;
3410                 
3411             case LE_OP : /* bit value <= 1 means no check */
3412                 optExpr = newAst(EX_VALUE,vright);              
3413                 break;
3414                 
3415             case GE_OP : /* bit value >= 1 means only check for = */
3416             case EQ_OP :
3417                 optExpr = newAst(EX_VALUE,vleft);               
3418                 break;
3419             }
3420         } else { /* literal is zero */
3421             switch (root->opval.op) {
3422             case '<' :  /* bit value < 0 cannot be */
3423                 werror(W_BAD_COMPARE);
3424                 goto noOptimize ;
3425                 break;
3426                 
3427             case '>' : /* bit value > 0 means 1 */
3428             case NE_OP :
3429                 optExpr = newAst(EX_VALUE,vleft);            
3430                 break;
3431                 
3432             case LE_OP : /* bit value <= 0 means no check */
3433             case GE_OP : /* bit value >= 0 means no check */
3434                 werror(W_BAD_COMPARE);
3435                 goto noOptimize ;
3436                 break;
3437                 
3438             case EQ_OP : /* bit == 0 means ! of bit */
3439                 optExpr = newNode('!',newAst(EX_VALUE,vleft),NULL);           
3440                 break;
3441             }
3442         }                      
3443         return decorateType(resolveSymbols(optExpr)); 
3444     }   /* end-of-if of BITVAR */
3445     
3446     noOptimize :
3447         return root;
3448 }
3449 /*-----------------------------------------------------------------*/
3450 /* addSymToBlock : adds the symbol to the first block we find      */
3451 /*-----------------------------------------------------------------*/
3452 void addSymToBlock (symbol *sym, ast *tree)
3453 {
3454     /* reached end of tree or a leaf */
3455     if (!tree || IS_AST_LINK(tree) || IS_AST_VALUE(tree))
3456         return ;
3457
3458     /* found a block */
3459     if (IS_AST_OP(tree) &&
3460         tree->opval.op == BLOCK ) {
3461         
3462         symbol *lsym = copySymbol(sym);
3463         
3464         lsym->next = AST_VALUES(tree,sym);
3465         AST_VALUES(tree,sym) = lsym ;
3466         return ;
3467     }
3468     
3469     addSymToBlock(sym,tree->left);
3470     addSymToBlock(sym,tree->right);
3471 }
3472
3473 /*-----------------------------------------------------------------*/
3474 /* processRegParms - do processing for register parameters         */
3475 /*-----------------------------------------------------------------*/
3476 static void processRegParms (value *args, ast *body)
3477 {
3478     while (args) {
3479         if (IS_REGPARM(args->etype))
3480             addSymToBlock(args->sym,body);
3481         args = args->next;
3482     }
3483 }
3484
3485 /*-----------------------------------------------------------------*/
3486 /* resetParmKey - resets the operandkeys for the symbols           */
3487 /*-----------------------------------------------------------------*/
3488 DEFSETFUNC(resetParmKey)
3489 {
3490     symbol *sym = item;
3491
3492     sym->key = 0 ;
3493     sym->defs = NULL ;
3494     sym->uses = NULL ;
3495     sym->remat= 0;
3496     return 1;
3497 }
3498
3499 /*-----------------------------------------------------------------*/
3500 /* createFunction - This is the key node that calls the iCode for  */
3501 /*                  generating the code for a function. Note code  */
3502 /*                  is generated function by function, later when  */
3503 /*                  add inter-procedural analysis this will change */
3504 /*-----------------------------------------------------------------*/
3505 ast  *createFunction   (symbol  *name,   ast  *body )
3506 {
3507     ast  *ex ;
3508     symbol *csym;
3509     int stack = 0 ;
3510     link *fetype;       
3511     iCode *piCode = NULL;
3512     
3513     /* if check function return 0 then some problem */
3514     if (checkFunction (name) == 0)
3515         return NULL;
3516     
3517     /* create a dummy block if none exists */
3518     if (!body)
3519         body = newNode(BLOCK,NULL,NULL);
3520
3521     noLineno++ ;
3522    
3523     /* check if the function name already in the symbol table */
3524     if ((csym = findSym (SymbolTab,NULL,name->name))) {
3525         name = csym ;     
3526         /* special case for compiler defined functions
3527            we need to add the name to the publics list : this
3528            actually means we are now compiling the compiler
3529            support routine */
3530         if (name->cdef)
3531             addSet(&publics,name);
3532     }
3533     else {
3534         addSymChain(name);
3535         allocVariables(name);
3536     }
3537     name->lastLine = yylineno;
3538     currFunc = name ;
3539     processFuncArgs(currFunc,0);
3540     
3541     /* set the stack pointer */
3542     /* PENDING: check this for the mcs51 */
3543     stackPtr = -port->stack.direction * port->stack.call_overhead;
3544     if (IS_ISR(name->etype))
3545         stackPtr -= port->stack.direction * port->stack.isr_overhead;
3546     if (IS_RENT(name->etype) || options.stackAuto)
3547         stackPtr -= port->stack.direction * port->stack.reent_overhead;
3548
3549     xstackPtr = -port->stack.direction * port->stack.call_overhead;
3550     
3551     fetype = getSpec(name->type); /* get the specifier for the function */
3552     /* if this is a reentrant function then */
3553     if (IS_RENT(fetype))
3554         reentrant++ ;
3555         
3556     allocParms (name->args);           /* allocate the parameters */
3557
3558     /* do processing for parameters that are passed in registers */
3559     processRegParms (name->args,body); 
3560
3561    /* set the stack pointer */
3562     stackPtr = 0;
3563     xstackPtr= -1;
3564     
3565     /* allocate & autoinit the block variables */
3566     processBlockVars (body, &stack,ALLOCATE); 
3567     
3568     /* save the stack information */
3569     if (options.useXstack)
3570         name->xstack = SPEC_STAK(fetype) = stack;
3571     else
3572         name->stack = SPEC_STAK(fetype) = stack;
3573     
3574     /* name needs to be mangled */
3575     sprintf (name->rname,"_%s",name->name);
3576     
3577     body = resolveSymbols(body); /* resolve the symbols */
3578     body = decorateType (body);  /* propagateType & do semantic checks */
3579     
3580     ex = newAst (EX_VALUE, symbolVal(name));    /* create name       */
3581     ex = newNode (FUNCTION,ex,body);
3582     ex->values.args = name->args ;
3583     
3584     if (fatalError) {
3585         werror(E_FUNC_NO_CODE,name->name);
3586         goto skipall ;
3587     }
3588         
3589     /* create the node & generate intermediate code */  
3590     codeOutFile = code->oFile;
3591     piCode = iCodeFromAst(ex);
3592
3593      if (fatalError) {
3594          werror(E_FUNC_NO_CODE,name->name);
3595          goto skipall ;
3596      }
3597      
3598      eBBlockFromiCode(piCode);
3599                     
3600     /* if there are any statics then do them */
3601     if (staticAutos) {
3602         codeOutFile = statsg->oFile;
3603         eBBlockFromiCode (iCodeFromAst (decorateType(resolveSymbols(staticAutos))));
3604         staticAutos = NULL;
3605     }
3606     
3607  skipall:
3608     
3609     /* dealloc the block variables */
3610     processBlockVars(body, &stack,DEALLOCATE);
3611     /* deallocate paramaters */
3612     deallocParms(name->args);
3613     
3614     if (IS_RENT(fetype))
3615         reentrant-- ;
3616     
3617     /* we are done freeup memory & cleanup */
3618     noLineno-- ;
3619     labelKey = 1 ;
3620     name->key = 0;
3621     name->fbody = 1;
3622     addSet(&operKeyReset,name);
3623     applyToSet(operKeyReset,resetParmKey);
3624        
3625     if (options.debug)
3626         cdbStructBlock(1,cdbFile);
3627
3628     cleanUpLevel(LabelTab,0);
3629     cleanUpBlock(StructTab,1);
3630     cleanUpBlock(TypedefTab,1);
3631
3632     xstack->syms = NULL;
3633     istack->syms = NULL;
3634     return NULL ;
3635 }
3636
3637