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