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