* src/SDCCval.c (cheapestVal, valueFromLit): use TYPE_* types
[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(right));
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         {
1085           if (SPEC_USIGN(let) || SPEC_USIGN(ret))
1086             /* one of the operands is unsigned */
1087             retval = operandFromLit ((TYPE_UDWORD) operandLitValue (left) %
1088                                      (TYPE_UDWORD) operandLitValue (right));
1089           else
1090             /* both operands are signed */
1091             retval = operandFromLit ((TYPE_DWORD) operandLitValue (left) %
1092                                      (TYPE_DWORD) operandLitValue (right));
1093         }
1094       break;
1095     case LEFT_OP:
1096       /* The number of left shifts is always unsigned. Signed doesn't make
1097          sense here. Shifting by a negative number is impossible. */
1098       retval = operandFromLit ((TYPE_UDWORD) operandLitValue (left) <<
1099                                (TYPE_UDWORD) operandLitValue (right));
1100       break;
1101     case RIGHT_OP: {
1102       /* The number of right shifts is always unsigned. Signed doesn't make
1103          sense here. Shifting by a negative number is impossible. */
1104       if (SPEC_USIGN(let))
1105         /* unsigned: logic shift right */
1106         retval = operandFromLit ((TYPE_UDWORD) operandLitValue (left) >>
1107                                  (TYPE_UDWORD) operandLitValue (right));
1108       else
1109         /* signed: arithmetic shift right */
1110         retval = operandFromLit ((TYPE_DWORD ) operandLitValue (left) >>
1111                                  (TYPE_UDWORD) operandLitValue (right));
1112       break;
1113     }
1114     case EQ_OP:
1115       retval = operandFromLit (operandLitValue (left) ==
1116                                operandLitValue (right));
1117       break;
1118     case '<':
1119       retval = operandFromLit (operandLitValue (left) <
1120                                operandLitValue (right));
1121       break;
1122     case LE_OP:
1123       retval = operandFromLit (operandLitValue (left) <=
1124                                operandLitValue (right));
1125       break;
1126     case NE_OP:
1127       retval = operandFromLit (operandLitValue (left) !=
1128                                operandLitValue (right));
1129       break;
1130     case '>':
1131       retval = operandFromLit (operandLitValue (left) >
1132                                operandLitValue (right));
1133       break;
1134     case GE_OP:
1135       retval = operandFromLit (operandLitValue (left) >=
1136                                operandLitValue (right));
1137       break;
1138     case BITWISEAND:
1139       retval = operandFromValue (valCastLiteral (type,
1140                                                  (TYPE_UDWORD)operandLitValue(left) &
1141                                                  (TYPE_UDWORD)operandLitValue(right)));
1142       break;
1143     case '|':
1144       retval = operandFromValue (valCastLiteral (type,
1145                                                  (TYPE_UDWORD)operandLitValue(left) |
1146                                                  (TYPE_UDWORD)operandLitValue(right)));
1147       break;
1148     case '^':
1149       retval = operandFromValue (valCastLiteral (type,
1150                                                  (TYPE_UDWORD)operandLitValue(left) ^
1151                                                  (TYPE_UDWORD)operandLitValue(right)));
1152       break;
1153     case AND_OP:
1154       retval = operandFromLit (operandLitValue (left) &&
1155                                operandLitValue (right));
1156       break;
1157     case OR_OP:
1158       retval = operandFromLit (operandLitValue (left) ||
1159                                operandLitValue (right));
1160       break;
1161     case RRC:
1162       {
1163         TYPE_UDWORD i = (TYPE_UDWORD) operandLitValue (left);
1164
1165         retval = operandFromLit ((i >> (getSize (operandType (left)) * 8 - 1)) |
1166                                  (i << 1));
1167       }
1168       break;
1169     case RLC:
1170       {
1171         TYPE_UDWORD i = (TYPE_UDWORD) operandLitValue (left);
1172
1173         retval = operandFromLit ((i << (getSize (operandType (left)) * 8 - 1)) |
1174                                  (i >> 1));
1175       }
1176       break;
1177
1178     case UNARYMINUS:
1179       retval = operandFromLit (-1 * operandLitValue (left));
1180       break;
1181
1182     case '~':
1183       retval = operandFromLit (~((TYPE_UDWORD) operandLitValue (left)));
1184       break;
1185
1186     case '!':
1187       retval = operandFromLit (!operandLitValue (left));
1188       break;
1189
1190     default:
1191       werror (E_INTERNAL_ERROR, __FILE__, __LINE__,
1192               " operandOperation invalid operator ");
1193       assert (0);
1194     }
1195
1196   return retval;
1197 }
1198
1199
1200 /*-----------------------------------------------------------------*/
1201 /* isOperandEqual - compares two operand & return 1 if they r =    */
1202 /*-----------------------------------------------------------------*/
1203 int 
1204 isOperandEqual (operand * left, operand * right)
1205 {
1206   /* if the pointers are equal then they are equal */
1207   if (left == right)
1208     return 1;
1209
1210   /* if either of them null then false */
1211   if (!left || !right)
1212     return 0;
1213
1214   if (left->type != right->type)
1215     return 0;
1216
1217   if (IS_SYMOP (left) && IS_SYMOP (right))
1218     return left->key == right->key;
1219
1220   /* if types are the same */
1221   switch (left->type)
1222     {
1223     case SYMBOL:
1224       return isSymbolEqual (left->operand.symOperand,
1225                             right->operand.symOperand);
1226     case VALUE:
1227       return (floatFromVal (left->operand.valOperand) ==
1228               floatFromVal (right->operand.valOperand));
1229     case TYPE:
1230       if (compareType (left->operand.typeOperand,
1231                      right->operand.typeOperand) == 1)
1232         return 1;
1233     }
1234
1235   return 0;
1236 }
1237
1238 /*-------------------------------------------------------------------*/
1239 /* isiCodeEqual - compares two iCodes are equal, returns true if yes */
1240 /*-------------------------------------------------------------------*/
1241 int 
1242 isiCodeEqual (iCode * left, iCode * right)
1243 {
1244   /* if the same pointer */
1245   if (left == right)
1246     return 1;
1247
1248   /* if either of them null */
1249   if (!left || !right)
1250     return 0;
1251
1252   /* if operand are the same */
1253   if (left->op == right->op)
1254     {
1255
1256       /* compare all the elements depending on type */
1257       if (left->op != IFX)
1258         {
1259           if (!isOperandEqual (IC_LEFT (left), IC_LEFT (right)))
1260             return 0;
1261           if (!isOperandEqual (IC_RIGHT (left), IC_RIGHT (right)))
1262             return 0;
1263
1264         }
1265       else
1266         {
1267           if (!isOperandEqual (IC_COND (left), IC_COND (right)))
1268             return 0;
1269           if (!isSymbolEqual (IC_TRUE (left), IC_TRUE (right)))
1270             return 0;
1271           if (!isSymbolEqual (IC_FALSE (left), IC_FALSE (right)))
1272             return 0;
1273         }
1274       
1275       return 1;
1276     }
1277   return 0;
1278 }
1279
1280 /*-----------------------------------------------------------------*/
1281 /* newiTempFromOp - create a temp Operand with same attributes     */
1282 /*-----------------------------------------------------------------*/
1283 operand *
1284 newiTempFromOp (operand * op)
1285 {
1286   operand *nop;
1287
1288   if (!op)
1289     return NULL;
1290
1291   if (!IS_ITEMP (op))
1292     return op;
1293
1294   nop = newiTempOperand (operandType (op), TRUE);
1295   nop->isaddr = op->isaddr;
1296   nop->isvolatile = op->isvolatile;
1297   nop->isGlobal = op->isGlobal;
1298   nop->isLiteral = op->isLiteral;
1299   nop->usesDefs = op->usesDefs;
1300   nop->isParm = op->isParm;
1301   return nop;
1302 }
1303
1304 /*-----------------------------------------------------------------*/
1305 /* operand from operand - creates an operand holder for the type   */
1306 /*-----------------------------------------------------------------*/
1307 operand *
1308 operandFromOperand (operand * op)
1309 {
1310   operand *nop;
1311
1312   if (!op)
1313     return NULL;
1314   nop = newOperand ();
1315   nop->type = op->type;
1316   nop->isaddr = op->isaddr;
1317   nop->key = op->key;
1318   nop->isvolatile = op->isvolatile;
1319   nop->isGlobal = op->isGlobal;
1320   nop->isLiteral = op->isLiteral;
1321   nop->usesDefs = op->usesDefs;
1322   nop->isParm = op->isParm;
1323
1324   switch (nop->type)
1325     {
1326     case SYMBOL:
1327       nop->operand.symOperand = op->operand.symOperand;
1328       break;
1329     case VALUE:
1330       nop->operand.valOperand = op->operand.valOperand;
1331       break;
1332     case TYPE:
1333       nop->operand.typeOperand = op->operand.typeOperand;
1334       break;
1335     }
1336
1337   return nop;
1338 }
1339
1340 /*-----------------------------------------------------------------*/
1341 /* opFromOpWithDU - makes a copy of the operand and DU chains      */
1342 /*-----------------------------------------------------------------*/
1343 operand *
1344 opFromOpWithDU (operand * op, bitVect * defs, bitVect * uses)
1345 {
1346   operand *nop = operandFromOperand (op);
1347
1348   if (nop->type == SYMBOL)
1349     {
1350       OP_SYMBOL (nop)->defs = bitVectCopy (defs);
1351       OP_SYMBOL (nop)->uses = bitVectCopy (uses);
1352     }
1353
1354   return nop;
1355 }
1356
1357 /*-----------------------------------------------------------------*/
1358 /* operandFromSymbol - creates an operand from a symbol            */
1359 /*-----------------------------------------------------------------*/
1360 operand *
1361 operandFromSymbol (symbol * sym)
1362 {
1363   operand *op;
1364   iCode *ic;
1365   int ok = 1;
1366   /* if the symbol's type is a literal */
1367   /* then it is an enumerator type     */
1368   if (IS_LITERAL (sym->etype) && SPEC_ENUM (sym->etype))
1369     return operandFromValue (valFromType (sym->etype));
1370
1371   if (!sym->key)
1372     sym->key = ++operandKey;
1373
1374   /* if this an implicit variable, means struct/union */
1375   /* member so just return it                         */
1376   if (sym->implicit || IS_FUNC (sym->type))
1377     {
1378       op = newOperand ();
1379       op->type = SYMBOL;
1380       op->operand.symOperand = sym;
1381       op->key = sym->key;
1382       op->isvolatile = isOperandVolatile (op, TRUE);
1383       op->isGlobal = isOperandGlobal (op);
1384       return op;
1385     }
1386
1387   /* under the following conditions create a
1388      register equivalent for a local symbol */
1389   if (sym->level && sym->etype && SPEC_OCLS (sym->etype) &&
1390       (IN_FARSPACE (SPEC_OCLS (sym->etype)) &&
1391       (!(options.model == MODEL_FLAT24)) ) &&
1392       options.stackAuto == 0)
1393     ok = 0;
1394
1395   if (!IS_AGGREGATE (sym->type) &&      /* not an aggregate */
1396       !IS_FUNC (sym->type) &&   /* not a function   */
1397       !sym->_isparm &&          /* not a parameter  */
1398       sym->level &&             /* is a local variable */
1399       !sym->addrtaken &&        /* whose address has not been taken */
1400       !sym->reqv &&             /* does not already have a reg equivalence */
1401       !IS_VOLATILE (sym->etype) &&      /* not declared as volatile */
1402       !IS_STATIC (sym->etype) &&        /* and not declared static  */
1403       !sym->islbl &&            /* not a label */
1404       ok &&                     /* farspace check */
1405       !IS_BITVAR (sym->etype)   /* not a bit variable */
1406     )
1407     {
1408
1409       /* we will use it after all optimizations
1410          and before liveRange calculation */
1411       sym->reqv = newiTempOperand (sym->type, 0);
1412       sym->reqv->key = sym->key;
1413       OP_SYMBOL (sym->reqv)->key = sym->key;
1414       OP_SYMBOL (sym->reqv)->isreqv = 1;
1415       OP_SYMBOL (sym->reqv)->islocal = 1;
1416       OP_SYMBOL (sym->reqv)->onStack = sym->onStack;
1417       SPIL_LOC (sym->reqv) = sym;
1418     }
1419
1420   if (!IS_AGGREGATE (sym->type))
1421     {
1422       op = newOperand ();
1423       op->type = SYMBOL;
1424       op->operand.symOperand = sym;
1425       op->isaddr = 1;
1426       op->key = sym->key;
1427       op->isvolatile = isOperandVolatile (op, TRUE);
1428       op->isGlobal = isOperandGlobal (op);
1429       op->isPtr = IS_PTR (operandType (op));
1430       op->isParm = sym->_isparm;
1431       return op;
1432     }
1433
1434   /* create :-                     */
1435   /*    itemp = &[_symbol]         */
1436
1437   ic = newiCode (ADDRESS_OF, newOperand (), NULL);
1438   IC_LEFT (ic)->type = SYMBOL;
1439   IC_LEFT (ic)->operand.symOperand = sym;
1440   IC_LEFT (ic)->key = sym->key;
1441   (IC_LEFT (ic))->isvolatile = isOperandVolatile (IC_LEFT (ic), TRUE);
1442   (IC_LEFT (ic))->isGlobal = isOperandGlobal (IC_LEFT (ic));
1443   IC_LEFT (ic)->isPtr = IS_PTR (operandType (IC_LEFT (ic)));
1444
1445   /* create result */
1446   IC_RESULT (ic) = newiTempOperand (sym->type, 0);
1447   if (IS_ARRAY (sym->type))
1448     {
1449       IC_RESULT (ic) = geniCodeArray2Ptr (IC_RESULT (ic));
1450       IC_RESULT (ic)->isaddr = 0;
1451     }
1452   else
1453     IC_RESULT (ic)->isaddr = (!IS_AGGREGATE (sym->type));
1454
1455   ADDTOCHAIN (ic);
1456
1457   return IC_RESULT (ic);
1458 }
1459
1460 /*-----------------------------------------------------------------*/
1461 /* operandFromValue - creates an operand from value                */
1462 /*-----------------------------------------------------------------*/
1463 operand *
1464 operandFromValue (value * val)
1465 {
1466   operand *op;
1467
1468   /* if this is a symbol then do the symbol thing */
1469   if (val->sym)
1470     return operandFromSymbol (val->sym);
1471
1472   /* this is not a symbol */
1473   op = newOperand ();
1474   op->type = VALUE;
1475   op->operand.valOperand = val;
1476   op->isLiteral = isOperandLiteral (op);
1477   return op;
1478 }
1479
1480 /*-----------------------------------------------------------------*/
1481 /* operandFromLink - operand from typeChain                        */
1482 /*-----------------------------------------------------------------*/
1483 operand *
1484 operandFromLink (sym_link * type)
1485 {
1486   operand *op;
1487
1488   /* operand from sym_link */
1489   if (!type)
1490     return NULL;
1491
1492   op = newOperand ();
1493   op->type = TYPE;
1494   op->operand.typeOperand = copyLinkChain (type);
1495   return op;
1496 }
1497
1498 /*-----------------------------------------------------------------*/
1499 /* operandFromLit - makes an operand from a literal value          */
1500 /*-----------------------------------------------------------------*/
1501 operand *
1502 operandFromLit (double i)
1503 {
1504   return operandFromValue (valueFromLit (i));
1505 }
1506
1507 /*-----------------------------------------------------------------*/
1508 /* operandFromAst - creates an operand from an ast                 */
1509 /*-----------------------------------------------------------------*/
1510 operand *
1511 operandFromAst (ast * tree,int lvl)
1512 {
1513
1514   if (!tree)
1515     return NULL;
1516
1517   /* depending on type do */
1518   switch (tree->type)
1519     {
1520     case EX_OP:
1521       return ast2iCode (tree,lvl+1);
1522       break;
1523
1524     case EX_VALUE:
1525       return operandFromValue (tree->opval.val);
1526       break;
1527
1528     case EX_LINK:
1529       return operandFromLink (tree->opval.lnk);
1530       break;
1531
1532     default:
1533       assert (0);
1534     }
1535   
1536   /*  Just to keep the compiler happy */
1537   return (operand *) 0;
1538 }
1539
1540 /*-----------------------------------------------------------------*/
1541 /* setOperandType - sets the operand's type to the given type      */
1542 /*-----------------------------------------------------------------*/
1543 void 
1544 setOperandType (operand * op, sym_link * type)
1545 {
1546   /* depending on the type of operand */
1547   switch (op->type)
1548     {
1549
1550     case VALUE:
1551       op->operand.valOperand->etype =
1552         getSpec (op->operand.valOperand->type =
1553                  copyLinkChain (type));
1554       return;
1555
1556     case SYMBOL:
1557       if (op->operand.symOperand->isitmp)
1558         op->operand.symOperand->etype =
1559           getSpec (op->operand.symOperand->type =
1560                    copyLinkChain (type));
1561       else
1562         werror (E_INTERNAL_ERROR, __FILE__, __LINE__,
1563                 "attempt to modify type of source");
1564       return;
1565
1566     case TYPE:
1567       op->operand.typeOperand = copyLinkChain (type);
1568       return;
1569     }
1570
1571 }
1572 /*-----------------------------------------------------------------*/
1573 /* Get size in byte of ptr need to access an array                 */
1574 /*-----------------------------------------------------------------*/
1575 int
1576 getArraySizePtr (operand * op)
1577 {
1578   sym_link *ltype = operandType(op);
1579
1580   if(IS_PTR(ltype))
1581     {
1582       int size = getSize(ltype);
1583       return(IS_GENPTR(ltype)?(size-1):size);
1584     }
1585
1586   if(IS_ARRAY(ltype))
1587     {
1588       sym_link *letype = getSpec(ltype);
1589       switch (PTR_TYPE (SPEC_OCLS (letype)))
1590         {
1591         case IPOINTER:
1592         case PPOINTER:
1593         case POINTER:
1594           return (PTRSIZE);
1595         case EEPPOINTER:
1596         case FPOINTER:
1597         case CPOINTER:
1598         case FUNCTION:
1599           return (FPTRSIZE);
1600         case GPOINTER:
1601           return (GPTRSIZE-1);
1602
1603         default:
1604           return (FPTRSIZE);
1605         }
1606     }
1607   return (FPTRSIZE);
1608 }
1609
1610 /*-----------------------------------------------------------------*/
1611 /* perform "usual unary conversions"                               */
1612 /*-----------------------------------------------------------------*/
1613 operand *
1614 usualUnaryConversions (operand * op)
1615 {
1616   if (IS_INTEGRAL (operandType (op)))
1617     {
1618       if (getSize (operandType (op)) < (unsigned int) INTSIZE)
1619         {
1620           /* Widen to int. */
1621           return geniCodeCast (INTTYPE, op, TRUE);
1622         }
1623     }
1624   return op;
1625 }
1626
1627 /*-----------------------------------------------------------------*/
1628 /* perform "usual binary conversions"                              */
1629 /*-----------------------------------------------------------------*/
1630 sym_link *
1631 usualBinaryConversions (operand ** op1, operand ** op2)
1632 {
1633   sym_link *ctype;
1634   sym_link *rtype = operandType (*op2);
1635   sym_link *ltype = operandType (*op1);
1636   
1637   ctype = computeType (ltype, rtype);
1638
1639   *op1 = geniCodeCast (ctype, *op1, TRUE);
1640   *op2 = geniCodeCast (ctype, *op2, TRUE);
1641   
1642   return ctype;
1643 }
1644
1645 /*-----------------------------------------------------------------*/
1646 /* geniCodeValueAtAddress - generate intermeditate code for value  */
1647 /*                          at address                             */
1648 /*-----------------------------------------------------------------*/
1649 operand *
1650 geniCodeRValue (operand * op, bool force)
1651 {
1652   iCode *ic;
1653   sym_link *type = operandType (op);
1654   sym_link *etype = getSpec (type);
1655
1656   /* if this is an array & already */
1657   /* an address then return this   */
1658   if (IS_AGGREGATE (type) ||
1659       (IS_PTR (type) && !force && !op->isaddr))
1660     return operandFromOperand (op);
1661
1662   /* if this is not an address then must be */
1663   /* rvalue already so return this one      */
1664   if (!op->isaddr)
1665     return op;
1666
1667   /* if this is not a temp symbol then */
1668   if (!IS_ITEMP (op) &&
1669       !force &&
1670       !IN_FARSPACE (SPEC_OCLS (etype)))
1671     {
1672       op = operandFromOperand (op);
1673       op->isaddr = 0;
1674       return op;
1675     }
1676
1677   if (IS_SPEC (type) &&
1678       IS_TRUE_SYMOP (op) &&
1679       (!IN_FARSPACE (SPEC_OCLS (etype)) ||
1680       (options.model == MODEL_FLAT24) ))
1681     {
1682       op = operandFromOperand (op);
1683       op->isaddr = 0;
1684       return op;
1685     }
1686
1687   ic = newiCode (GET_VALUE_AT_ADDRESS, op, NULL);
1688   if (IS_PTR (type) && op->isaddr && force)
1689     type = type->next;
1690
1691   type = copyLinkChain (type);
1692
1693   IC_RESULT (ic) = newiTempOperand (type, 1);
1694   IC_RESULT (ic)->isaddr = 0;
1695
1696 /*     ic->supportRtn = ((IS_GENPTR(type) | op->isGptr) & op->isaddr); */
1697
1698   ADDTOCHAIN (ic);
1699
1700   return IC_RESULT (ic);
1701 }
1702
1703 /*-----------------------------------------------------------------*/
1704 /* geniCodeCast - changes the value from one type to another       */
1705 /*-----------------------------------------------------------------*/
1706 operand *
1707 geniCodeCast (sym_link * type, operand * op, bool implicit)
1708 {
1709   iCode *ic;
1710   sym_link *optype;
1711   sym_link *opetype = getSpec (optype = operandType (op));
1712   sym_link *restype;
1713   int errors=0;
1714
1715   /* one of them has size zero then error */
1716   if (IS_VOID (optype))
1717     {
1718       werror (E_CAST_ZERO);
1719       return op;
1720     }
1721
1722   /* if the operand is already the desired type then do nothing */
1723   if (compareType (type, optype) == 1)
1724     return op;
1725
1726   /* if this is a literal then just change the type & return */
1727   if (IS_LITERAL (opetype) && op->type == VALUE && !IS_PTR (type) && !IS_PTR (optype))
1728     return operandFromValue (valCastLiteral (type,
1729                                              operandLitValue (op)));
1730
1731   /* if casting to/from pointers, do some checking */
1732   if (IS_PTR(type)) { // to a pointer
1733     if (!IS_PTR(optype) && !IS_FUNC(optype) && !IS_AGGREGATE(optype)) { // from a non pointer
1734       if (IS_INTEGRAL(optype)) { 
1735         // maybe this is NULL, than it's ok. 
1736         if (!(IS_LITERAL(optype) && (SPEC_CVAL(optype).v_ulong ==0))) {
1737           if (!TARGET_IS_Z80 && !TARGET_IS_GBZ80 && IS_GENPTR(type)) {
1738             // no way to set the storage
1739             if (IS_LITERAL(optype)) {
1740               werror(E_LITERAL_GENERIC);
1741               errors++;
1742             } else {
1743               werror(E_NONPTR2_GENPTR);
1744               errors++;
1745             }
1746           } else if (implicit) {
1747             werror(W_INTEGRAL2PTR_NOCAST);
1748             errors++;
1749           }
1750         }
1751       } else { 
1752         // shouldn't do that with float, array or structure unless to void
1753         if (!IS_VOID(getSpec(type)) && 
1754             !(IS_CODEPTR(type) && IS_FUNC(type->next) && IS_FUNC(optype))) {
1755           werror(E_INCOMPAT_TYPES);
1756           errors++;
1757         }
1758       }
1759     } else { // from a pointer to a pointer
1760       if (!TARGET_IS_Z80 && !TARGET_IS_GBZ80) {
1761         // if not a pointer to a function
1762         if (!(IS_CODEPTR(type) && IS_FUNC(type->next) && IS_FUNC(optype))) {
1763           if (implicit) { // if not to generic, they have to match 
1764             if ((!IS_GENPTR(type) && (DCL_TYPE(optype) != DCL_TYPE(type)))) {
1765               werror(E_INCOMPAT_PTYPES);
1766               errors++;
1767             }
1768           }
1769         }
1770       }
1771     }
1772   } else { // to a non pointer
1773     if (IS_PTR(optype)) { // from a pointer
1774       if (implicit) { // sneaky
1775         if (IS_INTEGRAL(type)) {
1776           werror(W_PTR2INTEGRAL_NOCAST);
1777           errors++;
1778         } else { // shouldn't do that with float, array or structure
1779           werror(E_INCOMPAT_TYPES);
1780           errors++;
1781         }
1782       }
1783     }
1784   }
1785   if (errors) {
1786     printFromToType (optype, type);
1787   }
1788
1789   /* if they are the same size create an assignment */
1790   if (getSize (type) == getSize (optype) &&
1791       !IS_BITFIELD (type) &&
1792       !IS_FLOAT (type) &&
1793       !IS_FLOAT (optype) &&
1794       ((IS_SPEC (type) && IS_SPEC (optype)) ||
1795        (!IS_SPEC (type) && !IS_SPEC (optype))))
1796     {
1797
1798       ic = newiCode ('=', NULL, op);
1799       IC_RESULT (ic) = newiTempOperand (type, 0);
1800       SPIL_LOC (IC_RESULT (ic)) =
1801         (IS_TRUE_SYMOP (op) ? OP_SYMBOL (op) : NULL);
1802       IC_RESULT (ic)->isaddr = 0;
1803     }
1804   else
1805     {
1806       ic = newiCode (CAST, operandFromLink (type),
1807                      geniCodeRValue (op, FALSE));
1808
1809       IC_RESULT (ic) = newiTempOperand (type, 0);
1810     }
1811
1812   /* preserve the storage class & output class */
1813   /* of the original variable                  */
1814   restype = getSpec (operandType (IC_RESULT (ic)));
1815   if (!IS_LITERAL(opetype))
1816       SPEC_SCLS (restype) = SPEC_SCLS (opetype);
1817   SPEC_OCLS (restype) = SPEC_OCLS (opetype);
1818
1819   ADDTOCHAIN (ic);
1820   return IC_RESULT (ic);
1821 }
1822
1823 /*-----------------------------------------------------------------*/
1824 /* geniCodeLabel - will create a Label                             */
1825 /*-----------------------------------------------------------------*/
1826 void 
1827 geniCodeLabel (symbol * label)
1828 {
1829   iCode *ic;
1830
1831   ic = newiCodeLabelGoto (LABEL, label);
1832   ADDTOCHAIN (ic);
1833 }
1834
1835 /*-----------------------------------------------------------------*/
1836 /* geniCodeGoto  - will create a Goto                              */
1837 /*-----------------------------------------------------------------*/
1838 void 
1839 geniCodeGoto (symbol * label)
1840 {
1841   iCode *ic;
1842
1843   ic = newiCodeLabelGoto (GOTO, label);
1844   ADDTOCHAIN (ic);
1845 }
1846
1847 /*-----------------------------------------------------------------*/
1848 /* geniCodeMultiply - gen intermediate code for multiplication     */
1849 /*-----------------------------------------------------------------*/
1850 operand *
1851 geniCodeMultiply (operand * left, operand * right,int resultIsInt)
1852 {
1853   iCode *ic;
1854   int p2 = 0;
1855   sym_link *resType;
1856   LRTYPE;
1857
1858   /* if they are both literal then we know the result */
1859   if (IS_LITERAL (letype) && IS_LITERAL (retype))
1860     return operandFromValue (valMult (left->operand.valOperand,
1861                                       right->operand.valOperand));
1862
1863   if (IS_LITERAL(retype)) {
1864     p2 = powof2 ((unsigned long) floatFromVal (right->operand.valOperand));
1865   }
1866
1867   resType = usualBinaryConversions (&left, &right);
1868 #if 1
1869   rtype = operandType (right);
1870   retype = getSpec (rtype);
1871   ltype = operandType (left);
1872   letype = getSpec (ltype);
1873 #endif
1874   if (resultIsInt)
1875     {
1876       SPEC_NOUN(getSpec(resType))=V_INT;
1877     }
1878
1879   /* if the right is a literal & power of 2 */
1880   /* then make it a left shift              */
1881   /* code generated for 1 byte * 1 byte literal = 2 bytes result is more 
1882      efficient in most cases than 2 bytes result = 2 bytes << literal 
1883      if port has 1 byte muldiv */
1884   if (p2 && !IS_FLOAT (letype) &&
1885       !((resultIsInt) && (getSize (resType) != getSize (ltype)) && 
1886         (port->support.muldiv == 1)))
1887     {
1888       if ((resultIsInt) && (getSize (resType) != getSize (ltype)))
1889         {
1890           /* LEFT_OP need same size for left and result, */
1891           left = geniCodeCast (resType, left, TRUE);
1892           ltype = operandType (left);
1893         }
1894       ic = newiCode (LEFT_OP, left, operandFromLit (p2)); /* left shift */
1895     }
1896   else
1897     {
1898       ic = newiCode ('*', left, right);         /* normal multiplication */
1899       /* if the size left or right > 1 then support routine */
1900       if (getSize (ltype) > 1 || getSize (rtype) > 1)
1901         ic->supportRtn = 1;
1902
1903     }
1904   IC_RESULT (ic) = newiTempOperand (resType, 1);
1905
1906   ADDTOCHAIN (ic);
1907   return IC_RESULT (ic);
1908 }
1909
1910 /*-----------------------------------------------------------------*/
1911 /* geniCodeDivision - gen intermediate code for division           */
1912 /*-----------------------------------------------------------------*/
1913 operand *
1914 geniCodeDivision (operand * left, operand * right)
1915 {
1916   iCode *ic;
1917   int p2 = 0;
1918   sym_link *resType;
1919   sym_link *rtype = operandType (right);
1920   sym_link *retype = getSpec (rtype);
1921   sym_link *ltype = operandType (left);
1922   sym_link *letype = getSpec (ltype);
1923
1924   resType = usualBinaryConversions (&left, &right);
1925
1926   /* if the right is a literal & power of 2 
1927      and left is unsigned then make it a    
1928      right shift */
1929   if (IS_LITERAL (retype) &&
1930       !IS_FLOAT (letype) &&
1931       SPEC_USIGN(letype) &&
1932       (p2 = powof2 ((unsigned long)
1933                     floatFromVal (right->operand.valOperand)))) {
1934     ic = newiCode (RIGHT_OP, left, operandFromLit (p2)); /* right shift */
1935   }
1936   else
1937     {
1938       ic = newiCode ('/', left, right);         /* normal division */
1939       /* if the size left or right > 1 then support routine */
1940       if (getSize (ltype) > 1 || getSize (rtype) > 1)
1941         ic->supportRtn = 1;
1942     }
1943   IC_RESULT (ic) = newiTempOperand (resType, 0);
1944
1945   ADDTOCHAIN (ic);
1946   return IC_RESULT (ic);
1947 }
1948 /*-----------------------------------------------------------------*/
1949 /* geniCodeModulus  - gen intermediate code for modulus            */
1950 /*-----------------------------------------------------------------*/
1951 operand *
1952 geniCodeModulus (operand * left, operand * right)
1953 {
1954   iCode *ic;
1955   sym_link *resType;
1956   LRTYPE;
1957
1958   /* if they are both literal then we know the result */
1959   if (IS_LITERAL (letype) && IS_LITERAL (retype))
1960     return operandFromValue (valMod (left->operand.valOperand,
1961                                      right->operand.valOperand));
1962
1963   resType = usualBinaryConversions (&left, &right);
1964
1965   /* now they are the same size */
1966   ic = newiCode ('%', left, right);
1967
1968   /* if the size left or right > 1 then support routine */
1969   if (getSize (ltype) > 1 || getSize (rtype) > 1)
1970     ic->supportRtn = 1;
1971   IC_RESULT (ic) = newiTempOperand (resType, 0);
1972
1973   ADDTOCHAIN (ic);
1974   return IC_RESULT (ic);
1975 }
1976
1977 /*-----------------------------------------------------------------*/
1978 /* geniCodePtrPtrSubtract - subtracts pointer from pointer         */
1979 /*-----------------------------------------------------------------*/
1980 operand *
1981 geniCodePtrPtrSubtract (operand * left, operand * right)
1982 {
1983   iCode *ic;
1984   operand *result;
1985   LRTYPE;
1986
1987   /* if they are both literals then */
1988   if (IS_LITERAL (letype) && IS_LITERAL (retype))
1989     {
1990       result = operandFromValue (valMinus (left->operand.valOperand,
1991                                            right->operand.valOperand));
1992       goto subtractExit;
1993     }
1994
1995   ic = newiCode ('-', left, right);
1996
1997   IC_RESULT (ic) = result = newiTempOperand (newIntLink (), 1);
1998   ADDTOCHAIN (ic);
1999
2000 subtractExit:
2001   if (IS_VOID(ltype->next) || IS_VOID(rtype->next)) {
2002     return result;
2003   }
2004
2005   // should we really do this? is this ANSI?
2006   return geniCodeDivision (result,
2007                            operandFromLit (getSize (ltype->next)));
2008 }
2009
2010 /*-----------------------------------------------------------------*/
2011 /* geniCodeSubtract - generates code for subtraction               */
2012 /*-----------------------------------------------------------------*/
2013 operand *
2014 geniCodeSubtract (operand * left, operand * right)
2015 {
2016   iCode *ic;
2017   int isarray = 0;
2018   sym_link *resType;
2019   LRTYPE;
2020
2021   /* if they both pointers then */
2022   if ((IS_PTR (ltype) || IS_ARRAY (ltype)) &&
2023       (IS_PTR (rtype) || IS_ARRAY (rtype)))
2024     return geniCodePtrPtrSubtract (left, right);
2025
2026   /* if they are both literal then we know the result */
2027   if (IS_LITERAL (letype) && IS_LITERAL (retype)
2028       && left->isLiteral && right->isLiteral)
2029     return operandFromValue (valMinus (left->operand.valOperand,
2030                                        right->operand.valOperand));
2031
2032   /* if left is an array or pointer */
2033   if (IS_PTR (ltype) || IS_ARRAY (ltype))
2034     {
2035       isarray = left->isaddr;
2036       right = geniCodeMultiply (right,
2037                                 operandFromLit (getSize (ltype->next)), (getArraySizePtr(left) >= INTSIZE));
2038       resType = copyLinkChain (IS_ARRAY (ltype) ? ltype->next : ltype);
2039     }
2040   else
2041     {                           /* make them the same size */
2042       resType = usualBinaryConversions (&left, &right);
2043     }
2044
2045   ic = newiCode ('-', left, right);
2046
2047   IC_RESULT (ic) = newiTempOperand (resType, 1);
2048   IC_RESULT (ic)->isaddr = (isarray ? 1 : 0);
2049
2050   /* if left or right is a float */
2051   if (IS_FLOAT (ltype) || IS_FLOAT (rtype))
2052     ic->supportRtn = 1;
2053
2054   ADDTOCHAIN (ic);
2055   return IC_RESULT (ic);
2056 }
2057
2058 /*-----------------------------------------------------------------*/
2059 /* geniCodeAdd - generates iCode for addition                      */
2060 /*-----------------------------------------------------------------*/
2061 operand *
2062 geniCodeAdd (operand * left, operand * right, int lvl)
2063 {
2064   iCode *ic;
2065   sym_link *resType;
2066   operand *size;
2067   int isarray = 0;
2068   LRTYPE;
2069
2070   /* if the right side is LITERAL zero */
2071   /* return the left side              */
2072   if (IS_LITERAL (retype) && right->isLiteral && !floatFromVal (valFromType (retype)))
2073     return left;
2074
2075   /* if left is literal zero return right */
2076   if (IS_LITERAL (letype) && left->isLiteral && !floatFromVal (valFromType (letype)))
2077     return right;
2078
2079   /* if left is a pointer then size */
2080   if (IS_PTR (ltype) || IS_ARRAY(ltype))
2081     {
2082       isarray = left->isaddr;
2083       // there is no need to multiply with 1
2084       if (getSize(ltype->next)!=1) {
2085         size  = operandFromLit (getSize (ltype->next));
2086         right = geniCodeMultiply (right, size, (getArraySizePtr(left) >= INTSIZE));
2087       }
2088       resType = copyLinkChain (ltype);
2089     }
2090   else
2091     { // make them the same size
2092       resType = usualBinaryConversions (&left, &right);
2093     }
2094
2095   /* if they are both literals then we know */
2096   if (IS_LITERAL (letype) && IS_LITERAL (retype)
2097       && left->isLiteral && right->isLiteral)
2098     return operandFromValue (valPlus (valFromType (letype),
2099                                       valFromType (retype)));
2100
2101   ic = newiCode ('+', left, right);
2102
2103   IC_RESULT (ic) = newiTempOperand (resType, 1);
2104   IC_RESULT (ic)->isaddr = (isarray ? 1 : 0);
2105
2106   /* if left or right is a float then support
2107      routine */
2108   if (IS_FLOAT (ltype) || IS_FLOAT (rtype))
2109     ic->supportRtn = 1;
2110
2111   ADDTOCHAIN (ic);
2112
2113   return IC_RESULT (ic);
2114
2115 }
2116
2117 /*-----------------------------------------------------------------*/
2118 /* aggrToPtr - changes an aggregate to pointer to an aggregate     */
2119 /*-----------------------------------------------------------------*/
2120 sym_link *
2121 aggrToPtr (sym_link * type, bool force)
2122 {
2123   sym_link *etype;
2124   sym_link *ptype;
2125
2126
2127   if (IS_PTR (type) && !force)
2128     return type;
2129
2130   etype = getSpec (type);
2131   ptype = newLink (DECLARATOR);
2132
2133   ptype->next = type;
2134
2135   /* if the output class is code */
2136   if ((DCL_TYPE (ptype) = PTR_TYPE (SPEC_OCLS (etype))) == CPOINTER)
2137     DCL_PTR_CONST (ptype) = port->mem.code_ro;
2138
2139   /* if the variable was declared a constant */
2140   /* then the pointer points to a constant */
2141   if (IS_CONSTANT (etype))
2142     DCL_PTR_CONST (ptype) = 1;
2143
2144   /* the variable was volatile then pointer to volatile */
2145   if (IS_VOLATILE (etype))
2146     DCL_PTR_VOLATILE (ptype) = 1;
2147
2148   return ptype;
2149 }
2150
2151 /*-----------------------------------------------------------------*/
2152 /* geniCodeArray2Ptr - array to pointer                            */
2153 /*-----------------------------------------------------------------*/
2154 operand *
2155 geniCodeArray2Ptr (operand * op)
2156 {
2157   sym_link *optype = operandType (op);
2158   sym_link *opetype = getSpec (optype);
2159
2160   /* set the pointer depending on the storage class */
2161   if ((DCL_TYPE (optype) = PTR_TYPE (SPEC_OCLS (opetype))) == CPOINTER)
2162     DCL_PTR_CONST (optype) = port->mem.code_ro;
2163
2164   /* if the variable was declared a constant */
2165   /* then the pointer points to a constant */
2166   if (IS_CONSTANT (opetype))
2167     DCL_PTR_CONST (optype) = 1;
2168
2169   /* the variable was volatile then pointer to volatile */
2170   if (IS_VOLATILE (opetype))
2171     DCL_PTR_VOLATILE (optype) = 1;
2172
2173   op->isaddr = 0;
2174   return op;
2175 }
2176
2177
2178 /*-----------------------------------------------------------------*/
2179 /* geniCodeArray - array access                                    */
2180 /*-----------------------------------------------------------------*/
2181 operand *
2182 geniCodeArray (operand * left, operand * right,int lvl)
2183 {
2184   iCode *ic;
2185   sym_link *ltype = operandType (left);
2186
2187   if (IS_PTR (ltype))
2188     {
2189       if (IS_PTR (ltype->next) && left->isaddr)
2190         {
2191           left = geniCodeRValue (left, FALSE);
2192         }
2193       return geniCodeDerefPtr (geniCodeAdd (left, right, lvl), lvl);
2194     }
2195
2196   right = geniCodeMultiply (right,
2197                             operandFromLit (getSize (ltype->next)), (getArraySizePtr(left) >= INTSIZE));
2198
2199   /* we can check for limits here */
2200   if (isOperandLiteral (right) &&
2201       IS_ARRAY (ltype) &&
2202       DCL_ELEM (ltype) &&
2203       (operandLitValue (right) / getSize (ltype->next)) >= DCL_ELEM (ltype))
2204     {
2205       werror (E_ARRAY_BOUND);
2206       right = operandFromLit (0);
2207     }
2208
2209   ic = newiCode ('+', left, right);
2210
2211   IC_RESULT (ic) = newiTempOperand (((IS_PTR (ltype) &&
2212                                       !IS_AGGREGATE (ltype->next) &&
2213                                       !IS_PTR (ltype->next))
2214                                      ? ltype : ltype->next), 0);
2215
2216   IC_RESULT (ic)->isaddr = (!IS_AGGREGATE (ltype->next));
2217   ADDTOCHAIN (ic);
2218   return IC_RESULT (ic);
2219 }
2220
2221 /*-----------------------------------------------------------------*/
2222 /* geniCodeStruct - generates intermediate code for structres      */
2223 /*-----------------------------------------------------------------*/
2224 operand *
2225 geniCodeStruct (operand * left, operand * right, bool islval)
2226 {
2227   iCode *ic;
2228   sym_link *type = operandType (left);
2229   sym_link *etype = getSpec (type);
2230   sym_link *retype;
2231   symbol *element = getStructElement (SPEC_STRUCT (etype),
2232                                       right->operand.symOperand);
2233
2234   wassert(IS_SYMOP(right));
2235     
2236   /* add the offset */
2237   ic = newiCode ('+', left, operandFromLit (element->offset));
2238
2239   IC_RESULT (ic) = newiTempOperand (element->type, 0);
2240
2241   /* preserve the storage & output class of the struct */
2242   /* as well as the volatile attribute */
2243   retype = getSpec (operandType (IC_RESULT (ic)));
2244   SPEC_SCLS (retype) = SPEC_SCLS (etype);
2245   SPEC_OCLS (retype) = SPEC_OCLS (etype);
2246   SPEC_VOLATILE (retype) |= SPEC_VOLATILE (etype);
2247
2248   if (IS_PTR (element->type))
2249     setOperandType (IC_RESULT (ic), aggrToPtr (operandType (IC_RESULT (ic)), TRUE));
2250
2251   IC_RESULT (ic)->isaddr = (!IS_AGGREGATE (element->type));
2252
2253
2254   ADDTOCHAIN (ic);
2255   return (islval ? IC_RESULT (ic) : geniCodeRValue (IC_RESULT (ic), TRUE));
2256 }
2257
2258 /*-----------------------------------------------------------------*/
2259 /* geniCodePostInc - generate int code for Post increment          */
2260 /*-----------------------------------------------------------------*/
2261 operand *
2262 geniCodePostInc (operand * op)
2263 {
2264   iCode *ic;
2265   operand *rOp;
2266   sym_link *optype = operandType (op);
2267   operand *result;
2268   operand *rv = (IS_ITEMP (op) ?
2269                  geniCodeRValue (op, (IS_PTR (optype) ? TRUE : FALSE)) :
2270                  op);
2271   sym_link *rvtype = operandType (rv);
2272   int size = 0;
2273
2274   /* if this is not an address we have trouble */
2275   if (!op->isaddr)
2276     {
2277       werror (E_LVALUE_REQUIRED, "++");
2278       return op;
2279     }
2280
2281   rOp = newiTempOperand (rvtype, 0);
2282   OP_SYMBOL(rOp)->noSpilLoc = 1;
2283
2284   if (IS_ITEMP (rv))
2285     OP_SYMBOL(rv)->noSpilLoc = 1;
2286
2287   geniCodeAssign (rOp, rv, 0);
2288
2289   size = (IS_PTR (rvtype) ? getSize (rvtype->next) : 1);
2290   if (IS_FLOAT (rvtype))
2291     ic = newiCode ('+', rv, operandFromValue (constFloatVal ("1.0")));
2292   else
2293     ic = newiCode ('+', rv, operandFromLit (size));
2294
2295   IC_RESULT (ic) = result = newiTempOperand (rvtype, 0);
2296   ADDTOCHAIN (ic);
2297
2298   geniCodeAssign (op, result, 0);
2299
2300   return rOp;
2301
2302 }
2303
2304 /*-----------------------------------------------------------------*/
2305 /* geniCodePreInc - generate code for preIncrement                 */
2306 /*-----------------------------------------------------------------*/
2307 operand *
2308 geniCodePreInc (operand * op)
2309 {
2310   iCode *ic;
2311   sym_link *optype = operandType (op);
2312   operand *rop = (IS_ITEMP (op) ?
2313                   geniCodeRValue (op, (IS_PTR (optype) ? TRUE : FALSE)) :
2314                   op);
2315   sym_link *roptype = operandType (rop);
2316   operand *result;
2317   int size = 0;
2318
2319   if (!op->isaddr)
2320     {
2321       werror (E_LVALUE_REQUIRED, "++");
2322       return op;
2323     }
2324
2325
2326   size = (IS_PTR (roptype) ? getSize (roptype->next) : 1);
2327   if (IS_FLOAT (roptype))
2328     ic = newiCode ('+', rop, operandFromValue (constFloatVal ("1.0")));
2329   else
2330     ic = newiCode ('+', rop, operandFromLit (size));
2331   IC_RESULT (ic) = result = newiTempOperand (roptype, 0);
2332   ADDTOCHAIN (ic);
2333
2334
2335   return geniCodeAssign (op, result, 0);
2336 }
2337
2338 /*-----------------------------------------------------------------*/
2339 /* geniCodePostDec - generates code for Post decrement             */
2340 /*-----------------------------------------------------------------*/
2341 operand *
2342 geniCodePostDec (operand * op)
2343 {
2344   iCode *ic;
2345   operand *rOp;
2346   sym_link *optype = operandType (op);
2347   operand *result;
2348   operand *rv = (IS_ITEMP (op) ?
2349                  geniCodeRValue (op, (IS_PTR (optype) ? TRUE : FALSE)) :
2350                  op);
2351   sym_link *rvtype = operandType (rv);
2352   int size = 0;
2353
2354   /* if this is not an address we have trouble */
2355   if (!op->isaddr)
2356     {
2357       werror (E_LVALUE_REQUIRED, "--");
2358       return op;
2359     }
2360
2361   rOp = newiTempOperand (rvtype, 0);
2362   OP_SYMBOL(rOp)->noSpilLoc = 1;
2363
2364   if (IS_ITEMP (rv))
2365     OP_SYMBOL(rv)->noSpilLoc = 1;
2366
2367   geniCodeAssign (rOp, rv, 0);
2368
2369   size = (IS_PTR (rvtype) ? getSize (rvtype->next) : 1);
2370   if (IS_FLOAT (rvtype))
2371     ic = newiCode ('-', rv, operandFromValue (constFloatVal ("1.0")));
2372   else
2373     ic = newiCode ('-', rv, operandFromLit (size));
2374
2375   IC_RESULT (ic) = result = newiTempOperand (rvtype, 0);
2376   ADDTOCHAIN (ic);
2377
2378   geniCodeAssign (op, result, 0);
2379
2380   return rOp;
2381
2382 }
2383
2384 /*-----------------------------------------------------------------*/
2385 /* geniCodePreDec - generate code for pre  decrement               */
2386 /*-----------------------------------------------------------------*/
2387 operand *
2388 geniCodePreDec (operand * op)
2389 {
2390   iCode *ic;
2391   sym_link *optype = operandType (op);
2392   operand *rop = (IS_ITEMP (op) ?
2393                   geniCodeRValue (op, (IS_PTR (optype) ? TRUE : FALSE)) :
2394                   op);
2395   sym_link *roptype = operandType (rop);
2396   operand *result;
2397   int size = 0;
2398
2399   if (!op->isaddr)
2400     {
2401       werror (E_LVALUE_REQUIRED, "--");
2402       return op;
2403     }
2404
2405
2406   size = (IS_PTR (roptype) ? getSize (roptype->next) : 1);
2407   if (IS_FLOAT (roptype))
2408     ic = newiCode ('-', rop, operandFromValue (constFloatVal ("1.0")));
2409   else
2410     ic = newiCode ('-', rop, operandFromLit (size));
2411   IC_RESULT (ic) = result = newiTempOperand (roptype, 0);
2412   ADDTOCHAIN (ic);
2413
2414
2415   return geniCodeAssign (op, result, 0);
2416 }
2417
2418
2419 /*-----------------------------------------------------------------*/
2420 /* geniCodeBitwise - gen int code for bitWise  operators           */
2421 /*-----------------------------------------------------------------*/
2422 operand *
2423 geniCodeBitwise (operand * left, operand * right,
2424                  int oper, sym_link * resType)
2425 {
2426   iCode *ic;
2427
2428   left = geniCodeCast (resType, left, TRUE);
2429   right = geniCodeCast (resType, right, TRUE);
2430
2431   ic = newiCode (oper, left, right);
2432   IC_RESULT (ic) = newiTempOperand (resType, 0);
2433
2434   ADDTOCHAIN (ic);
2435   return IC_RESULT (ic);
2436 }
2437
2438 /*-----------------------------------------------------------------*/
2439 /* geniCodeAddressOf - gens icode for '&' address of operator      */
2440 /*-----------------------------------------------------------------*/
2441 operand *
2442 geniCodeAddressOf (operand * op)
2443 {
2444   iCode *ic;
2445   sym_link *p;
2446   sym_link *optype = operandType (op);
2447   sym_link *opetype = getSpec (optype);
2448
2449   /* lvalue check already done in decorateType */
2450   /* this must be a lvalue */
2451 /*     if (!op->isaddr && !IS_AGGREGATE(optype)) { */
2452 /*  werror (E_LVALUE_REQUIRED,"&"); */
2453 /*  return op; */
2454 /*     } */
2455
2456   p = newLink (DECLARATOR);
2457
2458   /* set the pointer depending on the storage class */
2459   if ((DCL_TYPE (p) = PTR_TYPE (SPEC_OCLS (opetype))) == CPOINTER)
2460     DCL_PTR_CONST (p) = port->mem.code_ro;
2461
2462   /* make sure we preserve the const & volatile */
2463   if (IS_CONSTANT (opetype))
2464     DCL_PTR_CONST (p) = 1;
2465
2466   if (IS_VOLATILE (opetype))
2467     DCL_PTR_VOLATILE (p) = 1;
2468
2469   p->next = copyLinkChain (optype);
2470
2471   /* if already a temp */
2472   if (IS_ITEMP (op))
2473     {
2474       setOperandType (op, p);
2475       op->isaddr = 0;
2476       return op;
2477     }
2478
2479   /* other wise make this of the type coming in */
2480   ic = newiCode (ADDRESS_OF, op, NULL);
2481   IC_RESULT (ic) = newiTempOperand (p, 1);
2482   IC_RESULT (ic)->isaddr = 0;
2483   ADDTOCHAIN (ic);
2484   return IC_RESULT (ic);
2485 }
2486 /*-----------------------------------------------------------------*/
2487 /* setOClass - sets the output class depending on the pointer type */
2488 /*-----------------------------------------------------------------*/
2489 void 
2490 setOClass (sym_link * ptr, sym_link * spec)
2491 {
2492   switch (DCL_TYPE (ptr))
2493     {
2494     case POINTER:
2495       SPEC_OCLS (spec) = data;
2496       break;
2497
2498     case GPOINTER:
2499       SPEC_OCLS (spec) = generic;
2500       break;
2501
2502     case FPOINTER:
2503       SPEC_OCLS (spec) = xdata;
2504       break;
2505
2506     case CPOINTER:
2507       SPEC_OCLS (spec) = code;
2508       break;
2509
2510     case IPOINTER:
2511       SPEC_OCLS (spec) = idata;
2512       break;
2513
2514     case PPOINTER:
2515       SPEC_OCLS (spec) = xstack;
2516       break;
2517
2518     case EEPPOINTER:
2519       SPEC_OCLS (spec) = eeprom;
2520       break;
2521
2522     default:
2523       break;
2524
2525     }
2526 }
2527
2528 /*-----------------------------------------------------------------*/
2529 /* geniCodeDerefPtr - dereference pointer with '*'                 */
2530 /*-----------------------------------------------------------------*/
2531 operand *
2532 geniCodeDerefPtr (operand * op,int lvl)
2533 {
2534   sym_link *rtype, *retype;
2535   sym_link *optype = operandType (op);
2536
2537   // if this is an array then array access
2538   if (IS_ARRAY (optype)) {
2539     // don't worry, this will be optimized out later
2540     return geniCodeArray (op, operandFromLit (0), lvl);
2541   }
2542
2543   // just in case someone screws up
2544   wassert (IS_PTR (optype));
2545
2546   if (IS_TRUE_SYMOP (op))
2547     {
2548       op->isaddr = 1;
2549       op = geniCodeRValue (op, TRUE);
2550     }
2551
2552   /* now get rid of the pointer part */
2553   if (isLvaluereq(lvl) && IS_ITEMP (op))
2554     {
2555       retype = getSpec (rtype = copyLinkChain (optype));
2556     }
2557   else
2558     {
2559       retype = getSpec (rtype = copyLinkChain (optype->next));
2560     }
2561
2562   /* outputclass needs 2b updated */
2563   setOClass (optype, retype);
2564
2565   op->isGptr = IS_GENPTR (optype);
2566
2567   /* if the pointer was declared as a constant */
2568   /* then we cannot allow assignment to the derefed */
2569   if (IS_PTR_CONST (optype))
2570     SPEC_CONST (retype) = 1;
2571
2572   op->isaddr = (IS_PTR (rtype) ||
2573                 IS_STRUCT (rtype) ||
2574                 IS_INT (rtype) ||
2575                 IS_CHAR (rtype) ||
2576                 IS_FLOAT (rtype));
2577
2578   if (!isLvaluereq(lvl))
2579     op = geniCodeRValue (op, TRUE);
2580
2581   setOperandType (op, rtype);
2582
2583   return op;
2584 }
2585
2586 /*-----------------------------------------------------------------*/
2587 /* geniCodeUnaryMinus - does a unary minus of the operand          */
2588 /*-----------------------------------------------------------------*/
2589 operand *
2590 geniCodeUnaryMinus (operand * op)
2591 {
2592   iCode *ic;
2593   sym_link *optype = operandType (op);
2594
2595   if (IS_LITERAL (optype))
2596     return operandFromLit (-floatFromVal (op->operand.valOperand));
2597
2598   ic = newiCode (UNARYMINUS, op, NULL);
2599   IC_RESULT (ic) = newiTempOperand (optype, 0);
2600   ADDTOCHAIN (ic);
2601   return IC_RESULT (ic);
2602 }
2603
2604 /*-----------------------------------------------------------------*/
2605 /* geniCodeLeftShift - gen i code for left shift                   */
2606 /*-----------------------------------------------------------------*/
2607 operand *
2608 geniCodeLeftShift (operand * left, operand * right)
2609 {
2610   iCode *ic;
2611
2612   ic = newiCode (LEFT_OP, left, right);
2613   IC_RESULT (ic) = newiTempOperand (operandType (left), 0);
2614   ADDTOCHAIN (ic);
2615   return IC_RESULT (ic);
2616 }
2617
2618 /*-----------------------------------------------------------------*/
2619 /* geniCodeRightShift - gen i code for right shift                 */
2620 /*-----------------------------------------------------------------*/
2621 operand *
2622 geniCodeRightShift (operand * left, operand * right)
2623 {
2624   iCode *ic;
2625
2626   ic = newiCode (RIGHT_OP, left, right);
2627   IC_RESULT (ic) = newiTempOperand (operandType (left), 0);
2628   ADDTOCHAIN (ic);
2629   return IC_RESULT (ic);
2630 }
2631
2632 /*-----------------------------------------------------------------*/
2633 /* geniCodeLogic- logic code                                       */
2634 /*-----------------------------------------------------------------*/
2635 operand *
2636 geniCodeLogic (operand * left, operand * right, int op)
2637 {
2638   iCode *ic;
2639   sym_link *ctype;
2640   sym_link *rtype = operandType (right);
2641   sym_link *ltype = operandType (left);
2642
2643   /* left is integral type and right is literal then
2644      check if the literal value is within bounds */
2645   if (IS_INTEGRAL (ltype) && IS_VALOP (right) && IS_LITERAL (rtype))
2646     {
2647       checkConstantRange(ltype, 
2648                          OP_VALUE(right), "compare operation", 1);
2649     }
2650
2651   ctype = usualBinaryConversions (&left, &right);
2652
2653   ic = newiCode (op, left, right);
2654   IC_RESULT (ic) = newiTempOperand (newCharLink (), 1);
2655
2656   /* if comparing float
2657      and not a '==' || '!=' || '&&' || '||' (these
2658      will be inlined */
2659   if (IS_FLOAT(ctype) &&
2660       op != EQ_OP &&
2661       op != NE_OP &&
2662       op != AND_OP &&
2663       op != OR_OP)
2664     ic->supportRtn = 1;
2665
2666   ADDTOCHAIN (ic);
2667   return IC_RESULT (ic);
2668 }
2669
2670 /*-----------------------------------------------------------------*/
2671 /* geniCodeUnary - for a a generic unary operation                 */
2672 /*-----------------------------------------------------------------*/
2673 operand *
2674 geniCodeUnary (operand * op, int oper)
2675 {
2676   iCode *ic = newiCode (oper, op, NULL);
2677
2678   IC_RESULT (ic) = newiTempOperand (operandType (op), 0);
2679   ADDTOCHAIN (ic);
2680   return IC_RESULT (ic);
2681 }
2682
2683 /*-----------------------------------------------------------------*/
2684 /* geniCodeConditional - geniCode for '?' ':' operation            */
2685 /*-----------------------------------------------------------------*/
2686 operand *
2687 geniCodeConditional (ast * tree,int lvl)
2688 {
2689   iCode *ic;
2690   symbol *falseLabel = newiTempLabel (NULL);
2691   symbol *exitLabel = newiTempLabel (NULL);
2692   operand *cond = ast2iCode (tree->left,lvl+1);
2693   operand *true, *false, *result;
2694
2695   ic = newiCodeCondition (geniCodeRValue (cond, FALSE),
2696                           NULL, falseLabel);
2697   ADDTOCHAIN (ic);
2698
2699   true = ast2iCode (tree->right->left,lvl+1);
2700
2701   /* move the value to a new Operand */
2702   result = newiTempOperand (tree->right->ftype, 0);
2703   geniCodeAssign (result, geniCodeRValue (true, FALSE), 0);
2704
2705   /* generate an unconditional goto */
2706   geniCodeGoto (exitLabel);
2707
2708   /* now for the right side */
2709   geniCodeLabel (falseLabel);
2710
2711   false = ast2iCode (tree->right->right,lvl+1);
2712   geniCodeAssign (result, geniCodeRValue (false, FALSE), 0);
2713
2714   /* create the exit label */
2715   geniCodeLabel (exitLabel);
2716
2717   return result;
2718 }
2719
2720 /*-----------------------------------------------------------------*/
2721 /* geniCodeAssign - generate code for assignment                   */
2722 /*-----------------------------------------------------------------*/
2723 operand *
2724 geniCodeAssign (operand * left, operand * right, int nosupdate)
2725 {
2726   iCode *ic;
2727   sym_link *ltype = operandType (left);
2728   sym_link *rtype = operandType (right);
2729
2730   if (!left->isaddr && !IS_ITEMP (left))
2731     {
2732       werror (E_LVALUE_REQUIRED, "assignment");
2733       return left;
2734     }
2735
2736   /* left is integral type and right is literal then
2737      check if the literal value is within bounds */
2738   if (IS_INTEGRAL (ltype) && right->type == VALUE && IS_LITERAL (rtype))
2739     {
2740       checkConstantRange(ltype, 
2741                          OP_VALUE(right), "= operation", 0);
2742     }
2743
2744   /* if the left & right type don't exactly match */
2745   /* if pointer set then make sure the check is
2746      done with the type & not the pointer */
2747   /* then cast rights type to left */
2748
2749   /* first check the type for pointer assignement */
2750   if (left->isaddr && IS_PTR (ltype) && IS_ITEMP (left) &&
2751       compareType (ltype, rtype) <= 0)
2752     {
2753       if (compareType (ltype->next, rtype) < 0)
2754         right = geniCodeCast (ltype->next, right, TRUE);
2755     }
2756   else if (compareType (ltype, rtype) < 0)
2757     right = geniCodeCast (ltype, right, TRUE);
2758
2759   /* if left is a true symbol & ! volatile
2760      create an assignment to temporary for
2761      the right & then assign this temporary
2762      to the symbol this is SSA . isn't it simple
2763      and folks have published mountains of paper on it */
2764   if (IS_TRUE_SYMOP (left) &&
2765       !isOperandVolatile (left, FALSE) &&
2766       isOperandGlobal (left))
2767     {
2768       symbol *sym = NULL;
2769
2770       if (IS_TRUE_SYMOP (right))
2771         sym = OP_SYMBOL (right);
2772       ic = newiCode ('=', NULL, right);
2773       IC_RESULT (ic) = right = newiTempOperand (ltype, 0);
2774       SPIL_LOC (right) = sym;
2775       ADDTOCHAIN (ic);
2776     }
2777
2778   ic = newiCode ('=', NULL, right);
2779   IC_RESULT (ic) = left;
2780   ADDTOCHAIN (ic);
2781
2782   /* if left isgptr flag is set then support
2783      routine will be required */
2784   if (left->isGptr)
2785     ic->supportRtn = 1;
2786
2787   ic->nosupdate = nosupdate;
2788   return left;
2789 }
2790
2791 /*-----------------------------------------------------------------*/
2792 /* geniCodeSEParms - generate code for side effecting fcalls       */
2793 /*-----------------------------------------------------------------*/
2794 static void 
2795 geniCodeSEParms (ast * parms,int lvl)
2796 {
2797   if (!parms)
2798     return;
2799
2800   if (parms->type == EX_OP && parms->opval.op == PARAM)
2801     {
2802       geniCodeSEParms (parms->left,lvl);
2803       geniCodeSEParms (parms->right,lvl);
2804       return;
2805     }
2806
2807   /* hack don't like this but too lazy to think of
2808      something better */
2809   if (IS_ADDRESS_OF_OP (parms))
2810     parms->left->lvalue = 1;
2811
2812   if (IS_CAST_OP (parms) &&
2813       IS_PTR (parms->ftype) &&
2814       IS_ADDRESS_OF_OP (parms->right))
2815     parms->right->left->lvalue = 1;
2816
2817   parms->opval.oprnd = 
2818     geniCodeRValue (ast2iCode (parms,lvl+1), FALSE);
2819                 
2820   parms->type = EX_OPERAND;
2821   AST_ARGREG(parms) = parms->etype ? SPEC_ARGREG(parms->etype) :
2822                 SPEC_ARGREG(parms->ftype);
2823 }
2824
2825 /*-----------------------------------------------------------------*/
2826 /* geniCodeParms - generates parameters                            */
2827 /*-----------------------------------------------------------------*/
2828 value *
2829 geniCodeParms (ast * parms, value *argVals, int *stack, 
2830                sym_link * fetype, symbol * func,int lvl)
2831 {
2832   iCode *ic;
2833   operand *pval;
2834
2835   if (!parms)
2836     return argVals;
2837
2838   if (argVals==NULL) {
2839     // first argument
2840     argVals=FUNC_ARGS(func->type);
2841   }
2842
2843   /* if this is a param node then do the left & right */
2844   if (parms->type == EX_OP && parms->opval.op == PARAM)
2845     {
2846       argVals=geniCodeParms (parms->left, argVals, stack, fetype, func,lvl);
2847       argVals=geniCodeParms (parms->right, argVals, stack, fetype, func,lvl);
2848       return argVals;
2849     }
2850
2851   /* get the parameter value */
2852   if (parms->type == EX_OPERAND)
2853     pval = parms->opval.oprnd;
2854   else
2855     {
2856       /* maybe this else should go away ?? */
2857       /* hack don't like this but too lazy to think of
2858          something better */
2859       if (IS_ADDRESS_OF_OP (parms))
2860         parms->left->lvalue = 1;
2861
2862       if (IS_CAST_OP (parms) &&
2863           IS_PTR (parms->ftype) &&
2864           IS_ADDRESS_OF_OP (parms->right))
2865         parms->right->left->lvalue = 1;
2866
2867       pval = geniCodeRValue (ast2iCode (parms,lvl+1), FALSE);
2868     }
2869
2870   /* if register parm then make it a send */
2871   if ((IS_REGPARM (parms->etype) && !IFFUNC_HASVARARGS(func->type)) ||
2872       IFFUNC_ISBUILTIN(func->type))
2873     {
2874       ic = newiCode (SEND, pval, NULL);
2875       ic->argreg = SPEC_ARGREG(parms->etype);
2876       ic->builtinSEND = FUNC_ISBUILTIN(func->type);
2877       ADDTOCHAIN (ic);
2878     }
2879   else
2880     {
2881       /* now decide whether to push or assign */
2882       if (!(options.stackAuto || IFFUNC_ISREENT (func->type)))
2883         {
2884
2885           /* assign */
2886           operand *top = operandFromSymbol (argVals->sym);
2887           /* clear useDef and other bitVectors */
2888           OP_USES(top)=OP_DEFS(top)=OP_SYMBOL(top)->clashes = NULL;
2889           geniCodeAssign (top, pval, 1);
2890         }
2891       else
2892         {
2893           sym_link *p = operandType (pval);
2894           /* push */
2895           ic = newiCode (IPUSH, pval, NULL);
2896           ic->parmPush = 1;
2897           /* update the stack adjustment */
2898           *stack += getSize (IS_AGGREGATE (p) ? aggrToPtr (p, FALSE) : p);
2899           ADDTOCHAIN (ic);
2900         }
2901     }
2902
2903   argVals=argVals->next;
2904   return argVals;
2905 }
2906
2907 /*-----------------------------------------------------------------*/
2908 /* geniCodeCall - generates temp code for calling                  */
2909 /*-----------------------------------------------------------------*/
2910 operand *
2911 geniCodeCall (operand * left, ast * parms,int lvl)
2912 {
2913   iCode *ic;
2914   operand *result;
2915   sym_link *type, *etype;
2916   int stack = 0;
2917
2918   if (!IS_FUNC(OP_SYMBOL(left)->type) && 
2919       !IS_CODEPTR(OP_SYMBOL(left)->type)) {
2920     werror (E_FUNCTION_EXPECTED);
2921     return NULL;
2922   }
2923
2924   /* take care of parameters with side-effecting
2925      function calls in them, this is required to take care
2926      of overlaying function parameters */
2927   geniCodeSEParms (parms,lvl);
2928
2929   /* first the parameters */
2930   geniCodeParms (parms, NULL, &stack, getSpec (operandType (left)), OP_SYMBOL (left),lvl);
2931
2932   /* now call : if symbol then pcall */
2933   if (IS_OP_POINTER (left) || IS_ITEMP(left)) {
2934     ic = newiCode (PCALL, left, NULL);
2935   } else {
2936     ic = newiCode (CALL, left, NULL);
2937   }
2938
2939   type = copyLinkChain (operandType (left)->next);
2940   etype = getSpec (type);
2941   SPEC_EXTR (etype) = 0;
2942   IC_RESULT (ic) = result = newiTempOperand (type, 1);
2943
2944   ADDTOCHAIN (ic);
2945
2946   /* stack adjustment after call */
2947   ic->parmBytes = stack;
2948
2949   return result;
2950 }
2951
2952 /*-----------------------------------------------------------------*/
2953 /* geniCodeReceive - generate intermediate code for "receive"      */
2954 /*-----------------------------------------------------------------*/
2955 static void 
2956 geniCodeReceive (value * args)
2957 {
2958   /* for all arguments that are passed in registers */
2959   while (args)
2960     {
2961       int first = 1;
2962       if (IS_REGPARM (args->etype))
2963         {
2964           operand *opr = operandFromValue (args);
2965           operand *opl;
2966           symbol *sym = OP_SYMBOL (opr);
2967           iCode *ic;
2968
2969           /* we will use it after all optimizations
2970              and before liveRange calculation */
2971           if (!sym->addrtaken && !IS_VOLATILE (sym->etype))
2972             {
2973
2974               if (IN_FARSPACE (SPEC_OCLS (sym->etype)) &&
2975                   options.stackAuto == 0 &&
2976                   (!(options.model == MODEL_FLAT24)) )
2977                 {
2978                 }
2979               else
2980                 {
2981                   opl = newiTempOperand (args->type, 0);
2982                   sym->reqv = opl;
2983                   sym->reqv->key = sym->key;
2984                   OP_SYMBOL (sym->reqv)->key = sym->key;
2985                   OP_SYMBOL (sym->reqv)->isreqv = 1;
2986                   OP_SYMBOL (sym->reqv)->islocal = 0;
2987                   SPIL_LOC (sym->reqv) = sym;
2988                 }
2989             }
2990
2991           ic = newiCode (RECEIVE, NULL, NULL);    
2992           ic->argreg = SPEC_ARGREG(args->etype);
2993           if (first) {
2994               currFunc->recvSize = getSize (sym->type);
2995               first = 0;
2996           }
2997           IC_RESULT (ic) = opr;
2998           ADDTOCHAIN (ic);
2999         }
3000
3001       args = args->next;
3002     }
3003 }
3004
3005 /*-----------------------------------------------------------------*/
3006 /* geniCodeFunctionBody - create the function body                 */
3007 /*-----------------------------------------------------------------*/
3008 void 
3009 geniCodeFunctionBody (ast * tree,int lvl)
3010 {
3011   iCode *ic;
3012   operand *func;
3013   sym_link *fetype;
3014   int savelineno;
3015
3016   /* reset the auto generation */
3017   /* numbers */
3018   iTempNum = 0;
3019   iTempLblNum = 0;
3020   operandKey = 0;
3021   iCodeKey = 0;
3022   func = ast2iCode (tree->left,lvl+1);
3023   fetype = getSpec (operandType (func));
3024
3025   savelineno = lineno;
3026   lineno = OP_SYMBOL (func)->lineDef;
3027   /* create an entry label */
3028   geniCodeLabel (entryLabel);
3029   lineno = savelineno;
3030
3031   /* create a proc icode */
3032   ic = newiCode (FUNCTION, func, NULL);
3033   lineno=ic->lineno = OP_SYMBOL (func)->lineDef;
3034
3035   ADDTOCHAIN (ic);
3036
3037   /* for all parameters that are passed
3038      on registers add a "receive" */
3039   geniCodeReceive (tree->values.args);
3040
3041   /* generate code for the body */
3042   ast2iCode (tree->right,lvl+1);
3043
3044   /* create a label for return */
3045   geniCodeLabel (returnLabel);
3046
3047   /* now generate the end proc */
3048   ic = newiCode (ENDFUNCTION, func, NULL);
3049   ADDTOCHAIN (ic);
3050   return;
3051 }
3052
3053 /*-----------------------------------------------------------------*/
3054 /* geniCodeReturn - gen icode for 'return' statement               */
3055 /*-----------------------------------------------------------------*/
3056 void 
3057 geniCodeReturn (operand * op)
3058 {
3059   iCode *ic;
3060
3061   /* if the operand is present force an rvalue */
3062   if (op)
3063     op = geniCodeRValue (op, FALSE);
3064
3065   ic = newiCode (RETURN, op, NULL);
3066   ADDTOCHAIN (ic);
3067 }
3068
3069 /*-----------------------------------------------------------------*/
3070 /* geniCodeIfx - generates code for extended if statement          */
3071 /*-----------------------------------------------------------------*/
3072 void 
3073 geniCodeIfx (ast * tree,int lvl)
3074 {
3075   iCode *ic;
3076   operand *condition = ast2iCode (tree->left,lvl+1);
3077   sym_link *cetype;
3078
3079   /* if condition is null then exit */
3080   if (!condition)
3081     goto exit;
3082   else
3083     condition = geniCodeRValue (condition, FALSE);
3084
3085   cetype = getSpec (operandType (condition));
3086   /* if the condition is a literal */
3087   if (IS_LITERAL (cetype))
3088     {
3089       if (floatFromVal (condition->operand.valOperand))
3090         {
3091           if (tree->trueLabel)
3092             geniCodeGoto (tree->trueLabel);
3093           else
3094             assert (0);
3095         }
3096       else
3097         {
3098           if (tree->falseLabel)
3099             geniCodeGoto (tree->falseLabel);
3100           else
3101             assert (0);
3102         }
3103       goto exit;
3104     }
3105
3106   if (tree->trueLabel)
3107     {
3108       ic = newiCodeCondition (condition,
3109                               tree->trueLabel,
3110                               NULL);
3111       ADDTOCHAIN (ic);
3112
3113       if (tree->falseLabel)
3114         geniCodeGoto (tree->falseLabel);
3115     }
3116   else
3117     {
3118       ic = newiCodeCondition (condition,
3119                               NULL,
3120                               tree->falseLabel);
3121       ADDTOCHAIN (ic);
3122     }
3123
3124 exit:
3125   ast2iCode (tree->right,lvl+1);
3126 }
3127
3128 /*-----------------------------------------------------------------*/
3129 /* geniCodeJumpTable - tries to create a jump table for switch     */
3130 /*-----------------------------------------------------------------*/
3131 int 
3132 geniCodeJumpTable (operand * cond, value * caseVals, ast * tree)
3133 {
3134   int min = 0, max = 0, t, cnt = 0;
3135   value *vch;
3136   iCode *ic;
3137   operand *boundary;
3138   symbol *falseLabel;
3139   set *labels = NULL;
3140
3141   if (!tree || !caseVals)
3142     return 0;
3143
3144   /* the criteria for creating a jump table is */
3145   /* all integer numbers between the maximum & minimum must */
3146   /* be present , the maximum value should not exceed 255 */
3147   min = max = (int) floatFromVal (vch = caseVals);
3148   SNPRINTF (buffer, sizeof(buffer), 
3149             "_case_%d_%d",
3150            tree->values.switchVals.swNum,
3151            min);
3152   addSet (&labels, newiTempLabel (buffer));
3153
3154   /* if there is only one case value then no need */
3155   if (!(vch = vch->next))
3156     return 0;
3157
3158   while (vch)
3159     {
3160       if (((t = (int) floatFromVal (vch)) - max) != 1)
3161         return 0;
3162       SNPRINTF (buffer, sizeof(buffer), 
3163                 "_case_%d_%d",
3164                tree->values.switchVals.swNum,
3165                t);
3166       addSet (&labels, newiTempLabel (buffer));
3167       max = t;
3168       cnt++;
3169       vch = vch->next;
3170     }
3171
3172   /* if the number of case statements <= 2 then */
3173   /* it is not economical to create the jump table */
3174   /* since two compares are needed for boundary conditions */
3175   if ((!optimize.noJTabBoundary && cnt <= 2) || max > (255 / 3))
3176     return 0;
3177
3178   if (tree->values.switchVals.swDefault)
3179     {
3180         SNPRINTF (buffer, sizeof(buffer), "_default_%d", tree->values.switchVals.swNum);
3181     }
3182   else
3183     {
3184         SNPRINTF (buffer, sizeof(buffer), "_swBrk_%d", tree->values.switchVals.swNum);
3185     }
3186     
3187
3188   falseLabel = newiTempLabel (buffer);
3189
3190   /* so we can create a jumptable */
3191   /* first we rule out the boundary conditions */
3192   /* if only optimization says so */
3193   if (!optimize.noJTabBoundary)
3194     {
3195       sym_link *cetype = getSpec (operandType (cond));
3196       /* no need to check the lower bound if
3197          the condition is unsigned & minimum value is zero */
3198       if (!(min == 0 && SPEC_USIGN (cetype)))
3199         {
3200           boundary = geniCodeLogic (cond, operandFromLit (min), '<');
3201           ic = newiCodeCondition (boundary, falseLabel, NULL);
3202           ADDTOCHAIN (ic);
3203         }
3204
3205       /* now for upper bounds */
3206       boundary = geniCodeLogic (cond, operandFromLit (max), '>');
3207       ic = newiCodeCondition (boundary, falseLabel, NULL);
3208       ADDTOCHAIN (ic);
3209     }
3210
3211   /* if the min is not zero then we no make it zero */
3212   if (min)
3213     {
3214       cond = geniCodeSubtract (cond, operandFromLit (min));
3215       setOperandType (cond, UCHARTYPE);
3216     }
3217
3218   /* now create the jumptable */
3219   ic = newiCode (JUMPTABLE, NULL, NULL);
3220   IC_JTCOND (ic) = cond;
3221   IC_JTLABELS (ic) = labels;
3222   ADDTOCHAIN (ic);
3223   return 1;
3224 }
3225
3226 /*-----------------------------------------------------------------*/
3227 /* geniCodeSwitch - changes a switch to a if statement             */
3228 /*-----------------------------------------------------------------*/
3229 void 
3230 geniCodeSwitch (ast * tree,int lvl)
3231 {
3232   iCode *ic;
3233   operand *cond = geniCodeRValue (ast2iCode (tree->left,lvl+1), FALSE);
3234   value *caseVals = tree->values.switchVals.swVals;
3235   symbol *trueLabel, *falseLabel;
3236
3237   /* if we can make this a jump table */
3238   if (geniCodeJumpTable (cond, caseVals, tree))
3239     goto jumpTable;             /* no need for the comparison */
3240
3241   /* for the cases defined do */
3242   while (caseVals)
3243     {
3244
3245       operand *compare = geniCodeLogic (cond,
3246                                         operandFromValue (caseVals),
3247                                         EQ_OP);
3248
3249       SNPRINTF (buffer, sizeof(buffer), "_case_%d_%d",
3250                tree->values.switchVals.swNum,
3251                (int) floatFromVal (caseVals));
3252       trueLabel = newiTempLabel (buffer);
3253
3254       ic = newiCodeCondition (compare, trueLabel, NULL);
3255       ADDTOCHAIN (ic);
3256       caseVals = caseVals->next;
3257     }
3258
3259
3260
3261   /* if default is present then goto break else break */
3262   if (tree->values.switchVals.swDefault)
3263     {
3264         SNPRINTF (buffer, sizeof(buffer), "_default_%d", tree->values.switchVals.swNum);
3265     }
3266   else
3267     {
3268         SNPRINTF (buffer, sizeof(buffer), "_swBrk_%d", tree->values.switchVals.swNum);
3269     }
3270
3271   falseLabel = newiTempLabel (buffer);
3272   geniCodeGoto (falseLabel);
3273
3274 jumpTable:
3275   ast2iCode (tree->right,lvl+1);
3276 }
3277
3278 /*-----------------------------------------------------------------*/
3279 /* geniCodeInline - intermediate code for inline assembler         */
3280 /*-----------------------------------------------------------------*/
3281 static void 
3282 geniCodeInline (ast * tree)
3283 {
3284   iCode *ic;
3285
3286   ic = newiCode (INLINEASM, NULL, NULL);
3287   IC_INLINE (ic) = tree->values.inlineasm;
3288   ADDTOCHAIN (ic);
3289 }
3290
3291 /*-----------------------------------------------------------------*/
3292 /* geniCodeArrayInit - intermediate code for array initializer     */
3293 /*-----------------------------------------------------------------*/
3294 static void 
3295 geniCodeArrayInit (ast * tree, operand *array)
3296 {
3297   iCode *ic;
3298
3299   if (!getenv("TRY_THE_NEW_INITIALIZER")) {
3300     ic = newiCode (ARRAYINIT, array, NULL);
3301     IC_ARRAYILIST (ic) = tree->values.constlist;
3302   } else {
3303     operand *left=newOperand(), *right=newOperand();
3304     left->type=right->type=SYMBOL;
3305     OP_SYMBOL(left)=AST_SYMBOL(tree->left);
3306     OP_SYMBOL(right)=AST_SYMBOL(tree->right);
3307     ic = newiCode (ARRAYINIT, left, right);
3308   }
3309   ADDTOCHAIN (ic);
3310 }
3311
3312 /*-----------------------------------------------------------------*/
3313 /* Stuff used in ast2iCode to modify geniCodeDerefPtr in some      */
3314 /* particular case. Ie : assigning or dereferencing array or ptr   */
3315 /*-----------------------------------------------------------------*/
3316 set * lvaluereqSet = NULL;
3317 typedef struct lvalItem
3318   {
3319     int req;
3320     int lvl;
3321   }
3322 lvalItem;
3323
3324 /*-----------------------------------------------------------------*/
3325 /* addLvaluereq - add a flag for lvalreq for current ast level     */
3326 /*-----------------------------------------------------------------*/
3327 void addLvaluereq(int lvl)
3328 {
3329   lvalItem * lpItem = (lvalItem *)Safe_alloc ( sizeof (lvalItem));
3330   lpItem->req=1;
3331   lpItem->lvl=lvl;
3332   addSetHead(&lvaluereqSet,lpItem);
3333
3334 }
3335 /*-----------------------------------------------------------------*/
3336 /* delLvaluereq - del a flag for lvalreq for current ast level     */
3337 /*-----------------------------------------------------------------*/
3338 void delLvaluereq()
3339 {
3340   lvalItem * lpItem;
3341   lpItem = getSet(&lvaluereqSet);
3342   if(lpItem) Safe_free(lpItem);
3343 }
3344 /*-----------------------------------------------------------------*/
3345 /* clearLvaluereq - clear lvalreq flag                             */
3346 /*-----------------------------------------------------------------*/
3347 void clearLvaluereq()
3348 {
3349   lvalItem * lpItem;
3350   lpItem = peekSet(lvaluereqSet);
3351   if(lpItem) lpItem->req = 0;
3352 }
3353 /*-----------------------------------------------------------------*/
3354 /* getLvaluereq - get the last lvalreq level                       */
3355 /*-----------------------------------------------------------------*/
3356 int getLvaluereqLvl()
3357 {
3358   lvalItem * lpItem;
3359   lpItem = peekSet(lvaluereqSet);
3360   if(lpItem) return lpItem->lvl;
3361   return 0;
3362 }
3363 /*-----------------------------------------------------------------*/
3364 /* isLvaluereq - is lvalreq valid for this level ?                 */
3365 /*-----------------------------------------------------------------*/
3366 int isLvaluereq(int lvl)
3367 {
3368   lvalItem * lpItem;
3369   lpItem = peekSet(lvaluereqSet);
3370   if(lpItem) return ((lpItem->req)&&(lvl <= (lpItem->lvl+1)));
3371   return 0;
3372 }
3373
3374 /*-----------------------------------------------------------------*/
3375 /* ast2iCode - creates an icodeList from an ast                    */
3376 /*-----------------------------------------------------------------*/
3377 operand *
3378 ast2iCode (ast * tree,int lvl)
3379 {
3380   operand *left = NULL;
3381   operand *right = NULL;
3382   if (!tree)
3383     return NULL;
3384
3385   /* set the global variables for filename & line number */
3386   if (tree->filename)
3387     filename = tree->filename;
3388   if (tree->lineno)
3389     lineno = tree->lineno;
3390   if (tree->block)
3391     block = tree->block;
3392   if (tree->level)
3393     scopeLevel = tree->level;
3394
3395   if (tree->type == EX_VALUE)
3396     return operandFromValue (tree->opval.val);
3397
3398   if (tree->type == EX_LINK)
3399     return operandFromLink (tree->opval.lnk);
3400
3401   /* if we find a nullop */
3402   if (tree->type == EX_OP &&
3403      (tree->opval.op == NULLOP ||
3404      tree->opval.op == BLOCK))
3405     {
3406       ast2iCode (tree->left,lvl+1);
3407       ast2iCode (tree->right,lvl+1);
3408       return NULL;
3409     }
3410
3411   /* special cases for not evaluating */
3412   if (tree->opval.op != ':' &&
3413       tree->opval.op != '?' &&
3414       tree->opval.op != CALL &&
3415       tree->opval.op != IFX &&
3416       tree->opval.op != LABEL &&
3417       tree->opval.op != GOTO &&
3418       tree->opval.op != SWITCH &&
3419       tree->opval.op != FUNCTION &&
3420       tree->opval.op != INLINEASM)
3421     {
3422
3423         if (IS_ASSIGN_OP (tree->opval.op) ||
3424            IS_DEREF_OP (tree) ||
3425            (tree->opval.op == '&' && !tree->right) ||
3426            tree->opval.op == PTR_OP)
3427           {
3428             addLvaluereq(lvl);
3429             if ((IS_ARRAY_OP (tree->left) && IS_ARRAY_OP (tree->left->left)) ||
3430                (IS_DEREF_OP (tree) && IS_ARRAY_OP (tree->left)))
3431               clearLvaluereq();
3432
3433             left = operandFromAst (tree->left,lvl);
3434             delLvaluereq();
3435             if (IS_DEREF_OP (tree) && IS_DEREF_OP (tree->left))
3436               left = geniCodeRValue (left, TRUE);
3437           }
3438         else
3439           {
3440             left = operandFromAst (tree->left,lvl);
3441           }
3442         if (tree->opval.op == INC_OP ||
3443             tree->opval.op == DEC_OP)
3444           {
3445             addLvaluereq(lvl);
3446             right = operandFromAst (tree->right,lvl);
3447             delLvaluereq();
3448           }
3449         else
3450           {
3451             right = operandFromAst (tree->right,lvl);
3452           }
3453       }
3454
3455   /* now depending on the type of operand */
3456   /* this will be a biggy                 */
3457   switch (tree->opval.op)
3458     {
3459
3460     case '[':                   /* array operation */
3461       {
3462         //sym_link *ltype = operandType (left);
3463         //left = geniCodeRValue (left, IS_PTR (ltype->next) ? TRUE : FALSE);
3464         left = geniCodeRValue (left, FALSE);
3465         right = geniCodeRValue (right, TRUE);
3466       }
3467
3468       return geniCodeArray (left, right,lvl);
3469
3470     case '.':                   /* structure dereference */
3471       if (IS_PTR (operandType (left)))
3472         left = geniCodeRValue (left, TRUE);
3473       else
3474         left = geniCodeRValue (left, FALSE);
3475
3476       return geniCodeStruct (left, right, tree->lvalue);
3477
3478     case PTR_OP:                /* structure pointer dereference */
3479       {
3480         sym_link *pType;
3481         pType = operandType (left);
3482         left = geniCodeRValue (left, TRUE);
3483
3484         setOClass (pType, getSpec (operandType (left)));
3485       }
3486
3487       return geniCodeStruct (left, right, tree->lvalue);
3488
3489     case INC_OP:                /* increment operator */
3490       if (left)
3491         return geniCodePostInc (left);
3492       else
3493         return geniCodePreInc (right);
3494
3495     case DEC_OP:                /* decrement operator */
3496       if (left)
3497         return geniCodePostDec (left);
3498       else
3499         return geniCodePreDec (right);
3500
3501     case '&':                   /* bitwise and or address of operator */
3502       if (right)
3503         {                       /* this is a bitwise operator   */
3504           left = geniCodeRValue (left, FALSE);
3505           right = geniCodeRValue (right, FALSE);
3506           return geniCodeBitwise (left, right, BITWISEAND, tree->ftype);
3507         }
3508       else
3509         return geniCodeAddressOf (left);
3510
3511     case '|':                   /* bitwise or & xor */
3512     case '^':
3513       return geniCodeBitwise (geniCodeRValue (left, FALSE),
3514                               geniCodeRValue (right, FALSE),
3515                               tree->opval.op,
3516                               tree->ftype);
3517
3518     case '/':
3519       return geniCodeDivision (geniCodeRValue (left, FALSE),
3520                                geniCodeRValue (right, FALSE));
3521
3522     case '%':
3523       return geniCodeModulus (geniCodeRValue (left, FALSE),
3524                               geniCodeRValue (right, FALSE));
3525     case '*':
3526       if (right)
3527         return geniCodeMultiply (geniCodeRValue (left, FALSE),
3528                                  geniCodeRValue (right, FALSE),IS_INT(tree->ftype));
3529       else
3530         return geniCodeDerefPtr (geniCodeRValue (left, FALSE),lvl);
3531
3532     case '-':
3533       if (right)
3534         return geniCodeSubtract (geniCodeRValue (left, FALSE),
3535                                  geniCodeRValue (right, FALSE));
3536       else
3537         return geniCodeUnaryMinus (geniCodeRValue (left, FALSE));
3538
3539     case '+':
3540       if (right)
3541         return geniCodeAdd (geniCodeRValue (left, FALSE),
3542                             geniCodeRValue (right, FALSE),lvl);
3543       else
3544         return geniCodeRValue (left, FALSE);    /* unary '+' has no meaning */
3545
3546     case LEFT_OP:
3547       return geniCodeLeftShift (geniCodeRValue (left, FALSE),
3548                                 geniCodeRValue (right, FALSE));
3549
3550     case RIGHT_OP:
3551       return geniCodeRightShift (geniCodeRValue (left, FALSE),
3552                                  geniCodeRValue (right, FALSE));
3553     case CAST: 
3554 #if 0 // this indeed needs a second thought
3555       {
3556         operand *op;
3557         
3558         // let's keep this simple: get the rvalue we need
3559         op=geniCodeRValue (right, FALSE);
3560         // now cast it to whatever we want
3561         op=geniCodeCast (operandType(left), op, FALSE);
3562         // if this is going to be used as an lvalue, make it so
3563         if (tree->lvalue) {
3564           op->isaddr=1;
3565         }
3566         return op;
3567       }
3568 #else // bug #604575, is it a bug ????
3569       return geniCodeCast (operandType (left),
3570                            geniCodeRValue (right, FALSE), FALSE);
3571 #endif
3572
3573     case '~':
3574     case '!':
3575     case RRC:
3576     case RLC:
3577       return geniCodeUnary (geniCodeRValue (left, FALSE), tree->opval.op);
3578
3579     case GETHBIT:
3580       {
3581         operand *op = geniCodeUnary (geniCodeRValue (left, FALSE), tree->opval.op);
3582         setOperandType (op, UCHARTYPE);
3583         return op;
3584       }
3585     case '>':
3586     case '<':
3587     case LE_OP:
3588     case GE_OP:
3589     case EQ_OP:
3590     case NE_OP:
3591     case AND_OP:
3592     case OR_OP:
3593       return geniCodeLogic (geniCodeRValue (left, FALSE),
3594                             geniCodeRValue (right, FALSE),
3595                             tree->opval.op);
3596     case '?':
3597       return geniCodeConditional (tree,lvl);
3598
3599     case SIZEOF:
3600       return operandFromLit (getSize (tree->right->ftype));
3601
3602     case '=':
3603       {
3604         sym_link *rtype = operandType (right);
3605         sym_link *ltype = operandType (left);
3606         if (IS_PTR (rtype) && IS_ITEMP (right)
3607             && right->isaddr && compareType (rtype->next, ltype) == 1)
3608           right = geniCodeRValue (right, TRUE);
3609         else
3610           right = geniCodeRValue (right, FALSE);
3611
3612         geniCodeAssign (left, right, 0);
3613         return right;
3614       }
3615     case MUL_ASSIGN:
3616       return
3617         geniCodeAssign (left,
3618                 geniCodeMultiply (geniCodeRValue (operandFromOperand (left),
3619                                                   FALSE),
3620                                   geniCodeRValue (right, FALSE),FALSE), 0);
3621
3622     case DIV_ASSIGN:
3623       return
3624         geniCodeAssign (left,
3625                 geniCodeDivision (geniCodeRValue (operandFromOperand (left),
3626                                                   FALSE),
3627                                   geniCodeRValue (right, FALSE)), 0);
3628     case MOD_ASSIGN:
3629       return
3630         geniCodeAssign (left,
3631                  geniCodeModulus (geniCodeRValue (operandFromOperand (left),
3632                                                   FALSE),
3633                                   geniCodeRValue (right, FALSE)), 0);
3634     case ADD_ASSIGN:
3635       {
3636         sym_link *rtype = operandType (right);
3637         sym_link *ltype = operandType (left);
3638         if (IS_PTR (rtype) && IS_ITEMP (right)
3639             && right->isaddr && compareType (rtype->next, ltype) == 1)
3640           right = geniCodeRValue (right, TRUE);
3641         else
3642           right = geniCodeRValue (right, FALSE);
3643
3644
3645         return geniCodeAssign (left,
3646                      geniCodeAdd (geniCodeRValue (operandFromOperand (left),
3647                                                   FALSE),
3648                                   right,lvl), 0);
3649       }
3650     case SUB_ASSIGN:
3651       {
3652         sym_link *rtype = operandType (right);
3653         sym_link *ltype = operandType (left);
3654         if (IS_PTR (rtype) && IS_ITEMP (right)
3655             && right->isaddr && compareType (rtype->next, ltype) == 1)
3656           {
3657             right = geniCodeRValue (right, TRUE);
3658           }
3659         else
3660           {
3661             right = geniCodeRValue (right, FALSE);
3662           }
3663         return
3664           geniCodeAssign (left,
3665                 geniCodeSubtract (geniCodeRValue (operandFromOperand (left),
3666                                                   FALSE),
3667                                   right), 0);
3668       }
3669     case LEFT_ASSIGN:
3670       return
3671         geniCodeAssign (left,
3672                 geniCodeLeftShift (geniCodeRValue (operandFromOperand (left)
3673                                                    ,FALSE),
3674                                    geniCodeRValue (right, FALSE)), 0);
3675     case RIGHT_ASSIGN:
3676       return
3677         geniCodeAssign (left,
3678                geniCodeRightShift (geniCodeRValue (operandFromOperand (left)
3679                                                    ,FALSE),
3680                                    geniCodeRValue (right, FALSE)), 0);
3681     case AND_ASSIGN:
3682       return
3683         geniCodeAssign (left,
3684                  geniCodeBitwise (geniCodeRValue (operandFromOperand (left),
3685                                                   FALSE),
3686                                   geniCodeRValue (right, FALSE),
3687                                   BITWISEAND,
3688                                   operandType (left)), 0);
3689     case XOR_ASSIGN:
3690       return
3691         geniCodeAssign (left,
3692                  geniCodeBitwise (geniCodeRValue (operandFromOperand (left),
3693                                                   FALSE),
3694                                   geniCodeRValue (right, FALSE),
3695                                   '^',
3696                                   operandType (left)), 0);
3697     case OR_ASSIGN:
3698       return
3699         geniCodeAssign (left,
3700                   geniCodeBitwise (geniCodeRValue (operandFromOperand (left)
3701                                                    ,FALSE),
3702                                    geniCodeRValue (right, FALSE),
3703                                    '|',
3704                                    operandType (left)), 0);
3705     case ',':
3706       return geniCodeRValue (right, FALSE);
3707
3708     case CALL:
3709       return geniCodeCall (ast2iCode (tree->left,lvl+1),
3710                            tree->right,lvl);
3711     case LABEL:
3712       geniCodeLabel (ast2iCode (tree->left,lvl+1)->operand.symOperand);
3713       return ast2iCode (tree->right,lvl+1);
3714
3715     case GOTO:
3716       geniCodeGoto (ast2iCode (tree->left,lvl+1)->operand.symOperand);
3717       return ast2iCode (tree->right,lvl+1);
3718
3719     case FUNCTION:
3720       geniCodeFunctionBody (tree,lvl);
3721       return NULL;
3722
3723     case RETURN:
3724       geniCodeReturn (right);
3725       return NULL;
3726
3727     case IFX:
3728       geniCodeIfx (tree,lvl);
3729       return NULL;
3730
3731     case SWITCH:
3732       geniCodeSwitch (tree,lvl);
3733       return NULL;
3734
3735     case INLINEASM:
3736       geniCodeInline (tree);
3737       return NULL;
3738         
3739     case ARRAYINIT:
3740         geniCodeArrayInit(tree, ast2iCode (tree->left,lvl+1));
3741         return NULL;
3742     }
3743
3744   return NULL;
3745 }
3746
3747 /*-----------------------------------------------------------------*/
3748 /* reverseICChain - gets from the list and creates a linkedlist    */
3749 /*-----------------------------------------------------------------*/
3750 iCode *
3751 reverseiCChain ()
3752 {
3753   iCode *loop = NULL;
3754   iCode *prev = NULL;
3755
3756   while ((loop = getSet (&iCodeChain)))
3757     {
3758       loop->next = prev;
3759       if (prev)
3760         prev->prev = loop;
3761       prev = loop;
3762     }
3763
3764   return prev;
3765 }
3766
3767
3768 /*-----------------------------------------------------------------*/
3769 /* iCodeFromAst - given an ast will convert it to iCode            */
3770 /*-----------------------------------------------------------------*/
3771 iCode *
3772 iCodeFromAst (ast * tree)
3773 {
3774   returnLabel = newiTempLabel ("_return");
3775   entryLabel = newiTempLabel ("_entry");
3776   ast2iCode (tree,0);
3777   return reverseiCChain ();
3778 }
3779
3780 static const char *opTypeToStr(OPTYPE op)
3781 {
3782     switch(op)
3783     {
3784       case SYMBOL: return "symbol";
3785       case VALUE: return "value";
3786       case TYPE: return "type";
3787     }
3788     return "undefined type";    
3789 }
3790
3791
3792 operand *validateOpType(operand         *op, 
3793                         const char      *macro,
3794                         const char      *args,
3795                         OPTYPE          type,
3796                         const char      *file, 
3797                         unsigned        line)
3798 {    
3799     if (op && op->type == type)
3800     {
3801         return op;
3802     }
3803     fprintf(stderr, 
3804             "Internal error: validateOpType failed in %s(%s) @ %s:%u:"
3805             " expected %s, got %s\n",
3806             macro, args, file, line, 
3807             opTypeToStr(type), op ? opTypeToStr(op->type) : "null op");
3808     exit(-1);
3809     return op; // never reached, makes compiler happy.
3810 }