clean up garbage in last checkin
[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     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 (link *type, char throwType)
606 {
607     symbol *itmp;
608     operand *op = newOperand();
609     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 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 (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     link *optype ;
701     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     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     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     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, 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 (link *type)
1195 {
1196     operand *op ;
1197     
1198     /* operand from 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, 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     link *type = operandType(op);
1283     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 (link *type, operand *op, bool implicit) 
1337 {
1338     iCode *ic ;
1339     link *optype ;
1340     link *opetype = getSpec(optype = operandType(op));
1341     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     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     link *resType;
1467     link *rtype = operandType(right);
1468     link *retype= getSpec(rtype);
1469     link *ltype = operandType(left);
1470     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     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     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     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 link *aggrToPtr ( link *type, bool force)
1667 {
1668     link *etype ;
1669     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     link *optype = operandType(op);
1700     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     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     link *type = operandType(left);
1772     link *etype = getSpec(type);
1773     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     link *optype = operandType(op);
1807     operand *result ;
1808     operand *rv = (IS_ITEMP(op) ? 
1809                    geniCodeRValue(op,(IS_PTR(optype) ? TRUE : FALSE)) :
1810                    op);            
1811     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     link *optype = operandType(op);    
1846     operand *rop = (IS_ITEMP(op) ? 
1847                     geniCodeRValue (op,(IS_PTR(optype) ? TRUE : FALSE)) :
1848                     op);
1849     link *roptype = operandType(rop);
1850     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     link *optype = operandType(op);
1876     operand *result ;
1877     operand *rv = (IS_ITEMP(op) ? 
1878                    geniCodeRValue(op,(IS_PTR(optype) ? TRUE : FALSE)) :
1879                    op);            
1880     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     link *optype = operandType(op);    
1915     operand *rop = (IS_ITEMP(op) ? 
1916                     geniCodeRValue (op,(IS_PTR(optype) ? TRUE : FALSE)) :
1917                     op);
1918     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, 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     link *p ;
1963     link *optype = operandType(op);
1964     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 (link *ptr, 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     link *rtype , *retype ;
2049     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     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     link *ltype = operandType(left);
2120     
2121     ic = newiCode(LEFT_OP,left,right);
2122     IC_RESULT(ic) = newiTempOperand(ltype,0);
2123     ADDTOCHAIN(ic);
2124     return IC_RESULT(ic) ;  
2125 }
2126
2127 /*-----------------------------------------------------------------*/
2128 /* geniCodeRightShift - gen i code for right shift                 */
2129 /*-----------------------------------------------------------------*/
2130 operand *geniCodeRightShift (operand *left, operand *right)
2131
2132     iCode *ic;
2133     link *ltype = operandType(left);
2134     
2135     ic = newiCode(RIGHT_OP,left,right);
2136     IC_RESULT(ic) = newiTempOperand(ltype,0);
2137     ADDTOCHAIN(ic);
2138     return IC_RESULT(ic) ;  
2139 }
2140
2141 #ifdef __BORLANDC__
2142 #define LONG_LONG __int64
2143 #else
2144 #define LONG_LONG long long
2145 #endif
2146
2147 /*-----------------------------------------------------------------*/
2148 /* geniCodeLogic- logic code                                       */
2149 /*-----------------------------------------------------------------*/
2150 operand *geniCodeLogic (operand *left, operand *right, int op )
2151 {
2152     iCode *ic ;
2153     link *ctype; 
2154     link *rtype = operandType(right);
2155     link *ltype = operandType(left);
2156     
2157     /* left is integral type and right is literal then
2158        check if the literal value is within bounds */
2159     if (IS_INTEGRAL(ltype) && IS_LITERAL(rtype)) {
2160         int nbits = bitsForType(ltype);
2161         long v = operandLitValue(right);
2162
2163         if (v > ((LONG_LONG) 1 << nbits) && v > 0)
2164             werror(W_CONST_RANGE," compare operation ");
2165     }
2166
2167     ctype = computeType(ltype,rtype);                         
2168     left = geniCodeCast(ctype,left,TRUE);
2169     right= geniCodeCast(ctype,right,TRUE);
2170
2171     ic = newiCode(op,left,right);
2172     IC_RESULT(ic) = newiTempOperand (newCharLink(),1);
2173
2174     /* if comparing anything greater than one byte
2175        and not a '==' || '!=' || '&&' || '||' (these
2176        will be inlined */
2177     if (getSize(ctype) > 1 && 
2178         op != EQ_OP        && 
2179         op != NE_OP        &&
2180         op != AND_OP       &&
2181         op != OR_OP        )
2182         ic->supportRtn = 1;
2183
2184     ADDTOCHAIN(ic);
2185     return IC_RESULT(ic);
2186 }
2187
2188 /*-----------------------------------------------------------------*/
2189 /* geniCodeUnary - for a a generic unary operation                 */
2190 /*-----------------------------------------------------------------*/
2191 operand *geniCodeUnary (operand *op, int oper )
2192 {
2193     iCode *ic = newiCode (oper,op,NULL);
2194     
2195     IC_RESULT(ic)= newiTempOperand(operandType(op),0);
2196     ADDTOCHAIN(ic);
2197     return IC_RESULT(ic) ;
2198 }
2199
2200 /*-----------------------------------------------------------------*/
2201 /* geniCodeConditional - geniCode for '?' ':' operation            */
2202 /*-----------------------------------------------------------------*/
2203 operand *geniCodeConditional (ast *tree)
2204 {
2205     iCode *ic ;
2206     symbol *falseLabel = newiTempLabel(NULL);
2207     symbol *exitLabel  = newiTempLabel(NULL);
2208     operand *cond = ast2iCode(tree->left);
2209     operand *true, *false , *result;
2210     
2211     ic = newiCodeCondition(geniCodeRValue(cond,FALSE),
2212                            NULL,falseLabel);
2213     ADDTOCHAIN(ic);
2214     
2215     true = ast2iCode(tree->right->left);
2216     
2217     /* move the value to a new Operand */
2218     result = newiTempOperand(operandType(true),0);
2219     geniCodeAssign(result,geniCodeRValue(true,FALSE),0);
2220     
2221     /* generate an unconditional goto */
2222     geniCodeGoto(exitLabel);
2223     
2224     /* now for the right side */
2225     geniCodeLabel(falseLabel);
2226     
2227     false = ast2iCode(tree->right->right);
2228     geniCodeAssign(result,geniCodeRValue(false,FALSE),0);
2229     
2230     /* create the exit label */
2231     geniCodeLabel(exitLabel);
2232     
2233     return result ;
2234 }
2235
2236 /*-----------------------------------------------------------------*/
2237 /* geniCodeAssign - generate code for assignment                   */
2238 /*-----------------------------------------------------------------*/
2239 operand *geniCodeAssign (operand *left, operand *right, int nosupdate)
2240 {
2241     iCode *ic ;
2242     link *ltype = operandType(left);
2243     link *rtype = operandType(right);
2244     
2245     if (!left->isaddr && !IS_ITEMP(left)) {
2246         werror(E_LVALUE_REQUIRED,"assignment");
2247         return left;
2248     }
2249         
2250     /* left is integral type and right is literal then
2251        check if the literal value is within bounds */
2252     if (IS_INTEGRAL(ltype) && right->type == VALUE && IS_LITERAL(rtype)) {
2253         int nbits = bitsForType(ltype);
2254         long v = operandLitValue(right);
2255
2256         if (v > ((LONG_LONG)1 << nbits) && v > 0)
2257             werror(W_CONST_RANGE," = operation");
2258     }
2259
2260     /* if the left & right type don't exactly match */
2261     /* if pointer set then make sure the check is
2262        done with the type & not the pointer */
2263     /* then cast rights type to left */   
2264
2265     /* first check the type for pointer assignement */
2266     if (left->isaddr && IS_PTR(ltype) && IS_ITEMP(left) &&
2267         checkType(ltype,rtype)<0) {
2268         if (checkType(ltype->next,rtype) < 0)
2269             right = geniCodeCast(ltype->next,right,TRUE);
2270     } else
2271         if (checkType(ltype,rtype) < 0 )
2272             right = geniCodeCast(ltype,right,TRUE);
2273
2274     /* if left is a true symbol & ! volatile 
2275        create an assignment to temporary for
2276        the right & then assign this temporary
2277        to the symbol this is SSA . isn't it simple
2278        and folks have published mountains of paper on it */
2279     if (IS_TRUE_SYMOP(left) && 
2280         !isOperandVolatile(left,FALSE) &&
2281         isOperandGlobal(left)) {
2282         symbol *sym = NULL;
2283
2284         if (IS_TRUE_SYMOP(right))
2285             sym = OP_SYMBOL(right);
2286         ic = newiCode('=',NULL,right);
2287         IC_RESULT(ic) = right = newiTempOperand(ltype,0);       
2288         SPIL_LOC(right)  = sym ;
2289         ADDTOCHAIN(ic);
2290     }
2291     
2292     ic = newiCode('=',NULL,right);
2293     IC_RESULT(ic) = left;
2294     ADDTOCHAIN(ic);    
2295
2296     /* if left isgptr flag is set then support
2297        routine will be required */
2298     if (left->isGptr)
2299         ic->supportRtn = 1;
2300
2301     ic->nosupdate = nosupdate;
2302     return left;
2303 }
2304
2305 /*-----------------------------------------------------------------*/
2306 /* geniCodeSEParms - generate code for side effecting fcalls       */
2307 /*-----------------------------------------------------------------*/
2308 static void geniCodeSEParms (ast *parms)
2309 {
2310     if (!parms)
2311         return ;
2312
2313     if (parms->type == EX_OP && parms->opval.op == PARAM) {
2314         geniCodeSEParms (parms->left) ;
2315         geniCodeSEParms (parms->right);
2316         return ;
2317     }
2318
2319     /* hack don't like this but too lazy to think of
2320        something better */
2321     if (IS_ADDRESS_OF_OP(parms))
2322         parms->left->lvalue = 1;
2323     
2324     if (IS_CAST_OP(parms) && 
2325         IS_PTR(parms->ftype) && 
2326         IS_ADDRESS_OF_OP(parms->right))
2327         parms->right->left->lvalue = 1;
2328
2329     parms->opval.oprnd = 
2330         geniCodeRValue(ast2iCode (parms),FALSE);
2331    
2332     parms->type = EX_OPERAND ;
2333 }
2334
2335 /*-----------------------------------------------------------------*/
2336 /* geniCodeParms - generates parameters                            */
2337 /*-----------------------------------------------------------------*/
2338 static void geniCodeParms ( ast *parms , int *stack, link *fetype, symbol *func)
2339 {
2340     iCode *ic ;
2341     operand *pval ; 
2342     
2343     if ( ! parms )
2344         return ;
2345     
2346     /* if this is a param node then do the left & right */
2347     if (parms->type == EX_OP && parms->opval.op == PARAM) {
2348         geniCodeParms (parms->left, stack,fetype,func) ;
2349         geniCodeParms (parms->right, stack,fetype,func);
2350         return ;
2351     }
2352     
2353     /* get the parameter value */
2354     if (parms->type == EX_OPERAND)
2355         pval = parms->opval.oprnd ;
2356     else {
2357         /* maybe this else should go away ?? */
2358         /* hack don't like this but too lazy to think of
2359            something better */
2360         if (IS_ADDRESS_OF_OP(parms))
2361             parms->left->lvalue = 1;
2362     
2363         if (IS_CAST_OP(parms) && 
2364             IS_PTR(parms->ftype) && 
2365             IS_ADDRESS_OF_OP(parms->right))
2366             parms->right->left->lvalue = 1;
2367
2368         pval = geniCodeRValue(ast2iCode (parms),FALSE); 
2369     }
2370
2371     /* if register parm then make it a send */
2372     if (((parms->argSym && IS_REGPARM(parms->argSym->etype)) ||
2373         IS_REGPARM(parms->etype)) && !func->hasVargs ) {
2374         ic = newiCode(SEND,pval,NULL);
2375         ADDTOCHAIN(ic);
2376     } else {
2377         /* now decide whether to push or assign */
2378         if (!(options.stackAuto || IS_RENT(fetype))) { 
2379             
2380             /* assign */
2381             operand *top = operandFromSymbol(parms->argSym);
2382             geniCodeAssign(top,pval,1);
2383         }
2384         else { 
2385             link *p = operandType(pval);
2386             /* push */
2387             ic = newiCode(IPUSH,pval,NULL);
2388             ic->parmPush = 1;
2389             /* update the stack adjustment */
2390             *stack += getSize(IS_AGGREGATE(p)? aggrToPtr(p,FALSE):p);
2391             ADDTOCHAIN(ic);
2392         }
2393     }
2394     
2395 }
2396
2397 /*-----------------------------------------------------------------*/
2398 /* geniCodeCall - generates temp code for calling                  */
2399 /*-----------------------------------------------------------------*/
2400 operand *geniCodeCall (operand *left, ast *parms)
2401
2402     iCode *ic ;
2403     operand *result ;
2404     link *type, *etype;
2405     int stack = 0 ;
2406     
2407     /* take care of parameters with side-effecting
2408        function calls in them, this is required to take care 
2409        of overlaying function parameters */
2410     geniCodeSEParms ( parms );
2411
2412     /* first the parameters */
2413     geniCodeParms ( parms , &stack , getSpec(operandType(left)), OP_SYMBOL(left));
2414     
2415     /* now call : if symbol then pcall */
2416     if (IS_ITEMP(left)) 
2417         ic = newiCode(PCALL,left,NULL);
2418     else
2419         ic = newiCode(CALL,left,NULL);
2420     
2421     IC_ARGS(ic) = left->operand.symOperand->args ;
2422     type = copyLinkChain(operandType(left)->next);
2423     etype = getSpec(type);
2424     SPEC_EXTR(etype) = 0;
2425     IC_RESULT(ic) = result = newiTempOperand(type,1);
2426     
2427     ADDTOCHAIN(ic);
2428     
2429     /* stack adjustment after call */
2430     left->parmBytes = stack;
2431
2432     return result;
2433 }
2434
2435 /*-----------------------------------------------------------------*/
2436 /* geniCodeReceive - generate intermediate code for "receive"      */
2437 /*-----------------------------------------------------------------*/
2438 static void geniCodeReceive (value *args)
2439 {   
2440     /* for all arguments that are passed in registers */
2441     while (args) {
2442
2443         if (IS_REGPARM(args->etype)) {
2444             operand *opr = operandFromValue(args);
2445             operand *opl ;
2446             symbol *sym  = OP_SYMBOL(opr);
2447             iCode *ic ;
2448
2449             /* we will use it after all optimizations
2450                and before liveRange calculation */          
2451             if (!sym->addrtaken && !IS_VOLATILE(sym->etype)) {
2452
2453                 if (IN_FARSPACE(SPEC_OCLS(sym->etype)) &&
2454                    options.stackAuto == 0 &&
2455                    !IS_DS390_PORT) {
2456                 } else {
2457                     opl = newiTempOperand(args->type,0);
2458                     sym->reqv = opl ;       
2459                     sym->reqv->key = sym->key ;
2460                     OP_SYMBOL(sym->reqv)->key = sym->key;
2461                     OP_SYMBOL(sym->reqv)->isreqv = 1;
2462                     OP_SYMBOL(sym->reqv)->islocal= 0;
2463                     SPIL_LOC(sym->reqv) =  sym;
2464                 }
2465             }
2466
2467             ic = newiCode(RECEIVE,NULL,NULL);
2468             currFunc->recvSize = getSize(sym->etype);
2469             IC_RESULT(ic) = opr;
2470             ADDTOCHAIN(ic);
2471         }
2472         
2473         args = args->next;
2474     }
2475 }
2476
2477 /*-----------------------------------------------------------------*/
2478 /* geniCodeFunctionBody - create the function body                 */
2479 /*-----------------------------------------------------------------*/
2480 void geniCodeFunctionBody (ast *tree)
2481 {
2482     iCode *ic ;
2483     operand *func ;
2484     link *fetype  ;
2485     int savelineno ;
2486     
2487     /* reset the auto generation */
2488     /* numbers */
2489     iTempNum = 0 ;
2490     iTempLblNum = 0;   
2491     operandKey = 0 ;
2492     iCodeKey = 0 ;
2493     func  = ast2iCode(tree->left);
2494     fetype = getSpec(operandType(func));
2495     
2496     savelineno = lineno;
2497     lineno = OP_SYMBOL(func)->lineDef;
2498     /* create an entry label */
2499     geniCodeLabel(entryLabel);    
2500     lineno = savelineno;
2501
2502     /* create a proc icode */
2503     ic = newiCode(FUNCTION,func,NULL);
2504     /* if the function has parmas   then */
2505     /* save the parameters information    */
2506     ic->argLabel.args = tree->values.args ;
2507     ic->lineno = OP_SYMBOL(func)->lineDef;
2508
2509     ADDTOCHAIN(ic);   
2510     
2511     /* for all parameters that are passed
2512        on registers add a "receive" */
2513     geniCodeReceive( tree->values.args );
2514
2515     /* generate code for the body */
2516     ast2iCode(tree->right);
2517     
2518     /* create a label for return */
2519     geniCodeLabel(returnLabel);
2520     
2521     /* now generate the end proc */
2522     ic = newiCode(ENDFUNCTION,func,NULL);
2523     ADDTOCHAIN(ic);
2524     return ;
2525 }
2526
2527 /*-----------------------------------------------------------------*/
2528 /* geniCodeReturn - gen icode for 'return' statement               */
2529 /*-----------------------------------------------------------------*/
2530 void geniCodeReturn (operand *op)
2531 {
2532     iCode *ic;
2533     
2534     /* if the operand is present force an rvalue */
2535     if (op) 
2536         op = geniCodeRValue(op,FALSE);    
2537     
2538     ic = newiCode(RETURN,op,NULL);
2539     ADDTOCHAIN(ic);
2540 }
2541
2542 /*-----------------------------------------------------------------*/
2543 /* geniCodeIfx - generates code for extended if statement          */
2544 /*-----------------------------------------------------------------*/
2545 void geniCodeIfx (ast *tree)
2546 {
2547     iCode *ic;
2548     operand *condition = ast2iCode(tree->left);
2549     link *cetype; 
2550     
2551     /* if condition is null then exit */
2552     if (!condition)
2553         goto exit ;
2554     else
2555         condition = geniCodeRValue(condition,FALSE);
2556     
2557     cetype = getSpec(operandType(condition));
2558     /* if the condition is a literal */
2559     if (IS_LITERAL(cetype)) {
2560         if (floatFromVal(condition->operand.valOperand)) {
2561             if (tree->trueLabel)
2562                 geniCodeGoto(tree->trueLabel);
2563             else
2564                 assert(1);
2565         }
2566         else {
2567             if (tree->falseLabel)
2568                 geniCodeGoto (tree->falseLabel);
2569             else
2570                 assert(1);
2571         }
2572         goto exit;
2573     }
2574     
2575     if ( tree->trueLabel ) {
2576         ic = newiCodeCondition(condition,
2577                                tree->trueLabel,
2578                                NULL );
2579         ADDTOCHAIN(ic);
2580         
2581         if ( tree->falseLabel) 
2582             geniCodeGoto(tree->falseLabel);     
2583     }
2584     else {
2585         ic = newiCodeCondition (condition,
2586                                 NULL,
2587                                 tree->falseLabel);
2588         ADDTOCHAIN(ic);
2589     }
2590     
2591  exit:
2592     ast2iCode(tree->right);
2593 }
2594
2595 /*-----------------------------------------------------------------*/
2596 /* geniCodeJumpTable - tries to create a jump table for switch     */
2597 /*-----------------------------------------------------------------*/
2598 int geniCodeJumpTable (operand *cond, value *caseVals, ast *tree)
2599 {
2600     int min = 0 ,max = 0, t, cnt = 0;
2601     value *vch;
2602     iCode *ic;
2603     operand *boundary;
2604     symbol *falseLabel;
2605     set *labels = NULL ;
2606
2607     if (!tree || !caseVals)
2608         return 0;
2609
2610     /* the criteria for creating a jump table is */
2611     /* all integer numbers between the maximum & minimum must */
2612     /* be present , the maximum value should not exceed 255 */
2613     min = max = (int)floatFromVal(vch = caseVals);
2614     sprintf(buffer,"_case_%d_%d",
2615             tree->values.switchVals.swNum,
2616             min);
2617     addSet(&labels,newiTempLabel(buffer));
2618
2619     /* if there is only one case value then no need */
2620     if (!(vch = vch->next ))
2621         return 0;
2622
2623     while (vch) {
2624         if (((t = (int)floatFromVal(vch)) - max) != 1)
2625             return 0;
2626         sprintf(buffer,"_case_%d_%d",
2627                 tree->values.switchVals.swNum,
2628                 t);
2629         addSet(&labels,newiTempLabel(buffer));
2630         max = t;
2631         cnt++ ;
2632         vch = vch->next ;
2633     }
2634     
2635     /* if the number of case statements <= 2 then */
2636     /* it is not economical to create the jump table */
2637     /* since two compares are needed for boundary conditions */
2638     if ((! optimize.noJTabBoundary  && cnt <= 2) || max > (255/3))
2639         return 0;
2640     
2641     if ( tree->values.switchVals.swDefault )
2642         sprintf (buffer,"_default_%d",tree->values.switchVals.swNum);
2643     else
2644         sprintf (buffer,"_swBrk_%d",tree->values.switchVals.swNum  );
2645     
2646     falseLabel = newiTempLabel (buffer);
2647
2648     /* so we can create a jumptable */
2649     /* first we rule out the boundary conditions */
2650     /* if only optimization says so */
2651     if ( ! optimize.noJTabBoundary ) {
2652         link *cetype = getSpec(operandType(cond));
2653         /* no need to check the lower bound if
2654            the condition is unsigned & minimum value is zero */
2655         if (!( min == 0  && SPEC_USIGN(cetype))) {
2656             boundary = geniCodeLogic (cond,operandFromLit(min),'<');
2657             ic = newiCodeCondition (boundary,falseLabel,NULL);
2658             ADDTOCHAIN(ic);
2659         }
2660
2661         /* now for upper bounds */
2662         boundary = geniCodeLogic(cond,operandFromLit(max),'>');
2663         ic = newiCodeCondition (boundary,falseLabel,NULL);
2664         ADDTOCHAIN(ic);
2665     }
2666
2667     /* if the min is not zero then we no make it zero */
2668     if (min) {
2669         cond = geniCodeSubtract(cond,operandFromLit(min));
2670         setOperandType(cond, UCHARTYPE);
2671     }
2672
2673     /* now create the jumptable */
2674     ic = newiCode(JUMPTABLE,NULL,NULL);
2675     IC_JTCOND(ic) = cond;
2676     IC_JTLABELS(ic) = labels;
2677     ADDTOCHAIN(ic);
2678     return 1;       
2679 }
2680
2681 /*-----------------------------------------------------------------*/
2682 /* geniCodeSwitch - changes a switch to a if statement             */
2683 /*-----------------------------------------------------------------*/
2684 void geniCodeSwitch (ast *tree)
2685 {
2686     iCode *ic ;
2687     operand *cond = geniCodeRValue(ast2iCode (tree->left),FALSE);
2688     value *caseVals = tree->values.switchVals.swVals ;
2689     symbol *trueLabel , *falseLabel;
2690     
2691     /* if we can make this a jump table */
2692     if ( geniCodeJumpTable (cond,caseVals,tree) )
2693         goto jumpTable ; /* no need for the comparison */
2694
2695     /* for the cases defined do */
2696     while (caseVals) {
2697         
2698         operand *compare = geniCodeLogic (cond,
2699                                           operandFromValue(caseVals),
2700                                           EQ_OP);
2701         
2702         sprintf(buffer,"_case_%d_%d",
2703                 tree->values.switchVals.swNum,
2704                 (int) floatFromVal(caseVals));
2705         trueLabel = newiTempLabel(buffer);
2706         
2707         ic = newiCodeCondition(compare,trueLabel,NULL);
2708         ADDTOCHAIN(ic);
2709         caseVals = caseVals->next;
2710     }
2711
2712
2713     
2714     /* if default is present then goto break else break */
2715     if ( tree->values.switchVals.swDefault )
2716         sprintf (buffer,"_default_%d",tree->values.switchVals.swNum);
2717     else
2718         sprintf (buffer,"_swBrk_%d",tree->values.switchVals.swNum  );
2719     
2720     falseLabel = newiTempLabel (buffer);
2721     geniCodeGoto(falseLabel);
2722  
2723  jumpTable:   
2724     ast2iCode(tree->right);
2725
2726
2727 /*-----------------------------------------------------------------*/
2728 /* geniCodeInline - intermediate code for inline assembler         */
2729 /*-----------------------------------------------------------------*/
2730 static void geniCodeInline (ast *tree)
2731 {
2732     iCode *ic;
2733
2734     ic = newiCode(INLINEASM,NULL,NULL);
2735     IC_INLINE(ic) = tree->values.inlineasm;
2736     ADDTOCHAIN(ic);
2737 }
2738
2739 /*-----------------------------------------------------------------*/
2740 /* ast2iCode - creates an icodeList from an ast                    */
2741 /*-----------------------------------------------------------------*/
2742 operand *ast2iCode (ast *tree)
2743 {
2744     operand *left = NULL;
2745     operand *right= NULL;
2746     
2747     if (!tree)
2748         return NULL ;
2749     
2750     /* set the global variables for filename & line number */
2751     if ( tree->filename )
2752         filename =  tree->filename ;
2753     if ( tree->lineno)
2754         lineno   = tree->lineno ;
2755     if (tree->block)
2756         block = tree->block ;
2757     if (tree->level)
2758         scopeLevel = tree->level;
2759     
2760     if (tree->type == EX_VALUE )
2761         return operandFromValue(tree->opval.val);
2762     
2763     if (tree->type == EX_LINK )
2764         return operandFromLink (tree->opval.lnk);
2765     
2766     /* if we find a nullop */
2767     if (tree->type == EX_OP && 
2768         ( tree->opval.op == NULLOP || 
2769           tree->opval.op == BLOCK )) {
2770         ast2iCode (tree->left);
2771         ast2iCode (tree->right);
2772         return NULL ;
2773     }
2774     
2775     /* special cases for not evaluating */
2776     if ( tree->opval.op != ':'   && 
2777          tree->opval.op != '?'   &&
2778          tree->opval.op != CALL  && 
2779          tree->opval.op != IFX   &&
2780          tree->opval.op != LABEL &&
2781          tree->opval.op != GOTO  &&     
2782          tree->opval.op != SWITCH &&
2783          tree->opval.op != FUNCTION &&
2784          tree->opval.op != INLINEASM ) {
2785
2786         if (IS_ASSIGN_OP(tree->opval.op) || 
2787             IS_DEREF_OP(tree)            || 
2788             (tree->opval.op == '&' && !tree->right) ||
2789             tree->opval.op == PTR_OP) {
2790             lvaluereq++;
2791             if ((IS_ARRAY_OP(tree->left) && IS_ARRAY_OP(tree->left->left)) ||
2792                 (IS_DEREF_OP(tree) && IS_ARRAY_OP(tree->left)))
2793             {
2794                 int olvr = lvaluereq ;
2795                 lvaluereq = 0;
2796                 left = operandFromAst(tree->left);
2797                 lvaluereq = olvr - 1;
2798             } else {
2799                 left = operandFromAst(tree->left);
2800                 lvaluereq--;
2801             }
2802             if (IS_DEREF_OP(tree) && IS_DEREF_OP(tree->left))
2803                     left = geniCodeRValue(left,TRUE);
2804         } else {
2805             left =  operandFromAst(tree->left);
2806         }
2807         if (tree->opval.op == INC_OP || 
2808             tree->opval.op == DEC_OP) {
2809             lvaluereq++;
2810             right= operandFromAst(tree->right);
2811             lvaluereq--;
2812         } else {
2813             right= operandFromAst(tree->right);
2814         }
2815     }
2816     
2817     /* now depending on the type of operand */
2818     /* this will be a biggy                 */
2819     switch (tree->opval.op) {
2820         
2821     case '[' :    /* array operation */
2822         {
2823             link *ltype = operandType(left);
2824             left= geniCodeRValue (left,IS_PTR(ltype->next) ? TRUE : FALSE);
2825             right=geniCodeRValue (right,TRUE);             
2826         }
2827         
2828         return geniCodeArray (left,right);
2829         
2830     case '.' :   /* structure dereference */
2831         if (IS_PTR(operandType(left)))
2832             left = geniCodeRValue(left,TRUE);
2833         else
2834             left = geniCodeRValue(left,FALSE);            
2835         
2836         return geniCodeStruct (left,right,tree->lvalue);
2837         
2838     case PTR_OP: /* structure pointer dereference */
2839         {
2840             link *pType;
2841             pType = operandType(left);
2842             left = geniCodeRValue(left,TRUE);
2843             
2844             setOClass (pType,getSpec(operandType(left)));
2845         }              
2846         
2847         return geniCodeStruct (left, right,tree->lvalue);
2848         
2849     case INC_OP: /* increment operator */
2850         if ( left )
2851             return geniCodePostInc (left);
2852         else
2853             return geniCodePreInc (right);
2854         
2855     case DEC_OP: /* decrement operator */
2856         if ( left )
2857             return geniCodePostDec (left);
2858         else
2859             return geniCodePreDec (right);
2860         
2861     case '&' : /* bitwise and or address of operator */
2862         if ( right ) { /* this is a bitwise operator   */
2863             left= geniCodeRValue(left,FALSE);
2864             right= geniCodeRValue(right,FALSE);     
2865             return geniCodeBitwise (left,right,BITWISEAND,tree->ftype);
2866         } else
2867             return geniCodeAddressOf (left);
2868         
2869     case '|': /* bitwise or & xor */
2870     case '^':
2871         return geniCodeBitwise (geniCodeRValue(left,FALSE),
2872                                 geniCodeRValue(right,FALSE),
2873                                 tree->opval.op,
2874                                 tree->ftype);
2875         
2876     case '/':
2877         return geniCodeDivision (geniCodeRValue(left,FALSE),
2878                                  geniCodeRValue(right,FALSE));
2879         
2880     case '%' :
2881         return geniCodeModulus (geniCodeRValue(left,FALSE),
2882                                 geniCodeRValue(right,FALSE));
2883     case '*':
2884         if ( right ) 
2885             return geniCodeMultiply (geniCodeRValue(left,FALSE),
2886                                      geniCodeRValue(right,FALSE));
2887         else        
2888             return geniCodeDerefPtr (geniCodeRValue(left,FALSE));
2889         
2890     case '-' :
2891         if ( right ) 
2892             return geniCodeSubtract (geniCodeRValue(left,FALSE),
2893                                      geniCodeRValue(right,FALSE));
2894         else
2895             return geniCodeUnaryMinus (geniCodeRValue(left,FALSE));
2896         
2897     case '+' :
2898         if ( right ) 
2899             return geniCodeAdd (geniCodeRValue(left,FALSE),
2900                                 geniCodeRValue(right,FALSE));
2901         else
2902             return geniCodeRValue(left,FALSE) ; /* unary '+' has no meaning */
2903         
2904     case LEFT_OP:
2905         return geniCodeLeftShift (geniCodeRValue(left,FALSE),
2906                                   geniCodeRValue(right,FALSE));
2907         
2908     case RIGHT_OP:
2909         return geniCodeRightShift (geniCodeRValue(left,FALSE),
2910                                    geniCodeRValue(right,FALSE));
2911     case CAST:
2912         return geniCodeCast (operandType(left),
2913                              geniCodeRValue(right,FALSE),FALSE);
2914         
2915     case '~' :
2916     case '!' :
2917     case RRC:
2918     case RLC:   
2919         return geniCodeUnary (geniCodeRValue(left,FALSE),tree->opval.op);
2920         
2921     case GETHBIT:
2922         {
2923             operand *op = geniCodeUnary (geniCodeRValue(left,FALSE),tree->opval.op);
2924             setOperandType(op, UCHARTYPE);
2925             return op;
2926         }
2927     case '>' :
2928     case '<' :
2929     case LE_OP:
2930     case GE_OP:
2931     case EQ_OP:
2932     case NE_OP:
2933     case AND_OP:
2934     case OR_OP:
2935         return geniCodeLogic (geniCodeRValue(left,FALSE),
2936                               geniCodeRValue(right,FALSE),
2937                               tree->opval.op);
2938     case '?' : 
2939         return geniCodeConditional (tree); 
2940         
2941     case SIZEOF:
2942         return operandFromLit(getSize(tree->right->ftype));
2943         
2944     case '='        :
2945         {
2946             link *rtype = operandType(right);
2947             link *ltype = operandType(left);
2948             if (IS_PTR(rtype) && IS_ITEMP(right) 
2949                 && right->isaddr && checkType(rtype->next,ltype)==1)
2950                 right =  geniCodeRValue(right,TRUE);
2951             else
2952                 right = geniCodeRValue(right,FALSE);
2953
2954             geniCodeAssign (left,right,0);
2955             return right ;
2956         }              
2957     case MUL_ASSIGN:
2958         return 
2959             geniCodeAssign(left,
2960                            geniCodeMultiply(geniCodeRValue (operandFromOperand(left),
2961                                                             FALSE),
2962                                             geniCodeRValue(right,FALSE)),0);
2963                                                 
2964     case DIV_ASSIGN:
2965         return 
2966             geniCodeAssign(left,
2967                            geniCodeDivision(geniCodeRValue(operandFromOperand(left),
2968                                                            FALSE),
2969                                             geniCodeRValue(right,FALSE)),0);
2970     case MOD_ASSIGN:
2971         return 
2972             geniCodeAssign(left,
2973                            geniCodeModulus(geniCodeRValue(operandFromOperand(left),
2974                                                           FALSE),
2975                                            geniCodeRValue(right,FALSE)),0);
2976     case ADD_ASSIGN: 
2977         {
2978             link *rtype = operandType(right);
2979             link *ltype = operandType(left);
2980             if (IS_PTR(rtype) && IS_ITEMP(right) 
2981                 && right->isaddr && checkType(rtype->next,ltype)==1)
2982                 right =  geniCodeRValue(right,TRUE);
2983             else
2984                 right = geniCodeRValue(right,FALSE);
2985
2986            
2987             return geniCodeAssign(left,
2988                                   geniCodeAdd (geniCodeRValue(operandFromOperand(left),
2989                                                               FALSE),
2990                                                right),0);
2991         }
2992     case SUB_ASSIGN:
2993         {
2994             link *rtype = operandType(right);
2995             link *ltype = operandType(left);
2996             if (IS_PTR(rtype) && IS_ITEMP(right) 
2997                 && right->isaddr && checkType(rtype->next,ltype)==1) {
2998                 right =  geniCodeRValue(right,TRUE);
2999             }
3000             else {
3001                 right = geniCodeRValue(right,FALSE);
3002             }
3003             return 
3004                 geniCodeAssign (left,
3005                                 geniCodeSubtract(geniCodeRValue(operandFromOperand(left),
3006                                                                 FALSE),
3007                                                  right),0);
3008         }
3009     case LEFT_ASSIGN:
3010         return 
3011             geniCodeAssign (left,
3012                             geniCodeLeftShift(geniCodeRValue(operandFromOperand(left)
3013                                                              ,FALSE),
3014                                               geniCodeRValue(right,FALSE)),0);
3015     case RIGHT_ASSIGN:
3016         return 
3017             geniCodeAssign(left,
3018                            geniCodeRightShift(geniCodeRValue(operandFromOperand(left)
3019                                                              ,FALSE),
3020                                               geniCodeRValue(right,FALSE)),0);
3021     case AND_ASSIGN:
3022         return 
3023             geniCodeAssign (left,
3024                             geniCodeBitwise(geniCodeRValue(operandFromOperand(left),
3025                                                            FALSE),
3026                                             geniCodeRValue(right,FALSE),
3027                                             BITWISEAND,
3028                                             operandType(left)),0);
3029     case XOR_ASSIGN:
3030         return 
3031             geniCodeAssign (left,
3032                             geniCodeBitwise (geniCodeRValue(operandFromOperand(left),
3033                                                             FALSE),
3034                                              geniCodeRValue(right,FALSE),
3035                                              '^',
3036                                              operandType(left)),0);
3037     case OR_ASSIGN:
3038         return 
3039             geniCodeAssign (left,
3040                             geniCodeBitwise (geniCodeRValue(operandFromOperand(left)
3041                                                             ,FALSE),
3042                                              geniCodeRValue(right,FALSE),
3043                                              '|',
3044                                              operandType(left)),0);
3045     case ',' :
3046         return geniCodeRValue(right,FALSE);
3047         
3048     case CALL:
3049         return geniCodeCall (ast2iCode(tree->left),
3050                              tree->right);
3051     case LABEL:
3052         geniCodeLabel(ast2iCode(tree->left)->operand.symOperand);
3053         return ast2iCode (tree->right);
3054         
3055     case GOTO:
3056         geniCodeGoto (ast2iCode(tree->left)->operand.symOperand);
3057         return ast2iCode (tree->right);
3058         
3059     case FUNCTION:
3060         geniCodeFunctionBody ( tree );
3061         return NULL ;
3062         
3063     case RETURN:
3064         geniCodeReturn (right);
3065         return NULL ;
3066         
3067     case IFX:
3068         geniCodeIfx (tree);
3069         return NULL ;
3070         
3071     case SWITCH:
3072         geniCodeSwitch (tree);
3073         return NULL;
3074
3075     case INLINEASM:
3076         geniCodeInline (tree);
3077         return NULL ;
3078     }
3079     
3080     return NULL;
3081 }
3082
3083 /*-----------------------------------------------------------------*/
3084 /* reverseICChain - gets from the list and creates a linkedlist    */
3085 /*-----------------------------------------------------------------*/
3086 iCode *reverseiCChain ()
3087 {
3088     iCode *loop = NULL ;
3089     iCode *prev = NULL ;
3090     
3091     while ((loop = getSet(&iCodeChain))) {
3092         loop->next = prev ;
3093         if ( prev )
3094             prev->prev = loop; 
3095         prev = loop ;
3096     }
3097     
3098     return prev;
3099 }
3100
3101
3102 /*-----------------------------------------------------------------*/
3103 /* iCodeFromAst - given an ast will convert it to iCode            */
3104 /*-----------------------------------------------------------------*/
3105 iCode *iCodeFromAst ( ast *tree )
3106 {
3107     returnLabel = newiTempLabel("_return");
3108     entryLabel  = newiTempLabel("_entry") ;
3109     ast2iCode (tree);
3110     return reverseiCChain ();
3111 }
3112