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