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