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