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