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