* Added common.h
[fw/sdcc] / src / SDCCicode.c
1 /*-------------------------------------------------------------------------
2
3   SDCCicode.c - intermediate code generation etc.                  
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 /*-----------------------------------------------------------------*/
28 /* global variables       */
29
30 set *iCodeChain = NULL ;
31 int iTempNum = 0;
32 int iTempLblNum = 0;
33 int operandKey = 0 ;
34 int iCodeKey = 0;
35 char *filename ;
36 int lineno ;
37 int block;
38 int scopeLevel;
39 int lvaluereq;
40
41 extern int labelKey ;
42
43 symbol *returnLabel ; /* function return label */
44 symbol *entryLabel  ; /* function entry  label */
45 /*-----------------------------------------------------------------*/
46 /* forward definition of some functions */
47 operand *geniCodeDivision (operand *,operand *);
48 operand *geniCodeAssign   (operand *,operand *,int);
49 operand *geniCodeArray (operand *,operand *);
50 operand *geniCodeArray2Ptr (operand *);
51 operand *geniCodeRValue (operand *, bool );
52 operand *geniCodeDerefPtr (operand *);
53
54 #define PRINTFUNC(x) void x (FILE *of, iCode *ic, char *s)
55
56 /* forward definition of print functions */
57 PRINTFUNC(picGetValueAtAddr);
58 PRINTFUNC(picSetValueAtAddr);
59 PRINTFUNC(picAddrOf);
60 PRINTFUNC(picGeneric);
61 PRINTFUNC(picGenericOne);
62 PRINTFUNC(picCast);
63 PRINTFUNC(picIncrement);
64 PRINTFUNC(picDecrement);
65 PRINTFUNC(picAssign);
66 PRINTFUNC(picLabel);
67 PRINTFUNC(picGoto);
68 PRINTFUNC(picIfx);
69 PRINTFUNC(picJumpTable);
70 PRINTFUNC(picInline);
71 PRINTFUNC(picReceive);
72
73 iCodeTable codeTable[] = {
74   { '!'                 ,  "not", picGenericOne    , NULL },
75   { '~'                 ,  "~"  , picGenericOne    , NULL },
76   { RRC                 ,  "rrc", picGenericOne    , NULL },
77   { RLC                 ,  "rlc", picGenericOne    , NULL },
78   { GETHBIT             ,"ghbit", picGenericOne    , NULL },
79   { UNARYMINUS          ,  "-"  , picGenericOne    , NULL },
80   { IPUSH               ,  "push",picGenericOne    , NULL },
81   { IPOP                ,  "pop", picGenericOne    , NULL },
82   { CALL                ,  "call",picGenericOne    , NULL },
83   { PCALL               , "pcall",picGenericOne    , NULL }, 
84   { FUNCTION            , "proc", picGenericOne    , NULL },
85   { ENDFUNCTION         ,"eproc", picGenericOne    , NULL },
86   { RETURN              ,  "ret", picGenericOne    , NULL },
87   { '+'                 ,  "+"  , picGeneric       , NULL },
88   { '-'                 ,  "-"  , picGeneric       , NULL },
89   { '*'                 ,  "*"  , picGeneric       , NULL },
90   { '/'                 ,  "/"  , picGeneric       , NULL },
91   { '%'                 ,  "%"  , picGeneric       , NULL },
92   { '>'                 ,  ">"  , picGeneric       , NULL },
93   { '<'                 ,  "<"  , picGeneric       , NULL },
94   { LE_OP               ,  "<=" , picGeneric       , NULL },
95   { GE_OP               ,  ">=" , picGeneric       , NULL },
96   { EQ_OP               ,  "==" , picGeneric       , NULL },
97   { NE_OP               ,  "!=" , picGeneric       , NULL },  
98   { AND_OP              ,  "&&" , picGeneric       , NULL },
99   { OR_OP               ,  "||" , picGeneric       , NULL },
100   { '^'                 ,  "^"  , picGeneric       , NULL },
101   { '|'                 ,  "|"  , picGeneric       , NULL },
102   { BITWISEAND          ,  "&"  , picGeneric       , NULL },
103   { LEFT_OP             ,  "<<" , picGeneric       , NULL },
104   { RIGHT_OP            ,  ">>" , picGeneric       , NULL },
105   { GET_VALUE_AT_ADDRESS,  "@"  , picGetValueAtAddr, NULL },
106   { ADDRESS_OF          ,  "&"  , picAddrOf        , NULL },
107   { CAST                ,  "<>" , picCast          , NULL },
108   { '='                 ,  ":=" , picAssign        , NULL },
109   { LABEL               ,  ""   , picLabel         , NULL },
110   { GOTO                ,  ""   , picGoto          , NULL },
111   { JUMPTABLE           ,"jtab" , picJumpTable     , NULL },
112   { IFX                 ,  "if" , picIfx           , NULL },
113   { INLINEASM           , ""    , picInline        , NULL },
114   { RECEIVE             , "recv", picReceive       , NULL },
115   { SEND                , "send", picGenericOne    , NULL }
116 };
117
118
119 /*-----------------------------------------------------------------*/
120 /* operandName - returns the name of the operand                   */
121 /*-----------------------------------------------------------------*/
122 int printOperand (operand *op, FILE *file)
123 {
124     link *opetype;
125     int pnl = 0;
126
127     if (!op)
128         return 1;
129
130     if (!file) {
131         file = stdout;
132         pnl = 1;
133     }
134     switch (op->type) {
135         
136     case VALUE:
137         opetype = getSpec (operandType(op));
138         if (SPEC_NOUN(opetype) == V_FLOAT)
139             fprintf (file,"%g {", SPEC_CVAL(opetype).v_float);
140         else 
141             fprintf (file,"0x%x {",(int) floatFromVal(op->operand.valOperand));
142         printTypeChain(operandType(op),file);
143         fprintf(file,"}");
144         break;
145         
146     case SYMBOL :
147 #define REGA 1
148 #ifdef REGA     
149         fprintf (file,"%s [k%d lr%d:%d so:%d]{ ia%d re%d rm%d}",/*{ar%d rm%d ru%d p%d a%d u%d i%d au%d k%d ks%d}"  ,*/
150                  (OP_SYMBOL(op)->rname[0] ? OP_SYMBOL(op)->rname : OP_SYMBOL(op)->name), 
151                  op->key,
152                  OP_LIVEFROM(op),OP_LIVETO(op),
153                  OP_SYMBOL(op)->stack,
154                  op->isaddr, OP_SYMBOL(op)->isreqv,OP_SYMBOL(op)->remat
155 /*               , */
156 /*               OP_SYMBOL(op)->allocreq,OP_SYMBOL(op)->remat, */
157 /*               OP_SYMBOL(op)->ruonly, */
158 /*               OP_SYMBOL(op)->isptr,op->isaddr,OP_SYMBOL(op)->used, */
159 /*               OP_SYMBOL(op)->isind, */
160 /*               OP_SYMBOL(op)->accuse, op->key, OP_SYMBOL(op)->key */
161                  );
162         {
163             fprintf(file,"{"); printTypeChain(operandType(op),file); 
164             if (SPIL_LOC(op) && IS_ITEMP(op))
165                 fprintf(file,"}{ sir@ %s",SPIL_LOC(op)->rname);
166             fprintf(file,"}");
167
168         }
169         
170         /* if assigned to registers */
171         if (OP_SYMBOL(op)->nRegs) {
172             if (OP_SYMBOL(op)->isspilt) {
173                 if (!OP_SYMBOL(op)->remat)
174                     if (OP_SYMBOL(op)->usl.spillLoc)
175                         fprintf(file,"[%s]",(OP_SYMBOL(op)->usl.spillLoc->rname[0] ?
176                                              OP_SYMBOL(op)->usl.spillLoc->rname :
177                                              OP_SYMBOL(op)->usl.spillLoc->name));
178                     else
179                         fprintf(file,"[err]");
180                 else
181                     fprintf(file,"[remat]");
182             }
183             else {
184                 int i;
185                 fprintf(file,"[");
186                 for(i=0;i<OP_SYMBOL(op)->nRegs;i++)
187                     fprintf(file,"%s ",(OP_SYMBOL(op)->regs[i] ? 
188                                         OP_SYMBOL(op)->regs[i]->name :
189                                         "err"));
190                 fprintf(file,"]");
191             }
192         } 
193 #else
194         fprintf(file,"%s",(OP_SYMBOL(op)->rname[0] ?
195                            OP_SYMBOL(op)->rname : OP_SYMBOL(op)->name));
196         /* if assigned to registers */
197         if (OP_SYMBOL(op)->nRegs && !OP_SYMBOL(op)->isspilt) {
198             int i;
199             fprintf(file,"[");
200             for(i=0;i<OP_SYMBOL(op)->nRegs;i++)
201                 fprintf(file,"%s ",(OP_SYMBOL(op)->regs[i] ? 
202                                     OP_SYMBOL(op)->regs[i]->name :
203                                     "err"));
204             fprintf(file,"]");
205         } 
206 #endif
207         break ;
208         
209     case TYPE:
210         fprintf(file,"(");
211         printTypeChain(op->operand.typeOperand,file);
212         fprintf(file,")");
213         break;
214     }
215     
216     if (pnl)
217         fprintf(file,"\n");
218     return 0;
219 }
220
221
222 /*-----------------------------------------------------------------*/
223 /*                    print functions                              */
224 /*-----------------------------------------------------------------*/
225 PRINTFUNC(picGetValueAtAddr)
226 {
227     fprintf(of,"\t");
228     printOperand (IC_RESULT(ic),of);
229     fprintf (of," = ");
230     fprintf (of,"@[");
231     printOperand (IC_LEFT(ic), of);
232     fprintf (of,"]");
233     
234     fprintf(of,"\n");
235 }
236
237 PRINTFUNC(picSetValueAtAddr)
238 {
239     fprintf(of,"\t");
240     fprintf(of,"*[");
241     printOperand(IC_LEFT(ic),of);
242     fprintf(of,"] = ");
243     printOperand(IC_RIGHT(ic),of);
244     fprintf (of,"\n");
245 }
246
247 PRINTFUNC(picAddrOf)
248 {
249     fprintf(of,"\t");
250     printOperand(IC_RESULT(ic),of);
251     if (IS_ITEMP(IC_LEFT(ic)))
252         fprintf(of," = ");
253     else
254         fprintf(of," = &[");
255     printOperand(IC_LEFT(ic),of);
256     if (IC_RIGHT(ic)) {
257         if (IS_ITEMP(IC_LEFT(ic)))
258             fprintf(of," offsetAdd ");
259         else
260             fprintf(of," , ");
261         printOperand(IC_RIGHT(ic),of);
262     }
263     if (IS_ITEMP(IC_LEFT(ic)))
264         fprintf (of,"\n");
265     else
266         fprintf (of,"]\n");
267 }
268
269 PRINTFUNC(picJumpTable)
270 {
271     symbol *sym;
272
273     fprintf(of,"\t");
274     fprintf(of,"%s\t",s);
275     printOperand(IC_JTCOND(ic),of);
276     fprintf(of,"\n");
277     for ( sym = setFirstItem(IC_JTLABELS(ic)); sym;
278           sym = setNextItem(IC_JTLABELS(ic))) 
279         fprintf(of,"\t\t\t%s\n",sym->name);
280 }
281
282 PRINTFUNC(picGeneric)
283 {
284     fprintf(of,"\t");
285     printOperand(IC_RESULT(ic),of);
286     fprintf(of," = ");
287     printOperand(IC_LEFT(ic),of);
288     fprintf(of," %s ",s);
289     printOperand(IC_RIGHT(ic),of);
290     fprintf(of,"\n");
291 }
292
293 PRINTFUNC(picGenericOne)
294 {
295     fprintf(of,"\t");
296     if ( IC_RESULT(ic) ) {
297         printOperand(IC_RESULT(ic),of);
298         fprintf (of," = ");
299     }
300     
301     if (IC_LEFT(ic)) {
302         fprintf (of,"%s ",s);
303         printOperand(IC_LEFT(ic),of);     
304     }
305     
306     if (! IC_RESULT(ic) && !IC_LEFT(ic))
307         fprintf (of,s);
308     
309     fprintf(of,"\n");
310 }
311
312 PRINTFUNC(picCast)
313 {
314     fprintf(of,"\t");
315     printOperand(IC_RESULT(ic),of);
316     fprintf (of," = ");
317     printOperand(IC_LEFT(ic),of);
318     printOperand(IC_RIGHT(ic),of);
319     fprintf(of,"\n");
320 }
321
322
323 PRINTFUNC(picAssign)
324 {
325     fprintf(of,"\t");
326     
327     if (IC_RESULT(ic)->isaddr && IS_ITEMP(IC_RESULT(ic)))
328         fprintf(of,"*(");
329     
330     printOperand(IC_RESULT(ic),of);  
331     
332     if (IC_RESULT(ic)->isaddr && IS_ITEMP(IC_RESULT(ic)))
333         fprintf(of,")");
334     
335     fprintf(of," %s ", s);
336     printOperand (IC_RIGHT(ic),of);
337     
338     fprintf(of,"\n");
339 }
340
341 PRINTFUNC(picLabel)
342 {
343     fprintf(of," %s($%d) :\n",IC_LABEL(ic)->name,IC_LABEL(ic)->key);
344 }
345
346 PRINTFUNC(picGoto)
347 {
348    fprintf(of,"\t");
349    fprintf (of," goto %s($%d)\n", IC_LABEL(ic)->name,IC_LABEL(ic)->key);
350 }
351
352 PRINTFUNC(picIfx)
353 {    
354     fprintf(of,"\t");
355     fprintf (of,"if ");
356     printOperand(IC_COND(ic),of);
357     
358     if ( ! IC_TRUE(ic) ) 
359         fprintf (of," == 0 goto %s($%d)\n",IC_FALSE(ic)->name,IC_FALSE(ic)->key);
360     else {
361         fprintf (of," != 0 goto %s($%d)\n",IC_TRUE(ic)->name,IC_TRUE(ic)->key);
362         if (IC_FALSE(ic))
363             fprintf (of,"\tzzgoto %s\n",IC_FALSE(ic)->name);
364     }
365 }
366
367 PRINTFUNC(picInline)
368 {
369     fprintf(of,"%s",IC_INLINE(ic));
370 }
371
372 PRINTFUNC(picReceive)
373 {
374     printOperand(IC_RESULT(ic),of);
375     fprintf(of," = %s ",s);
376     printOperand(IC_LEFT(ic),of);
377     fprintf(of,"\n");
378 }
379
380 /*-----------------------------------------------------------------*/
381 /* piCode - prints one iCode                                       */
382 /*-----------------------------------------------------------------*/
383 int piCode (void *item, FILE *of)
384 {
385     iCode *ic = item;
386     iCodeTable *icTab ;
387     
388     if (!of)
389         of = stdout;
390
391     icTab = getTableEntry(ic->op) ;
392     fprintf(stdout,"%s(%d:%d:%d:%d:%d)\t",
393                     ic->filename,ic->lineno,
394                     ic->seq,ic->key,ic->depth,ic->supportRtn);
395     icTab->iCodePrint(of,ic,icTab->printName);
396     return 1;
397 }
398
399 /*-----------------------------------------------------------------*/
400 /* printiCChain - prints intermediate code for humans              */
401 /*-----------------------------------------------------------------*/
402 void printiCChain (iCode *icChain, FILE *of)
403 {
404     iCode *loop ;
405     iCodeTable *icTab ;
406
407     if (!of)
408         of = stdout;
409     for ( loop = icChain ; loop ; loop = loop->next ) {
410         if ((icTab = getTableEntry (loop->op ))) {
411             fprintf(of,"%s(%d:%d:%d:%d:%d)\t",
412                     loop->filename,loop->lineno,
413                     loop->seq,loop->key,loop->depth,loop->supportRtn);
414
415             icTab->iCodePrint (of,loop,icTab->printName);
416         }
417     }
418 }
419
420
421 /*-----------------------------------------------------------------*/
422 /* newOperand - allocate, init & return a new iCode                */
423 /*-----------------------------------------------------------------*/
424 operand *newOperand ()
425 {
426     operand *op ;
427     
428     ALLOC(op,sizeof(operand));
429     
430     op->key = 0 ;
431     return op;
432 }
433
434 /*-----------------------------------------------------------------*/
435 /* newiCode - create and return a new iCode entry initialised      */
436 /*-----------------------------------------------------------------*/
437 iCode *newiCode (int op, operand *left, operand *right)
438 {
439     iCode *ic ;
440     
441     ALLOC(ic,sizeof(iCode));
442    
443     ic->lineno = lineno ;
444     ic->filename= filename ;
445     ic->block = block;
446     ic->level = scopeLevel;
447     ic->op = op;
448     ic->key= iCodeKey++ ;
449     IC_LEFT(ic) = left;
450     IC_RIGHT(ic)= right;
451
452     return ic;
453 }       
454
455 /*-----------------------------------------------------------------*/
456 /* newiCode for conditional statements                             */
457 /*-----------------------------------------------------------------*/
458 iCode *newiCodeCondition (operand *condition,
459                           symbol  *trueLabel, 
460                           symbol  *falseLabel )
461 {
462     iCode *ic ;
463     
464     ic = newiCode(IFX,NULL,NULL);
465     IC_COND(ic) = condition ;
466     IC_TRUE(ic) = trueLabel ;
467     IC_FALSE(ic) = falseLabel;
468     return ic;
469 }
470
471 /*-----------------------------------------------------------------*/
472 /* newiCodeLabelGoto - unconditional goto statement| label stmnt   */
473 /*-----------------------------------------------------------------*/
474 iCode *newiCodeLabelGoto (int op, symbol *label)
475 {
476     iCode *ic ;
477     
478     ic = newiCode(op,NULL,NULL);
479     ic->op = op ;
480     ic->argLabel.label = label ;
481     IC_LEFT(ic) = NULL ;
482     IC_RIGHT(ic) = NULL ;
483     IC_RESULT(ic) = NULL ;
484     return ic;
485 }
486
487 /*-----------------------------------------------------------------*/
488 /* newiTemp - allocate & return a newItemp Variable                */
489 /*-----------------------------------------------------------------*/
490 symbol *newiTemp (char *s)
491
492     symbol *itmp;
493     
494     if (s) 
495         sprintf(buffer,"%s",s);
496     else
497         sprintf (buffer,"iTemp%d",iTempNum++);  
498     itmp =  newSymbol (buffer,1);
499     strcpy(itmp->rname,itmp->name);
500     itmp->isitmp = 1;
501     
502     return itmp;
503 }
504
505 /*-----------------------------------------------------------------*/
506 /* newiTempLabel - creates a temp variable label                   */
507 /*-----------------------------------------------------------------*/
508 symbol *newiTempLabel (char *s)
509 {
510     symbol *itmplbl;
511
512     /* check if this alredy exists */
513     if (s && (itmplbl = findSym(LabelTab, NULL, s)))
514         return itmplbl ;
515
516     if (s) 
517         itmplbl = newSymbol(s,1);
518     else {
519         sprintf(buffer,"iTempLbl%d",iTempLblNum++);
520         itmplbl = newSymbol(buffer,1);  
521     }
522     
523     itmplbl->isitmp = 1;
524     itmplbl->islbl = 1;
525     itmplbl->key = labelKey++ ;
526     addSym (LabelTab, itmplbl, itmplbl->name,0,0);
527     return itmplbl ;  
528 }
529
530 /*-----------------------------------------------------------------*/
531 /* newiTempPreheaderLabel - creates a new preheader label          */
532 /*-----------------------------------------------------------------*/
533 symbol *newiTempPreheaderLabel()
534 {
535     symbol *itmplbl ;
536
537     sprintf(buffer,"preHeaderLbl%d",iTempLblNum++);
538     itmplbl = newSymbol(buffer,1);    
539     
540     itmplbl->isitmp = 1;
541     itmplbl->islbl = 1;
542     itmplbl->key = labelKey++ ;
543     addSym (LabelTab, itmplbl, itmplbl->name,0,0);
544     return itmplbl ;  
545 }
546
547
548 /*-----------------------------------------------------------------*/
549 /* initiCode - initialises some iCode related stuff                */
550 /*-----------------------------------------------------------------*/
551 void initiCode ()
552 {
553
554 }
555
556 /*-----------------------------------------------------------------*/
557 /* getTableEntry - gets the table entry for the given operator     */
558 /*-----------------------------------------------------------------*/
559 iCodeTable *getTableEntry (int oper )
560 {
561     int i ;
562     
563     for ( i = 0 ; i < (sizeof(codeTable)/sizeof(iCodeTable)); i++ ) 
564         if (oper == codeTable[i].icode)
565             return &codeTable[i] ;
566     
567     return NULL ;
568 }
569
570 /*-----------------------------------------------------------------*/
571 /* newiTempOperand - new intermediate temp operand                 */
572 /*-----------------------------------------------------------------*/
573 operand *newiTempOperand (link *type, char throwType)
574 {
575     symbol *itmp;
576     operand *op = newOperand();
577     link *etype;
578
579     op->type = SYMBOL ;
580     itmp = newiTemp(NULL);
581
582     etype = getSpec(type);
583
584     if (IS_LITERAL(etype) )
585         throwType = 0 ;
586
587     /* copy the type information */
588     if (type) 
589         itmp->etype = getSpec (itmp->type = (throwType ? type :
590                                              copyLinkChain(type)));
591     if (IS_LITERAL(itmp->etype)) {
592         SPEC_SCLS(itmp->etype) = S_REGISTER ;
593         SPEC_OCLS(itmp->etype) = reg;
594     }
595         
596     op->operand.symOperand = itmp;
597     op->key = itmp->key = ++operandKey ;
598     return op;
599 }
600
601 /*-----------------------------------------------------------------*/
602 /* operandType - returns the type chain for an operand             */
603 /*-----------------------------------------------------------------*/
604 link *operandType (operand *op) 
605 {
606     /* depending on type of operand */
607     switch (op->type) {
608         
609     case VALUE :
610         return op->operand.valOperand->type ;
611         
612     case SYMBOL:
613         return op->operand.symOperand->type ;
614         
615     case TYPE :
616         return op->operand.typeOperand ;
617     }
618     
619     werror (E_INTERNAL_ERROR,__FILE__,__LINE__,
620             " operand type not known ");
621     assert (0) ; /* should never come here */
622     /*  Just to keep the compiler happy */
623     return (link *)0;
624 }
625
626 /*-----------------------------------------------------------------*/
627 /* isParamterToCall - will return 1 if op is a parameter to args   */
628 /*-----------------------------------------------------------------*/
629 int isParameterToCall (value *args, operand *op)
630 {
631     value *tval = args ;
632
633     while (tval) {
634         if (tval->sym && 
635             isSymbolEqual(op->operand.symOperand,tval->sym))
636             return 1;
637         tval = tval->next ;
638     }
639     return 0;
640 }
641
642 /*-----------------------------------------------------------------*/
643 /* isOperandGlobal   - return 1 if operand is a global variable    */
644 /*-----------------------------------------------------------------*/
645 int isOperandGlobal ( operand *op )
646 {
647     if (!op)
648         return 0;
649
650     if (IS_ITEMP(op))
651         return 0;
652
653     if (op->type == SYMBOL &&       
654          (op->operand.symOperand->level == 0 ||  
655          IS_STATIC(op->operand.symOperand->etype) ||
656          IS_EXTERN(op->operand.symOperand->etype))
657           )
658         return 1;
659     
660     return 0;
661 }
662
663 /*-----------------------------------------------------------------*/
664 /* isOperandVolatile - return 1 if the operand is volatile         */
665 /*-----------------------------------------------------------------*/
666 int isOperandVolatile ( operand *op , bool chkTemp)
667 {
668     link *optype ;
669     link *opetype ;
670
671     if (IS_ITEMP(op) && !chkTemp)
672         return 0;
673
674     opetype = getSpec(optype = operandType(op));
675     
676     if (IS_PTR(optype) && DCL_PTR_VOLATILE(optype))
677         return 1;
678
679     if (IS_VOLATILE(opetype))
680         return 1;
681     return 0;
682 }
683
684 /*-----------------------------------------------------------------*/
685 /* isOperandLiteral - returns 1 if an operand contains a literal   */
686 /*-----------------------------------------------------------------*/
687 int isOperandLiteral ( operand *op )
688 {
689     link *opetype ;
690     
691     if (!op)
692         return 0;
693     
694     opetype = getSpec (operandType(op));
695
696     if (IS_LITERAL(opetype))
697         return 1;
698
699     return 0;
700 }
701 /*-----------------------------------------------------------------*/
702 /* isOperandInFarSpace - will return true if operand is in farSpace*/
703 /*-----------------------------------------------------------------*/
704 bool isOperandInFarSpace (operand *op)
705 {
706     link *etype;
707
708     if (!op)
709         return FALSE;
710
711     if (!IS_SYMOP(op))
712         return FALSE ;
713
714     if (!IS_TRUE_SYMOP(op)) {
715         if (SPIL_LOC(op))
716             etype = SPIL_LOC(op)->etype;
717         else            
718             return FALSE;
719     }
720
721     etype = getSpec(operandType(op));
722     return (IN_FARSPACE(SPEC_OCLS(etype)) ? TRUE : FALSE);
723 }
724
725 /*-----------------------------------------------------------------*/
726 /* operandLitValue - literal value of an operand                   */
727 /*-----------------------------------------------------------------*/
728 double operandLitValue ( operand *op )
729 {
730     assert(isOperandLiteral(op));
731     
732     return floatFromVal(op->operand.valOperand);    
733 }
734
735 /*-----------------------------------------------------------------*/
736 /* operandOperation - perforoms operations on operands             */
737 /*-----------------------------------------------------------------*/
738 operand *operandOperation (operand *left,operand *right,
739                            int op, link *type)
740 {
741     operand *retval = (operand *)0;
742         
743     assert(isOperandLiteral(left));
744     if (right) 
745         assert(isOperandLiteral(right));
746     
747     switch (op) {
748     case '+' :
749         retval =  operandFromValue (valCastLiteral(type,
750                                                    operandLitValue(left) + 
751                                                    operandLitValue(right)));
752         break ;
753     case '-' :
754         retval = operandFromValue(valCastLiteral(type,
755                                                  operandLitValue(left) -
756                                                  operandLitValue(right)));
757         break;
758     case '*':
759         retval = operandFromValue(valCastLiteral(type,
760                                                  operandLitValue(left) *
761                                                  operandLitValue(right)));
762         break;
763     case '/':
764         if ((unsigned long) operandLitValue(right) == 0){           
765             werror(E_DIVIDE_BY_ZERO);
766             retval = right;
767             
768         }
769         else
770             retval = operandFromValue (valCastLiteral(type,
771                                                       operandLitValue(left) /
772                                                       operandLitValue(right)));
773         break;
774     case '%':      
775         if ((unsigned long) operandLitValue(right) == 0){           
776             werror(E_DIVIDE_BY_ZERO);
777             retval = right;         
778         }
779         else
780             retval = operandFromLit ((unsigned long) operandLitValue(left) %
781                                      (unsigned long) operandLitValue(right));
782         break;
783     case LEFT_OP :
784         retval = operandFromLit ((unsigned long) operandLitValue(left) <<
785                                  (unsigned long) operandLitValue(right));
786         break;
787     case RIGHT_OP :
788         retval = operandFromLit ((unsigned long) operandLitValue(left) >>
789                                  (unsigned long) operandLitValue(right));
790         break;
791     case EQ_OP :
792         retval = operandFromLit (operandLitValue(left) ==
793                                  operandLitValue(right));
794         break;
795     case '<' :
796         retval = operandFromLit (operandLitValue(left) <
797                                  operandLitValue(right));
798         break;
799     case LE_OP :
800         retval = operandFromLit (operandLitValue(left) <=
801                                  operandLitValue(right));
802         break;
803     case NE_OP :
804         retval = operandFromLit (operandLitValue(left) !=
805                                  operandLitValue(right));
806         break;
807     case '>' :
808         retval = operandFromLit (operandLitValue(left) >
809                                  operandLitValue(right));
810         break;
811     case GE_OP :
812         retval = operandFromLit (operandLitValue(left) >=
813                                  operandLitValue(right));
814         break;
815     case BITWISEAND :
816         retval = operandFromLit ((unsigned long) operandLitValue(left) &
817                                  (unsigned long) operandLitValue(right));
818         break;
819     case '|' :
820         retval = operandFromLit ((unsigned long) operandLitValue(left) |
821                                  (unsigned long) operandLitValue(right));       
822         break;
823     case '^' :
824         retval = operandFromLit ((unsigned long) operandLitValue(left) ^
825                                  (unsigned long) operandLitValue(right));
826         break;
827     case AND_OP:
828         retval = operandFromLit (operandLitValue(left) &&
829                                  operandLitValue(right));
830         break;
831     case OR_OP:
832         retval = operandFromLit (operandLitValue(left) ||
833                                  operandLitValue(right));
834         break;
835     case RRC:
836         {
837             long i = operandLitValue(left);
838             
839             retval = operandFromLit ((i >> (getSize(operandType(left))*8 - 1)) |
840                                      (i << 1));
841         }
842         break;
843     case RLC:
844         {
845             long i = operandLitValue(left);
846             
847             retval = operandFromLit ((i << (getSize(operandType(left))*8 - 1)) |
848                                      (i >> 1));
849         }
850         break;
851         
852     case UNARYMINUS:
853         retval = operandFromLit(-1 * operandLitValue(left));
854         break;
855         
856     case '~':
857         retval = operandFromLit(~ ((long) operandLitValue(left)));
858         break;
859
860     case '!':
861         retval = operandFromLit(! operandLitValue(left));
862         break;
863
864     default :
865         werror(E_INTERNAL_ERROR,__FILE__,__LINE__,
866                " operandOperation invalid operator ");
867         assert (0);
868     }
869     
870     return retval;
871 }
872
873
874 /*-----------------------------------------------------------------*/
875 /* isOperandEqual - compares two operand & return 1 if they r =    */
876 /*-----------------------------------------------------------------*/
877 int isOperandEqual (operand *left, operand *right)
878 {
879     /* if the pointers are equal then they are equal */
880     if ( left == right )
881         return 1;
882     
883     /* if either of them null then false */
884     if ( !left || !right)
885         return 0;
886
887     if (left->type != right->type)
888         return 0;
889
890     if (IS_SYMOP(left) && IS_SYMOP(right))
891         return left->key == right->key ;
892
893     /* if types are the same */
894     switch (left->type) {
895     case SYMBOL :
896         return isSymbolEqual(left->operand.symOperand,
897                              right->operand.symOperand);
898     case VALUE :
899         return (floatFromVal(left->operand.valOperand) ==
900                 floatFromVal(right->operand.valOperand));
901     case TYPE :
902         if (checkType(left->operand.typeOperand,
903                       right->operand.typeOperand) == 1)
904             return 1;      
905     }
906
907     return 0;
908 }
909
910 /*-----------------------------------------------------------------*/
911 /* isiCodeEqual - comapres two iCodes are returns true if yes      */
912 /*-----------------------------------------------------------------*/
913 int isiCodeEqual (iCode *left, iCode *right)
914 {
915     /* if the same pointer */
916     if (left == right)
917         return 1;
918     
919     /* if either of them null */
920     if (!left || !right)
921         return 0;
922
923     /* if operand are the same */
924     if ( left->op == right->op ) {
925         
926         /* compare all the elements depending on type */
927         if (left->op != IFX ) {
928             if (!isOperandEqual(IC_LEFT(left),IC_LEFT(right)))
929                 return 0;
930             if (!isOperandEqual(IC_RIGHT(left),IC_RIGHT(right)))
931                 return 0;
932
933         } else {
934             if (!isOperandEqual(IC_COND(left),IC_COND(right)))
935                 return 0;
936             if (!isSymbolEqual (IC_TRUE(left),IC_TRUE(right)))
937                 return 0;
938             if (!isSymbolEqual(IC_FALSE(left),IC_FALSE(right)))
939                 return 0;
940         }
941         return 1;
942     }
943     return 0;
944 }
945
946 /*-----------------------------------------------------------------*/
947 /* operand from operand - creates an operand holder for the type   */
948 /*-----------------------------------------------------------------*/
949 operand *operandFromOperand (operand *op)
950 {
951     operand *nop = newOperand();
952     
953     nop->type = op->type;
954     nop->isaddr = op->isaddr ;
955     nop->key = op->key ;
956     nop->isvolatile = op->isvolatile ;
957     nop->isGlobal = op->isGlobal ;
958     nop->isLiteral= op->isLiteral ;
959     nop->noSpilLoc= op->noSpilLoc;
960     nop->usesDefs = op->usesDefs;
961     nop->isParm = op->isParm;
962     nop->parmBytes = op->parmBytes;
963
964     switch (nop->type) {
965     case SYMBOL :
966         nop->operand.symOperand = op->operand.symOperand ;      
967         break;
968     case VALUE :
969         nop->operand.valOperand = op->operand.valOperand;
970         break;
971     case TYPE :
972         nop->operand.typeOperand = op->operand.typeOperand ;
973         break ;
974     }   
975
976     return nop;
977 }
978
979 /*-----------------------------------------------------------------*/
980 /* opFromOpWithDU - makes a copy of the operand and DU chains      */
981 /*-----------------------------------------------------------------*/
982 operand *opFromOpWithDU (operand *op, bitVect *defs, bitVect *uses)
983 {
984     operand *nop = operandFromOperand(op);
985
986     if (nop->type == SYMBOL) {
987         OP_SYMBOL(nop)->defs = bitVectCopy(defs);
988         OP_SYMBOL(nop)->uses = bitVectCopy(uses);
989     }
990
991     return nop;
992 }
993
994 /*-----------------------------------------------------------------*/
995 /* operandFromSymbol - creates an operand from a symbol            */
996 /*-----------------------------------------------------------------*/
997 operand *operandFromSymbol (symbol *sym)
998 {
999     operand *op ;
1000     iCode *ic ;
1001     
1002     /* if the symbol's type is a literal */
1003     /* then it is an enumerator type     */
1004     if (IS_LITERAL(sym->etype) && SPEC_ENUM(sym->etype)) 
1005         return operandFromValue (valFromType(sym->etype));
1006
1007     if (!sym->key)
1008         sym->key = ++operandKey ;
1009
1010     /* if this an implicit variable, means struct/union */
1011     /* member so just return it                         */
1012     if (sym->implicit || IS_FUNC(sym->type)) {
1013         op = newOperand();
1014         op->type = SYMBOL ;
1015         op->operand.symOperand = sym;
1016         op->key = sym->key ;
1017         op->isvolatile = isOperandVolatile(op,TRUE);
1018         op->isGlobal   = isOperandGlobal(op);
1019         return op;
1020     }
1021     
1022     /* under the following conditions create a
1023        register equivalent for a local symbol */
1024     if (!IS_AGGREGATE(sym->type) &&     /* not an aggregate */
1025         !IS_FUNC(sym->type)      &&     /* not a function   */
1026         !sym->_isparm            &&     /* not a parameter  */
1027         sym->level               &&     /* is a local variable */
1028         !sym->addrtaken          &&     /* whose address has not been taken */
1029         !sym->reqv               &&     /* does not already have a register euivalence */
1030         !IS_VOLATILE(sym->etype) &&     /* not declared as volatile */
1031         !IS_STATIC(sym->etype)   &&     /* and not declared static  */
1032         !sym->islbl              &&
1033         !IN_FARSPACE(SPEC_OCLS(sym->etype))) {     /* not a label */
1034         
1035         /* we will use it after all optimizations
1036            and before liveRange calculation */
1037         sym->reqv = newiTempOperand(sym->type,0);       
1038         sym->reqv->key = sym->key ;
1039         OP_SYMBOL(sym->reqv)->key = sym->key;
1040         OP_SYMBOL(sym->reqv)->isreqv = 1;
1041         OP_SYMBOL(sym->reqv)->islocal = 1;
1042         SPIL_LOC(sym->reqv) = sym;
1043     }
1044
1045     if (!IS_AGGREGATE(sym->type)) {
1046         op = newOperand();
1047         op->type = SYMBOL;
1048         op->operand.symOperand = sym;
1049         op->isaddr = 1;
1050         op->key = sym->key;
1051         op->isvolatile = isOperandVolatile(op,TRUE);
1052         op->isGlobal   = isOperandGlobal(op);
1053         op->isPtr = IS_PTR(operandType(op));
1054         op->isParm = sym->_isparm ;
1055         return op;
1056     }
1057     
1058     /* create :-                     */
1059     /*    itemp = &[_symbol]         */
1060     
1061     ic = newiCode(ADDRESS_OF,newOperand(),NULL);
1062     IC_LEFT(ic)->type = SYMBOL ;
1063     IC_LEFT(ic)->operand.symOperand = sym ;
1064     IC_LEFT(ic)->key = sym->key;    
1065     (IC_LEFT(ic))->isvolatile = isOperandVolatile(IC_LEFT(ic),TRUE);
1066     (IC_LEFT(ic))->isGlobal   = isOperandGlobal(IC_LEFT(ic));
1067     IC_LEFT(ic)->isPtr = IS_PTR(operandType(IC_LEFT(ic)));
1068
1069     /* create result */
1070     IC_RESULT(ic) = newiTempOperand(sym->type,0);
1071     if (IS_ARRAY(sym->type)) {
1072         IC_RESULT(ic) = geniCodeArray2Ptr (IC_RESULT(ic));
1073         IC_RESULT(ic)->isaddr = 0;
1074     } else
1075         IC_RESULT(ic)->isaddr = (!IS_AGGREGATE(sym->type));
1076
1077     IC_RESULT(ic)->operand.symOperand->args = sym->args;
1078
1079     ADDTOCHAIN(ic);
1080     
1081     return IC_RESULT(ic) ;
1082 }
1083
1084 /*-----------------------------------------------------------------*/
1085 /* operandFromValue - creates an operand from value                */
1086 /*-----------------------------------------------------------------*/
1087 operand *operandFromValue (value *val)
1088 {
1089     operand *op ;
1090     
1091     /* if this is a symbol then do the symbol thing */
1092     if (val->sym)
1093         return operandFromSymbol (val->sym);
1094     
1095     /* this is not a symbol */
1096     op = newOperand();
1097     op->type = VALUE ;
1098     op->operand.valOperand = val ;
1099     op->isLiteral = isOperandLiteral(op);
1100     return op;
1101 }
1102
1103 /*-----------------------------------------------------------------*/
1104 /* operandFromLink - operand from typeChain                        */
1105 /*-----------------------------------------------------------------*/
1106 operand *operandFromLink (link *type)
1107 {
1108     operand *op ;
1109     
1110     /* operand from link */
1111     if ( ! type )
1112         return NULL ;
1113     
1114     op = newOperand();
1115     op->type = TYPE ;
1116     op->operand.typeOperand = copyLinkChain(type);
1117     return op;
1118 }
1119
1120 /*-----------------------------------------------------------------*/
1121 /* operandFromLit - makes an operand from a literal value          */
1122 /*-----------------------------------------------------------------*/
1123 operand *operandFromLit ( float i)
1124 {
1125     return operandFromValue (valueFromLit (i));
1126 }
1127
1128 /*-----------------------------------------------------------------*/
1129 /* operandFromAst - creates an operand from an ast                 */
1130 /*-----------------------------------------------------------------*/
1131 operand *operandFromAst ( ast *tree )
1132 {
1133     
1134     if (! tree )
1135         return NULL ;
1136     
1137     /* depending on type do */
1138     switch (tree->type ) {      
1139     case EX_OP : 
1140         return ast2iCode (tree) ;    
1141         break ;
1142         
1143     case EX_VALUE :
1144         return operandFromValue(tree->opval.val) ;
1145         break ;
1146         
1147     case EX_LINK :
1148         return operandFromLink (tree->opval.lnk) ; 
1149     }
1150     
1151     assert(0);
1152     /*  Just to keep the comiler happy */
1153     return (operand *)0;
1154 }
1155
1156 /*-----------------------------------------------------------------*/
1157 /* setOperandType - sets the operand's type to the given type      */
1158 /*-----------------------------------------------------------------*/
1159 void setOperandType (operand *op, link *type)
1160 {
1161     /* depending on the type of operand */
1162     switch (op->type) {
1163         
1164     case VALUE :
1165         op->operand.valOperand->etype = 
1166             getSpec( op->operand.valOperand->type = 
1167                      copyLinkChain (type )) ;
1168         return ;
1169         
1170     case SYMBOL :
1171         if (op->operand.symOperand->isitmp )
1172             op->operand.symOperand->etype = 
1173                 getSpec( op->operand.symOperand->type = 
1174                          copyLinkChain (type )) ;
1175         else
1176             werror (E_INTERNAL_ERROR,__FILE__,__LINE__,
1177                     "attempt to modify type of source");
1178         return;
1179         
1180     case TYPE:
1181         op->operand.typeOperand = copyLinkChain (type);
1182         return ;
1183     }
1184     
1185 }
1186
1187 /*-----------------------------------------------------------------*/
1188 /* geniCodeValueAtAddress - generate intermeditate code for value  */
1189 /*                          at address                             */
1190 /*-----------------------------------------------------------------*/
1191 operand *geniCodeRValue (operand *op, bool force)
1192 {
1193     iCode *ic ;
1194     link *type = operandType(op);
1195     link *etype= getSpec(type);
1196     
1197     /* if this is an array & already */
1198     /* an address then return this   */
1199     if (IS_AGGREGATE(type) || 
1200         (IS_PTR(type) && !force && !op->isaddr))
1201         return operandFromOperand(op);
1202         
1203     /* if this is not an address then must be */
1204     /* rvalue already so return this one      */
1205     if (!op->isaddr)
1206         return op ;
1207     
1208     /* if this is not a temp symbol then */
1209     if (!IS_ITEMP(op) && 
1210         !force        && 
1211         !IN_FARSPACE(SPEC_OCLS(etype))) {
1212         op = operandFromOperand(op);
1213         op->isaddr = 0;
1214         return op;
1215     }
1216     
1217     if (IS_SPEC(type) && 
1218         IS_TRUE_SYMOP(op) &&
1219         !IN_FARSPACE(SPEC_OCLS(etype))) {
1220         op = operandFromOperand(op);
1221         op->isaddr = 0;
1222         return op;
1223     }
1224
1225     ic = newiCode(GET_VALUE_AT_ADDRESS,op,NULL);
1226     if (IS_PTR(type) && op->isaddr && force) 
1227         type = type->next;
1228     
1229     type = copyLinkChain(type);
1230
1231     IC_RESULT(ic) = newiTempOperand (type,1);
1232     IC_RESULT(ic)->isaddr = 0;
1233  
1234 /*     ic->supportRtn = ((IS_GENPTR(type) | op->isGptr) & op->isaddr); */
1235
1236     /* if the right is a symbol */
1237     if (op->type == SYMBOL)
1238         IC_RESULT(ic)->operand.symOperand->args = 
1239             op->operand.symOperand->args ;
1240     ADDTOCHAIN(ic);
1241     
1242     return IC_RESULT(ic) ;
1243 }
1244
1245 /*-----------------------------------------------------------------*/
1246 /* geniCodeCast - changes the value from one type to another       */
1247 /*-----------------------------------------------------------------*/
1248 operand *geniCodeCast (link *type, operand *op, bool implicit) 
1249 {
1250     iCode *ic ;
1251     link *optype ;
1252     link *opetype = getSpec(optype = operandType(op));
1253     link *restype ;
1254     
1255     /* one of them has size zero then error */
1256     if (IS_VOID(optype)) {
1257         werror(E_CAST_ZERO);
1258         return op;
1259     }
1260
1261     /* if the operand is already the desired type then do nothing */
1262     if ( checkType (type,optype) == 1)  
1263         return op;
1264     
1265     /* if this is a literal then just change the type & return */
1266     if (IS_LITERAL(opetype) && !IS_PTR(type) && !IS_PTR(optype))
1267         return operandFromValue(valCastLiteral(type,
1268                                                operandLitValue(op)));
1269           
1270     /* if casting to some pointer type &&
1271        the destination is not a generic pointer 
1272        then give a warning : (only for implicit casts)*/
1273     if (IS_PTR(optype) && implicit &&
1274         (DCL_TYPE(optype) != DCL_TYPE(type)) && 
1275         !IS_GENPTR(type)) {
1276         werror(E_INCOMPAT_CAST);
1277         werror(E_CONTINUE,"from type '");
1278         printTypeChain(optype,stderr);fprintf(stderr,"' to type '");      
1279         printTypeChain(type,stderr);fprintf(stderr,"'\n");
1280     }
1281
1282     /* if they are the same size create an assignment */
1283     if (getSize(type) == getSize(optype) && 
1284         !IS_BITFIELD(type)               &&
1285         !IS_FLOAT(type)                  &&
1286         !IS_FLOAT(optype)                &&
1287         ((IS_SPEC(type) && IS_SPEC(optype)) ||
1288          (!IS_SPEC(type) && !IS_SPEC(optype)))) {
1289
1290         ic = newiCode('=',NULL,op);     
1291         IC_RESULT(ic) = newiTempOperand(type,0);
1292          SPIL_LOC(IC_RESULT(ic))  =
1293              (IS_TRUE_SYMOP(op) ? OP_SYMBOL(op) : NULL);
1294         IC_RESULT(ic)->isaddr = 0;
1295     } else { 
1296         ic = newiCode(CAST,operandFromLink(type),
1297                       geniCodeRValue(op,FALSE));
1298         
1299         IC_RESULT(ic)= newiTempOperand(type,0);
1300     }
1301     
1302     /* preserve the storage class & output class */
1303     /* of the original variable                  */
1304     restype = getSpec(operandType(IC_RESULT(ic)));
1305     SPEC_SCLS(restype) = SPEC_SCLS(opetype);
1306     SPEC_OCLS(restype) = SPEC_OCLS(opetype);
1307     
1308     ADDTOCHAIN(ic);
1309     return IC_RESULT(ic) ;
1310 }
1311
1312 /*-----------------------------------------------------------------*/
1313 /* geniCodeLabel - will create a Label                             */
1314 /*-----------------------------------------------------------------*/
1315 void geniCodeLabel (symbol *label)
1316 {
1317     iCode *ic;
1318     
1319     ic = newiCodeLabelGoto(LABEL,label);
1320     ADDTOCHAIN(ic);
1321 }
1322
1323 /*-----------------------------------------------------------------*/
1324 /* geniCodeGoto  - will create a Goto                              */
1325 /*-----------------------------------------------------------------*/
1326 void geniCodeGoto (symbol *label)
1327 {
1328     iCode *ic;
1329     
1330     ic = newiCodeLabelGoto(GOTO,label);
1331     ADDTOCHAIN(ic);
1332 }
1333
1334 /*-----------------------------------------------------------------*/
1335 /* geniCodeMultiply - gen intermediate code for multiplication     */
1336 /*-----------------------------------------------------------------*/
1337 operand *geniCodeMultiply (operand *left, operand *right)
1338
1339     iCode *ic ;
1340     int p2 = 0;
1341     link *resType ;
1342     LRTYPE ;
1343     
1344     /* if they are both literal then we know the result */
1345     if (IS_LITERAL(letype) && IS_LITERAL(retype)) 
1346         return operandFromValue (valMult(left->operand.valOperand,
1347                                          right->operand.valOperand));
1348         
1349     resType = computeType (ltype,rtype) ;
1350     left = geniCodeCast(resType,left,TRUE);
1351     right= geniCodeCast(resType,right,TRUE);
1352     
1353     /* if the right is a literal & power of 2 */
1354     /* then make it a left shift              */
1355     if (IS_LITERAL(retype) && !IS_FLOAT(letype) &&
1356         (p2 = powof2 ((unsigned long)floatFromVal(right->operand.valOperand)))) 
1357         ic = newiCode(LEFT_OP, left,operandFromLit(p2)); /* left shift */
1358     else {
1359         ic = newiCode('*',left,right);  /* normal multiplication */
1360         /* if the size left or right > 1 then support routine */
1361         if (getSize(ltype) > 1 || getSize(rtype) > 1)
1362             ic->supportRtn = 1;
1363
1364     }
1365     IC_RESULT(ic) = newiTempOperand(resType,1);
1366     
1367     ADDTOCHAIN(ic);
1368     return IC_RESULT(ic) ;
1369 }
1370
1371 /*-----------------------------------------------------------------*/
1372 /* geniCodeDivision - gen intermediate code for division           */
1373 /*-----------------------------------------------------------------*/
1374 operand *geniCodeDivision (operand *left, operand *right)
1375
1376     iCode *ic ;
1377     int p2 = 0;
1378     link *resType;
1379     link *rtype = operandType(right);
1380     link *retype= getSpec(rtype);
1381     link *ltype = operandType(left);
1382     link *letype= getSpec(ltype);
1383     
1384     resType = computeType (ltype,rtype) ;
1385     left = geniCodeCast(resType,left,TRUE);
1386     right= geniCodeCast(resType,right,TRUE);
1387     
1388     /* if the right is a literal & power of 2 */
1389     /* then make it a right shift             */
1390     if (IS_LITERAL(retype) && 
1391         !IS_FLOAT(letype)  &&
1392         (p2 = powof2 ((unsigned long) 
1393                       floatFromVal(right->operand.valOperand)))) 
1394         ic = newiCode(RIGHT_OP, left,operandFromLit(p2)); /* right shift */
1395     else {
1396         ic = newiCode('/',left,right);  /* normal division */
1397         /* if the size left or right > 1 then support routine */
1398         if (getSize(ltype) > 1 || getSize(rtype) > 1)
1399             ic->supportRtn = 1;
1400     }
1401     IC_RESULT(ic) = newiTempOperand(resType,0);
1402     
1403     ADDTOCHAIN(ic);
1404     return IC_RESULT(ic) ;
1405 }
1406 /*-----------------------------------------------------------------*/
1407 /* geniCodeModulus  - gen intermediate code for modulus            */
1408 /*-----------------------------------------------------------------*/
1409 operand *geniCodeModulus (operand *left, operand *right)
1410
1411     iCode *ic ;
1412     link *resType;
1413     LRTYPE ;
1414     
1415     /* if they are both literal then we know the result */
1416     if (IS_LITERAL(letype) && IS_LITERAL(retype)) 
1417         return operandFromValue (valMod(left->operand.valOperand,
1418                                         right->operand.valOperand));
1419     
1420     resType = computeType (ltype,rtype) ;
1421     left = geniCodeCast(resType,left,TRUE);
1422     right= geniCodeCast(resType,right,TRUE);
1423     
1424     /* now they are the same size */
1425     ic = newiCode('%',left,right);
1426
1427     /* if the size left or right > 1 then support routine */
1428     if (getSize(ltype) > 1 || getSize(rtype) > 1)
1429         ic->supportRtn = 1;
1430     IC_RESULT(ic) = newiTempOperand(resType,0);
1431     
1432     ADDTOCHAIN(ic);
1433     return IC_RESULT(ic) ;
1434 }
1435
1436 /*-----------------------------------------------------------------*/
1437 /* geniCodePtrPtrSubtract - subtracts pointer from pointer         */
1438 /*-----------------------------------------------------------------*/
1439 operand *geniCodePtrPtrSubtract (operand *left, operand *right)
1440 {
1441     iCode *ic ;
1442     operand *result;
1443     LRTYPE ;
1444     
1445     /* if they are both literals then */
1446     if (IS_LITERAL(letype) && IS_LITERAL(retype)) {
1447         result = operandFromValue (valMinus(left->operand.valOperand,
1448                                             right->operand.valOperand));
1449         goto subtractExit;
1450     }
1451     
1452     ic = newiCode('-',left,right);
1453     
1454     IC_RESULT(ic) = result = newiTempOperand(newIntLink(),1);
1455     ADDTOCHAIN(ic);
1456     
1457  subtractExit:
1458     return geniCodeDivision (result,
1459                              operandFromLit(getSize(ltype->next)));   
1460 }
1461
1462 /*-----------------------------------------------------------------*/
1463 /* geniCodeSubtract - generates code for subtraction               */
1464 /*-----------------------------------------------------------------*/
1465 operand *geniCodeSubtract (operand *left, operand *right)
1466 {
1467     iCode *ic ;
1468     int isarray= 0;
1469     link *resType;
1470     LRTYPE ;
1471     
1472     /* if they both pointers then */
1473     if ((IS_PTR(ltype) || IS_ARRAY(ltype)) &&
1474         (IS_PTR(rtype) || IS_ARRAY(rtype)))
1475         return geniCodePtrPtrSubtract (left,right);
1476     
1477     /* if they are both literal then we know the result */
1478     if (IS_LITERAL(letype) && IS_LITERAL(retype)) 
1479         return operandFromValue (valMinus(left->operand.valOperand,
1480                                           right->operand.valOperand));
1481     
1482     /* if left is an array or pointer */
1483     if ( IS_PTR(ltype) || IS_ARRAY(ltype) ) {    
1484         isarray = left->isaddr ;    
1485         right = geniCodeMultiply (right,
1486                                   operandFromLit(getSize(ltype->next)));
1487         resType = copyLinkChain(IS_ARRAY(ltype) ? ltype->next : ltype);
1488     }
1489     else { /* make them the same size */
1490         resType = computeType (ltype,rtype) ;
1491         left = geniCodeCast(resType,left,TRUE);
1492         right= geniCodeCast(resType,right,TRUE);    
1493     }
1494     
1495     ic = newiCode('-',left,right);
1496     
1497     IC_RESULT(ic)= newiTempOperand(resType,1);
1498     IC_RESULT(ic)->isaddr = (isarray ? 1 : 0);
1499
1500     /* if left or right is a float */
1501     if (IS_FLOAT(ltype) || IS_FLOAT(rtype))
1502         ic->supportRtn = 1;
1503
1504     ADDTOCHAIN(ic);
1505     return IC_RESULT(ic) ;
1506 }
1507
1508 /*-----------------------------------------------------------------*/
1509 /* geniCodeAdd - generates iCode for addition                      */
1510 /*-----------------------------------------------------------------*/
1511 operand *geniCodeAdd (operand *left, operand *right )
1512 {
1513     iCode *ic ;
1514     link *resType ;
1515     operand *size ;
1516     int isarray = 0;
1517     LRTYPE ;
1518     
1519     /* if left is an array then array access */
1520     if (IS_ARRAY(ltype)) 
1521         return geniCodeArray (left,right);           
1522     
1523     /* if the right side is LITERAL zero */
1524     /* return the left side              */
1525     if (IS_LITERAL(retype) && !floatFromVal(valFromType(retype)))
1526         return left;
1527     
1528     /* if left is literal zero return right */
1529     if (IS_LITERAL(letype) && !floatFromVal(valFromType(letype)))
1530         return right ;
1531     
1532     /* if left is an array or pointer then size */
1533     if (IS_PTR(ltype)) {    
1534         
1535         isarray = left->isaddr;
1536         size = 
1537             operandFromLit(getSize(ltype->next));
1538         right = geniCodeMultiply (right ,size);
1539         resType = copyLinkChain(ltype);
1540     }
1541     else { /* make them the same size */
1542         resType = computeType (ltype,rtype) ;
1543         left = geniCodeCast(resType,left,TRUE);
1544         right= geniCodeCast(resType,right,TRUE);
1545     }
1546     
1547     /* if they are both literals then we know */
1548     if (IS_LITERAL(letype) && IS_LITERAL(retype))
1549         return operandFromValue (valPlus(valFromType(letype),
1550                                          valFromType(retype)));
1551     
1552     ic = newiCode('+',left,right);
1553     
1554     IC_RESULT(ic) = newiTempOperand(resType,1);
1555     IC_RESULT(ic)->isaddr = ( isarray ? 1 : 0);
1556
1557     /* if left or right is a float then support
1558        routine */
1559     if (IS_FLOAT(ltype) || IS_FLOAT(rtype))
1560         ic->supportRtn = 1;
1561
1562     ADDTOCHAIN(ic);
1563     
1564     return IC_RESULT(ic) ;
1565     
1566 }
1567
1568 /*-----------------------------------------------------------------*/
1569 /* aggrToPtr - changes an aggregate to pointer to an aggregate     */
1570 /*-----------------------------------------------------------------*/
1571 link *aggrToPtr ( link *type, bool force)
1572 {
1573     link *etype ;
1574     link *ptype ;
1575
1576     
1577     if (IS_PTR(type) && !force)
1578         return type;
1579
1580     etype = getSpec(type);
1581     ptype = newLink();
1582
1583     ptype->next = type;
1584     /* if the output class is generic */
1585     if (SPEC_OCLS(etype) == generic)
1586         DCL_TYPE(ptype) = GPOINTER;
1587     else
1588         if (SPEC_OCLS(etype)->codesp ) {
1589             DCL_TYPE(ptype) = CPOINTER ;
1590             DCL_PTR_CONST(ptype) = 1;
1591         }
1592         else
1593             if (SPEC_OCLS(etype)->fmap && !SPEC_OCLS(etype)->paged)
1594                 DCL_TYPE(ptype) = FPOINTER ;
1595             else
1596                 if (SPEC_OCLS(etype)->fmap && SPEC_OCLS(etype)->paged)
1597                     DCL_TYPE(ptype) = PPOINTER ;
1598                 else
1599                     if (SPEC_OCLS(etype) == idata)
1600                         DCL_TYPE(ptype) = IPOINTER;
1601                     else
1602                         DCL_TYPE(ptype) = POINTER ;
1603     
1604     /* if the variable was declared a constant */
1605     /* then the pointer points to a constant */
1606     if (IS_CONSTANT(etype) )
1607         DCL_PTR_CONST(ptype) = 1;
1608
1609     /* the variable was volatile then pointer to volatile */
1610     if (IS_VOLATILE(etype))
1611         DCL_PTR_VOLATILE(ptype) = 1;
1612     return ptype; 
1613 }
1614
1615 /*-----------------------------------------------------------------*/
1616 /* geniCodeArray2Ptr - array to pointer                            */
1617 /*-----------------------------------------------------------------*/
1618 operand *geniCodeArray2Ptr (operand *op)
1619 {
1620     link *optype = operandType(op);
1621     link *opetype = getSpec(optype);
1622     
1623     /* set the pointer depending on the storage class */
1624     if (SPEC_OCLS(opetype)->codesp ) {
1625         DCL_TYPE(optype) = CPOINTER ;
1626         DCL_PTR_CONST(optype) = 1;
1627     }
1628     else
1629         if (SPEC_OCLS(opetype)->fmap && !SPEC_OCLS(opetype)->paged)
1630             DCL_TYPE(optype) = FPOINTER ;
1631         else
1632             if (SPEC_OCLS(opetype)->fmap && SPEC_OCLS(opetype)->paged)
1633                 DCL_TYPE(optype) = PPOINTER ;
1634             else
1635                 if (SPEC_OCLS(opetype) == idata)
1636                     DCL_TYPE(optype) = IPOINTER;
1637                 else
1638                     DCL_TYPE(optype) = POINTER ;
1639     
1640     /* if the variable was declared a constant */
1641     /* then the pointer points to a constant */
1642     if (IS_CONSTANT(opetype) )
1643         DCL_PTR_CONST(optype) = 1;
1644
1645     /* the variable was volatile then pointer to volatile */
1646     if (IS_VOLATILE(opetype))
1647         DCL_PTR_VOLATILE(optype) = 1;
1648     op->isaddr = 0;
1649     return op;
1650 }
1651
1652 /*-----------------------------------------------------------------*/
1653 /* geniCodeArray - array access                                    */
1654 /*-----------------------------------------------------------------*/
1655 operand *geniCodeArray (operand *left,operand *right)
1656 {
1657     iCode *ic;
1658     link *ltype = operandType(left);
1659     
1660     if (IS_PTR(ltype)) {
1661         operand *r ;
1662         int olval = lvaluereq ;
1663         lvaluereq = IS_PTR(ltype->next);
1664         r= geniCodeDerefPtr(geniCodeAdd(left,right));
1665         lvaluereq = olval;
1666         return r;
1667     }
1668
1669    /* array access */
1670     right = geniCodeMultiply(right,
1671                              operandFromLit(getSize(ltype->next)));
1672
1673     /* we can check for limits here */
1674     if (isOperandLiteral(right) &&
1675         IS_ARRAY(ltype)         &&
1676         DCL_ELEM(ltype)         &&
1677         (operandLitValue(right)/getSize(ltype->next)) >= DCL_ELEM(ltype)) {
1678         werror(E_ARRAY_BOUND);
1679         right = operandFromLit(0);
1680     }
1681
1682     ic = newiCode('+',left,right);    
1683
1684     IC_RESULT(ic) = newiTempOperand(((IS_PTR(ltype) && 
1685                                       !IS_AGGREGATE(ltype->next) &&
1686                                       !IS_PTR(ltype->next))
1687                                      ? ltype : ltype->next),0);
1688 /*     IC_RESULT(ic) = newiTempOperand(ltype->next,0); */
1689     IC_RESULT(ic)->isaddr = (!IS_AGGREGATE(ltype->next));
1690     ADDTOCHAIN(ic);
1691     return IC_RESULT(ic) ;
1692 }
1693
1694 /*-----------------------------------------------------------------*/
1695 /* geniCodeStruct - generates intermediate code for structres      */
1696 /*-----------------------------------------------------------------*/
1697 operand *geniCodeStruct (operand *left, operand *right, bool islval)
1698 {
1699     iCode *ic ;
1700     link *type = operandType(left);
1701     link *etype = getSpec(type);
1702     link *retype ;
1703     symbol *element = getStructElement(SPEC_STRUCT(etype), 
1704                                        right->operand.symOperand);
1705     
1706     /* add the offset */
1707     ic = newiCode('+',left,operandFromLit(element->offset));
1708     
1709     IC_RESULT(ic) = newiTempOperand(element->type,0);
1710
1711     /* preserve the storage & output class of the struct */
1712     /* as well as the volatile attribute */
1713     retype = getSpec(operandType(IC_RESULT(ic)));
1714     SPEC_SCLS(retype) = SPEC_SCLS(etype);
1715     SPEC_OCLS(retype) = SPEC_OCLS(etype);
1716     SPEC_VOLATILE(retype) |= SPEC_VOLATILE(etype);    
1717
1718     if (IS_PTR(element->type)) 
1719         setOperandType(IC_RESULT(ic),aggrToPtr(operandType(IC_RESULT(ic)),TRUE));
1720     
1721     IC_RESULT(ic)->isaddr = (!IS_AGGREGATE(element->type));
1722
1723     
1724     ADDTOCHAIN(ic);
1725     return (islval ? IC_RESULT(ic) : geniCodeRValue(IC_RESULT(ic),TRUE));
1726 }
1727
1728 /*-----------------------------------------------------------------*/
1729 /* geniCodePostInc - generate int code for Post increment          */
1730 /*-----------------------------------------------------------------*/
1731 operand *geniCodePostInc (operand *op)
1732 {
1733     iCode *ic ;
1734     operand *rOp ;
1735     link *optype = operandType(op);
1736     operand *result ;
1737     operand *rv = (IS_ITEMP(op) ? 
1738                    geniCodeRValue(op,(IS_PTR(optype) ? TRUE : FALSE)) :
1739                    op);            
1740     link *rvtype = operandType(rv);    
1741     int diff = (IS_PTR(rvtype) && DCL_TYPE(optype) != DCL_TYPE(rvtype));
1742     int size = 0;
1743     
1744     /* if this is not an address we have trouble */
1745     if ( ! op->isaddr ) {
1746         werror (E_LVALUE_REQUIRED,"++");
1747         return op ;
1748     }
1749     
1750     rOp = newiTempOperand((diff ? rvtype : optype),0);
1751     rOp->noSpilLoc = 1;
1752
1753     if (IS_ITEMP(rv))
1754         rv->noSpilLoc = 1;
1755
1756     geniCodeAssign(rOp,rv,0);
1757    
1758     size = (IS_PTR(rvtype) ? getSize(rvtype->next) : 1);
1759     ic = newiCode('+',rv,operandFromLit(size));          
1760     IC_RESULT(ic) = result =newiTempOperand((diff ? rvtype : optype),0);
1761     ADDTOCHAIN(ic);
1762
1763     geniCodeAssign(op,result,0);
1764     
1765     return rOp;
1766     
1767 }
1768
1769 /*-----------------------------------------------------------------*/
1770 /* geniCodePreInc - generate code for preIncrement                 */
1771 /*-----------------------------------------------------------------*/
1772 operand *geniCodePreInc (operand *op)
1773 {
1774     iCode *ic ;
1775     link *optype = operandType(op);    
1776     operand *rop = (IS_ITEMP(op) ? 
1777                     geniCodeRValue (op,(IS_PTR(optype) ? TRUE : FALSE)) :
1778                     op);
1779     link *roptype = operandType(rop);
1780     int diff = (IS_PTR(roptype) && (DCL_TYPE(roptype) != DCL_TYPE(optype)));
1781     operand *result;
1782     int size = 0;
1783     
1784     if ( ! op->isaddr ) {
1785         werror(E_LVALUE_REQUIRED,"++");
1786         return op ;
1787     }
1788
1789
1790     size = (IS_PTR(roptype) ? getSize(roptype->next) : 1);
1791     ic = newiCode('+',rop,operandFromLit(size));
1792     IC_RESULT(ic) = result = newiTempOperand((diff ? roptype : optype),0) ;
1793     ADDTOCHAIN(ic);
1794
1795     
1796     return geniCodeAssign(op,result,0) ;
1797 }
1798
1799 /*-----------------------------------------------------------------*/
1800 /* geniCodePostDec - generates code for Post decrement             */
1801 /*-----------------------------------------------------------------*/
1802 operand *geniCodePostDec (operand *op)
1803 {
1804     iCode *ic ;
1805     operand *rOp ;
1806     link *optype = operandType(op);
1807     operand *result ;
1808     operand *rv = (IS_ITEMP(op) ? 
1809                    geniCodeRValue(op,(IS_PTR(optype) ? TRUE : FALSE)) :
1810                    op);            
1811     link *rvtype = operandType(rv);    
1812     int diff = (IS_PTR(rvtype) && DCL_TYPE(optype) != DCL_TYPE(rvtype));
1813     int size = 0;
1814     
1815     /* if this is not an address we have trouble */
1816     if ( ! op->isaddr ) {
1817         werror (E_LVALUE_REQUIRED,"++");
1818         return op ;
1819     }
1820     
1821     rOp = newiTempOperand((diff ? rvtype : optype),0);
1822     rOp->noSpilLoc = 1;
1823
1824     if (IS_ITEMP(rv))
1825         rv->noSpilLoc = 1;
1826
1827     geniCodeAssign(rOp,rv,0);
1828    
1829     size = (IS_PTR(rvtype) ? getSize(rvtype->next) : 1);
1830     ic = newiCode('-',rv,operandFromLit(size));          
1831     IC_RESULT(ic) = result =newiTempOperand((diff ? rvtype : optype),0);
1832     ADDTOCHAIN(ic);
1833
1834     geniCodeAssign(op,result,0);
1835     
1836     return rOp;
1837     
1838 }
1839
1840 /*-----------------------------------------------------------------*/
1841 /* geniCodePreDec - generate code for pre  decrement               */
1842 /*-----------------------------------------------------------------*/
1843 operand *geniCodePreDec (operand *op)
1844 {  
1845     iCode *ic ;
1846     link *optype = operandType(op);    
1847     operand *rop = (IS_ITEMP(op) ? 
1848                     geniCodeRValue (op,(IS_PTR(optype) ? TRUE : FALSE)) :
1849                     op);
1850     link *roptype = operandType(rop);
1851     int diff = (IS_PTR(roptype) && (DCL_TYPE(roptype) != DCL_TYPE(optype)));
1852     operand *result;
1853     int size = 0;
1854     
1855     if ( ! op->isaddr ) {
1856         werror(E_LVALUE_REQUIRED,"++");
1857         return op ;
1858     }
1859
1860
1861     size = (IS_PTR(roptype) ? getSize(roptype->next) : 1);
1862     ic = newiCode('-',rop,operandFromLit(size));
1863     IC_RESULT(ic) = result = newiTempOperand((diff ? roptype : optype),0) ;
1864     ADDTOCHAIN(ic);
1865
1866     
1867     return geniCodeAssign(op,result,0) ;
1868 }
1869
1870
1871 /*-----------------------------------------------------------------*/
1872 /* geniCodeBitwise - gen int code for bitWise  operators           */
1873 /*-----------------------------------------------------------------*/
1874 operand *geniCodeBitwise (operand *left, operand *right, 
1875                           int oper, link *resType)
1876 {
1877     iCode *ic;   
1878     
1879     left = geniCodeCast(resType,left,TRUE);
1880     right= geniCodeCast(resType,right,TRUE);
1881     
1882     ic = newiCode(oper,left,right);
1883     IC_RESULT(ic) = newiTempOperand(resType,0);
1884     
1885     ADDTOCHAIN(ic);
1886     return IC_RESULT(ic) ;
1887 }
1888
1889 /*-----------------------------------------------------------------*/
1890 /* geniCodeAddressOf - gens icode for '&' address of operator      */
1891 /*-----------------------------------------------------------------*/
1892 operand *geniCodeAddressOf (operand *op) 
1893 {
1894     iCode *ic;
1895     link *p ;
1896     link *optype = operandType(op);
1897     link *opetype= getSpec(optype);
1898     
1899     /* this must be a lvalue */
1900     if (!op->isaddr && !IS_AGGREGATE(optype)) {
1901         werror (E_LVALUE_REQUIRED,"&");
1902         return op;
1903     }
1904     
1905     p = newLink();
1906     p->class = DECLARATOR ;
1907     /* set the pointer depending on the storage class */
1908     if (SPEC_OCLS(opetype)->codesp ) {
1909         DCL_TYPE(p) = CPOINTER ;
1910         DCL_PTR_CONST(p) = 1;
1911     }
1912     else
1913         if (SPEC_OCLS(opetype)->fmap && !SPEC_OCLS(opetype)->paged)
1914             DCL_TYPE(p) = FPOINTER ;
1915         else
1916             if (SPEC_OCLS(opetype)->fmap && SPEC_OCLS(opetype)->paged)
1917                 DCL_TYPE(p) = PPOINTER ;
1918             else
1919                 if (SPEC_OCLS(opetype) == idata)
1920                     DCL_TYPE(p) = IPOINTER;
1921                 else
1922                     if (SPEC_OCLS(opetype) == data ||
1923                         SPEC_OCLS(opetype) == overlay)
1924                         DCL_TYPE(p) = POINTER ;
1925                     else
1926                         DCL_TYPE(p) = GPOINTER;
1927     
1928     /* make sure we preserve the const & volatile */
1929     if (IS_CONSTANT(opetype)) 
1930         DCL_PTR_CONST(p) = 1;
1931
1932     if (IS_VOLATILE(opetype))
1933         DCL_PTR_VOLATILE(p) = 1;
1934     
1935     p->next = copyLinkChain(optype);
1936     
1937     /* if already a temp */
1938     if (IS_ITEMP(op)) {
1939         setOperandType (op,p);     
1940         op->isaddr= 0;
1941         return op;
1942     }
1943     
1944     /* other wise make this of the type coming in */
1945     ic = newiCode(ADDRESS_OF,op,NULL);
1946     IC_RESULT(ic) = newiTempOperand(p,1);
1947     IC_RESULT(ic)->isaddr = 0;
1948     ADDTOCHAIN(ic);
1949     return IC_RESULT(ic);
1950 }
1951 /*-----------------------------------------------------------------*/
1952 /* setOClass - sets the output class depending on the pointer type */
1953 /*-----------------------------------------------------------------*/
1954 void setOClass (link *ptr, link *spec)
1955 {
1956     switch (DCL_TYPE(ptr)) {
1957     case POINTER:
1958         SPEC_OCLS(spec) = data ;
1959         break ;
1960         
1961     case GPOINTER:
1962         SPEC_OCLS(spec) = generic;
1963         break;
1964         
1965     case FPOINTER:
1966         SPEC_OCLS(spec) = xdata ;
1967         break ;
1968         
1969     case CPOINTER:
1970         SPEC_OCLS(spec) = code ;
1971         break ;  
1972         
1973     case IPOINTER:
1974         SPEC_OCLS(spec) = idata;
1975         break;
1976
1977     case PPOINTER:
1978         SPEC_OCLS(spec) = xstack;
1979         break;
1980         
1981     }
1982 }
1983
1984 /*-----------------------------------------------------------------*/
1985 /* geniCodeDerefPtr - dereference pointer with '*'                 */
1986 /*-----------------------------------------------------------------*/
1987 operand *geniCodeDerefPtr (operand *op)
1988 {    
1989     link *rtype , *retype ;
1990     link *optype = operandType(op);  
1991
1992     /* if this is a pointer then generate the rvalue */
1993     if (IS_PTR(optype)) {
1994         if (IS_TRUE_SYMOP(op)) {
1995             op->isaddr = 1;
1996             op = geniCodeRValue(op,TRUE);
1997         }
1998         else    
1999             op = geniCodeRValue(op,TRUE);       
2000     }
2001     
2002     /* now get rid of the pointer part */
2003     if (lvaluereq && IS_ITEMP(op))
2004         retype = getSpec(rtype = copyLinkChain(optype)) ;
2005     else
2006         retype = getSpec(rtype = copyLinkChain(optype->next)) ;
2007     
2008     /* if this is a pointer then outputclass needs 2b updated */
2009     if (IS_PTR(optype)) 
2010         setOClass(optype,retype);    
2011         
2012     op = geniCodeRValue(op,TRUE);
2013     op->isGptr = IS_GENPTR(optype);
2014
2015     /* if the pointer was declared as a constant */
2016     /* then we cannot allow assignment to the derefed */
2017     if (IS_PTR_CONST(optype))
2018         SPEC_CONST(retype) = 1;
2019     
2020
2021     setOperandType(op,rtype);
2022     op->isaddr = (IS_PTR(rtype)    ||
2023                   IS_STRUCT(rtype) || 
2024                   IS_INT(rtype)    ||
2025                   IS_CHAR(rtype)   ||
2026                   IS_FLOAT(rtype) );
2027     
2028     return op;    
2029 }
2030
2031 /*-----------------------------------------------------------------*/
2032 /* geniCodeUnaryMinus - does a unary minus of the operand          */
2033 /*-----------------------------------------------------------------*/
2034 operand *geniCodeUnaryMinus (operand *op)
2035 {
2036     iCode *ic ;
2037     link *optype = operandType(op);
2038     
2039     if (IS_LITERAL(optype))
2040         return operandFromLit(- floatFromVal(op->operand.valOperand));
2041     
2042     ic = newiCode(UNARYMINUS,op,NULL);
2043     IC_RESULT(ic) = newiTempOperand(optype,0);
2044     ADDTOCHAIN(ic);
2045     return IC_RESULT(ic);
2046 }
2047
2048 /*-----------------------------------------------------------------*/
2049 /* geniCodeLeftShift - gen i code for left shift                   */
2050 /*-----------------------------------------------------------------*/
2051 operand *geniCodeLeftShift (operand *left, operand *right)
2052
2053     iCode *ic;
2054     link *ltype = operandType(left);
2055     
2056     ic = newiCode(LEFT_OP,left,right);
2057     IC_RESULT(ic) = newiTempOperand(ltype,0);
2058     ADDTOCHAIN(ic);
2059     return IC_RESULT(ic) ;  
2060 }
2061
2062 /*-----------------------------------------------------------------*/
2063 /* geniCodeRightShift - gen i code for right shift                 */
2064 /*-----------------------------------------------------------------*/
2065 operand *geniCodeRightShift (operand *left, operand *right)
2066
2067     iCode *ic;
2068     link *ltype = operandType(left);
2069     
2070     ic = newiCode(RIGHT_OP,left,right);
2071     IC_RESULT(ic) = newiTempOperand(ltype,0);
2072     ADDTOCHAIN(ic);
2073     return IC_RESULT(ic) ;  
2074 }
2075
2076 /*-----------------------------------------------------------------*/
2077 /* geniCodeLogic- logic code                                       */
2078 /*-----------------------------------------------------------------*/
2079 operand *geniCodeLogic (operand *left, operand *right, int op )
2080 {
2081     iCode *ic ;
2082     link *ctype; 
2083     link *rtype = operandType(right);
2084     link *ltype = operandType(left);
2085     
2086     /* left is integral type and right is literal then
2087        check if the literal value is within bounds */
2088     if (IS_INTEGRAL(ltype) && IS_LITERAL(rtype)) {
2089         int nbits = bitsForType(ltype);
2090         long v = operandLitValue(right);
2091
2092         if (v > ((long long) 1 << nbits) && v > 0)
2093             werror(W_CONST_RANGE," compare operation ");
2094     }
2095
2096     ctype = computeType(ltype,rtype);                         
2097     left = geniCodeCast(ctype,left,TRUE);
2098     right= geniCodeCast(ctype,right,TRUE);
2099
2100     ic = newiCode(op,left,right);
2101     IC_RESULT(ic) = newiTempOperand (newCharLink(),1);
2102
2103     /* if comparing anything greater than one byte
2104        and not a '==' || '!=' || '&&' || '||' (these
2105        will be inlined */
2106     if (getSize(ctype) > 1 && 
2107         op != EQ_OP        && 
2108         op != NE_OP        &&
2109         op != AND_OP       &&
2110         op != OR_OP        )
2111         ic->supportRtn = 1;
2112
2113     ADDTOCHAIN(ic);
2114     return IC_RESULT(ic);
2115 }
2116
2117 /*-----------------------------------------------------------------*/
2118 /* geniCodeUnary - for a a generic unary operation                 */
2119 /*-----------------------------------------------------------------*/
2120 operand *geniCodeUnary (operand *op, int oper )
2121 {
2122     iCode *ic = newiCode (oper,op,NULL);
2123     
2124     IC_RESULT(ic)= newiTempOperand(operandType(op),0);
2125     ADDTOCHAIN(ic);
2126     return IC_RESULT(ic) ;
2127 }
2128
2129 /*-----------------------------------------------------------------*/
2130 /* geniCodeConditional - geniCode for '?' ':' operation            */
2131 /*-----------------------------------------------------------------*/
2132 operand *geniCodeConditional (ast *tree)
2133 {
2134     iCode *ic ;
2135     symbol *falseLabel = newiTempLabel(NULL);
2136     symbol *exitLabel  = newiTempLabel(NULL);
2137     operand *cond = ast2iCode(tree->left);
2138     operand *true, *false , *result;
2139     
2140     ic = newiCodeCondition(geniCodeRValue(cond,FALSE),
2141                            NULL,falseLabel);
2142     ADDTOCHAIN(ic);
2143     
2144     true = ast2iCode(tree->right->left);
2145     
2146     /* move the value to a new Operand */
2147     result = newiTempOperand(operandType(true),0);
2148     geniCodeAssign(result,geniCodeRValue(true,FALSE),0);
2149     
2150     /* generate an unconditional goto */
2151     geniCodeGoto(exitLabel);
2152     
2153     /* now for the right side */
2154     geniCodeLabel(falseLabel);
2155     
2156     false = ast2iCode(tree->right->right);
2157     geniCodeAssign(result,geniCodeRValue(false,FALSE),0);
2158     
2159     /* create the exit label */
2160     geniCodeLabel(exitLabel);
2161     
2162     return result ;
2163 }
2164
2165 /*-----------------------------------------------------------------*/
2166 /* geniCodeAssign - generate code for assignment                   */
2167 /*-----------------------------------------------------------------*/
2168 operand *geniCodeAssign (operand *left, operand *right, int nosupdate)
2169 {
2170     iCode *ic ;
2171     link *ltype = operandType(left);
2172     link *rtype = operandType(right);
2173     
2174     if (!left->isaddr && !IS_ITEMP(left)) {
2175         werror(E_LVALUE_REQUIRED,"assignment");
2176         return left;
2177     }
2178         
2179     /* left is integral type and right is literal then
2180        check if the literal value is within bounds */
2181     if (IS_INTEGRAL(ltype) && IS_LITERAL(rtype)) {
2182         int nbits = bitsForType(ltype);
2183         long v = operandLitValue(right);
2184
2185         if (v > ((long long)1 << nbits) && v > 0)
2186             werror(W_CONST_RANGE," = operation");
2187     }
2188     /* if the left & right type don't exactly match */
2189     /* if pointer set then make sure the check is
2190        done with the type & not the pointer */
2191     /* then cast rights type to left */   
2192
2193     /* first check the type for pointer assignement */
2194     if (left->isaddr && IS_PTR(ltype) && IS_ITEMP(left) &&
2195         checkType(ltype,rtype)<0) {
2196         if (checkType(ltype->next,rtype) < 0)
2197             right = geniCodeCast(ltype->next,right,TRUE);
2198     } else
2199         if (checkType(ltype,rtype) < 0 )
2200             right = geniCodeCast(ltype,right,TRUE);
2201
2202     /* if left is a true symbol & ! volatile 
2203        create an assignment to temporary for
2204        the right & then assign this temporary
2205        to the symbol this is SSA . isn't it simple
2206        and folks have published mountains of paper on it */
2207     if (IS_TRUE_SYMOP(left) && 
2208         !isOperandVolatile(left,FALSE) &&
2209         isOperandGlobal(left)) {
2210         symbol *sym = NULL;
2211
2212         if (IS_TRUE_SYMOP(right))
2213             sym = OP_SYMBOL(right);
2214         ic = newiCode('=',NULL,right);
2215         IC_RESULT(ic) = right = newiTempOperand(ltype,0);       
2216         SPIL_LOC(right)  = sym ;
2217         ADDTOCHAIN(ic);
2218     }
2219     
2220     ic = newiCode('=',NULL,right);
2221     IC_RESULT(ic) = left;
2222     ADDTOCHAIN(ic);    
2223
2224     /* if left isgptr flag is set then support
2225        routine will be required */
2226     if (left->isGptr)
2227         ic->supportRtn = 1;
2228
2229     ic->nosupdate = nosupdate;
2230     return left;
2231 }
2232
2233 /*-----------------------------------------------------------------*/
2234 /* geniCodeSEParms - generate code for side effecting fcalls       */
2235 /*-----------------------------------------------------------------*/
2236 static void geniCodeSEParms (ast *parms)
2237 {
2238     if (!parms)
2239         return ;
2240
2241     if (parms->type == EX_OP && parms->opval.op == PARAM) {
2242         geniCodeSEParms (parms->left) ;
2243         geniCodeSEParms (parms->right);
2244         return ;
2245     }
2246
2247     /* hack don't like this but too lazy to think of
2248        something better */
2249     if (IS_ADDRESS_OF_OP(parms))
2250         parms->left->lvalue = 1;
2251     
2252     if (IS_CAST_OP(parms) && 
2253         IS_PTR(parms->ftype) && 
2254         IS_ADDRESS_OF_OP(parms->right))
2255         parms->right->left->lvalue = 1;
2256
2257     parms->opval.oprnd = 
2258         geniCodeRValue(ast2iCode (parms),TRUE);   
2259    
2260     parms->type = EX_OPERAND ;
2261 }
2262
2263 /*-----------------------------------------------------------------*/
2264 /* geniCodeParms - generates parameters                            */
2265 /*-----------------------------------------------------------------*/
2266 static void geniCodeParms ( ast *parms , int *stack, link *fetype)
2267 {
2268     iCode *ic ;
2269     operand *pval ; 
2270     
2271     if ( ! parms )
2272         return ;
2273     
2274     /* if this is a param node then do the left & right */
2275     if (parms->type == EX_OP && parms->opval.op == PARAM) {
2276         geniCodeParms (parms->left, stack,fetype) ;
2277         geniCodeParms (parms->right, stack,fetype);
2278         return ;
2279     }
2280     
2281     /* get the parameter value */
2282     if (parms->type == EX_OPERAND)
2283         pval = parms->opval.oprnd ;
2284     else {
2285         /* maybe this else should go away ?? */
2286         /* hack don't like this but too lazy to think of
2287            something better */
2288         if (IS_ADDRESS_OF_OP(parms))
2289             parms->left->lvalue = 1;
2290     
2291         if (IS_CAST_OP(parms) && 
2292             IS_PTR(parms->ftype) && 
2293             IS_ADDRESS_OF_OP(parms->right))
2294             parms->right->left->lvalue = 1;
2295
2296         pval = geniCodeRValue(ast2iCode (parms),FALSE); 
2297     }
2298
2299     /* if register parm then make it a send */
2300     if ((parms->argSym && IS_REGPARM(parms->argSym->etype)) ||
2301         IS_REGPARM(parms->etype)) {
2302         ic = newiCode(SEND,pval,NULL);
2303         ADDTOCHAIN(ic);
2304     } else {
2305         /* now decide whether to push or assign */
2306         if (!(options.stackAuto || IS_RENT(fetype))) { 
2307             
2308             /* assign */
2309             operand *top = operandFromSymbol(parms->argSym);
2310             geniCodeAssign(top,pval,1);
2311         }
2312         else { 
2313
2314             /* push */
2315             ic = newiCode(IPUSH,pval,NULL);
2316             ic->parmPush = 1;
2317             /* update the stack adjustment */
2318             *stack += getSize(operandType(pval));
2319             ADDTOCHAIN(ic);
2320         }
2321     }
2322     
2323 }
2324
2325 /*-----------------------------------------------------------------*/
2326 /* geniCodeCall - generates temp code for calling                  */
2327 /*-----------------------------------------------------------------*/
2328 operand *geniCodeCall (operand *left, ast *parms)
2329
2330     iCode *ic ;
2331     operand *result ;
2332     link *type, *etype;
2333     int stack = 0 ;
2334     
2335     /* take care of parameters with side-effecting
2336        function calls in them, this is required to take care 
2337        of overlaying function parameters */
2338     geniCodeSEParms ( parms );
2339
2340     /* first the parameters */
2341     geniCodeParms ( parms , &stack , getSpec(operandType(left)));
2342     
2343     /* now call : if symbol then pcall */
2344     if (IS_ITEMP(left)) 
2345         ic = newiCode(PCALL,left,NULL);
2346     else
2347         ic = newiCode(CALL,left,NULL);
2348     
2349     IC_ARGS(ic) = left->operand.symOperand->args ;
2350     type = copyLinkChain(operandType(left)->next);
2351     etype = getSpec(type);
2352     SPEC_EXTR(etype) = 0;
2353     IC_RESULT(ic) = result = newiTempOperand(type,1);
2354     
2355     ADDTOCHAIN(ic);
2356     
2357     /* stack adjustment after call */
2358     left->parmBytes = stack;
2359
2360     return result;
2361 }
2362
2363 /*-----------------------------------------------------------------*/
2364 /* geniCodeReceive - generate intermediate code for "receive"      */
2365 /*-----------------------------------------------------------------*/
2366 static void geniCodeReceive (value *args)
2367 {   
2368     /* for all arguments that are passed in registers */
2369     while (args) {
2370
2371         if (IS_REGPARM(args->etype)) {
2372             operand *opr = operandFromValue(args);
2373             operand *opl ;
2374             symbol *sym  = OP_SYMBOL(opr);
2375             iCode *ic ;
2376
2377             /* we will use it after all optimizations
2378                and before liveRange calculation */          
2379             if (!sym->addrtaken && 
2380                 !IS_VOLATILE(sym->etype) &&
2381                 !IN_FARSPACE(SPEC_OCLS(sym->etype))) {
2382                 opl = newiTempOperand(args->type,0);
2383                 sym->reqv = opl ;           
2384                 sym->reqv->key = sym->key ;
2385                 OP_SYMBOL(sym->reqv)->key = sym->key;
2386                 OP_SYMBOL(sym->reqv)->isreqv = 1;
2387                 OP_SYMBOL(sym->reqv)->islocal= 0;
2388                 SPIL_LOC(sym->reqv) =  sym;
2389             }
2390
2391             ic = newiCode(RECEIVE,NULL,NULL);
2392             currFunc->recvSize = getSize(sym->etype);
2393             IC_RESULT(ic) = opr;
2394             ADDTOCHAIN(ic);
2395         }
2396         
2397         args = args->next;
2398     }
2399 }
2400
2401 /*-----------------------------------------------------------------*/
2402 /* geniCodeFunctionBody - create the function body                 */
2403 /*-----------------------------------------------------------------*/
2404 void geniCodeFunctionBody (ast *tree)
2405 {
2406     iCode *ic ;
2407     operand *func ;
2408     link *fetype  ;
2409     int savelineno ;
2410     
2411     /* reset the auto generation */
2412     /* numbers */
2413     iTempNum = 0 ;
2414     iTempLblNum = 0;   
2415     operandKey = 0 ;
2416     iCodeKey = 0 ;
2417     func  = ast2iCode(tree->left);
2418     fetype = getSpec(operandType(func));
2419     
2420     savelineno = lineno;
2421     lineno = OP_SYMBOL(func)->lineDef;
2422     /* create an entry label */
2423     geniCodeLabel(entryLabel);    
2424     lineno = savelineno;
2425
2426     /* create a proc icode */
2427     ic = newiCode(FUNCTION,func,NULL);
2428     /* if the function has parmas   then */
2429     /* save the parameters information    */
2430     ic->argLabel.args = tree->values.args ;
2431     ic->lineno = OP_SYMBOL(func)->lineDef;
2432
2433     ADDTOCHAIN(ic);   
2434     
2435     /* for all parameters that are passed
2436        on registers add a "receive" */
2437     geniCodeReceive( tree->values.args );
2438
2439     /* generate code for the body */
2440     ast2iCode(tree->right);
2441     
2442     /* create a label for return */
2443     geniCodeLabel(returnLabel);
2444     
2445     /* now generate the end proc */
2446     ic = newiCode(ENDFUNCTION,func,NULL);
2447     ADDTOCHAIN(ic);
2448     return ;
2449 }
2450
2451 /*-----------------------------------------------------------------*/
2452 /* geniCodeReturn - gen icode for 'return' statement               */
2453 /*-----------------------------------------------------------------*/
2454 void geniCodeReturn (operand *op)
2455 {
2456     iCode *ic;
2457     
2458     /* if the operand is present force an rvalue */
2459     if (op) 
2460         op = geniCodeRValue(op,FALSE);    
2461     
2462     ic = newiCode(RETURN,op,NULL);
2463     ADDTOCHAIN(ic);
2464 }
2465
2466 /*-----------------------------------------------------------------*/
2467 /* geniCodeIfx - generates code for extended if statement          */
2468 /*-----------------------------------------------------------------*/
2469 void geniCodeIfx (ast *tree)
2470 {
2471     iCode *ic;
2472     operand *condition = ast2iCode(tree->left);
2473 /*     link *ctype = operandType(condition);     */
2474     link *cetype; 
2475     
2476     /* if condition is null then exit */
2477     if (!condition)
2478         goto exit ;
2479     else
2480         condition = geniCodeRValue(condition,FALSE);
2481     
2482     cetype = getSpec(operandType(condition));
2483     /* if the condition is a literal */
2484     if (IS_LITERAL(cetype)) {
2485         if (floatFromVal(condition->operand.valOperand)) {
2486             if (tree->trueLabel)
2487                 geniCodeGoto(tree->trueLabel);
2488             else
2489                 assert(1);
2490         }
2491         else {
2492             if (tree->falseLabel)
2493                 geniCodeGoto (tree->falseLabel);
2494             else
2495                 assert(1);
2496         }
2497         goto exit;
2498     }
2499     
2500     if ( tree->trueLabel ) {
2501         ic = newiCodeCondition(condition,
2502                                tree->trueLabel,
2503                                NULL );
2504         ADDTOCHAIN(ic);
2505         
2506         if ( tree->falseLabel) 
2507             geniCodeGoto(tree->falseLabel);     
2508     }
2509     else {
2510         ic = newiCodeCondition (condition,
2511                                 NULL,
2512                                 tree->falseLabel);
2513         ADDTOCHAIN(ic);
2514     }
2515     
2516  exit:
2517     ast2iCode(tree->right);
2518 }
2519
2520 /*-----------------------------------------------------------------*/
2521 /* geniCodeJumpTable - tries to create a jump table for switch     */
2522 /*-----------------------------------------------------------------*/
2523 int geniCodeJumpTable (operand *cond, value *caseVals, ast *tree)
2524 {
2525     int min = 0 ,max = 0, t, cnt = 0;
2526     value *vch;
2527     iCode *ic;
2528     operand *boundary;
2529     symbol *falseLabel;
2530     set *labels = NULL ;
2531
2532     if (!tree || !caseVals)
2533         return 0;
2534
2535     /* the criteria for creating a jump table is */
2536     /* all integer numbers between the maximum & minimum must */
2537     /* be present , the maximum value should not exceed 255 */
2538     min = max = (int)floatFromVal(vch = caseVals);
2539     sprintf(buffer,"_case_%d_%d",
2540             tree->values.switchVals.swNum,
2541             min);
2542     addSet(&labels,newiTempLabel(buffer));
2543
2544     /* if there is only one case value then no need */
2545     if (!(vch = vch->next ))
2546         return 0;
2547
2548     while (vch) {
2549         if (((t = (int)floatFromVal(vch)) - max) != 1)
2550             return 0;
2551         sprintf(buffer,"_case_%d_%d",
2552                 tree->values.switchVals.swNum,
2553                 t);
2554         addSet(&labels,newiTempLabel(buffer));
2555         max = t;
2556         cnt++ ;
2557         vch = vch->next ;
2558     }
2559     
2560     /* if the number of case statements <= 2 then */
2561     /* it is not economical to create the jump table */
2562     /* since two compares are needed for boundary conditions */
2563     if ((! optimize.noJTabBoundary  && cnt <= 2) || max > (255/3))
2564         return 0;
2565     
2566     if ( tree->values.switchVals.swDefault )
2567         sprintf (buffer,"_default_%d",tree->values.switchVals.swNum);
2568     else
2569         sprintf (buffer,"_swBrk_%d",tree->values.switchVals.swNum  );
2570     
2571     falseLabel = newiTempLabel (buffer);
2572
2573     /* so we can create a jumptable */
2574     /* first we rule out the boundary conditions */
2575     /* if only optimization says so */
2576     if ( ! optimize.noJTabBoundary ) {
2577         link *cetype = getSpec(operandType(cond));
2578         /* no need to check the lower bound if
2579            the condition is unsigned & minimum value is zero */
2580         if (!( min == 0  && SPEC_USIGN(cetype))) {
2581             boundary = geniCodeLogic (cond,operandFromLit(min),'<');
2582             ic = newiCodeCondition (boundary,falseLabel,NULL);
2583             ADDTOCHAIN(ic);
2584         }
2585
2586         /* now for upper bounds */
2587         boundary = geniCodeLogic(cond,operandFromLit(max),'>');
2588         ic = newiCodeCondition (boundary,falseLabel,NULL);
2589         ADDTOCHAIN(ic);
2590     }
2591
2592     /* if the min is not zero then we no make it zero */
2593     if (min) {
2594         cond = geniCodeSubtract(cond,operandFromLit(min));
2595         setOperandType(cond,ucharType);
2596     }
2597
2598     /* now create the jumptable */
2599     ic = newiCode(JUMPTABLE,NULL,NULL);
2600     IC_JTCOND(ic) = cond;
2601     IC_JTLABELS(ic) = labels;
2602     ADDTOCHAIN(ic);
2603     return 1;       
2604 }
2605
2606 /*-----------------------------------------------------------------*/
2607 /* geniCodeSwitch - changes a switch to a if statement             */
2608 /*-----------------------------------------------------------------*/
2609 void geniCodeSwitch (ast *tree)
2610 {
2611     iCode *ic ;
2612     operand *cond = geniCodeRValue(ast2iCode (tree->left),FALSE);
2613     value *caseVals = tree->values.switchVals.swVals ;
2614     symbol *trueLabel , *falseLabel;
2615     
2616     /* if we can make this a jump table */
2617     if ( geniCodeJumpTable (cond,caseVals,tree) )
2618         goto jumpTable ; /* no need for the comparison */
2619
2620     /* for the cases defined do */
2621     while (caseVals) {
2622         
2623         operand *compare = geniCodeLogic (cond,
2624                                           operandFromValue(caseVals),
2625                                           EQ_OP);
2626         
2627         sprintf(buffer,"_case_%d_%d",
2628                 tree->values.switchVals.swNum,
2629                 (int) floatFromVal(caseVals));
2630         trueLabel = newiTempLabel(buffer);
2631         
2632         ic = newiCodeCondition(compare,trueLabel,NULL);
2633         ADDTOCHAIN(ic);
2634         caseVals = caseVals->next;
2635     }
2636
2637
2638     
2639     /* if default is present then goto break else break */
2640     if ( tree->values.switchVals.swDefault )
2641         sprintf (buffer,"_default_%d",tree->values.switchVals.swNum);
2642     else
2643         sprintf (buffer,"_swBrk_%d",tree->values.switchVals.swNum  );
2644     
2645     falseLabel = newiTempLabel (buffer);
2646     geniCodeGoto(falseLabel);
2647  
2648  jumpTable:   
2649     ast2iCode(tree->right);
2650
2651
2652 /*-----------------------------------------------------------------*/
2653 /* geniCodeInline - intermediate code for inline assembler         */
2654 /*-----------------------------------------------------------------*/
2655 static void geniCodeInline (ast *tree)
2656 {
2657     iCode *ic;
2658
2659     ic = newiCode(INLINEASM,NULL,NULL);
2660     IC_INLINE(ic) = tree->values.inlineasm;
2661     ADDTOCHAIN(ic);
2662 }
2663
2664 /*-----------------------------------------------------------------*/
2665 /* ast2iCode - creates an icodeList from an ast                    */
2666 /*-----------------------------------------------------------------*/
2667 operand *ast2iCode (ast *tree)
2668 {
2669     operand *left = NULL;
2670     operand *right= NULL;
2671     
2672     if (!tree)
2673         return NULL ;
2674     
2675     /* set the global variables for filename & line number */
2676     if ( tree->filename )
2677         filename =  tree->filename ;
2678     if ( tree->lineno)
2679         lineno   = tree->lineno ;
2680     if (tree->block)
2681         block = tree->block ;
2682     if (tree->level)
2683         scopeLevel = tree->level;
2684     
2685     if (tree->type == EX_VALUE )
2686         return operandFromValue(tree->opval.val);
2687     
2688     if (tree->type == EX_LINK )
2689         return operandFromLink (tree->opval.lnk);
2690     
2691     /* if we find a nullop */
2692     if (tree->type == EX_OP && 
2693         ( tree->opval.op == NULLOP || 
2694           tree->opval.op == BLOCK )) {
2695         ast2iCode (tree->left);
2696         ast2iCode (tree->right);
2697         return NULL ;
2698     }
2699     
2700     /* special cases for not evaluating */
2701     if ( tree->opval.op != ':'   && 
2702          tree->opval.op != '?'   &&
2703          tree->opval.op != CALL  && 
2704          tree->opval.op != IFX   &&
2705          tree->opval.op != LABEL &&
2706          tree->opval.op != GOTO  &&     
2707          tree->opval.op != SWITCH &&
2708          tree->opval.op != FUNCTION &&
2709          tree->opval.op != INLINEASM ) {
2710         if (IS_ASSIGN_OP(tree->opval.op) || IS_DEREF_OP(tree)) {
2711             lvaluereq++;
2712             left = operandFromAst(tree->left);
2713             lvaluereq--;
2714         } else {
2715             left =  operandFromAst(tree->left);
2716         }
2717         right= operandFromAst(tree->right);
2718     }
2719     
2720     /* now depending on the type of operand */
2721     /* this will be a biggy                 */
2722     switch (tree->opval.op) {
2723         
2724     case '[' :    /* array operation */
2725         left= geniCodeRValue (left,FALSE);
2726         right=geniCodeRValue (right,TRUE);                 
2727         
2728         return geniCodeArray (left,right);
2729         
2730     case '.' :   /* structure dereference */
2731         if (IS_PTR(operandType(left)))
2732             left = geniCodeRValue(left,TRUE);
2733         else
2734             left = geniCodeRValue(left,FALSE);            
2735         
2736         return geniCodeStruct (left,right,tree->lvalue);
2737         
2738     case PTR_OP: /* structure pointer dereference */
2739         {
2740             link *pType;
2741             pType = operandType(left);
2742             left = geniCodeRValue(left,TRUE);
2743             
2744             setOClass (pType,getSpec(operandType(left)));
2745         }              
2746         
2747         return geniCodeStruct (left, right,tree->lvalue);
2748         
2749     case INC_OP: /* increment operator */
2750         if ( left )
2751             return geniCodePostInc (left);
2752         else
2753             return geniCodePreInc (right);
2754         
2755     case DEC_OP: /* decrement operator */
2756         if ( left )
2757             return geniCodePostDec (left);
2758         else
2759             return geniCodePreDec (right);
2760         
2761     case '&' : /* bitwise and or address of operator */
2762         if ( right ) { /* this is a bitwise operator   */
2763             left= geniCodeRValue(left,FALSE);
2764             right= geniCodeRValue(right,FALSE);     
2765             return geniCodeBitwise (left,right,BITWISEAND,tree->ftype);
2766         } else
2767             return geniCodeAddressOf (left);
2768         
2769     case '|': /* bitwise or & xor */
2770     case '^':
2771         return geniCodeBitwise (geniCodeRValue(left,FALSE),
2772                                 geniCodeRValue(right,FALSE),
2773                                 tree->opval.op,
2774                                 tree->ftype);
2775         
2776     case '/':
2777         return geniCodeDivision (geniCodeRValue(left,FALSE),
2778                                  geniCodeRValue(right,FALSE));
2779         
2780     case '%' :
2781         return geniCodeModulus (geniCodeRValue(left,FALSE),
2782                                 geniCodeRValue(right,FALSE));
2783     case '*':
2784         if ( right ) 
2785             return geniCodeMultiply (geniCodeRValue(left,FALSE),
2786                                      geniCodeRValue(right,FALSE));
2787         else        
2788             return geniCodeDerefPtr (geniCodeRValue(left,FALSE));
2789         
2790     case '-' :
2791         if ( right ) 
2792             return geniCodeSubtract (geniCodeRValue(left,FALSE),
2793                                      geniCodeRValue(right,FALSE));
2794         else
2795             return geniCodeUnaryMinus (geniCodeRValue(left,FALSE));
2796         
2797     case '+' :
2798         if ( right ) 
2799             return geniCodeAdd (geniCodeRValue(left,FALSE),
2800                                 geniCodeRValue(right,FALSE));
2801         else
2802             return geniCodeRValue(left,FALSE) ; /* unary '+' has no meaning */
2803         
2804     case LEFT_OP:
2805         return geniCodeLeftShift (geniCodeRValue(left,FALSE),
2806                                   geniCodeRValue(right,FALSE));
2807         
2808     case RIGHT_OP:
2809         return geniCodeRightShift (geniCodeRValue(left,FALSE),
2810                                    geniCodeRValue(right,FALSE));
2811     case CAST:
2812         return geniCodeCast (operandType(left),
2813                              geniCodeRValue(right,FALSE),FALSE);
2814         
2815     case '~' :
2816     case '!' :
2817     case RRC:
2818     case RLC:   
2819         return geniCodeUnary (geniCodeRValue(left,FALSE),tree->opval.op);
2820         
2821     case GETHBIT:
2822         {
2823             operand *op = geniCodeUnary (geniCodeRValue(left,FALSE),tree->opval.op);
2824             setOperandType(op,ucharType);
2825             return op;
2826         }
2827     case '>' :
2828     case '<' :
2829     case LE_OP:
2830     case GE_OP:
2831     case EQ_OP:
2832     case NE_OP:
2833     case AND_OP:
2834     case OR_OP:
2835         return geniCodeLogic (geniCodeRValue(left,FALSE),
2836                               geniCodeRValue(right,FALSE),
2837                               tree->opval.op);
2838     case '?' : 
2839         return geniCodeConditional (tree); 
2840         
2841     case SIZEOF:
2842         return operandFromLit(getSize(tree->right->ftype));
2843         
2844     case '='        :
2845         {
2846             link *rtype = operandType(right);
2847             link *ltype = operandType(left);
2848             if (IS_PTR(rtype) && IS_ITEMP(right) 
2849                 && right->isaddr && checkType(rtype->next,ltype)==1)
2850                 right =  geniCodeRValue(right,TRUE);
2851             else
2852                 right = geniCodeRValue(right,FALSE);
2853
2854             geniCodeAssign (left,right,0);
2855             return right ;
2856         }              
2857     case MUL_ASSIGN:
2858         return 
2859             geniCodeAssign(left,
2860                            geniCodeMultiply(geniCodeRValue (operandFromOperand(left),
2861                                                             FALSE),
2862                                             geniCodeRValue(right,FALSE)),0);
2863                                                 
2864     case DIV_ASSIGN:
2865         return 
2866             geniCodeAssign(left,
2867                            geniCodeDivision(geniCodeRValue(operandFromOperand(left),
2868                                                            FALSE),
2869                                             geniCodeRValue(right,FALSE)),0);
2870     case MOD_ASSIGN:
2871         return 
2872             geniCodeAssign(left,
2873                            geniCodeModulus(geniCodeRValue(operandFromOperand(left),
2874                                                           FALSE),
2875                                            geniCodeRValue(right,FALSE)),0);
2876     case ADD_ASSIGN: 
2877         {
2878             link *rtype = operandType(right);
2879             link *ltype = operandType(left);
2880             if (IS_PTR(rtype) && IS_ITEMP(right) 
2881                 && right->isaddr && checkType(rtype->next,ltype)==1)
2882                 right =  geniCodeRValue(right,TRUE);
2883             else
2884                 right = geniCodeRValue(right,FALSE);
2885
2886            
2887             return geniCodeAssign(left,
2888                                   geniCodeAdd (geniCodeRValue(operandFromOperand(left),
2889                                                               FALSE),
2890                                                right),0);
2891         }
2892     case SUB_ASSIGN:
2893         {
2894             link *rtype = operandType(right);
2895             link *ltype = operandType(left);
2896             if (IS_PTR(rtype) && IS_ITEMP(right) 
2897                 && right->isaddr && checkType(rtype->next,ltype)==1) {
2898                 right =  geniCodeRValue(right,TRUE);
2899             }
2900             else {
2901                 right = geniCodeRValue(right,FALSE);
2902             }
2903             return 
2904                 geniCodeAssign (left,
2905                                 geniCodeSubtract(geniCodeRValue(operandFromOperand(left),
2906                                                                 FALSE),
2907                                                  right),0);
2908         }
2909     case LEFT_ASSIGN:
2910         return 
2911             geniCodeAssign (left,
2912                             geniCodeLeftShift(geniCodeRValue(operandFromOperand(left)
2913                                                              ,FALSE),
2914                                               geniCodeRValue(right,FALSE)),0);
2915     case RIGHT_ASSIGN:
2916         return 
2917             geniCodeAssign(left,
2918                            geniCodeRightShift(geniCodeRValue(operandFromOperand(left)
2919                                                              ,FALSE),
2920                                               geniCodeRValue(right,FALSE)),0);
2921     case AND_ASSIGN:
2922         return 
2923             geniCodeAssign (left,
2924                             geniCodeBitwise(geniCodeRValue(operandFromOperand(left),
2925                                                            FALSE),
2926                                             geniCodeRValue(right,FALSE),
2927                                             BITWISEAND,
2928                                             operandType(left)),0);
2929     case XOR_ASSIGN:
2930         return 
2931             geniCodeAssign (left,
2932                             geniCodeBitwise (geniCodeRValue(operandFromOperand(left),
2933                                                             FALSE),
2934                                              geniCodeRValue(right,FALSE),
2935                                              '^',
2936                                              operandType(left)),0);
2937     case OR_ASSIGN:
2938         return 
2939             geniCodeAssign (left,
2940                             geniCodeBitwise (geniCodeRValue(operandFromOperand(left)
2941                                                             ,FALSE),
2942                                              geniCodeRValue(right,FALSE),
2943                                              '|',
2944                                              operandType(left)),0);
2945     case ',' :
2946         return geniCodeRValue(right,FALSE);
2947         
2948     case CALL:
2949         return geniCodeCall (ast2iCode(tree->left),
2950                              tree->right);
2951     case LABEL:
2952         geniCodeLabel(ast2iCode(tree->left)->operand.symOperand);
2953         return ast2iCode (tree->right);
2954         
2955     case GOTO:
2956         geniCodeGoto (ast2iCode(tree->left)->operand.symOperand);
2957         return ast2iCode (tree->right);
2958         
2959     case FUNCTION:
2960         geniCodeFunctionBody ( tree );
2961         return NULL ;
2962         
2963     case RETURN:
2964         geniCodeReturn (right);
2965         return NULL ;
2966         
2967     case IFX:
2968         geniCodeIfx (tree);
2969         return NULL ;
2970         
2971     case SWITCH:
2972         geniCodeSwitch (tree);
2973         return NULL;
2974
2975     case INLINEASM:
2976         geniCodeInline (tree);
2977         return NULL ;
2978     }
2979     
2980     return NULL;
2981 }
2982
2983 /*-----------------------------------------------------------------*/
2984 /* reverseICChain - gets from the list and creates a linkedlist    */
2985 /*-----------------------------------------------------------------*/
2986 iCode *reverseiCChain ()
2987 {
2988     iCode *loop = NULL ;
2989     iCode *prev = NULL ;
2990     
2991     while ((loop = getSet(&iCodeChain))) {
2992         loop->next = prev ;
2993         if ( prev )
2994             prev->prev = loop; 
2995         prev = loop ;
2996     }
2997     
2998     return prev;
2999 }
3000
3001
3002 /*-----------------------------------------------------------------*/
3003 /* iCodeFromAst - given an ast will convert it to iCode            */
3004 /*-----------------------------------------------------------------*/
3005 iCode *iCodeFromAst ( ast *tree )
3006 {
3007     returnLabel = newiTempLabel("_return");
3008     entryLabel  = newiTempLabel("_entry") ;
3009     ast2iCode (tree);
3010     return reverseiCChain ();
3011 }
3012