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