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