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