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