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