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