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