More AVR stuff
[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     int ok =1 ;
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 (sym->level && sym->etype && SPEC_OCLS(sym->etype) &&
1088         IN_FARSPACE(SPEC_OCLS(sym->etype))  &&
1089         options.stackAuto == 0)
1090         ok =0;
1091
1092     if (!IS_AGGREGATE(sym->type) &&     /* not an aggregate */
1093         !IS_FUNC(sym->type)      &&     /* not a function   */
1094         !sym->_isparm            &&     /* not a parameter  */
1095         sym->level               &&     /* is a local variable */
1096         !sym->addrtaken          &&     /* whose address has not been taken */
1097         !sym->reqv               &&     /* does not already have a register euivalence */
1098         !IS_VOLATILE(sym->etype) &&     /* not declared as volatile */
1099         !IS_STATIC(sym->etype)   &&     /* and not declared static  */
1100         !sym->islbl              &&     /* not a label */
1101         ok                       &&     /* farspace check */
1102         !IS_BITVAR(sym->etype)          /* not a bit variable */
1103         ) {
1104         
1105         /* we will use it after all optimizations
1106            and before liveRange calculation */
1107         sym->reqv = newiTempOperand(sym->type,0);       
1108         sym->reqv->key = sym->key ;
1109         OP_SYMBOL(sym->reqv)->key = sym->key;
1110         OP_SYMBOL(sym->reqv)->isreqv = 1;
1111         OP_SYMBOL(sym->reqv)->islocal = 1;
1112         SPIL_LOC(sym->reqv) = sym;
1113     }
1114    
1115     if (!IS_AGGREGATE(sym->type)) {
1116         op = newOperand();
1117         op->type = SYMBOL;
1118         op->operand.symOperand = sym;
1119         op->isaddr = 1;
1120         op->key = sym->key;
1121         op->isvolatile = isOperandVolatile(op,TRUE);
1122         op->isGlobal   = isOperandGlobal(op);
1123         op->isPtr = IS_PTR(operandType(op));
1124         op->isParm = sym->_isparm ;
1125         return op;
1126     }
1127     
1128     /* create :-                     */
1129     /*    itemp = &[_symbol]         */
1130     
1131     ic = newiCode(ADDRESS_OF,newOperand(),NULL);
1132     IC_LEFT(ic)->type = SYMBOL ;
1133     IC_LEFT(ic)->operand.symOperand = sym ;
1134     IC_LEFT(ic)->key = sym->key;    
1135     (IC_LEFT(ic))->isvolatile = isOperandVolatile(IC_LEFT(ic),TRUE);
1136     (IC_LEFT(ic))->isGlobal   = isOperandGlobal(IC_LEFT(ic));
1137     IC_LEFT(ic)->isPtr = IS_PTR(operandType(IC_LEFT(ic)));
1138
1139     /* create result */
1140     IC_RESULT(ic) = newiTempOperand(sym->type,0);
1141     if (IS_ARRAY(sym->type)) {
1142         IC_RESULT(ic) = geniCodeArray2Ptr (IC_RESULT(ic));
1143         IC_RESULT(ic)->isaddr = 0;
1144     } else
1145         IC_RESULT(ic)->isaddr = (!IS_AGGREGATE(sym->type));
1146
1147     IC_RESULT(ic)->operand.symOperand->args = sym->args;
1148
1149     ADDTOCHAIN(ic);
1150     
1151     return IC_RESULT(ic) ;
1152 }
1153
1154 /*-----------------------------------------------------------------*/
1155 /* operandFromValue - creates an operand from value                */
1156 /*-----------------------------------------------------------------*/
1157 operand *operandFromValue (value *val)
1158 {
1159     operand *op ;
1160     
1161     /* if this is a symbol then do the symbol thing */
1162     if (val->sym)
1163         return operandFromSymbol (val->sym);
1164     
1165     /* this is not a symbol */
1166     op = newOperand();
1167     op->type = VALUE ;
1168     op->operand.valOperand = val ;
1169     op->isLiteral = isOperandLiteral(op);
1170     return op;
1171 }
1172
1173 /*-----------------------------------------------------------------*/
1174 /* operandFromLink - operand from typeChain                        */
1175 /*-----------------------------------------------------------------*/
1176 operand *operandFromLink (link *type)
1177 {
1178     operand *op ;
1179     
1180     /* operand from link */
1181     if ( ! type )
1182         return NULL ;
1183     
1184     op = newOperand();
1185     op->type = TYPE ;
1186     op->operand.typeOperand = copyLinkChain(type);
1187     return op;
1188 }
1189
1190 /*-----------------------------------------------------------------*/
1191 /* operandFromLit - makes an operand from a literal value          */
1192 /*-----------------------------------------------------------------*/
1193 operand *operandFromLit ( float i)
1194 {
1195     return operandFromValue (valueFromLit (i));
1196 }
1197
1198 /*-----------------------------------------------------------------*/
1199 /* operandFromAst - creates an operand from an ast                 */
1200 /*-----------------------------------------------------------------*/
1201 operand *operandFromAst ( ast *tree )
1202 {
1203     
1204     if (! tree )
1205         return NULL ;
1206     
1207     /* depending on type do */
1208     switch (tree->type ) {      
1209     case EX_OP : 
1210         return ast2iCode (tree) ;    
1211         break ;
1212         
1213     case EX_VALUE :
1214         return operandFromValue(tree->opval.val) ;
1215         break ;
1216         
1217     case EX_LINK :
1218         return operandFromLink (tree->opval.lnk) ; 
1219     }
1220     
1221     assert(0);
1222     /*  Just to keep the comiler happy */
1223     return (operand *)0;
1224 }
1225
1226 /*-----------------------------------------------------------------*/
1227 /* setOperandType - sets the operand's type to the given type      */
1228 /*-----------------------------------------------------------------*/
1229 void setOperandType (operand *op, link *type)
1230 {
1231     /* depending on the type of operand */
1232     switch (op->type) {
1233         
1234     case VALUE :
1235         op->operand.valOperand->etype = 
1236             getSpec( op->operand.valOperand->type = 
1237                      copyLinkChain (type )) ;
1238         return ;
1239         
1240     case SYMBOL :
1241         if (op->operand.symOperand->isitmp )
1242             op->operand.symOperand->etype = 
1243                 getSpec( op->operand.symOperand->type = 
1244                          copyLinkChain (type )) ;
1245         else
1246             werror (E_INTERNAL_ERROR,__FILE__,__LINE__,
1247                     "attempt to modify type of source");
1248         return;
1249         
1250     case TYPE:
1251         op->operand.typeOperand = copyLinkChain (type);
1252         return ;
1253     }
1254     
1255 }
1256
1257 /*-----------------------------------------------------------------*/
1258 /* geniCodeValueAtAddress - generate intermeditate code for value  */
1259 /*                          at address                             */
1260 /*-----------------------------------------------------------------*/
1261 operand *geniCodeRValue (operand *op, bool force)
1262 {
1263     iCode *ic ;
1264     link *type = operandType(op);
1265     link *etype= getSpec(type);
1266     
1267     /* if this is an array & already */
1268     /* an address then return this   */
1269     if (IS_AGGREGATE(type) || 
1270         (IS_PTR(type) && !force && !op->isaddr))
1271         return operandFromOperand(op);
1272         
1273     /* if this is not an address then must be */
1274     /* rvalue already so return this one      */
1275     if (!op->isaddr)
1276         return op ;
1277     
1278     /* if this is not a temp symbol then */
1279     if (!IS_ITEMP(op) && 
1280         !force        && 
1281         !IN_FARSPACE(SPEC_OCLS(etype))) {
1282         op = operandFromOperand(op);
1283         op->isaddr = 0;
1284         return op;
1285     }
1286     
1287     if (IS_SPEC(type) && 
1288         IS_TRUE_SYMOP(op) &&
1289         !IN_FARSPACE(SPEC_OCLS(etype))) {
1290         op = operandFromOperand(op);
1291         op->isaddr = 0;
1292         return op;
1293     }
1294
1295     ic = newiCode(GET_VALUE_AT_ADDRESS,op,NULL);
1296     if (IS_PTR(type) && op->isaddr && force) 
1297         type = type->next;
1298     
1299     type = copyLinkChain(type);
1300
1301     IC_RESULT(ic) = newiTempOperand (type,1);
1302     IC_RESULT(ic)->isaddr = 0;
1303  
1304 /*     ic->supportRtn = ((IS_GENPTR(type) | op->isGptr) & op->isaddr); */
1305
1306     /* if the right is a symbol */
1307     if (op->type == SYMBOL)
1308         IC_RESULT(ic)->operand.symOperand->args = 
1309             op->operand.symOperand->args ;
1310     ADDTOCHAIN(ic);
1311     
1312     return IC_RESULT(ic) ;
1313 }
1314
1315 /*-----------------------------------------------------------------*/
1316 /* geniCodeCast - changes the value from one type to another       */
1317 /*-----------------------------------------------------------------*/
1318 operand *geniCodeCast (link *type, operand *op, bool implicit) 
1319 {
1320     iCode *ic ;
1321     link *optype ;
1322     link *opetype = getSpec(optype = operandType(op));
1323     link *restype ;
1324     
1325     /* one of them has size zero then error */
1326     if (IS_VOID(optype)) {
1327         werror(E_CAST_ZERO);
1328         return op;
1329     }
1330
1331     /* if the operand is already the desired type then do nothing */
1332     if ( checkType (type,optype) == 1)  
1333         return op;
1334     
1335     /* if this is a literal then just change the type & return */
1336     if (IS_LITERAL(opetype) && op->type == VALUE && !IS_PTR(type) && !IS_PTR(optype))
1337         return operandFromValue(valCastLiteral(type,
1338                                                operandLitValue(op)));
1339           
1340     /* if casting to some pointer type &&
1341        the destination is not a generic pointer 
1342        then give a warning : (only for implicit casts)*/
1343     if (IS_PTR(optype) && implicit &&
1344         (DCL_TYPE(optype) != DCL_TYPE(type)) && 
1345         !IS_GENPTR(type)) {
1346         werror(E_INCOMPAT_CAST);
1347         werror(E_CONTINUE,"from type '");
1348         printTypeChain(optype,stderr);fprintf(stderr,"' to type '");      
1349         printTypeChain(type,stderr);fprintf(stderr,"'\n");
1350     }
1351
1352     /* if they are the same size create an assignment */
1353     if (getSize(type) == getSize(optype) && 
1354         !IS_BITFIELD(type)               &&
1355         !IS_FLOAT(type)                  &&
1356         !IS_FLOAT(optype)                &&
1357         ((IS_SPEC(type) && IS_SPEC(optype)) ||
1358          (!IS_SPEC(type) && !IS_SPEC(optype)))) {
1359
1360         ic = newiCode('=',NULL,op);     
1361         IC_RESULT(ic) = newiTempOperand(type,0);
1362          SPIL_LOC(IC_RESULT(ic))  =
1363              (IS_TRUE_SYMOP(op) ? OP_SYMBOL(op) : NULL);
1364         IC_RESULT(ic)->isaddr = 0;
1365     } else { 
1366         ic = newiCode(CAST,operandFromLink(type),
1367                       geniCodeRValue(op,FALSE));
1368         
1369         IC_RESULT(ic)= newiTempOperand(type,0);
1370     }
1371     
1372     /* preserve the storage class & output class */
1373     /* of the original variable                  */
1374     restype = getSpec(operandType(IC_RESULT(ic)));
1375     SPEC_SCLS(restype) = SPEC_SCLS(opetype);
1376     SPEC_OCLS(restype) = SPEC_OCLS(opetype);
1377     
1378     ADDTOCHAIN(ic);
1379     return IC_RESULT(ic) ;
1380 }
1381
1382 /*-----------------------------------------------------------------*/
1383 /* geniCodeLabel - will create a Label                             */
1384 /*-----------------------------------------------------------------*/
1385 void geniCodeLabel (symbol *label)
1386 {
1387     iCode *ic;
1388     
1389     ic = newiCodeLabelGoto(LABEL,label);
1390     ADDTOCHAIN(ic);
1391 }
1392
1393 /*-----------------------------------------------------------------*/
1394 /* geniCodeGoto  - will create a Goto                              */
1395 /*-----------------------------------------------------------------*/
1396 void geniCodeGoto (symbol *label)
1397 {
1398     iCode *ic;
1399     
1400     ic = newiCodeLabelGoto(GOTO,label);
1401     ADDTOCHAIN(ic);
1402 }
1403
1404 /*-----------------------------------------------------------------*/
1405 /* geniCodeMultiply - gen intermediate code for multiplication     */
1406 /*-----------------------------------------------------------------*/
1407 operand *geniCodeMultiply (operand *left, operand *right)
1408
1409     iCode *ic ;
1410     int p2 = 0;
1411     link *resType ;
1412     LRTYPE ;
1413     
1414     /* if they are both literal then we know the result */
1415     if (IS_LITERAL(letype) && IS_LITERAL(retype)) 
1416         return operandFromValue (valMult(left->operand.valOperand,
1417                                          right->operand.valOperand));
1418         
1419     resType = computeType (ltype,rtype) ;
1420     left = geniCodeCast(resType,left,TRUE);
1421     right= geniCodeCast(resType,right,TRUE);
1422     
1423     /* if the right is a literal & power of 2 */
1424     /* then make it a left shift              */
1425     if (IS_LITERAL(retype) && !IS_FLOAT(letype) &&
1426         (p2 = powof2 ((unsigned long)floatFromVal(right->operand.valOperand)))) 
1427         ic = newiCode(LEFT_OP, left,operandFromLit(p2)); /* left shift */
1428     else {
1429         ic = newiCode('*',left,right);  /* normal multiplication */
1430         /* if the size left or right > 1 then support routine */
1431         if (getSize(ltype) > 1 || getSize(rtype) > 1)
1432             ic->supportRtn = 1;
1433
1434     }
1435     IC_RESULT(ic) = newiTempOperand(resType,1);
1436     
1437     ADDTOCHAIN(ic);
1438     return IC_RESULT(ic) ;
1439 }
1440
1441 /*-----------------------------------------------------------------*/
1442 /* geniCodeDivision - gen intermediate code for division           */
1443 /*-----------------------------------------------------------------*/
1444 operand *geniCodeDivision (operand *left, operand *right)
1445
1446     iCode *ic ;
1447     int p2 = 0;
1448     link *resType;
1449     link *rtype = operandType(right);
1450     link *retype= getSpec(rtype);
1451     link *ltype = operandType(left);
1452     link *letype= getSpec(ltype);
1453     
1454     resType = computeType (ltype,rtype) ;
1455     left = geniCodeCast(resType,left,TRUE);
1456     right= geniCodeCast(resType,right,TRUE);
1457     
1458     /* if the right is a literal & power of 2 */
1459     /* then make it a right shift             */
1460     if (IS_LITERAL(retype) && 
1461         !IS_FLOAT(letype)  &&
1462         (p2 = powof2 ((unsigned long) 
1463                       floatFromVal(right->operand.valOperand)))) 
1464         ic = newiCode(RIGHT_OP, left,operandFromLit(p2)); /* right shift */
1465     else {
1466         ic = newiCode('/',left,right);  /* normal division */
1467         /* if the size left or right > 1 then support routine */
1468         if (getSize(ltype) > 1 || getSize(rtype) > 1)
1469             ic->supportRtn = 1;
1470     }
1471     IC_RESULT(ic) = newiTempOperand(resType,0);
1472     
1473     ADDTOCHAIN(ic);
1474     return IC_RESULT(ic) ;
1475 }
1476 /*-----------------------------------------------------------------*/
1477 /* geniCodeModulus  - gen intermediate code for modulus            */
1478 /*-----------------------------------------------------------------*/
1479 operand *geniCodeModulus (operand *left, operand *right)
1480
1481     iCode *ic ;
1482     link *resType;
1483     LRTYPE ;
1484     
1485     /* if they are both literal then we know the result */
1486     if (IS_LITERAL(letype) && IS_LITERAL(retype)) 
1487         return operandFromValue (valMod(left->operand.valOperand,
1488                                         right->operand.valOperand));
1489     
1490     resType = computeType (ltype,rtype) ;
1491     left = geniCodeCast(resType,left,TRUE);
1492     right= geniCodeCast(resType,right,TRUE);
1493     
1494     /* now they are the same size */
1495     ic = newiCode('%',left,right);
1496
1497     /* if the size left or right > 1 then support routine */
1498     if (getSize(ltype) > 1 || getSize(rtype) > 1)
1499         ic->supportRtn = 1;
1500     IC_RESULT(ic) = newiTempOperand(resType,0);
1501     
1502     ADDTOCHAIN(ic);
1503     return IC_RESULT(ic) ;
1504 }
1505
1506 /*-----------------------------------------------------------------*/
1507 /* geniCodePtrPtrSubtract - subtracts pointer from pointer         */
1508 /*-----------------------------------------------------------------*/
1509 operand *geniCodePtrPtrSubtract (operand *left, operand *right)
1510 {
1511     iCode *ic ;
1512     operand *result;
1513     LRTYPE ;
1514     
1515     /* if they are both literals then */
1516     if (IS_LITERAL(letype) && IS_LITERAL(retype)) {
1517         result = operandFromValue (valMinus(left->operand.valOperand,
1518                                             right->operand.valOperand));
1519         goto subtractExit;
1520     }
1521     
1522     ic = newiCode('-',left,right);
1523     
1524     IC_RESULT(ic) = result = newiTempOperand(newIntLink(),1);
1525     ADDTOCHAIN(ic);
1526     
1527  subtractExit:
1528     return geniCodeDivision (result,
1529                              operandFromLit(getSize(ltype->next)));   
1530 }
1531
1532 /*-----------------------------------------------------------------*/
1533 /* geniCodeSubtract - generates code for subtraction               */
1534 /*-----------------------------------------------------------------*/
1535 operand *geniCodeSubtract (operand *left, operand *right)
1536 {
1537     iCode *ic ;
1538     int isarray= 0;
1539     link *resType;
1540     LRTYPE ;
1541     
1542     /* if they both pointers then */
1543     if ((IS_PTR(ltype) || IS_ARRAY(ltype)) &&
1544         (IS_PTR(rtype) || IS_ARRAY(rtype)))
1545         return geniCodePtrPtrSubtract (left,right);
1546     
1547     /* if they are both literal then we know the result */
1548     if (IS_LITERAL(letype) && IS_LITERAL(retype)) 
1549         return operandFromValue (valMinus(left->operand.valOperand,
1550                                           right->operand.valOperand));
1551     
1552     /* if left is an array or pointer */
1553     if ( IS_PTR(ltype) || IS_ARRAY(ltype) ) {    
1554         isarray = left->isaddr ;    
1555         right = geniCodeMultiply (right,
1556                                   operandFromLit(getSize(ltype->next)));
1557         resType = copyLinkChain(IS_ARRAY(ltype) ? ltype->next : ltype);
1558     }
1559     else { /* make them the same size */
1560         resType = computeType (ltype,rtype) ;
1561         left = geniCodeCast(resType,left,TRUE);
1562         right= geniCodeCast(resType,right,TRUE);    
1563     }
1564     
1565     ic = newiCode('-',left,right);
1566     
1567     IC_RESULT(ic)= newiTempOperand(resType,1);
1568     IC_RESULT(ic)->isaddr = (isarray ? 1 : 0);
1569
1570     /* if left or right is a float */
1571     if (IS_FLOAT(ltype) || IS_FLOAT(rtype))
1572         ic->supportRtn = 1;
1573
1574     ADDTOCHAIN(ic);
1575     return IC_RESULT(ic) ;
1576 }
1577
1578 /*-----------------------------------------------------------------*/
1579 /* geniCodeAdd - generates iCode for addition                      */
1580 /*-----------------------------------------------------------------*/
1581 operand *geniCodeAdd (operand *left, operand *right )
1582 {
1583     iCode *ic ;
1584     link *resType ;
1585     operand *size ;
1586     int isarray = 0;
1587     LRTYPE ;
1588     
1589     /* if left is an array then array access */
1590     if (IS_ARRAY(ltype)) 
1591         return geniCodeArray (left,right);           
1592     
1593     /* if the right side is LITERAL zero */
1594     /* return the left side              */
1595     if (IS_LITERAL(retype) && !floatFromVal(valFromType(retype)))
1596         return left;
1597     
1598     /* if left is literal zero return right */
1599     if (IS_LITERAL(letype) && !floatFromVal(valFromType(letype)))
1600         return right ;
1601     
1602     /* if left is an array or pointer then size */
1603     if (IS_PTR(ltype)) {    
1604         
1605         isarray = left->isaddr;
1606         size = 
1607             operandFromLit(getSize(ltype->next));
1608         right = geniCodeMultiply (right ,size);
1609         resType = copyLinkChain(ltype);
1610     }
1611     else { /* make them the same size */
1612         resType = computeType (ltype,rtype) ;
1613         left = geniCodeCast(resType,left,TRUE);
1614         right= geniCodeCast(resType,right,TRUE);
1615     }
1616     
1617     /* if they are both literals then we know */
1618     if (IS_LITERAL(letype) && IS_LITERAL(retype))
1619         return operandFromValue (valPlus(valFromType(letype),
1620                                          valFromType(retype)));
1621     
1622     ic = newiCode('+',left,right);
1623     
1624     IC_RESULT(ic) = newiTempOperand(resType,1);
1625     IC_RESULT(ic)->isaddr = ( isarray ? 1 : 0);
1626
1627     /* if left or right is a float then support
1628        routine */
1629     if (IS_FLOAT(ltype) || IS_FLOAT(rtype))
1630         ic->supportRtn = 1;
1631
1632     ADDTOCHAIN(ic);
1633     
1634     return IC_RESULT(ic) ;
1635     
1636 }
1637
1638 /*-----------------------------------------------------------------*/
1639 /* aggrToPtr - changes an aggregate to pointer to an aggregate     */
1640 /*-----------------------------------------------------------------*/
1641 link *aggrToPtr ( link *type, bool force)
1642 {
1643     link *etype ;
1644     link *ptype ;
1645
1646     
1647     if (IS_PTR(type) && !force)
1648         return type;
1649
1650     etype = getSpec(type);
1651     ptype = newLink();
1652
1653     ptype->next = type;
1654     /* if the output class is generic */
1655     if ((DCL_TYPE(ptype) = PTR_TYPE(SPEC_OCLS(etype))) == CPOINTER)
1656         DCL_PTR_CONST(ptype) = port->mem.code_ro;
1657
1658     /* if the variable was declared a constant */
1659     /* then the pointer points to a constant */
1660     if (IS_CONSTANT(etype) )
1661         DCL_PTR_CONST(ptype) = 1;
1662
1663     /* the variable was volatile then pointer to volatile */
1664     if (IS_VOLATILE(etype))
1665         DCL_PTR_VOLATILE(ptype) = 1;
1666     return ptype; 
1667 }
1668
1669 /*-----------------------------------------------------------------*/
1670 /* geniCodeArray2Ptr - array to pointer                            */
1671 /*-----------------------------------------------------------------*/
1672 operand *geniCodeArray2Ptr (operand *op)
1673 {
1674     link *optype = operandType(op);
1675     link *opetype = getSpec(optype);
1676
1677     /* set the pointer depending on the storage class */    
1678     if ((DCL_TYPE(optype) = PTR_TYPE(SPEC_OCLS(opetype))) == CPOINTER)
1679         DCL_PTR_CONST(optype) = port->mem.code_ro;
1680
1681     
1682     /* if the variable was declared a constant */
1683     /* then the pointer points to a constant */
1684     if (IS_CONSTANT(opetype) )
1685         DCL_PTR_CONST(optype) = 1;
1686
1687     /* the variable was volatile then pointer to volatile */
1688     if (IS_VOLATILE(opetype))
1689         DCL_PTR_VOLATILE(optype) = 1;
1690     op->isaddr = 0;
1691     return op;
1692 }
1693
1694 /*-----------------------------------------------------------------*/
1695 /* geniCodeArray - array access                                    */
1696 /*-----------------------------------------------------------------*/
1697 operand *geniCodeArray (operand *left,operand *right)
1698 {
1699     iCode *ic;
1700     link *ltype = operandType(left);
1701     
1702     if (IS_PTR(ltype)) {
1703         if (IS_PTR(ltype->next) && left->isaddr)
1704             left = geniCodeRValue(left,FALSE);
1705         return geniCodeDerefPtr(geniCodeAdd(left,right));
1706     }
1707
1708     /* array access */
1709     right = geniCodeMultiply(right,
1710                              operandFromLit(getSize(ltype->next)));
1711
1712     /* we can check for limits here */
1713     if (isOperandLiteral(right) &&
1714         IS_ARRAY(ltype)         &&
1715         DCL_ELEM(ltype)         &&
1716         (operandLitValue(right)/getSize(ltype->next)) >= DCL_ELEM(ltype)) {
1717         werror(E_ARRAY_BOUND);
1718         right = operandFromLit(0);
1719     }
1720
1721     ic = newiCode('+',left,right);    
1722
1723     IC_RESULT(ic) = newiTempOperand(((IS_PTR(ltype) && 
1724                                       !IS_AGGREGATE(ltype->next) &&
1725                                       !IS_PTR(ltype->next))
1726                                      ? ltype : ltype->next),0);
1727
1728     IC_RESULT(ic)->isaddr = (!IS_AGGREGATE(ltype->next));
1729     ADDTOCHAIN(ic);
1730     return IC_RESULT(ic) ;
1731 }
1732
1733 /*-----------------------------------------------------------------*/
1734 /* geniCodeStruct - generates intermediate code for structres      */
1735 /*-----------------------------------------------------------------*/
1736 operand *geniCodeStruct (operand *left, operand *right, bool islval)
1737 {
1738     iCode *ic ;
1739     link *type = operandType(left);
1740     link *etype = getSpec(type);
1741     link *retype ;
1742     symbol *element = getStructElement(SPEC_STRUCT(etype), 
1743                                        right->operand.symOperand);
1744     
1745     /* add the offset */
1746     ic = newiCode('+',left,operandFromLit(element->offset));
1747     
1748     IC_RESULT(ic) = newiTempOperand(element->type,0);
1749
1750     /* preserve the storage & output class of the struct */
1751     /* as well as the volatile attribute */
1752     retype = getSpec(operandType(IC_RESULT(ic)));
1753     SPEC_SCLS(retype) = SPEC_SCLS(etype);
1754     SPEC_OCLS(retype) = SPEC_OCLS(etype);
1755     SPEC_VOLATILE(retype) |= SPEC_VOLATILE(etype);    
1756
1757     if (IS_PTR(element->type)) 
1758         setOperandType(IC_RESULT(ic),aggrToPtr(operandType(IC_RESULT(ic)),TRUE));
1759     
1760     IC_RESULT(ic)->isaddr = (!IS_AGGREGATE(element->type));
1761
1762     
1763     ADDTOCHAIN(ic);
1764     return (islval ? IC_RESULT(ic) : geniCodeRValue(IC_RESULT(ic),TRUE));
1765 }
1766
1767 /*-----------------------------------------------------------------*/
1768 /* geniCodePostInc - generate int code for Post increment          */
1769 /*-----------------------------------------------------------------*/
1770 operand *geniCodePostInc (operand *op)
1771 {
1772     iCode *ic ;
1773     operand *rOp ;
1774     link *optype = operandType(op);
1775     operand *result ;
1776     operand *rv = (IS_ITEMP(op) ? 
1777                    geniCodeRValue(op,(IS_PTR(optype) ? TRUE : FALSE)) :
1778                    op);            
1779     link *rvtype = operandType(rv);    
1780     int size = 0;
1781     
1782     /* if this is not an address we have trouble */
1783     if ( ! op->isaddr ) {
1784         werror (E_LVALUE_REQUIRED,"++");
1785         return op ;
1786     }
1787     
1788     rOp = newiTempOperand(rvtype,0);
1789     rOp->noSpilLoc = 1;
1790
1791     if (IS_ITEMP(rv))
1792         rv->noSpilLoc = 1;
1793
1794     geniCodeAssign(rOp,rv,0);
1795    
1796     size = (IS_PTR(rvtype) ? getSize(rvtype->next) : 1);
1797     ic = newiCode('+',rv,operandFromLit(size));          
1798     IC_RESULT(ic) = result =newiTempOperand(rvtype,0);
1799     ADDTOCHAIN(ic);
1800
1801     geniCodeAssign(op,result,0);
1802     
1803     return rOp;
1804     
1805 }
1806
1807 /*-----------------------------------------------------------------*/
1808 /* geniCodePreInc - generate code for preIncrement                 */
1809 /*-----------------------------------------------------------------*/
1810 operand *geniCodePreInc (operand *op)
1811 {
1812     iCode *ic ;
1813     link *optype = operandType(op);    
1814     operand *rop = (IS_ITEMP(op) ? 
1815                     geniCodeRValue (op,(IS_PTR(optype) ? TRUE : FALSE)) :
1816                     op);
1817     link *roptype = operandType(rop);
1818     operand *result;
1819     int size = 0;
1820     
1821     if ( ! op->isaddr ) {
1822         werror(E_LVALUE_REQUIRED,"++");
1823         return op ;
1824     }
1825
1826
1827     size = (IS_PTR(roptype) ? getSize(roptype->next) : 1);
1828     ic = newiCode('+',rop,operandFromLit(size));
1829     IC_RESULT(ic) = result = newiTempOperand(roptype,0) ;
1830     ADDTOCHAIN(ic);
1831
1832     
1833     return geniCodeAssign(op,result,0) ;
1834 }
1835
1836 /*-----------------------------------------------------------------*/
1837 /* geniCodePostDec - generates code for Post decrement             */
1838 /*-----------------------------------------------------------------*/
1839 operand *geniCodePostDec (operand *op)
1840 {
1841     iCode *ic ;
1842     operand *rOp ;
1843     link *optype = operandType(op);
1844     operand *result ;
1845     operand *rv = (IS_ITEMP(op) ? 
1846                    geniCodeRValue(op,(IS_PTR(optype) ? TRUE : FALSE)) :
1847                    op);            
1848     link *rvtype = operandType(rv);    
1849     int size = 0;
1850     
1851     /* if this is not an address we have trouble */
1852     if ( ! op->isaddr ) {
1853         werror (E_LVALUE_REQUIRED,"++");
1854         return op ;
1855     }
1856     
1857     rOp = newiTempOperand(rvtype,0);
1858     rOp->noSpilLoc = 1;
1859
1860     if (IS_ITEMP(rv))
1861         rv->noSpilLoc = 1;
1862
1863     geniCodeAssign(rOp,rv,0);
1864    
1865     size = (IS_PTR(rvtype) ? getSize(rvtype->next) : 1);
1866     ic = newiCode('-',rv,operandFromLit(size));          
1867     IC_RESULT(ic) = result =newiTempOperand(rvtype,0);
1868     ADDTOCHAIN(ic);
1869
1870     geniCodeAssign(op,result,0);
1871     
1872     return rOp;
1873     
1874 }
1875
1876 /*-----------------------------------------------------------------*/
1877 /* geniCodePreDec - generate code for pre  decrement               */
1878 /*-----------------------------------------------------------------*/
1879 operand *geniCodePreDec (operand *op)
1880 {  
1881     iCode *ic ;
1882     link *optype = operandType(op);    
1883     operand *rop = (IS_ITEMP(op) ? 
1884                     geniCodeRValue (op,(IS_PTR(optype) ? TRUE : FALSE)) :
1885                     op);
1886     link *roptype = operandType(rop);
1887     operand *result;
1888     int size = 0;
1889     
1890     if ( ! op->isaddr ) {
1891         werror(E_LVALUE_REQUIRED,"++");
1892         return op ;
1893     }
1894
1895
1896     size = (IS_PTR(roptype) ? getSize(roptype->next) : 1);
1897     ic = newiCode('-',rop,operandFromLit(size));
1898     IC_RESULT(ic) = result = newiTempOperand(roptype,0) ;
1899     ADDTOCHAIN(ic);
1900
1901     
1902     return geniCodeAssign(op,result,0) ;
1903 }
1904
1905
1906 /*-----------------------------------------------------------------*/
1907 /* geniCodeBitwise - gen int code for bitWise  operators           */
1908 /*-----------------------------------------------------------------*/
1909 operand *geniCodeBitwise (operand *left, operand *right, 
1910                           int oper, link *resType)
1911 {
1912     iCode *ic;   
1913     
1914     left = geniCodeCast(resType,left,TRUE);
1915     right= geniCodeCast(resType,right,TRUE);
1916     
1917     ic = newiCode(oper,left,right);
1918     IC_RESULT(ic) = newiTempOperand(resType,0);
1919     
1920     ADDTOCHAIN(ic);
1921     return IC_RESULT(ic) ;
1922 }
1923
1924 /*-----------------------------------------------------------------*/
1925 /* geniCodeAddressOf - gens icode for '&' address of operator      */
1926 /*-----------------------------------------------------------------*/
1927 operand *geniCodeAddressOf (operand *op) 
1928 {
1929     iCode *ic;
1930     link *p ;
1931     link *optype = operandType(op);
1932     link *opetype= getSpec(optype);
1933     
1934     /* lvalue check already done in decorateType */
1935     /* this must be a lvalue */
1936 /*     if (!op->isaddr && !IS_AGGREGATE(optype)) { */
1937 /*      werror (E_LVALUE_REQUIRED,"&"); */
1938 /*      return op; */
1939 /*     } */
1940     
1941     p = newLink();
1942     p->class = DECLARATOR ;
1943     
1944     /* set the pointer depending on the storage class */
1945     if ((DCL_TYPE(p) = PTR_TYPE(SPEC_OCLS(opetype))) == CPOINTER)
1946         DCL_PTR_CONST(p) = port->mem.code_ro;
1947
1948     /* make sure we preserve the const & volatile */
1949     if (IS_CONSTANT(opetype)) 
1950         DCL_PTR_CONST(p) = 1;
1951
1952     if (IS_VOLATILE(opetype))
1953         DCL_PTR_VOLATILE(p) = 1;
1954     
1955     p->next = copyLinkChain(optype);
1956     
1957     /* if already a temp */
1958     if (IS_ITEMP(op)) {
1959         setOperandType (op,p);     
1960         op->isaddr= 0;
1961         return op;
1962     }
1963     
1964     /* other wise make this of the type coming in */
1965     ic = newiCode(ADDRESS_OF,op,NULL);
1966     IC_RESULT(ic) = newiTempOperand(p,1);
1967     IC_RESULT(ic)->isaddr = 0;
1968     ADDTOCHAIN(ic);
1969     return IC_RESULT(ic);
1970 }
1971 /*-----------------------------------------------------------------*/
1972 /* setOClass - sets the output class depending on the pointer type */
1973 /*-----------------------------------------------------------------*/
1974 void setOClass (link *ptr, link *spec)
1975 {
1976     switch (DCL_TYPE(ptr)) {
1977     case POINTER:
1978         SPEC_OCLS(spec) = data ;
1979         break ;
1980         
1981     case GPOINTER:
1982         SPEC_OCLS(spec) = generic;
1983         break;
1984         
1985     case FPOINTER:
1986         SPEC_OCLS(spec) = xdata ;
1987         break ;
1988         
1989     case CPOINTER:
1990         SPEC_OCLS(spec) = code ;
1991         break ;  
1992         
1993     case IPOINTER:
1994         SPEC_OCLS(spec) = idata;
1995         break;
1996
1997     case PPOINTER:
1998         SPEC_OCLS(spec) = xstack;
1999         break;
2000
2001     case EEPPOINTER:
2002         SPEC_OCLS(spec) = eeprom;
2003         break;
2004
2005     default:
2006         break;
2007
2008     }
2009 }
2010
2011 /*-----------------------------------------------------------------*/
2012 /* geniCodeDerefPtr - dereference pointer with '*'                 */
2013 /*-----------------------------------------------------------------*/
2014 operand *geniCodeDerefPtr (operand *op)
2015 {    
2016     link *rtype , *retype ;
2017     link *optype = operandType(op);  
2018
2019     /* if this is a pointer then generate the rvalue */
2020     if (IS_PTR(optype)) {
2021         if (IS_TRUE_SYMOP(op)) {
2022             op->isaddr = 1;
2023             op = geniCodeRValue(op,TRUE);
2024         }
2025         else    
2026             op = geniCodeRValue(op,TRUE);       
2027     }
2028     
2029     /* now get rid of the pointer part */
2030     if (lvaluereq && IS_ITEMP(op) )
2031     {
2032         retype = getSpec(rtype = copyLinkChain(optype)) ;
2033     }
2034     else
2035     {
2036         retype = getSpec(rtype = copyLinkChain(optype->next)) ;
2037     }
2038     
2039     /* if this is a pointer then outputclass needs 2b updated */
2040     if (IS_PTR(optype)) 
2041         setOClass(optype,retype);    
2042         
2043     op->isGptr = IS_GENPTR(optype);
2044
2045     /* if the pointer was declared as a constant */
2046     /* then we cannot allow assignment to the derefed */
2047     if (IS_PTR_CONST(optype))
2048         SPEC_CONST(retype) = 1;
2049     
2050     op->isaddr = (IS_PTR(rtype)    ||
2051                   IS_STRUCT(rtype) || 
2052                   IS_INT(rtype)    ||
2053                   IS_CHAR(rtype)   ||
2054                   IS_FLOAT(rtype) );
2055
2056     if (!lvaluereq)
2057         op = geniCodeRValue(op,TRUE);
2058
2059     setOperandType(op,rtype);
2060     
2061     return op;    
2062 }
2063
2064 /*-----------------------------------------------------------------*/
2065 /* geniCodeUnaryMinus - does a unary minus of the operand          */
2066 /*-----------------------------------------------------------------*/
2067 operand *geniCodeUnaryMinus (operand *op)
2068 {
2069     iCode *ic ;
2070     link *optype = operandType(op);
2071     
2072     if (IS_LITERAL(optype))
2073         return operandFromLit(- floatFromVal(op->operand.valOperand));
2074     
2075     ic = newiCode(UNARYMINUS,op,NULL);
2076     IC_RESULT(ic) = newiTempOperand(optype,0);
2077     ADDTOCHAIN(ic);
2078     return IC_RESULT(ic);
2079 }
2080
2081 /*-----------------------------------------------------------------*/
2082 /* geniCodeLeftShift - gen i code for left shift                   */
2083 /*-----------------------------------------------------------------*/
2084 operand *geniCodeLeftShift (operand *left, operand *right)
2085
2086     iCode *ic;
2087     link *ltype = operandType(left);
2088     
2089     ic = newiCode(LEFT_OP,left,right);
2090     IC_RESULT(ic) = newiTempOperand(ltype,0);
2091     ADDTOCHAIN(ic);
2092     return IC_RESULT(ic) ;  
2093 }
2094
2095 /*-----------------------------------------------------------------*/
2096 /* geniCodeRightShift - gen i code for right shift                 */
2097 /*-----------------------------------------------------------------*/
2098 operand *geniCodeRightShift (operand *left, operand *right)
2099
2100     iCode *ic;
2101     link *ltype = operandType(left);
2102     
2103     ic = newiCode(RIGHT_OP,left,right);
2104     IC_RESULT(ic) = newiTempOperand(ltype,0);
2105     ADDTOCHAIN(ic);
2106     return IC_RESULT(ic) ;  
2107 }
2108
2109 #ifdef __BORLANDC__
2110 #define LONG_LONG __int64
2111 #else
2112 #define LONG_LONG long long
2113 #endif
2114
2115 /*-----------------------------------------------------------------*/
2116 /* geniCodeLogic- logic code                                       */
2117 /*-----------------------------------------------------------------*/
2118 operand *geniCodeLogic (operand *left, operand *right, int op )
2119 {
2120     iCode *ic ;
2121     link *ctype; 
2122     link *rtype = operandType(right);
2123     link *ltype = operandType(left);
2124     
2125     /* left is integral type and right is literal then
2126        check if the literal value is within bounds */
2127     if (IS_INTEGRAL(ltype) && IS_LITERAL(rtype)) {
2128         int nbits = bitsForType(ltype);
2129         long v = operandLitValue(right);
2130
2131         if (v > ((LONG_LONG) 1 << nbits) && v > 0)
2132             werror(W_CONST_RANGE," compare operation ");
2133     }
2134
2135     ctype = computeType(ltype,rtype);                         
2136     left = geniCodeCast(ctype,left,TRUE);
2137     right= geniCodeCast(ctype,right,TRUE);
2138
2139     ic = newiCode(op,left,right);
2140     IC_RESULT(ic) = newiTempOperand (newCharLink(),1);
2141
2142     /* if comparing anything greater than one byte
2143        and not a '==' || '!=' || '&&' || '||' (these
2144        will be inlined */
2145     if (getSize(ctype) > 1 && 
2146         op != EQ_OP        && 
2147         op != NE_OP        &&
2148         op != AND_OP       &&
2149         op != OR_OP        )
2150         ic->supportRtn = 1;
2151
2152     ADDTOCHAIN(ic);
2153     return IC_RESULT(ic);
2154 }
2155
2156 /*-----------------------------------------------------------------*/
2157 /* geniCodeUnary - for a a generic unary operation                 */
2158 /*-----------------------------------------------------------------*/
2159 operand *geniCodeUnary (operand *op, int oper )
2160 {
2161     iCode *ic = newiCode (oper,op,NULL);
2162     
2163     IC_RESULT(ic)= newiTempOperand(operandType(op),0);
2164     ADDTOCHAIN(ic);
2165     return IC_RESULT(ic) ;
2166 }
2167
2168 /*-----------------------------------------------------------------*/
2169 /* geniCodeConditional - geniCode for '?' ':' operation            */
2170 /*-----------------------------------------------------------------*/
2171 operand *geniCodeConditional (ast *tree)
2172 {
2173     iCode *ic ;
2174     symbol *falseLabel = newiTempLabel(NULL);
2175     symbol *exitLabel  = newiTempLabel(NULL);
2176     operand *cond = ast2iCode(tree->left);
2177     operand *true, *false , *result;
2178     
2179     ic = newiCodeCondition(geniCodeRValue(cond,FALSE),
2180                            NULL,falseLabel);
2181     ADDTOCHAIN(ic);
2182     
2183     true = ast2iCode(tree->right->left);
2184     
2185     /* move the value to a new Operand */
2186     result = newiTempOperand(operandType(true),0);
2187     geniCodeAssign(result,geniCodeRValue(true,FALSE),0);
2188     
2189     /* generate an unconditional goto */
2190     geniCodeGoto(exitLabel);
2191     
2192     /* now for the right side */
2193     geniCodeLabel(falseLabel);
2194     
2195     false = ast2iCode(tree->right->right);
2196     geniCodeAssign(result,geniCodeRValue(false,FALSE),0);
2197     
2198     /* create the exit label */
2199     geniCodeLabel(exitLabel);
2200     
2201     return result ;
2202 }
2203
2204 /*-----------------------------------------------------------------*/
2205 /* geniCodeAssign - generate code for assignment                   */
2206 /*-----------------------------------------------------------------*/
2207 operand *geniCodeAssign (operand *left, operand *right, int nosupdate)
2208 {
2209     iCode *ic ;
2210     link *ltype = operandType(left);
2211     link *rtype = operandType(right);
2212     
2213     if (!left->isaddr && !IS_ITEMP(left)) {
2214         werror(E_LVALUE_REQUIRED,"assignment");
2215         return left;
2216     }
2217         
2218     /* left is integral type and right is literal then
2219        check if the literal value is within bounds */
2220     if (IS_INTEGRAL(ltype) && right->type == VALUE && IS_LITERAL(rtype)) {
2221         int nbits = bitsForType(ltype);
2222         long v = operandLitValue(right);
2223
2224         if (v > ((LONG_LONG)1 << nbits) && v > 0)
2225             werror(W_CONST_RANGE," = operation");
2226     }
2227
2228     /* if the left & right type don't exactly match */
2229     /* if pointer set then make sure the check is
2230        done with the type & not the pointer */
2231     /* then cast rights type to left */   
2232
2233     /* first check the type for pointer assignement */
2234     if (left->isaddr && IS_PTR(ltype) && IS_ITEMP(left) &&
2235         checkType(ltype,rtype)<0) {
2236         if (checkType(ltype->next,rtype) < 0)
2237             right = geniCodeCast(ltype->next,right,TRUE);
2238     } else
2239         if (checkType(ltype,rtype) < 0 )
2240             right = geniCodeCast(ltype,right,TRUE);
2241
2242     /* if left is a true symbol & ! volatile 
2243        create an assignment to temporary for
2244        the right & then assign this temporary
2245        to the symbol this is SSA . isn't it simple
2246        and folks have published mountains of paper on it */
2247     if (IS_TRUE_SYMOP(left) && 
2248         !isOperandVolatile(left,FALSE) &&
2249         isOperandGlobal(left)) {
2250         symbol *sym = NULL;
2251
2252         if (IS_TRUE_SYMOP(right))
2253             sym = OP_SYMBOL(right);
2254         ic = newiCode('=',NULL,right);
2255         IC_RESULT(ic) = right = newiTempOperand(ltype,0);       
2256         SPIL_LOC(right)  = sym ;
2257         ADDTOCHAIN(ic);
2258     }
2259     
2260     ic = newiCode('=',NULL,right);
2261     IC_RESULT(ic) = left;
2262     ADDTOCHAIN(ic);    
2263
2264     /* if left isgptr flag is set then support
2265        routine will be required */
2266     if (left->isGptr)
2267         ic->supportRtn = 1;
2268
2269     ic->nosupdate = nosupdate;
2270     return left;
2271 }
2272
2273 /*-----------------------------------------------------------------*/
2274 /* geniCodeSEParms - generate code for side effecting fcalls       */
2275 /*-----------------------------------------------------------------*/
2276 static void geniCodeSEParms (ast *parms)
2277 {
2278     if (!parms)
2279         return ;
2280
2281     if (parms->type == EX_OP && parms->opval.op == PARAM) {
2282         geniCodeSEParms (parms->left) ;
2283         geniCodeSEParms (parms->right);
2284         return ;
2285     }
2286
2287     /* hack don't like this but too lazy to think of
2288        something better */
2289     if (IS_ADDRESS_OF_OP(parms))
2290         parms->left->lvalue = 1;
2291     
2292     if (IS_CAST_OP(parms) && 
2293         IS_PTR(parms->ftype) && 
2294         IS_ADDRESS_OF_OP(parms->right))
2295         parms->right->left->lvalue = 1;
2296
2297     parms->opval.oprnd = 
2298         geniCodeRValue(ast2iCode (parms),FALSE);
2299    
2300     parms->type = EX_OPERAND ;
2301 }
2302
2303 /*-----------------------------------------------------------------*/
2304 /* geniCodeParms - generates parameters                            */
2305 /*-----------------------------------------------------------------*/
2306 static void geniCodeParms ( ast *parms , int *stack, link *fetype)
2307 {
2308     iCode *ic ;
2309     operand *pval ; 
2310     
2311     if ( ! parms )
2312         return ;
2313     
2314     /* if this is a param node then do the left & right */
2315     if (parms->type == EX_OP && parms->opval.op == PARAM) {
2316         geniCodeParms (parms->left, stack,fetype) ;
2317         geniCodeParms (parms->right, stack,fetype);
2318         return ;
2319     }
2320     
2321     /* get the parameter value */
2322     if (parms->type == EX_OPERAND)
2323         pval = parms->opval.oprnd ;
2324     else {
2325         /* maybe this else should go away ?? */
2326         /* hack don't like this but too lazy to think of
2327            something better */
2328         if (IS_ADDRESS_OF_OP(parms))
2329             parms->left->lvalue = 1;
2330     
2331         if (IS_CAST_OP(parms) && 
2332             IS_PTR(parms->ftype) && 
2333             IS_ADDRESS_OF_OP(parms->right))
2334             parms->right->left->lvalue = 1;
2335
2336         pval = geniCodeRValue(ast2iCode (parms),FALSE); 
2337     }
2338
2339     /* if register parm then make it a send */
2340     if ((parms->argSym && IS_REGPARM(parms->argSym->etype)) ||
2341         IS_REGPARM(parms->etype)) {
2342         ic = newiCode(SEND,pval,NULL);
2343         ADDTOCHAIN(ic);
2344     } else {
2345         /* now decide whether to push or assign */
2346         if (!(options.stackAuto || IS_RENT(fetype))) { 
2347             
2348             /* assign */
2349             operand *top = operandFromSymbol(parms->argSym);
2350             geniCodeAssign(top,pval,1);
2351         }
2352         else { 
2353             link *p = operandType(pval);
2354             /* push */
2355             ic = newiCode(IPUSH,pval,NULL);
2356             ic->parmPush = 1;
2357             /* update the stack adjustment */
2358             *stack += getSize(IS_AGGREGATE(p)? aggrToPtr(p,FALSE):p);
2359             ADDTOCHAIN(ic);
2360         }
2361     }
2362     
2363 }
2364
2365 /*-----------------------------------------------------------------*/
2366 /* geniCodeCall - generates temp code for calling                  */
2367 /*-----------------------------------------------------------------*/
2368 operand *geniCodeCall (operand *left, ast *parms)
2369
2370     iCode *ic ;
2371     operand *result ;
2372     link *type, *etype;
2373     int stack = 0 ;
2374     
2375     /* take care of parameters with side-effecting
2376        function calls in them, this is required to take care 
2377        of overlaying function parameters */
2378     geniCodeSEParms ( parms );
2379
2380     /* first the parameters */
2381     geniCodeParms ( parms , &stack , getSpec(operandType(left)));
2382     
2383     /* now call : if symbol then pcall */
2384     if (IS_ITEMP(left)) 
2385         ic = newiCode(PCALL,left,NULL);
2386     else
2387         ic = newiCode(CALL,left,NULL);
2388     
2389     IC_ARGS(ic) = left->operand.symOperand->args ;
2390     type = copyLinkChain(operandType(left)->next);
2391     etype = getSpec(type);
2392     SPEC_EXTR(etype) = 0;
2393     IC_RESULT(ic) = result = newiTempOperand(type,1);
2394     
2395     ADDTOCHAIN(ic);
2396     
2397     /* stack adjustment after call */
2398     left->parmBytes = stack;
2399
2400     return result;
2401 }
2402
2403 /*-----------------------------------------------------------------*/
2404 /* geniCodeReceive - generate intermediate code for "receive"      */
2405 /*-----------------------------------------------------------------*/
2406 static void geniCodeReceive (value *args)
2407 {   
2408     /* for all arguments that are passed in registers */
2409     while (args) {
2410
2411         if (IS_REGPARM(args->etype)) {
2412             operand *opr = operandFromValue(args);
2413             operand *opl ;
2414             symbol *sym  = OP_SYMBOL(opr);
2415             iCode *ic ;
2416
2417             /* we will use it after all optimizations
2418                and before liveRange calculation */          
2419             if (!sym->addrtaken && !IS_VOLATILE(sym->etype)) {
2420
2421                 if(IN_FARSPACE(SPEC_OCLS(sym->etype)) &&
2422                    options.stackAuto == 0) {
2423                 } else {
2424                     opl = newiTempOperand(args->type,0);
2425                     sym->reqv = opl ;       
2426                     sym->reqv->key = sym->key ;
2427                     OP_SYMBOL(sym->reqv)->key = sym->key;
2428                     OP_SYMBOL(sym->reqv)->isreqv = 1;
2429                     OP_SYMBOL(sym->reqv)->islocal= 0;
2430                     SPIL_LOC(sym->reqv) =  sym;
2431                 }
2432             }
2433
2434             ic = newiCode(RECEIVE,NULL,NULL);
2435             currFunc->recvSize = getSize(sym->etype);
2436             IC_RESULT(ic) = opr;
2437             ADDTOCHAIN(ic);
2438         }
2439         
2440         args = args->next;
2441     }
2442 }
2443
2444 /*-----------------------------------------------------------------*/
2445 /* geniCodeFunctionBody - create the function body                 */
2446 /*-----------------------------------------------------------------*/
2447 void geniCodeFunctionBody (ast *tree)
2448 {
2449     iCode *ic ;
2450     operand *func ;
2451     link *fetype  ;
2452     int savelineno ;
2453     
2454     /* reset the auto generation */
2455     /* numbers */
2456     iTempNum = 0 ;
2457     iTempLblNum = 0;   
2458     operandKey = 0 ;
2459     iCodeKey = 0 ;
2460     func  = ast2iCode(tree->left);
2461     fetype = getSpec(operandType(func));
2462     
2463     savelineno = lineno;
2464     lineno = OP_SYMBOL(func)->lineDef;
2465     /* create an entry label */
2466     geniCodeLabel(entryLabel);    
2467     lineno = savelineno;
2468
2469     /* create a proc icode */
2470     ic = newiCode(FUNCTION,func,NULL);
2471     /* if the function has parmas   then */
2472     /* save the parameters information    */
2473     ic->argLabel.args = tree->values.args ;
2474     ic->lineno = OP_SYMBOL(func)->lineDef;
2475
2476     ADDTOCHAIN(ic);   
2477     
2478     /* for all parameters that are passed
2479        on registers add a "receive" */
2480     geniCodeReceive( tree->values.args );
2481
2482     /* generate code for the body */
2483     ast2iCode(tree->right);
2484     
2485     /* create a label for return */
2486     geniCodeLabel(returnLabel);
2487     
2488     /* now generate the end proc */
2489     ic = newiCode(ENDFUNCTION,func,NULL);
2490     ADDTOCHAIN(ic);
2491     return ;
2492 }
2493
2494 /*-----------------------------------------------------------------*/
2495 /* geniCodeReturn - gen icode for 'return' statement               */
2496 /*-----------------------------------------------------------------*/
2497 void geniCodeReturn (operand *op)
2498 {
2499     iCode *ic;
2500     
2501     /* if the operand is present force an rvalue */
2502     if (op) 
2503         op = geniCodeRValue(op,FALSE);    
2504     
2505     ic = newiCode(RETURN,op,NULL);
2506     ADDTOCHAIN(ic);
2507 }
2508
2509 /*-----------------------------------------------------------------*/
2510 /* geniCodeIfx - generates code for extended if statement          */
2511 /*-----------------------------------------------------------------*/
2512 void geniCodeIfx (ast *tree)
2513 {
2514     iCode *ic;
2515     operand *condition = ast2iCode(tree->left);
2516     link *cetype; 
2517     
2518     /* if condition is null then exit */
2519     if (!condition)
2520         goto exit ;
2521     else
2522         condition = geniCodeRValue(condition,FALSE);
2523     
2524     cetype = getSpec(operandType(condition));
2525     /* if the condition is a literal */
2526     if (IS_LITERAL(cetype)) {
2527         if (floatFromVal(condition->operand.valOperand)) {
2528             if (tree->trueLabel)
2529                 geniCodeGoto(tree->trueLabel);
2530             else
2531                 assert(1);
2532         }
2533         else {
2534             if (tree->falseLabel)
2535                 geniCodeGoto (tree->falseLabel);
2536             else
2537                 assert(1);
2538         }
2539         goto exit;
2540     }
2541     
2542     if ( tree->trueLabel ) {
2543         ic = newiCodeCondition(condition,
2544                                tree->trueLabel,
2545                                NULL );
2546         ADDTOCHAIN(ic);
2547         
2548         if ( tree->falseLabel) 
2549             geniCodeGoto(tree->falseLabel);     
2550     }
2551     else {
2552         ic = newiCodeCondition (condition,
2553                                 NULL,
2554                                 tree->falseLabel);
2555         ADDTOCHAIN(ic);
2556     }
2557     
2558  exit:
2559     ast2iCode(tree->right);
2560 }
2561
2562 /*-----------------------------------------------------------------*/
2563 /* geniCodeJumpTable - tries to create a jump table for switch     */
2564 /*-----------------------------------------------------------------*/
2565 int geniCodeJumpTable (operand *cond, value *caseVals, ast *tree)
2566 {
2567     int min = 0 ,max = 0, t, cnt = 0;
2568     value *vch;
2569     iCode *ic;
2570     operand *boundary;
2571     symbol *falseLabel;
2572     set *labels = NULL ;
2573
2574     if (!tree || !caseVals)
2575         return 0;
2576
2577     /* the criteria for creating a jump table is */
2578     /* all integer numbers between the maximum & minimum must */
2579     /* be present , the maximum value should not exceed 255 */
2580     min = max = (int)floatFromVal(vch = caseVals);
2581     sprintf(buffer,"_case_%d_%d",
2582             tree->values.switchVals.swNum,
2583             min);
2584     addSet(&labels,newiTempLabel(buffer));
2585
2586     /* if there is only one case value then no need */
2587     if (!(vch = vch->next ))
2588         return 0;
2589
2590     while (vch) {
2591         if (((t = (int)floatFromVal(vch)) - max) != 1)
2592             return 0;
2593         sprintf(buffer,"_case_%d_%d",
2594                 tree->values.switchVals.swNum,
2595                 t);
2596         addSet(&labels,newiTempLabel(buffer));
2597         max = t;
2598         cnt++ ;
2599         vch = vch->next ;
2600     }
2601     
2602     /* if the number of case statements <= 2 then */
2603     /* it is not economical to create the jump table */
2604     /* since two compares are needed for boundary conditions */
2605     if ((! optimize.noJTabBoundary  && cnt <= 2) || max > (255/3))
2606         return 0;
2607     
2608     if ( tree->values.switchVals.swDefault )
2609         sprintf (buffer,"_default_%d",tree->values.switchVals.swNum);
2610     else
2611         sprintf (buffer,"_swBrk_%d",tree->values.switchVals.swNum  );
2612     
2613     falseLabel = newiTempLabel (buffer);
2614
2615     /* so we can create a jumptable */
2616     /* first we rule out the boundary conditions */
2617     /* if only optimization says so */
2618     if ( ! optimize.noJTabBoundary ) {
2619         link *cetype = getSpec(operandType(cond));
2620         /* no need to check the lower bound if
2621            the condition is unsigned & minimum value is zero */
2622         if (!( min == 0  && SPEC_USIGN(cetype))) {
2623             boundary = geniCodeLogic (cond,operandFromLit(min),'<');
2624             ic = newiCodeCondition (boundary,falseLabel,NULL);
2625             ADDTOCHAIN(ic);
2626         }
2627
2628         /* now for upper bounds */
2629         boundary = geniCodeLogic(cond,operandFromLit(max),'>');
2630         ic = newiCodeCondition (boundary,falseLabel,NULL);
2631         ADDTOCHAIN(ic);
2632     }
2633
2634     /* if the min is not zero then we no make it zero */
2635     if (min) {
2636         cond = geniCodeSubtract(cond,operandFromLit(min));
2637         setOperandType(cond, UCHARTYPE);
2638     }
2639
2640     /* now create the jumptable */
2641     ic = newiCode(JUMPTABLE,NULL,NULL);
2642     IC_JTCOND(ic) = cond;
2643     IC_JTLABELS(ic) = labels;
2644     ADDTOCHAIN(ic);
2645     return 1;       
2646 }
2647
2648 /*-----------------------------------------------------------------*/
2649 /* geniCodeSwitch - changes a switch to a if statement             */
2650 /*-----------------------------------------------------------------*/
2651 void geniCodeSwitch (ast *tree)
2652 {
2653     iCode *ic ;
2654     operand *cond = geniCodeRValue(ast2iCode (tree->left),FALSE);
2655     value *caseVals = tree->values.switchVals.swVals ;
2656     symbol *trueLabel , *falseLabel;
2657     
2658     /* if we can make this a jump table */
2659     if ( geniCodeJumpTable (cond,caseVals,tree) )
2660         goto jumpTable ; /* no need for the comparison */
2661
2662     /* for the cases defined do */
2663     while (caseVals) {
2664         
2665         operand *compare = geniCodeLogic (cond,
2666                                           operandFromValue(caseVals),
2667                                           EQ_OP);
2668         
2669         sprintf(buffer,"_case_%d_%d",
2670                 tree->values.switchVals.swNum,
2671                 (int) floatFromVal(caseVals));
2672         trueLabel = newiTempLabel(buffer);
2673         
2674         ic = newiCodeCondition(compare,trueLabel,NULL);
2675         ADDTOCHAIN(ic);
2676         caseVals = caseVals->next;
2677     }
2678
2679
2680     
2681     /* if default is present then goto break else break */
2682     if ( tree->values.switchVals.swDefault )
2683         sprintf (buffer,"_default_%d",tree->values.switchVals.swNum);
2684     else
2685         sprintf (buffer,"_swBrk_%d",tree->values.switchVals.swNum  );
2686     
2687     falseLabel = newiTempLabel (buffer);
2688     geniCodeGoto(falseLabel);
2689  
2690  jumpTable:   
2691     ast2iCode(tree->right);
2692
2693
2694 /*-----------------------------------------------------------------*/
2695 /* geniCodeInline - intermediate code for inline assembler         */
2696 /*-----------------------------------------------------------------*/
2697 static void geniCodeInline (ast *tree)
2698 {
2699     iCode *ic;
2700
2701     ic = newiCode(INLINEASM,NULL,NULL);
2702     IC_INLINE(ic) = tree->values.inlineasm;
2703     ADDTOCHAIN(ic);
2704 }
2705
2706 /*-----------------------------------------------------------------*/
2707 /* ast2iCode - creates an icodeList from an ast                    */
2708 /*-----------------------------------------------------------------*/
2709 operand *ast2iCode (ast *tree)
2710 {
2711     operand *left = NULL;
2712     operand *right= NULL;
2713     
2714     if (!tree)
2715         return NULL ;
2716     
2717     /* set the global variables for filename & line number */
2718     if ( tree->filename )
2719         filename =  tree->filename ;
2720     if ( tree->lineno)
2721         lineno   = tree->lineno ;
2722     if (tree->block)
2723         block = tree->block ;
2724     if (tree->level)
2725         scopeLevel = tree->level;
2726     
2727     if (tree->type == EX_VALUE )
2728         return operandFromValue(tree->opval.val);
2729     
2730     if (tree->type == EX_LINK )
2731         return operandFromLink (tree->opval.lnk);
2732     
2733     /* if we find a nullop */
2734     if (tree->type == EX_OP && 
2735         ( tree->opval.op == NULLOP || 
2736           tree->opval.op == BLOCK )) {
2737         ast2iCode (tree->left);
2738         ast2iCode (tree->right);
2739         return NULL ;
2740     }
2741     
2742     /* special cases for not evaluating */
2743     if ( tree->opval.op != ':'   && 
2744          tree->opval.op != '?'   &&
2745          tree->opval.op != CALL  && 
2746          tree->opval.op != IFX   &&
2747          tree->opval.op != LABEL &&
2748          tree->opval.op != GOTO  &&     
2749          tree->opval.op != SWITCH &&
2750          tree->opval.op != FUNCTION &&
2751          tree->opval.op != INLINEASM ) {
2752         if (IS_ASSIGN_OP(tree->opval.op) || 
2753             IS_DEREF_OP(tree)            || 
2754             (tree->opval.op == '&' && !tree->right) ||
2755             tree->opval.op == PTR_OP) {
2756             lvaluereq++;
2757             left = operandFromAst(tree->left);
2758             lvaluereq--;
2759         } else {
2760             left =  operandFromAst(tree->left);
2761         }
2762         if (tree->opval.op == INC_OP || 
2763             tree->opval.op == DEC_OP) {
2764             lvaluereq++;
2765             right= operandFromAst(tree->right);
2766             lvaluereq--;
2767         } else {
2768             right= operandFromAst(tree->right);
2769         }
2770     }
2771     
2772     /* now depending on the type of operand */
2773     /* this will be a biggy                 */
2774     switch (tree->opval.op) {
2775         
2776     case '[' :    /* array operation */
2777         {
2778             link *ltype = operandType(left);
2779             left= geniCodeRValue (left,IS_PTR(ltype->next) ? TRUE : FALSE);
2780             right=geniCodeRValue (right,TRUE);             
2781         }
2782         
2783         return geniCodeArray (left,right);
2784         
2785     case '.' :   /* structure dereference */
2786         if (IS_PTR(operandType(left)))
2787             left = geniCodeRValue(left,TRUE);
2788         else
2789             left = geniCodeRValue(left,FALSE);            
2790         
2791         return geniCodeStruct (left,right,tree->lvalue);
2792         
2793     case PTR_OP: /* structure pointer dereference */
2794         {
2795             link *pType;
2796             pType = operandType(left);
2797             left = geniCodeRValue(left,TRUE);
2798             
2799             setOClass (pType,getSpec(operandType(left)));
2800         }              
2801         
2802         return geniCodeStruct (left, right,tree->lvalue);
2803         
2804     case INC_OP: /* increment operator */
2805         if ( left )
2806             return geniCodePostInc (left);
2807         else
2808             return geniCodePreInc (right);
2809         
2810     case DEC_OP: /* decrement operator */
2811         if ( left )
2812             return geniCodePostDec (left);
2813         else
2814             return geniCodePreDec (right);
2815         
2816     case '&' : /* bitwise and or address of operator */
2817         if ( right ) { /* this is a bitwise operator   */
2818             left= geniCodeRValue(left,FALSE);
2819             right= geniCodeRValue(right,FALSE);     
2820             return geniCodeBitwise (left,right,BITWISEAND,tree->ftype);
2821         } else
2822             return geniCodeAddressOf (left);
2823         
2824     case '|': /* bitwise or & xor */
2825     case '^':
2826         return geniCodeBitwise (geniCodeRValue(left,FALSE),
2827                                 geniCodeRValue(right,FALSE),
2828                                 tree->opval.op,
2829                                 tree->ftype);
2830         
2831     case '/':
2832         return geniCodeDivision (geniCodeRValue(left,FALSE),
2833                                  geniCodeRValue(right,FALSE));
2834         
2835     case '%' :
2836         return geniCodeModulus (geniCodeRValue(left,FALSE),
2837                                 geniCodeRValue(right,FALSE));
2838     case '*':
2839         if ( right ) 
2840             return geniCodeMultiply (geniCodeRValue(left,FALSE),
2841                                      geniCodeRValue(right,FALSE));
2842         else        
2843             return geniCodeDerefPtr (geniCodeRValue(left,FALSE));
2844         
2845     case '-' :
2846         if ( right ) 
2847             return geniCodeSubtract (geniCodeRValue(left,FALSE),
2848                                      geniCodeRValue(right,FALSE));
2849         else
2850             return geniCodeUnaryMinus (geniCodeRValue(left,FALSE));
2851         
2852     case '+' :
2853         if ( right ) 
2854             return geniCodeAdd (geniCodeRValue(left,FALSE),
2855                                 geniCodeRValue(right,FALSE));
2856         else
2857             return geniCodeRValue(left,FALSE) ; /* unary '+' has no meaning */
2858         
2859     case LEFT_OP:
2860         return geniCodeLeftShift (geniCodeRValue(left,FALSE),
2861                                   geniCodeRValue(right,FALSE));
2862         
2863     case RIGHT_OP:
2864         return geniCodeRightShift (geniCodeRValue(left,FALSE),
2865                                    geniCodeRValue(right,FALSE));
2866     case CAST:
2867         return geniCodeCast (operandType(left),
2868                              geniCodeRValue(right,FALSE),FALSE);
2869         
2870     case '~' :
2871     case '!' :
2872     case RRC:
2873     case RLC:   
2874         return geniCodeUnary (geniCodeRValue(left,FALSE),tree->opval.op);
2875         
2876     case GETHBIT:
2877         {
2878             operand *op = geniCodeUnary (geniCodeRValue(left,FALSE),tree->opval.op);
2879             setOperandType(op, UCHARTYPE);
2880             return op;
2881         }
2882     case '>' :
2883     case '<' :
2884     case LE_OP:
2885     case GE_OP:
2886     case EQ_OP:
2887     case NE_OP:
2888     case AND_OP:
2889     case OR_OP:
2890         return geniCodeLogic (geniCodeRValue(left,FALSE),
2891                               geniCodeRValue(right,FALSE),
2892                               tree->opval.op);
2893     case '?' : 
2894         return geniCodeConditional (tree); 
2895         
2896     case SIZEOF:
2897         return operandFromLit(getSize(tree->right->ftype));
2898         
2899     case '='        :
2900         {
2901             link *rtype = operandType(right);
2902             link *ltype = operandType(left);
2903             if (IS_PTR(rtype) && IS_ITEMP(right) 
2904                 && right->isaddr && checkType(rtype->next,ltype)==1)
2905                 right =  geniCodeRValue(right,TRUE);
2906             else
2907                 right = geniCodeRValue(right,FALSE);
2908
2909             geniCodeAssign (left,right,0);
2910             return right ;
2911         }              
2912     case MUL_ASSIGN:
2913         return 
2914             geniCodeAssign(left,
2915                            geniCodeMultiply(geniCodeRValue (operandFromOperand(left),
2916                                                             FALSE),
2917                                             geniCodeRValue(right,FALSE)),0);
2918                                                 
2919     case DIV_ASSIGN:
2920         return 
2921             geniCodeAssign(left,
2922                            geniCodeDivision(geniCodeRValue(operandFromOperand(left),
2923                                                            FALSE),
2924                                             geniCodeRValue(right,FALSE)),0);
2925     case MOD_ASSIGN:
2926         return 
2927             geniCodeAssign(left,
2928                            geniCodeModulus(geniCodeRValue(operandFromOperand(left),
2929                                                           FALSE),
2930                                            geniCodeRValue(right,FALSE)),0);
2931     case ADD_ASSIGN: 
2932         {
2933             link *rtype = operandType(right);
2934             link *ltype = operandType(left);
2935             if (IS_PTR(rtype) && IS_ITEMP(right) 
2936                 && right->isaddr && checkType(rtype->next,ltype)==1)
2937                 right =  geniCodeRValue(right,TRUE);
2938             else
2939                 right = geniCodeRValue(right,FALSE);
2940
2941            
2942             return geniCodeAssign(left,
2943                                   geniCodeAdd (geniCodeRValue(operandFromOperand(left),
2944                                                               FALSE),
2945                                                right),0);
2946         }
2947     case SUB_ASSIGN:
2948         {
2949             link *rtype = operandType(right);
2950             link *ltype = operandType(left);
2951             if (IS_PTR(rtype) && IS_ITEMP(right) 
2952                 && right->isaddr && checkType(rtype->next,ltype)==1) {
2953                 right =  geniCodeRValue(right,TRUE);
2954             }
2955             else {
2956                 right = geniCodeRValue(right,FALSE);
2957             }
2958             return 
2959                 geniCodeAssign (left,
2960                                 geniCodeSubtract(geniCodeRValue(operandFromOperand(left),
2961                                                                 FALSE),
2962                                                  right),0);
2963         }
2964     case LEFT_ASSIGN:
2965         return 
2966             geniCodeAssign (left,
2967                             geniCodeLeftShift(geniCodeRValue(operandFromOperand(left)
2968                                                              ,FALSE),
2969                                               geniCodeRValue(right,FALSE)),0);
2970     case RIGHT_ASSIGN:
2971         return 
2972             geniCodeAssign(left,
2973                            geniCodeRightShift(geniCodeRValue(operandFromOperand(left)
2974                                                              ,FALSE),
2975                                               geniCodeRValue(right,FALSE)),0);
2976     case AND_ASSIGN:
2977         return 
2978             geniCodeAssign (left,
2979                             geniCodeBitwise(geniCodeRValue(operandFromOperand(left),
2980                                                            FALSE),
2981                                             geniCodeRValue(right,FALSE),
2982                                             BITWISEAND,
2983                                             operandType(left)),0);
2984     case XOR_ASSIGN:
2985         return 
2986             geniCodeAssign (left,
2987                             geniCodeBitwise (geniCodeRValue(operandFromOperand(left),
2988                                                             FALSE),
2989                                              geniCodeRValue(right,FALSE),
2990                                              '^',
2991                                              operandType(left)),0);
2992     case OR_ASSIGN:
2993         return 
2994             geniCodeAssign (left,
2995                             geniCodeBitwise (geniCodeRValue(operandFromOperand(left)
2996                                                             ,FALSE),
2997                                              geniCodeRValue(right,FALSE),
2998                                              '|',
2999                                              operandType(left)),0);
3000     case ',' :
3001         return geniCodeRValue(right,FALSE);
3002         
3003     case CALL:
3004         return geniCodeCall (ast2iCode(tree->left),
3005                              tree->right);
3006     case LABEL:
3007         geniCodeLabel(ast2iCode(tree->left)->operand.symOperand);
3008         return ast2iCode (tree->right);
3009         
3010     case GOTO:
3011         geniCodeGoto (ast2iCode(tree->left)->operand.symOperand);
3012         return ast2iCode (tree->right);
3013         
3014     case FUNCTION:
3015         geniCodeFunctionBody ( tree );
3016         return NULL ;
3017         
3018     case RETURN:
3019         geniCodeReturn (right);
3020         return NULL ;
3021         
3022     case IFX:
3023         geniCodeIfx (tree);
3024         return NULL ;
3025         
3026     case SWITCH:
3027         geniCodeSwitch (tree);
3028         return NULL;
3029
3030     case INLINEASM:
3031         geniCodeInline (tree);
3032         return NULL ;
3033     }
3034     
3035     return NULL;
3036 }
3037
3038 /*-----------------------------------------------------------------*/
3039 /* reverseICChain - gets from the list and creates a linkedlist    */
3040 /*-----------------------------------------------------------------*/
3041 iCode *reverseiCChain ()
3042 {
3043     iCode *loop = NULL ;
3044     iCode *prev = NULL ;
3045     
3046     while ((loop = getSet(&iCodeChain))) {
3047         loop->next = prev ;
3048         if ( prev )
3049             prev->prev = loop; 
3050         prev = loop ;
3051     }
3052     
3053     return prev;
3054 }
3055
3056
3057 /*-----------------------------------------------------------------*/
3058 /* iCodeFromAst - given an ast will convert it to iCode            */
3059 /*-----------------------------------------------------------------*/
3060 iCode *iCodeFromAst ( ast *tree )
3061 {
3062     returnLabel = newiTempLabel("_return");
3063     entryLabel  = newiTempLabel("_entry") ;
3064     ast2iCode (tree);
3065     return reverseiCChain ();
3066 }
3067