some -xstack related stuff
[fw/sdcc] / src / SDCCicode.c
1 /*-------------------------------------------------------------------------
2
3   SDCCicode.c - intermediate code generation etc.                  
4                 Written By -  Sandeep Dutta . sandeep.dutta@usa.net (1998)
5
6    This program is free software; you can redistribute it and/or modify it
7    under the terms of the GNU General Public License as published by the
8    Free Software Foundation; either version 2, or (at your option) any
9    later version.
10    
11    This program is distributed in the hope that it will be useful,
12    but WITHOUT ANY WARRANTY; without even the implied warranty of
13    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14    GNU General Public License for more details.
15    
16    You should have received a copy of the GNU General Public License
17    along with this program; if not, write to the Free Software
18    Foundation, 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
19    
20    In other words, you are welcome to use, share and improve this program.
21    You are forbidden to forbid anyone else to use, share and improve
22    what you give them.   Help stamp out software-hoarding!  
23 -------------------------------------------------------------------------*/
24
25 #include "common.h"
26
27 /*-----------------------------------------------------------------*/
28 /* global variables       */
29
30 set *iCodeChain = NULL ;
31 int iTempNum = 0;
32 int iTempLblNum = 0;
33 int operandKey = 0 ;
34 int iCodeKey = 0;
35 char *filename ;
36 int lineno ;
37 int block;
38 int scopeLevel;
39 int lvaluereq;
40
41 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         right = geniCodeMultiply (right ,size);
1628         if (getSize(ltype) > 1) 
1629                 right = geniCodeCast(INTTYPE,right,TRUE);
1630         resType = copyLinkChain(ltype);
1631     }
1632     else { /* make them the same size */
1633         resType = computeType (ltype,rtype) ;
1634         left = geniCodeCast(resType,left,TRUE);
1635         right= geniCodeCast(resType,right,TRUE);
1636     }
1637     
1638     /* if they are both literals then we know */
1639     if (IS_LITERAL(letype) && IS_LITERAL(retype)
1640         && left->isLiteral && right->isLiteral)
1641         return operandFromValue (valPlus(valFromType(letype),
1642                                          valFromType(retype)));
1643     
1644     ic = newiCode('+',left,right);
1645     
1646     IC_RESULT(ic) = newiTempOperand(resType,1);
1647     IC_RESULT(ic)->isaddr = ( isarray ? 1 : 0);
1648
1649     /* if left or right is a float then support
1650        routine */
1651     if (IS_FLOAT(ltype) || IS_FLOAT(rtype))
1652         ic->supportRtn = 1;
1653
1654     ADDTOCHAIN(ic);
1655     
1656     return IC_RESULT(ic) ;
1657     
1658 }
1659
1660 /*-----------------------------------------------------------------*/
1661 /* aggrToPtr - changes an aggregate to pointer to an aggregate     */
1662 /*-----------------------------------------------------------------*/
1663 link *aggrToPtr ( link *type, bool force)
1664 {
1665     link *etype ;
1666     link *ptype ;
1667
1668     
1669     if (IS_PTR(type) && !force)
1670         return type;
1671
1672     etype = getSpec(type);
1673     ptype = newLink();
1674
1675     ptype->next = type;
1676     /* if the output class is generic */
1677     if ((DCL_TYPE(ptype) = PTR_TYPE(SPEC_OCLS(etype))) == CPOINTER)
1678         DCL_PTR_CONST(ptype) = port->mem.code_ro;
1679
1680     /* if the variable was declared a constant */
1681     /* then the pointer points to a constant */
1682     if (IS_CONSTANT(etype) )
1683         DCL_PTR_CONST(ptype) = 1;
1684
1685     /* the variable was volatile then pointer to volatile */
1686     if (IS_VOLATILE(etype))
1687         DCL_PTR_VOLATILE(ptype) = 1;
1688     return ptype; 
1689 }
1690
1691 /*-----------------------------------------------------------------*/
1692 /* geniCodeArray2Ptr - array to pointer                            */
1693 /*-----------------------------------------------------------------*/
1694 operand *geniCodeArray2Ptr (operand *op)
1695 {
1696     link *optype = operandType(op);
1697     link *opetype = getSpec(optype);
1698
1699     /* set the pointer depending on the storage class */    
1700     if ((DCL_TYPE(optype) = PTR_TYPE(SPEC_OCLS(opetype))) == CPOINTER)
1701         DCL_PTR_CONST(optype) = port->mem.code_ro;
1702
1703     
1704     /* if the variable was declared a constant */
1705     /* then the pointer points to a constant */
1706     if (IS_CONSTANT(opetype) )
1707         DCL_PTR_CONST(optype) = 1;
1708
1709     /* the variable was volatile then pointer to volatile */
1710     if (IS_VOLATILE(opetype))
1711         DCL_PTR_VOLATILE(optype) = 1;
1712     op->isaddr = 0;
1713     return op;
1714 }
1715
1716 /*-----------------------------------------------------------------*/
1717 /* geniCodeArray - array access                                    */
1718 /*-----------------------------------------------------------------*/
1719 operand *geniCodeArray (operand *left,operand *right)
1720 {
1721     iCode *ic;
1722     link *ltype = operandType(left);
1723     
1724     if (IS_PTR(ltype)) {
1725         if (IS_PTR(ltype->next) && left->isaddr)
1726             left = geniCodeRValue(left,FALSE);
1727         return geniCodeDerefPtr(geniCodeAdd(left,right));
1728     }
1729
1730     /* array access */
1731     right = geniCodeMultiply(right,
1732                              operandFromLit(getSize(ltype->next)));
1733
1734     /* we can check for limits here */
1735     if (isOperandLiteral(right) &&
1736         IS_ARRAY(ltype)         &&
1737         DCL_ELEM(ltype)         &&
1738         (operandLitValue(right)/getSize(ltype->next)) >= DCL_ELEM(ltype)) {
1739         werror(E_ARRAY_BOUND);
1740         right = operandFromLit(0);
1741     }
1742
1743     ic = newiCode('+',left,right);    
1744
1745     IC_RESULT(ic) = newiTempOperand(((IS_PTR(ltype) && 
1746                                       !IS_AGGREGATE(ltype->next) &&
1747                                       !IS_PTR(ltype->next))
1748                                      ? ltype : ltype->next),0);
1749
1750     IC_RESULT(ic)->isaddr = (!IS_AGGREGATE(ltype->next));
1751     ADDTOCHAIN(ic);
1752     return IC_RESULT(ic) ;
1753 }
1754
1755 /*-----------------------------------------------------------------*/
1756 /* geniCodeStruct - generates intermediate code for structres      */
1757 /*-----------------------------------------------------------------*/
1758 operand *geniCodeStruct (operand *left, operand *right, bool islval)
1759 {
1760     iCode *ic ;
1761     link *type = operandType(left);
1762     link *etype = getSpec(type);
1763     link *retype ;
1764     symbol *element = getStructElement(SPEC_STRUCT(etype), 
1765                                        right->operand.symOperand);
1766     
1767     /* add the offset */
1768     ic = newiCode('+',left,operandFromLit(element->offset));
1769     
1770     IC_RESULT(ic) = newiTempOperand(element->type,0);
1771
1772     /* preserve the storage & output class of the struct */
1773     /* as well as the volatile attribute */
1774     retype = getSpec(operandType(IC_RESULT(ic)));
1775     SPEC_SCLS(retype) = SPEC_SCLS(etype);
1776     SPEC_OCLS(retype) = SPEC_OCLS(etype);
1777     SPEC_VOLATILE(retype) |= SPEC_VOLATILE(etype);    
1778
1779     if (IS_PTR(element->type)) 
1780         setOperandType(IC_RESULT(ic),aggrToPtr(operandType(IC_RESULT(ic)),TRUE));
1781     
1782     IC_RESULT(ic)->isaddr = (!IS_AGGREGATE(element->type));
1783
1784     
1785     ADDTOCHAIN(ic);
1786     return (islval ? IC_RESULT(ic) : geniCodeRValue(IC_RESULT(ic),TRUE));
1787 }
1788
1789 /*-----------------------------------------------------------------*/
1790 /* geniCodePostInc - generate int code for Post increment          */
1791 /*-----------------------------------------------------------------*/
1792 operand *geniCodePostInc (operand *op)
1793 {
1794     iCode *ic ;
1795     operand *rOp ;
1796     link *optype = operandType(op);
1797     operand *result ;
1798     operand *rv = (IS_ITEMP(op) ? 
1799                    geniCodeRValue(op,(IS_PTR(optype) ? TRUE : FALSE)) :
1800                    op);            
1801     link *rvtype = operandType(rv);    
1802     int size = 0;
1803     
1804     /* if this is not an address we have trouble */
1805     if ( ! op->isaddr ) {
1806         werror (E_LVALUE_REQUIRED,"++");
1807         return op ;
1808     }
1809     
1810     rOp = newiTempOperand(rvtype,0);
1811     rOp->noSpilLoc = 1;
1812
1813     if (IS_ITEMP(rv))
1814         rv->noSpilLoc = 1;
1815
1816     geniCodeAssign(rOp,rv,0);
1817    
1818     size = (IS_PTR(rvtype) ? getSize(rvtype->next) : 1);
1819     ic = newiCode('+',rv,operandFromLit(size));          
1820     IC_RESULT(ic) = result =newiTempOperand(rvtype,0);
1821     ADDTOCHAIN(ic);
1822
1823     geniCodeAssign(op,result,0);
1824     
1825     return rOp;
1826     
1827 }
1828
1829 /*-----------------------------------------------------------------*/
1830 /* geniCodePreInc - generate code for preIncrement                 */
1831 /*-----------------------------------------------------------------*/
1832 operand *geniCodePreInc (operand *op)
1833 {
1834     iCode *ic ;
1835     link *optype = operandType(op);    
1836     operand *rop = (IS_ITEMP(op) ? 
1837                     geniCodeRValue (op,(IS_PTR(optype) ? TRUE : FALSE)) :
1838                     op);
1839     link *roptype = operandType(rop);
1840     operand *result;
1841     int size = 0;
1842     
1843     if ( ! op->isaddr ) {
1844         werror(E_LVALUE_REQUIRED,"++");
1845         return op ;
1846     }
1847
1848
1849     size = (IS_PTR(roptype) ? getSize(roptype->next) : 1);
1850     ic = newiCode('+',rop,operandFromLit(size));
1851     IC_RESULT(ic) = result = newiTempOperand(roptype,0) ;
1852     ADDTOCHAIN(ic);
1853
1854     
1855     return geniCodeAssign(op,result,0) ;
1856 }
1857
1858 /*-----------------------------------------------------------------*/
1859 /* geniCodePostDec - generates code for Post decrement             */
1860 /*-----------------------------------------------------------------*/
1861 operand *geniCodePostDec (operand *op)
1862 {
1863     iCode *ic ;
1864     operand *rOp ;
1865     link *optype = operandType(op);
1866     operand *result ;
1867     operand *rv = (IS_ITEMP(op) ? 
1868                    geniCodeRValue(op,(IS_PTR(optype) ? TRUE : FALSE)) :
1869                    op);            
1870     link *rvtype = operandType(rv);    
1871     int size = 0;
1872     
1873     /* if this is not an address we have trouble */
1874     if ( ! op->isaddr ) {
1875         werror (E_LVALUE_REQUIRED,"++");
1876         return op ;
1877     }
1878     
1879     rOp = newiTempOperand(rvtype,0);
1880     rOp->noSpilLoc = 1;
1881
1882     if (IS_ITEMP(rv))
1883         rv->noSpilLoc = 1;
1884
1885     geniCodeAssign(rOp,rv,0);
1886    
1887     size = (IS_PTR(rvtype) ? getSize(rvtype->next) : 1);
1888     ic = newiCode('-',rv,operandFromLit(size));          
1889     IC_RESULT(ic) = result =newiTempOperand(rvtype,0);
1890     ADDTOCHAIN(ic);
1891
1892     geniCodeAssign(op,result,0);
1893     
1894     return rOp;
1895     
1896 }
1897
1898 /*-----------------------------------------------------------------*/
1899 /* geniCodePreDec - generate code for pre  decrement               */
1900 /*-----------------------------------------------------------------*/
1901 operand *geniCodePreDec (operand *op)
1902 {  
1903     iCode *ic ;
1904     link *optype = operandType(op);    
1905     operand *rop = (IS_ITEMP(op) ? 
1906                     geniCodeRValue (op,(IS_PTR(optype) ? TRUE : FALSE)) :
1907                     op);
1908     link *roptype = operandType(rop);
1909     operand *result;
1910     int size = 0;
1911     
1912     if ( ! op->isaddr ) {
1913         werror(E_LVALUE_REQUIRED,"++");
1914         return op ;
1915     }
1916
1917
1918     size = (IS_PTR(roptype) ? getSize(roptype->next) : 1);
1919     ic = newiCode('-',rop,operandFromLit(size));
1920     IC_RESULT(ic) = result = newiTempOperand(roptype,0) ;
1921     ADDTOCHAIN(ic);
1922
1923     
1924     return geniCodeAssign(op,result,0) ;
1925 }
1926
1927
1928 /*-----------------------------------------------------------------*/
1929 /* geniCodeBitwise - gen int code for bitWise  operators           */
1930 /*-----------------------------------------------------------------*/
1931 operand *geniCodeBitwise (operand *left, operand *right, 
1932                           int oper, link *resType)
1933 {
1934     iCode *ic;   
1935     
1936     left = geniCodeCast(resType,left,TRUE);
1937     right= geniCodeCast(resType,right,TRUE);
1938     
1939     ic = newiCode(oper,left,right);
1940     IC_RESULT(ic) = newiTempOperand(resType,0);
1941     
1942     ADDTOCHAIN(ic);
1943     return IC_RESULT(ic) ;
1944 }
1945
1946 /*-----------------------------------------------------------------*/
1947 /* geniCodeAddressOf - gens icode for '&' address of operator      */
1948 /*-----------------------------------------------------------------*/
1949 operand *geniCodeAddressOf (operand *op) 
1950 {
1951     iCode *ic;
1952     link *p ;
1953     link *optype = operandType(op);
1954     link *opetype= getSpec(optype);
1955     
1956     /* lvalue check already done in decorateType */
1957     /* this must be a lvalue */
1958 /*     if (!op->isaddr && !IS_AGGREGATE(optype)) { */
1959 /*      werror (E_LVALUE_REQUIRED,"&"); */
1960 /*      return op; */
1961 /*     } */
1962     
1963     p = newLink();
1964     p->class = DECLARATOR ;
1965     
1966     /* set the pointer depending on the storage class */
1967     if ((DCL_TYPE(p) = PTR_TYPE(SPEC_OCLS(opetype))) == CPOINTER)
1968         DCL_PTR_CONST(p) = port->mem.code_ro;
1969
1970     /* make sure we preserve the const & volatile */
1971     if (IS_CONSTANT(opetype)) 
1972         DCL_PTR_CONST(p) = 1;
1973
1974     if (IS_VOLATILE(opetype))
1975         DCL_PTR_VOLATILE(p) = 1;
1976     
1977     p->next = copyLinkChain(optype);
1978     
1979     /* if already a temp */
1980     if (IS_ITEMP(op)) {
1981         setOperandType (op,p);     
1982         op->isaddr= 0;
1983         return op;
1984     }
1985     
1986     /* other wise make this of the type coming in */
1987     ic = newiCode(ADDRESS_OF,op,NULL);
1988     IC_RESULT(ic) = newiTempOperand(p,1);
1989     IC_RESULT(ic)->isaddr = 0;
1990     ADDTOCHAIN(ic);
1991     return IC_RESULT(ic);
1992 }
1993 /*-----------------------------------------------------------------*/
1994 /* setOClass - sets the output class depending on the pointer type */
1995 /*-----------------------------------------------------------------*/
1996 void setOClass (link *ptr, link *spec)
1997 {
1998     switch (DCL_TYPE(ptr)) {
1999     case POINTER:
2000         SPEC_OCLS(spec) = data ;
2001         break ;
2002         
2003     case GPOINTER:
2004         SPEC_OCLS(spec) = generic;
2005         break;
2006         
2007     case FPOINTER:
2008         SPEC_OCLS(spec) = xdata ;
2009         break ;
2010         
2011     case CPOINTER:
2012         SPEC_OCLS(spec) = code ;
2013         break ;  
2014         
2015     case IPOINTER:
2016         SPEC_OCLS(spec) = idata;
2017         break;
2018
2019     case PPOINTER:
2020         SPEC_OCLS(spec) = xstack;
2021         break;
2022
2023     case EEPPOINTER:
2024         SPEC_OCLS(spec) = eeprom;
2025         break;
2026
2027     default:
2028         break;
2029
2030     }
2031 }
2032
2033 /*-----------------------------------------------------------------*/
2034 /* geniCodeDerefPtr - dereference pointer with '*'                 */
2035 /*-----------------------------------------------------------------*/
2036 operand *geniCodeDerefPtr (operand *op)
2037 {    
2038     link *rtype , *retype ;
2039     link *optype = operandType(op);  
2040
2041     /* if this is a pointer then generate the rvalue */
2042     if (IS_PTR(optype)) {
2043         if (IS_TRUE_SYMOP(op)) {
2044             op->isaddr = 1;
2045             op = geniCodeRValue(op,TRUE);
2046         }
2047         else    
2048             op = geniCodeRValue(op,TRUE);       
2049     }
2050     
2051     /* now get rid of the pointer part */
2052     if (lvaluereq && IS_ITEMP(op) )
2053     {
2054         retype = getSpec(rtype = copyLinkChain(optype)) ;
2055     }
2056     else
2057     {
2058         retype = getSpec(rtype = copyLinkChain(optype->next)) ;
2059     }
2060     
2061     /* if this is a pointer then outputclass needs 2b updated */
2062     if (IS_PTR(optype)) 
2063         setOClass(optype,retype);    
2064         
2065     op->isGptr = IS_GENPTR(optype);
2066
2067     /* if the pointer was declared as a constant */
2068     /* then we cannot allow assignment to the derefed */
2069     if (IS_PTR_CONST(optype))
2070         SPEC_CONST(retype) = 1;
2071     
2072     op->isaddr = (IS_PTR(rtype)    ||
2073                   IS_STRUCT(rtype) || 
2074                   IS_INT(rtype)    ||
2075                   IS_CHAR(rtype)   ||
2076                   IS_FLOAT(rtype) );
2077
2078     if (!lvaluereq)
2079         op = geniCodeRValue(op,TRUE);
2080
2081     setOperandType(op,rtype);
2082     
2083     return op;    
2084 }
2085
2086 /*-----------------------------------------------------------------*/
2087 /* geniCodeUnaryMinus - does a unary minus of the operand          */
2088 /*-----------------------------------------------------------------*/
2089 operand *geniCodeUnaryMinus (operand *op)
2090 {
2091     iCode *ic ;
2092     link *optype = operandType(op);
2093     
2094     if (IS_LITERAL(optype))
2095         return operandFromLit(- floatFromVal(op->operand.valOperand));
2096     
2097     ic = newiCode(UNARYMINUS,op,NULL);
2098     IC_RESULT(ic) = newiTempOperand(optype,0);
2099     ADDTOCHAIN(ic);
2100     return IC_RESULT(ic);
2101 }
2102
2103 /*-----------------------------------------------------------------*/
2104 /* geniCodeLeftShift - gen i code for left shift                   */
2105 /*-----------------------------------------------------------------*/
2106 operand *geniCodeLeftShift (operand *left, operand *right)
2107
2108     iCode *ic;
2109     link *ltype = operandType(left);
2110     
2111     ic = newiCode(LEFT_OP,left,right);
2112     IC_RESULT(ic) = newiTempOperand(ltype,0);
2113     ADDTOCHAIN(ic);
2114     return IC_RESULT(ic) ;  
2115 }
2116
2117 /*-----------------------------------------------------------------*/
2118 /* geniCodeRightShift - gen i code for right shift                 */
2119 /*-----------------------------------------------------------------*/
2120 operand *geniCodeRightShift (operand *left, operand *right)
2121
2122     iCode *ic;
2123     link *ltype = operandType(left);
2124     
2125     ic = newiCode(RIGHT_OP,left,right);
2126     IC_RESULT(ic) = newiTempOperand(ltype,0);
2127     ADDTOCHAIN(ic);
2128     return IC_RESULT(ic) ;  
2129 }
2130
2131 #ifdef __BORLANDC__
2132 #define LONG_LONG __int64
2133 #else
2134 #define LONG_LONG long long
2135 #endif
2136
2137 /*-----------------------------------------------------------------*/
2138 /* geniCodeLogic- logic code                                       */
2139 /*-----------------------------------------------------------------*/
2140 operand *geniCodeLogic (operand *left, operand *right, int op )
2141 {
2142     iCode *ic ;
2143     link *ctype; 
2144     link *rtype = operandType(right);
2145     link *ltype = operandType(left);
2146     
2147     /* left is integral type and right is literal then
2148        check if the literal value is within bounds */
2149     if (IS_INTEGRAL(ltype) && IS_LITERAL(rtype)) {
2150         int nbits = bitsForType(ltype);
2151         long v = operandLitValue(right);
2152
2153         if (v > ((LONG_LONG) 1 << nbits) && v > 0)
2154             werror(W_CONST_RANGE," compare operation ");
2155     }
2156
2157     ctype = computeType(ltype,rtype);                         
2158     left = geniCodeCast(ctype,left,TRUE);
2159     right= geniCodeCast(ctype,right,TRUE);
2160
2161     ic = newiCode(op,left,right);
2162     IC_RESULT(ic) = newiTempOperand (newCharLink(),1);
2163
2164     /* if comparing anything greater than one byte
2165        and not a '==' || '!=' || '&&' || '||' (these
2166        will be inlined */
2167     if (getSize(ctype) > 1 && 
2168         op != EQ_OP        && 
2169         op != NE_OP        &&
2170         op != AND_OP       &&
2171         op != OR_OP        )
2172         ic->supportRtn = 1;
2173
2174     ADDTOCHAIN(ic);
2175     return IC_RESULT(ic);
2176 }
2177
2178 /*-----------------------------------------------------------------*/
2179 /* geniCodeUnary - for a a generic unary operation                 */
2180 /*-----------------------------------------------------------------*/
2181 operand *geniCodeUnary (operand *op, int oper )
2182 {
2183     iCode *ic = newiCode (oper,op,NULL);
2184     
2185     IC_RESULT(ic)= newiTempOperand(operandType(op),0);
2186     ADDTOCHAIN(ic);
2187     return IC_RESULT(ic) ;
2188 }
2189
2190 /*-----------------------------------------------------------------*/
2191 /* geniCodeConditional - geniCode for '?' ':' operation            */
2192 /*-----------------------------------------------------------------*/
2193 operand *geniCodeConditional (ast *tree)
2194 {
2195     iCode *ic ;
2196     symbol *falseLabel = newiTempLabel(NULL);
2197     symbol *exitLabel  = newiTempLabel(NULL);
2198     operand *cond = ast2iCode(tree->left);
2199     operand *true, *false , *result;
2200     
2201     ic = newiCodeCondition(geniCodeRValue(cond,FALSE),
2202                            NULL,falseLabel);
2203     ADDTOCHAIN(ic);
2204     
2205     true = ast2iCode(tree->right->left);
2206     
2207     /* move the value to a new Operand */
2208     result = newiTempOperand(operandType(true),0);
2209     geniCodeAssign(result,geniCodeRValue(true,FALSE),0);
2210     
2211     /* generate an unconditional goto */
2212     geniCodeGoto(exitLabel);
2213     
2214     /* now for the right side */
2215     geniCodeLabel(falseLabel);
2216     
2217     false = ast2iCode(tree->right->right);
2218     geniCodeAssign(result,geniCodeRValue(false,FALSE),0);
2219     
2220     /* create the exit label */
2221     geniCodeLabel(exitLabel);
2222     
2223     return result ;
2224 }
2225
2226 /*-----------------------------------------------------------------*/
2227 /* geniCodeAssign - generate code for assignment                   */
2228 /*-----------------------------------------------------------------*/
2229 operand *geniCodeAssign (operand *left, operand *right, int nosupdate)
2230 {
2231     iCode *ic ;
2232     link *ltype = operandType(left);
2233     link *rtype = operandType(right);
2234     
2235     if (!left->isaddr && !IS_ITEMP(left)) {
2236         werror(E_LVALUE_REQUIRED,"assignment");
2237         return left;
2238     }
2239         
2240     /* left is integral type and right is literal then
2241        check if the literal value is within bounds */
2242     if (IS_INTEGRAL(ltype) && right->type == VALUE && IS_LITERAL(rtype)) {
2243         int nbits = bitsForType(ltype);
2244         long v = operandLitValue(right);
2245
2246         if (v > ((LONG_LONG)1 << nbits) && v > 0)
2247             werror(W_CONST_RANGE," = operation");
2248     }
2249
2250     /* if the left & right type don't exactly match */
2251     /* if pointer set then make sure the check is
2252        done with the type & not the pointer */
2253     /* then cast rights type to left */   
2254
2255     /* first check the type for pointer assignement */
2256     if (left->isaddr && IS_PTR(ltype) && IS_ITEMP(left) &&
2257         checkType(ltype,rtype)<0) {
2258         if (checkType(ltype->next,rtype) < 0)
2259             right = geniCodeCast(ltype->next,right,TRUE);
2260     } else
2261         if (checkType(ltype,rtype) < 0 )
2262             right = geniCodeCast(ltype,right,TRUE);
2263
2264     /* if left is a true symbol & ! volatile 
2265        create an assignment to temporary for
2266        the right & then assign this temporary
2267        to the symbol this is SSA . isn't it simple
2268        and folks have published mountains of paper on it */
2269     if (IS_TRUE_SYMOP(left) && 
2270         !isOperandVolatile(left,FALSE) &&
2271         isOperandGlobal(left)) {
2272         symbol *sym = NULL;
2273
2274         if (IS_TRUE_SYMOP(right))
2275             sym = OP_SYMBOL(right);
2276         ic = newiCode('=',NULL,right);
2277         IC_RESULT(ic) = right = newiTempOperand(ltype,0);       
2278         SPIL_LOC(right)  = sym ;
2279         ADDTOCHAIN(ic);
2280     }
2281     
2282     ic = newiCode('=',NULL,right);
2283     IC_RESULT(ic) = left;
2284     ADDTOCHAIN(ic);    
2285
2286     /* if left isgptr flag is set then support
2287        routine will be required */
2288     if (left->isGptr)
2289         ic->supportRtn = 1;
2290
2291     ic->nosupdate = nosupdate;
2292     return left;
2293 }
2294
2295 /*-----------------------------------------------------------------*/
2296 /* geniCodeSEParms - generate code for side effecting fcalls       */
2297 /*-----------------------------------------------------------------*/
2298 static void geniCodeSEParms (ast *parms)
2299 {
2300     if (!parms)
2301         return ;
2302
2303     if (parms->type == EX_OP && parms->opval.op == PARAM) {
2304         geniCodeSEParms (parms->left) ;
2305         geniCodeSEParms (parms->right);
2306         return ;
2307     }
2308
2309     /* hack don't like this but too lazy to think of
2310        something better */
2311     if (IS_ADDRESS_OF_OP(parms))
2312         parms->left->lvalue = 1;
2313     
2314     if (IS_CAST_OP(parms) && 
2315         IS_PTR(parms->ftype) && 
2316         IS_ADDRESS_OF_OP(parms->right))
2317         parms->right->left->lvalue = 1;
2318
2319     parms->opval.oprnd = 
2320         geniCodeRValue(ast2iCode (parms),FALSE);
2321    
2322     parms->type = EX_OPERAND ;
2323 }
2324
2325 /*-----------------------------------------------------------------*/
2326 /* geniCodeParms - generates parameters                            */
2327 /*-----------------------------------------------------------------*/
2328 static void geniCodeParms ( ast *parms , int *stack, link *fetype, symbol *func)
2329 {
2330     iCode *ic ;
2331     operand *pval ; 
2332     
2333     if ( ! parms )
2334         return ;
2335     
2336     /* if this is a param node then do the left & right */
2337     if (parms->type == EX_OP && parms->opval.op == PARAM) {
2338         geniCodeParms (parms->left, stack,fetype,func) ;
2339         geniCodeParms (parms->right, stack,fetype,func);
2340         return ;
2341     }
2342     
2343     /* get the parameter value */
2344     if (parms->type == EX_OPERAND)
2345         pval = parms->opval.oprnd ;
2346     else {
2347         /* maybe this else should go away ?? */
2348         /* hack don't like this but too lazy to think of
2349            something better */
2350         if (IS_ADDRESS_OF_OP(parms))
2351             parms->left->lvalue = 1;
2352     
2353         if (IS_CAST_OP(parms) && 
2354             IS_PTR(parms->ftype) && 
2355             IS_ADDRESS_OF_OP(parms->right))
2356             parms->right->left->lvalue = 1;
2357
2358         pval = geniCodeRValue(ast2iCode (parms),FALSE); 
2359     }
2360
2361     /* if register parm then make it a send */
2362     if (((parms->argSym && IS_REGPARM(parms->argSym->etype)) ||
2363         IS_REGPARM(parms->etype)) && !func->hasVargs ) {
2364         ic = newiCode(SEND,pval,NULL);
2365         ADDTOCHAIN(ic);
2366     } else {
2367         /* now decide whether to push or assign */
2368         if (!(options.stackAuto || IS_RENT(fetype))) { 
2369             
2370             /* assign */
2371             operand *top = operandFromSymbol(parms->argSym);
2372             geniCodeAssign(top,pval,1);
2373         }
2374         else { 
2375             link *p = operandType(pval);
2376             /* push */
2377             ic = newiCode(IPUSH,pval,NULL);
2378             ic->parmPush = 1;
2379             /* update the stack adjustment */
2380             *stack += getSize(IS_AGGREGATE(p)? aggrToPtr(p,FALSE):p);
2381             ADDTOCHAIN(ic);
2382         }
2383     }
2384     
2385 }
2386
2387 /*-----------------------------------------------------------------*/
2388 /* geniCodeCall - generates temp code for calling                  */
2389 /*-----------------------------------------------------------------*/
2390 operand *geniCodeCall (operand *left, ast *parms)
2391
2392     iCode *ic ;
2393     operand *result ;
2394     link *type, *etype;
2395     int stack = 0 ;
2396     
2397     /* take care of parameters with side-effecting
2398        function calls in them, this is required to take care 
2399        of overlaying function parameters */
2400     geniCodeSEParms ( parms );
2401
2402     /* first the parameters */
2403     geniCodeParms ( parms , &stack , getSpec(operandType(left)), OP_SYMBOL(left));
2404     
2405     /* now call : if symbol then pcall */
2406     if (IS_ITEMP(left)) 
2407         ic = newiCode(PCALL,left,NULL);
2408     else
2409         ic = newiCode(CALL,left,NULL);
2410     
2411     IC_ARGS(ic) = left->operand.symOperand->args ;
2412     type = copyLinkChain(operandType(left)->next);
2413     etype = getSpec(type);
2414     SPEC_EXTR(etype) = 0;
2415     IC_RESULT(ic) = result = newiTempOperand(type,1);
2416     
2417     ADDTOCHAIN(ic);
2418     
2419     /* stack adjustment after call */
2420     left->parmBytes = stack;
2421
2422     return result;
2423 }
2424
2425 /*-----------------------------------------------------------------*/
2426 /* geniCodeReceive - generate intermediate code for "receive"      */
2427 /*-----------------------------------------------------------------*/
2428 static void geniCodeReceive (value *args)
2429 {   
2430     /* for all arguments that are passed in registers */
2431     while (args) {
2432
2433         if (IS_REGPARM(args->etype)) {
2434             operand *opr = operandFromValue(args);
2435             operand *opl ;
2436             symbol *sym  = OP_SYMBOL(opr);
2437             iCode *ic ;
2438
2439             /* we will use it after all optimizations
2440                and before liveRange calculation */          
2441             if (!sym->addrtaken && !IS_VOLATILE(sym->etype)) {
2442
2443                 if (IN_FARSPACE(SPEC_OCLS(sym->etype)) &&
2444                    options.stackAuto == 0 &&
2445                    !IS_DS390_PORT) {
2446                 } else {
2447                     opl = newiTempOperand(args->type,0);
2448                     sym->reqv = opl ;       
2449                     sym->reqv->key = sym->key ;
2450                     OP_SYMBOL(sym->reqv)->key = sym->key;
2451                     OP_SYMBOL(sym->reqv)->isreqv = 1;
2452                     OP_SYMBOL(sym->reqv)->islocal= 0;
2453                     SPIL_LOC(sym->reqv) =  sym;
2454                 }
2455             }
2456
2457             ic = newiCode(RECEIVE,NULL,NULL);
2458             currFunc->recvSize = getSize(sym->etype);
2459             IC_RESULT(ic) = opr;
2460             ADDTOCHAIN(ic);
2461         }
2462         
2463         args = args->next;
2464     }
2465 }
2466
2467 /*-----------------------------------------------------------------*/
2468 /* geniCodeFunctionBody - create the function body                 */
2469 /*-----------------------------------------------------------------*/
2470 void geniCodeFunctionBody (ast *tree)
2471 {
2472     iCode *ic ;
2473     operand *func ;
2474     link *fetype  ;
2475     int savelineno ;
2476     
2477     /* reset the auto generation */
2478     /* numbers */
2479     iTempNum = 0 ;
2480     iTempLblNum = 0;   
2481     operandKey = 0 ;
2482     iCodeKey = 0 ;
2483     func  = ast2iCode(tree->left);
2484     fetype = getSpec(operandType(func));
2485     
2486     savelineno = lineno;
2487     lineno = OP_SYMBOL(func)->lineDef;
2488     /* create an entry label */
2489     geniCodeLabel(entryLabel);    
2490     lineno = savelineno;
2491
2492     /* create a proc icode */
2493     ic = newiCode(FUNCTION,func,NULL);
2494     /* if the function has parmas   then */
2495     /* save the parameters information    */
2496     ic->argLabel.args = tree->values.args ;
2497     ic->lineno = OP_SYMBOL(func)->lineDef;
2498
2499     ADDTOCHAIN(ic);   
2500     
2501     /* for all parameters that are passed
2502        on registers add a "receive" */
2503     geniCodeReceive( tree->values.args );
2504
2505     /* generate code for the body */
2506     ast2iCode(tree->right);
2507     
2508     /* create a label for return */
2509     geniCodeLabel(returnLabel);
2510     
2511     /* now generate the end proc */
2512     ic = newiCode(ENDFUNCTION,func,NULL);
2513     ADDTOCHAIN(ic);
2514     return ;
2515 }
2516
2517 /*-----------------------------------------------------------------*/
2518 /* geniCodeReturn - gen icode for 'return' statement               */
2519 /*-----------------------------------------------------------------*/
2520 void geniCodeReturn (operand *op)
2521 {
2522     iCode *ic;
2523     
2524     /* if the operand is present force an rvalue */
2525     if (op) 
2526         op = geniCodeRValue(op,FALSE);    
2527     
2528     ic = newiCode(RETURN,op,NULL);
2529     ADDTOCHAIN(ic);
2530 }
2531
2532 /*-----------------------------------------------------------------*/
2533 /* geniCodeIfx - generates code for extended if statement          */
2534 /*-----------------------------------------------------------------*/
2535 void geniCodeIfx (ast *tree)
2536 {
2537     iCode *ic;
2538     operand *condition = ast2iCode(tree->left);
2539     link *cetype; 
2540     
2541     /* if condition is null then exit */
2542     if (!condition)
2543         goto exit ;
2544     else
2545         condition = geniCodeRValue(condition,FALSE);
2546     
2547     cetype = getSpec(operandType(condition));
2548     /* if the condition is a literal */
2549     if (IS_LITERAL(cetype)) {
2550         if (floatFromVal(condition->operand.valOperand)) {
2551             if (tree->trueLabel)
2552                 geniCodeGoto(tree->trueLabel);
2553             else
2554                 assert(1);
2555         }
2556         else {
2557             if (tree->falseLabel)
2558                 geniCodeGoto (tree->falseLabel);
2559             else
2560                 assert(1);
2561         }
2562         goto exit;
2563     }
2564     
2565     if ( tree->trueLabel ) {
2566         ic = newiCodeCondition(condition,
2567                                tree->trueLabel,
2568                                NULL );
2569         ADDTOCHAIN(ic);
2570         
2571         if ( tree->falseLabel) 
2572             geniCodeGoto(tree->falseLabel);     
2573     }
2574     else {
2575         ic = newiCodeCondition (condition,
2576                                 NULL,
2577                                 tree->falseLabel);
2578         ADDTOCHAIN(ic);
2579     }
2580     
2581  exit:
2582     ast2iCode(tree->right);
2583 }
2584
2585 /*-----------------------------------------------------------------*/
2586 /* geniCodeJumpTable - tries to create a jump table for switch     */
2587 /*-----------------------------------------------------------------*/
2588 int geniCodeJumpTable (operand *cond, value *caseVals, ast *tree)
2589 {
2590     int min = 0 ,max = 0, t, cnt = 0;
2591     value *vch;
2592     iCode *ic;
2593     operand *boundary;
2594     symbol *falseLabel;
2595     set *labels = NULL ;
2596
2597     if (!tree || !caseVals)
2598         return 0;
2599
2600     /* the criteria for creating a jump table is */
2601     /* all integer numbers between the maximum & minimum must */
2602     /* be present , the maximum value should not exceed 255 */
2603     min = max = (int)floatFromVal(vch = caseVals);
2604     sprintf(buffer,"_case_%d_%d",
2605             tree->values.switchVals.swNum,
2606             min);
2607     addSet(&labels,newiTempLabel(buffer));
2608
2609     /* if there is only one case value then no need */
2610     if (!(vch = vch->next ))
2611         return 0;
2612
2613     while (vch) {
2614         if (((t = (int)floatFromVal(vch)) - max) != 1)
2615             return 0;
2616         sprintf(buffer,"_case_%d_%d",
2617                 tree->values.switchVals.swNum,
2618                 t);
2619         addSet(&labels,newiTempLabel(buffer));
2620         max = t;
2621         cnt++ ;
2622         vch = vch->next ;
2623     }
2624     
2625     /* if the number of case statements <= 2 then */
2626     /* it is not economical to create the jump table */
2627     /* since two compares are needed for boundary conditions */
2628     if ((! optimize.noJTabBoundary  && cnt <= 2) || max > (255/3))
2629         return 0;
2630     
2631     if ( tree->values.switchVals.swDefault )
2632         sprintf (buffer,"_default_%d",tree->values.switchVals.swNum);
2633     else
2634         sprintf (buffer,"_swBrk_%d",tree->values.switchVals.swNum  );
2635     
2636     falseLabel = newiTempLabel (buffer);
2637
2638     /* so we can create a jumptable */
2639     /* first we rule out the boundary conditions */
2640     /* if only optimization says so */
2641     if ( ! optimize.noJTabBoundary ) {
2642         link *cetype = getSpec(operandType(cond));
2643         /* no need to check the lower bound if
2644            the condition is unsigned & minimum value is zero */
2645         if (!( min == 0  && SPEC_USIGN(cetype))) {
2646             boundary = geniCodeLogic (cond,operandFromLit(min),'<');
2647             ic = newiCodeCondition (boundary,falseLabel,NULL);
2648             ADDTOCHAIN(ic);
2649         }
2650
2651         /* now for upper bounds */
2652         boundary = geniCodeLogic(cond,operandFromLit(max),'>');
2653         ic = newiCodeCondition (boundary,falseLabel,NULL);
2654         ADDTOCHAIN(ic);
2655     }
2656
2657     /* if the min is not zero then we no make it zero */
2658     if (min) {
2659         cond = geniCodeSubtract(cond,operandFromLit(min));
2660         setOperandType(cond, UCHARTYPE);
2661     }
2662
2663     /* now create the jumptable */
2664     ic = newiCode(JUMPTABLE,NULL,NULL);
2665     IC_JTCOND(ic) = cond;
2666     IC_JTLABELS(ic) = labels;
2667     ADDTOCHAIN(ic);
2668     return 1;       
2669 }
2670
2671 /*-----------------------------------------------------------------*/
2672 /* geniCodeSwitch - changes a switch to a if statement             */
2673 /*-----------------------------------------------------------------*/
2674 void geniCodeSwitch (ast *tree)
2675 {
2676     iCode *ic ;
2677     operand *cond = geniCodeRValue(ast2iCode (tree->left),FALSE);
2678     value *caseVals = tree->values.switchVals.swVals ;
2679     symbol *trueLabel , *falseLabel;
2680     
2681     /* if we can make this a jump table */
2682     if ( geniCodeJumpTable (cond,caseVals,tree) )
2683         goto jumpTable ; /* no need for the comparison */
2684
2685     /* for the cases defined do */
2686     while (caseVals) {
2687         
2688         operand *compare = geniCodeLogic (cond,
2689                                           operandFromValue(caseVals),
2690                                           EQ_OP);
2691         
2692         sprintf(buffer,"_case_%d_%d",
2693                 tree->values.switchVals.swNum,
2694                 (int) floatFromVal(caseVals));
2695         trueLabel = newiTempLabel(buffer);
2696         
2697         ic = newiCodeCondition(compare,trueLabel,NULL);
2698         ADDTOCHAIN(ic);
2699         caseVals = caseVals->next;
2700     }
2701
2702
2703     
2704     /* if default is present then goto break else break */
2705     if ( tree->values.switchVals.swDefault )
2706         sprintf (buffer,"_default_%d",tree->values.switchVals.swNum);
2707     else
2708         sprintf (buffer,"_swBrk_%d",tree->values.switchVals.swNum  );
2709     
2710     falseLabel = newiTempLabel (buffer);
2711     geniCodeGoto(falseLabel);
2712  
2713  jumpTable:   
2714     ast2iCode(tree->right);
2715
2716
2717 /*-----------------------------------------------------------------*/
2718 /* geniCodeInline - intermediate code for inline assembler         */
2719 /*-----------------------------------------------------------------*/
2720 static void geniCodeInline (ast *tree)
2721 {
2722     iCode *ic;
2723
2724     ic = newiCode(INLINEASM,NULL,NULL);
2725     IC_INLINE(ic) = tree->values.inlineasm;
2726     ADDTOCHAIN(ic);
2727 }
2728
2729 /*-----------------------------------------------------------------*/
2730 /* ast2iCode - creates an icodeList from an ast                    */
2731 /*-----------------------------------------------------------------*/
2732 operand *ast2iCode (ast *tree)
2733 {
2734     operand *left = NULL;
2735     operand *right= NULL;
2736     
2737     if (!tree)
2738         return NULL ;
2739     
2740     /* set the global variables for filename & line number */
2741     if ( tree->filename )
2742         filename =  tree->filename ;
2743     if ( tree->lineno)
2744         lineno   = tree->lineno ;
2745     if (tree->block)
2746         block = tree->block ;
2747     if (tree->level)
2748         scopeLevel = tree->level;
2749     
2750     if (tree->type == EX_VALUE )
2751         return operandFromValue(tree->opval.val);
2752     
2753     if (tree->type == EX_LINK )
2754         return operandFromLink (tree->opval.lnk);
2755     
2756     /* if we find a nullop */
2757     if (tree->type == EX_OP && 
2758         ( tree->opval.op == NULLOP || 
2759           tree->opval.op == BLOCK )) {
2760         ast2iCode (tree->left);
2761         ast2iCode (tree->right);
2762         return NULL ;
2763     }
2764     
2765     /* special cases for not evaluating */
2766     if ( tree->opval.op != ':'   && 
2767          tree->opval.op != '?'   &&
2768          tree->opval.op != CALL  && 
2769          tree->opval.op != IFX   &&
2770          tree->opval.op != LABEL &&
2771          tree->opval.op != GOTO  &&     
2772          tree->opval.op != SWITCH &&
2773          tree->opval.op != FUNCTION &&
2774          tree->opval.op != INLINEASM ) {
2775
2776         if (IS_ASSIGN_OP(tree->opval.op) || 
2777             IS_DEREF_OP(tree)            || 
2778             (tree->opval.op == '&' && !tree->right) ||
2779             tree->opval.op == PTR_OP) {
2780             lvaluereq++;
2781             if ((IS_ARRAY_OP(tree->left) && IS_ARRAY_OP(tree->left->left)) ||
2782                 (IS_DEREF_OP(tree) && IS_ARRAY_OP(tree->left)))
2783             {
2784                 int olvr = lvaluereq ;
2785                 lvaluereq = 0;
2786                 left = operandFromAst(tree->left);
2787                 lvaluereq = olvr - 1;
2788             } else {
2789                 left = operandFromAst(tree->left);
2790                 lvaluereq--;
2791             }
2792             if (IS_DEREF_OP(tree) && IS_DEREF_OP(tree->left))
2793                     left = geniCodeRValue(left,TRUE);
2794         } else {
2795             left =  operandFromAst(tree->left);
2796         }
2797         if (tree->opval.op == INC_OP || 
2798             tree->opval.op == DEC_OP) {
2799             lvaluereq++;
2800             right= operandFromAst(tree->right);
2801             lvaluereq--;
2802         } else {
2803             right= operandFromAst(tree->right);
2804         }
2805     }
2806     
2807     /* now depending on the type of operand */
2808     /* this will be a biggy                 */
2809     switch (tree->opval.op) {
2810         
2811     case '[' :    /* array operation */
2812         {
2813             link *ltype = operandType(left);
2814             left= geniCodeRValue (left,IS_PTR(ltype->next) ? TRUE : FALSE);
2815             right=geniCodeRValue (right,TRUE);             
2816         }
2817         
2818         return geniCodeArray (left,right);
2819         
2820     case '.' :   /* structure dereference */
2821         if (IS_PTR(operandType(left)))
2822             left = geniCodeRValue(left,TRUE);
2823         else
2824             left = geniCodeRValue(left,FALSE);            
2825         
2826         return geniCodeStruct (left,right,tree->lvalue);
2827         
2828     case PTR_OP: /* structure pointer dereference */
2829         {
2830             link *pType;
2831             pType = operandType(left);
2832             left = geniCodeRValue(left,TRUE);
2833             
2834             setOClass (pType,getSpec(operandType(left)));
2835         }              
2836         
2837         return geniCodeStruct (left, right,tree->lvalue);
2838         
2839     case INC_OP: /* increment operator */
2840         if ( left )
2841             return geniCodePostInc (left);
2842         else
2843             return geniCodePreInc (right);
2844         
2845     case DEC_OP: /* decrement operator */
2846         if ( left )
2847             return geniCodePostDec (left);
2848         else
2849             return geniCodePreDec (right);
2850         
2851     case '&' : /* bitwise and or address of operator */
2852         if ( right ) { /* this is a bitwise operator   */
2853             left= geniCodeRValue(left,FALSE);
2854             right= geniCodeRValue(right,FALSE);     
2855             return geniCodeBitwise (left,right,BITWISEAND,tree->ftype);
2856         } else
2857             return geniCodeAddressOf (left);
2858         
2859     case '|': /* bitwise or & xor */
2860     case '^':
2861         return geniCodeBitwise (geniCodeRValue(left,FALSE),
2862                                 geniCodeRValue(right,FALSE),
2863                                 tree->opval.op,
2864                                 tree->ftype);
2865         
2866     case '/':
2867         return geniCodeDivision (geniCodeRValue(left,FALSE),
2868                                  geniCodeRValue(right,FALSE));
2869         
2870     case '%' :
2871         return geniCodeModulus (geniCodeRValue(left,FALSE),
2872                                 geniCodeRValue(right,FALSE));
2873     case '*':
2874         if ( right ) 
2875             return geniCodeMultiply (geniCodeRValue(left,FALSE),
2876                                      geniCodeRValue(right,FALSE));
2877         else        
2878             return geniCodeDerefPtr (geniCodeRValue(left,FALSE));
2879         
2880     case '-' :
2881         if ( right ) 
2882             return geniCodeSubtract (geniCodeRValue(left,FALSE),
2883                                      geniCodeRValue(right,FALSE));
2884         else
2885             return geniCodeUnaryMinus (geniCodeRValue(left,FALSE));
2886         
2887     case '+' :
2888         if ( right ) 
2889             return geniCodeAdd (geniCodeRValue(left,FALSE),
2890                                 geniCodeRValue(right,FALSE));
2891         else
2892             return geniCodeRValue(left,FALSE) ; /* unary '+' has no meaning */
2893         
2894     case LEFT_OP:
2895         return geniCodeLeftShift (geniCodeRValue(left,FALSE),
2896                                   geniCodeRValue(right,FALSE));
2897         
2898     case RIGHT_OP:
2899         return geniCodeRightShift (geniCodeRValue(left,FALSE),
2900                                    geniCodeRValue(right,FALSE));
2901     case CAST:
2902         return geniCodeCast (operandType(left),
2903                              geniCodeRValue(right,FALSE),FALSE);
2904         
2905     case '~' :
2906     case '!' :
2907     case RRC:
2908     case RLC:   
2909         return geniCodeUnary (geniCodeRValue(left,FALSE),tree->opval.op);
2910         
2911     case GETHBIT:
2912         {
2913             operand *op = geniCodeUnary (geniCodeRValue(left,FALSE),tree->opval.op);
2914             setOperandType(op, UCHARTYPE);
2915             return op;
2916         }
2917     case '>' :
2918     case '<' :
2919     case LE_OP:
2920     case GE_OP:
2921     case EQ_OP:
2922     case NE_OP:
2923     case AND_OP:
2924     case OR_OP:
2925         return geniCodeLogic (geniCodeRValue(left,FALSE),
2926                               geniCodeRValue(right,FALSE),
2927                               tree->opval.op);
2928     case '?' : 
2929         return geniCodeConditional (tree); 
2930         
2931     case SIZEOF:
2932         return operandFromLit(getSize(tree->right->ftype));
2933         
2934     case '='        :
2935         {
2936             link *rtype = operandType(right);
2937             link *ltype = operandType(left);
2938             if (IS_PTR(rtype) && IS_ITEMP(right) 
2939                 && right->isaddr && checkType(rtype->next,ltype)==1)
2940                 right =  geniCodeRValue(right,TRUE);
2941             else
2942                 right = geniCodeRValue(right,FALSE);
2943
2944             geniCodeAssign (left,right,0);
2945             return right ;
2946         }              
2947     case MUL_ASSIGN:
2948         return 
2949             geniCodeAssign(left,
2950                            geniCodeMultiply(geniCodeRValue (operandFromOperand(left),
2951                                                             FALSE),
2952                                             geniCodeRValue(right,FALSE)),0);
2953                                                 
2954     case DIV_ASSIGN:
2955         return 
2956             geniCodeAssign(left,
2957                            geniCodeDivision(geniCodeRValue(operandFromOperand(left),
2958                                                            FALSE),
2959                                             geniCodeRValue(right,FALSE)),0);
2960     case MOD_ASSIGN:
2961         return 
2962             geniCodeAssign(left,
2963                            geniCodeModulus(geniCodeRValue(operandFromOperand(left),
2964                                                           FALSE),
2965                                            geniCodeRValue(right,FALSE)),0);
2966     case ADD_ASSIGN: 
2967         {
2968             link *rtype = operandType(right);
2969             link *ltype = operandType(left);
2970             if (IS_PTR(rtype) && IS_ITEMP(right) 
2971                 && right->isaddr && checkType(rtype->next,ltype)==1)
2972                 right =  geniCodeRValue(right,TRUE);
2973             else
2974                 right = geniCodeRValue(right,FALSE);
2975
2976            
2977             return geniCodeAssign(left,
2978                                   geniCodeAdd (geniCodeRValue(operandFromOperand(left),
2979                                                               FALSE),
2980                                                right),0);
2981         }
2982     case SUB_ASSIGN:
2983         {
2984             link *rtype = operandType(right);
2985             link *ltype = operandType(left);
2986             if (IS_PTR(rtype) && IS_ITEMP(right) 
2987                 && right->isaddr && checkType(rtype->next,ltype)==1) {
2988                 right =  geniCodeRValue(right,TRUE);
2989             }
2990             else {
2991                 right = geniCodeRValue(right,FALSE);
2992             }
2993             return 
2994                 geniCodeAssign (left,
2995                                 geniCodeSubtract(geniCodeRValue(operandFromOperand(left),
2996                                                                 FALSE),
2997                                                  right),0);
2998         }
2999     case LEFT_ASSIGN:
3000         return 
3001             geniCodeAssign (left,
3002                             geniCodeLeftShift(geniCodeRValue(operandFromOperand(left)
3003                                                              ,FALSE),
3004                                               geniCodeRValue(right,FALSE)),0);
3005     case RIGHT_ASSIGN:
3006         return 
3007             geniCodeAssign(left,
3008                            geniCodeRightShift(geniCodeRValue(operandFromOperand(left)
3009                                                              ,FALSE),
3010                                               geniCodeRValue(right,FALSE)),0);
3011     case AND_ASSIGN:
3012         return 
3013             geniCodeAssign (left,
3014                             geniCodeBitwise(geniCodeRValue(operandFromOperand(left),
3015                                                            FALSE),
3016                                             geniCodeRValue(right,FALSE),
3017                                             BITWISEAND,
3018                                             operandType(left)),0);
3019     case XOR_ASSIGN:
3020         return 
3021             geniCodeAssign (left,
3022                             geniCodeBitwise (geniCodeRValue(operandFromOperand(left),
3023                                                             FALSE),
3024                                              geniCodeRValue(right,FALSE),
3025                                              '^',
3026                                              operandType(left)),0);
3027     case OR_ASSIGN:
3028         return 
3029             geniCodeAssign (left,
3030                             geniCodeBitwise (geniCodeRValue(operandFromOperand(left)
3031                                                             ,FALSE),
3032                                              geniCodeRValue(right,FALSE),
3033                                              '|',
3034                                              operandType(left)),0);
3035     case ',' :
3036         return geniCodeRValue(right,FALSE);
3037         
3038     case CALL:
3039         return geniCodeCall (ast2iCode(tree->left),
3040                              tree->right);
3041     case LABEL:
3042         geniCodeLabel(ast2iCode(tree->left)->operand.symOperand);
3043         return ast2iCode (tree->right);
3044         
3045     case GOTO:
3046         geniCodeGoto (ast2iCode(tree->left)->operand.symOperand);
3047         return ast2iCode (tree->right);
3048         
3049     case FUNCTION:
3050         geniCodeFunctionBody ( tree );
3051         return NULL ;
3052         
3053     case RETURN:
3054         geniCodeReturn (right);
3055         return NULL ;
3056         
3057     case IFX:
3058         geniCodeIfx (tree);
3059         return NULL ;
3060         
3061     case SWITCH:
3062         geniCodeSwitch (tree);
3063         return NULL;
3064
3065     case INLINEASM:
3066         geniCodeInline (tree);
3067         return NULL ;
3068     }
3069     
3070     return NULL;
3071 }
3072
3073 /*-----------------------------------------------------------------*/
3074 /* reverseICChain - gets from the list and creates a linkedlist    */
3075 /*-----------------------------------------------------------------*/
3076 iCode *reverseiCChain ()
3077 {
3078     iCode *loop = NULL ;
3079     iCode *prev = NULL ;
3080     
3081     while ((loop = getSet(&iCodeChain))) {
3082         loop->next = prev ;
3083         if ( prev )
3084             prev->prev = loop; 
3085         prev = loop ;
3086     }
3087     
3088     return prev;
3089 }
3090
3091
3092 /*-----------------------------------------------------------------*/
3093 /* iCodeFromAst - given an ast will convert it to iCode            */
3094 /*-----------------------------------------------------------------*/
3095 iCode *iCodeFromAst ( ast *tree )
3096 {
3097     returnLabel = newiTempLabel("_return");
3098     entryLabel  = newiTempLabel("_entry") ;
3099     ast2iCode (tree);
3100     return reverseiCChain ();
3101 }
3102