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