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