1e651850cf0cd6a62d0b81e40e026dfbf5b42e86
[fw/sdcc] / src / z80 / ralloc.c
1 /** @name Z80 Register allocation functions.
2     @author Michael Hope
3
4     Note: much of this is ripped straight from Sandeep's mcs51 code.
5
6     This code maps the virtual symbols and code onto the real
7     hardware.  It allocates based on usage and how long the varible
8     lives into registers or temporary memory on the stack.
9
10     On the Z80 hl, ix, iy, and a are reserved for the code generator,
11     leaving bc and de for allocation.  The extra register pressure
12     from reserving hl is made up for by how much easier the sub
13     operations become.  You could swap hl for iy if the undocumented
14     iyl/iyh instructions are available.
15
16     The stack frame is the common ix-bp style.  Basically:
17
18     ix+4+n:     param 1 
19     ix+4:       param 0 
20     ix+2:       return address 
21     ix+0:       calling functions ix 
22     ix-n:       local varibles 
23     ...  
24     sp:         end of local varibles
25
26     There is currently no support for bit spaces or banked functions.
27     
28     This program is free software; you can redistribute it and/or
29     modify it under the terms of the GNU General Public License as
30     published by the Free Software Foundation; either version 2, or (at
31     your option) any later version.  This program is distributed in the
32     hope that it will be useful, but WITHOUT ANY WARRANTY; without even
33     the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR
34     PURPOSE.  See the GNU General Public License for more details.
35     
36     You should have received a copy of the GNU General Public License
37     along with this program; if not, write to the Free Software
38     Foundation, 59 Temple Place - Suite 330, Boston, MA 02111-1307,
39     USA.  In other words, you are welcome to use, share and improve
40     this program.  You are forbidden to forbid anyone else to use,
41     share and improve what you give them.  Help stamp out
42     software-hoarding!  
43 */
44
45 #include <stdio.h>
46 #include <stdlib.h>
47 #include "SDCCglobl.h"
48 #include "SDCCast.h"
49 #include "SDCCmem.h"
50 #include "SDCCy.h" 
51 #include "SDCChasht.h"
52 #include "SDCCbitv.h"
53 #include "SDCCset.h"
54 #include "SDCCicode.h"
55 #include "SDCClabel.h"
56 #include "SDCCBBlock.h"
57 #include "SDCCloop.h"
58 #include "SDCCcse.h"
59 #include "SDCCcflow.h"
60 #include "SDCCdflow.h"
61 #include "SDCClrange.h"
62 #include "ralloc.h"
63
64 /*-----------------------------------------------------------------*/
65 /* At this point we start getting processor specific although      */
66 /* some routines are non-processor specific & can be reused when   */
67 /* targetting other processors. The decision for this will have    */
68 /* to be made on a routine by routine basis                        */
69 /* routines used to pack registers are most definitely not reusable*/
70 /* since the pack the registers depending strictly on the MCU      */
71 /*-----------------------------------------------------------------*/
72
73 bitVect *spiltSet = NULL ; 
74 set *stackSpil = NULL;
75 bitVect *regAssigned = NULL;
76 short blockSpil = 0;
77 int slocNum = 0 ;
78 extern void genZ80Code(iCode *);
79 int ptrRegReq = 0; /* one byte pointer register required */
80 bitVect *funcrUsed = NULL; /* registers used in a function */
81 int stackExtend = 0;
82 int dataExtend  = 0;
83
84 /** Set to help debug register pressure related problems */
85 #define DEBUG_FAKE_EXTRA_REGS   0
86
87 static regs regsZ80[] = 
88 {
89     { REG_GPR, C_IDX , "c", 1 },
90     { REG_GPR, B_IDX , "b", 1 },
91     { REG_GPR, E_IDX , "e", 1 },
92     { REG_GPR, D_IDX , "d", 1 },
93     /*    { REG_GPR, L_IDX , "l", 1 },
94     { REG_GPR, H_IDX , "h", 1 },*/
95 #if DEBUG_FAKE_EXTRA_REGS
96     { REG_GPR, M_IDX , "m", 1 },
97     { REG_GPR, N_IDX , "n", 1 },
98     { REG_GPR, O_IDX , "o", 1 },
99     { REG_GPR, P_IDX , "p", 1 },
100     { REG_GPR, Q_IDX , "q", 1 },
101     { REG_GPR, R_IDX , "r", 1 },
102     { REG_GPR, S_IDX , "s", 1 },
103     { REG_GPR, T_IDX , "t", 1 },
104 #endif
105     { REG_CND, CND_IDX, "c", 1}
106 };
107
108 /** Number of usable registers (all but C) */
109 #define MAX_REGS ((sizeof(regsZ80)/sizeof(regs))-1)
110
111 static void spillThis (symbol *);
112
113 /** Allocates register of given type.
114     'type' is not used on the z80 version.  It was used to select
115     between pointer and general purpose registers on the mcs51 version.
116
117     @return             Pointer to the newly allocated register.
118  */
119 static regs *allocReg (short type)
120 {
121     int i;
122
123     for ( i = 0 ; i < MAX_REGS ; i++ ) {
124         /* For now we allocate from any free */
125         if (regsZ80[i].isFree ) {
126             regsZ80[i].isFree = 0;
127             if (currFunc)
128                 currFunc->regsUsed = 
129                     bitVectSetBit(currFunc->regsUsed,i);
130             return &regsZ80[i];
131         }
132     }
133     return NULL;
134 }
135
136 /** Returns pointer to register wit index number
137  */
138 regs *regWithIdx (int idx)
139 {
140     int i;
141     
142     for (i=0;i < MAX_REGS;i++)
143         if (regsZ80[i].rIdx == idx)
144             return &regsZ80[i];
145
146     werror(E_INTERNAL_ERROR,__FILE__,__LINE__,
147            "regWithIdx not found");
148     exit(1);
149 }
150
151 /** Frees a register.
152  */
153 static void freeReg (regs *reg)
154 {
155     assert(!reg->isFree);
156     reg->isFree = 1;
157 }
158
159
160 /** Returns number of free registers.
161  */
162 static int nFreeRegs (int type)
163 {
164     int i;
165     int nfr=0;
166     
167     for (i = 0 ; i < MAX_REGS; i++ ) {
168         /* For now only one reg type */
169         if (regsZ80[i].isFree)
170             nfr++;
171     }
172     return nfr;
173 }
174
175 /** Free registers with type.
176  */
177 static int nfreeRegsType (int type)
178 {
179     int nfr ;
180     if (type == REG_PTR) {
181         if ((nfr = nFreeRegs(type)) == 0)
182             return nFreeRegs(REG_GPR);
183     } 
184     
185     return nFreeRegs(type);
186 }
187
188
189 #if 0
190 /*-----------------------------------------------------------------*/
191 /* allDefsOutOfRange - all definitions are out of a range          */
192 /*-----------------------------------------------------------------*/
193 static bool allDefsOutOfRange (bitVect *defs,int fseq, int toseq) 
194 {
195     int i ;
196
197     if (!defs)
198         return TRUE ;
199
200     for ( i = 0 ;i < defs->size ; i++ ) {
201         iCode *ic;
202
203         if (bitVectBitValue(defs,i)             &&
204             (ic = hTabItemWithKey(iCodehTab,i)) &&
205             ( ic->seq >= fseq  && ic->seq <= toseq))
206             
207             return FALSE;
208         
209     }
210     
211     return TRUE;
212 }
213 #endif
214   
215 /*-----------------------------------------------------------------*/
216 /* computeSpillable - given a point find the spillable live ranges */
217 /*-----------------------------------------------------------------*/
218 static bitVect *computeSpillable (iCode *ic)
219 {
220     bitVect *spillable ;
221
222     /* spillable live ranges are those that are live at this 
223        point . the following categories need to be subtracted
224        from this set. 
225        a) - those that are already spilt
226        b) - if being used by this one
227        c) - defined by this one */
228     
229     spillable = bitVectCopy(ic->rlive);
230     spillable = 
231         bitVectCplAnd(spillable,spiltSet); /* those already spilt */
232     spillable = 
233         bitVectCplAnd(spillable,ic->uses); /* used in this one */    
234     bitVectUnSetBit(spillable,ic->defKey);
235     spillable = bitVectIntersect(spillable,regAssigned);
236     return spillable;
237     
238 }
239
240 /*-----------------------------------------------------------------*/
241 /* noSpilLoc - return true if a variable has no spil location      */
242 /*-----------------------------------------------------------------*/
243 static int noSpilLoc (symbol *sym, eBBlock *ebp,iCode *ic)
244 {
245     return (sym->usl.spillLoc ? 0 : 1);
246 }
247
248 /*-----------------------------------------------------------------*/
249 /* hasSpilLoc - will return 1 if the symbol has spil location      */
250 /*-----------------------------------------------------------------*/
251 static int hasSpilLoc (symbol *sym, eBBlock *ebp, iCode *ic)
252 {
253     return (sym->usl.spillLoc ? 1 : 0);
254 }
255
256 /** Will return 1 if the remat flag is set.
257     A symbol is rematerialisable if it doesnt need to be allocated
258     into registers at creation as it can be re-created at any time -
259     i.e. it's constant in some way.
260 */
261 static int rematable (symbol *sym, eBBlock *ebp, iCode *ic)
262 {
263     return sym->remat;
264 }
265
266 /*-----------------------------------------------------------------*/
267 /* allLRs - return true for all                                    */
268 /*-----------------------------------------------------------------*/
269 static int allLRs (symbol *sym, eBBlock *ebp, iCode *ic)
270 {
271     return 1;
272 }
273
274 /*-----------------------------------------------------------------*/
275 /* liveRangesWith - applies function to a given set of live range  */
276 /*-----------------------------------------------------------------*/
277 set *liveRangesWith (bitVect *lrs, int (func)(symbol *,eBBlock *, iCode *),
278                      eBBlock *ebp, iCode *ic)
279 {
280     set *rset = NULL;
281     int i;
282
283     if (!lrs || !lrs->size)
284         return NULL;
285
286     for ( i = 1 ; i < lrs->size ; i++ ) {
287         symbol *sym;
288         if (!bitVectBitValue(lrs,i))
289             continue ;
290
291         /* if we don't find it in the live range 
292            hash table we are in serious trouble */
293         if (!(sym = hTabItemWithKey(liveRanges,i))) {
294             werror(E_INTERNAL_ERROR,__FILE__,__LINE__,
295                    "liveRangesWith could not find liveRange");
296             exit(1);
297         }
298         
299         if (func(sym,ebp,ic) && bitVectBitValue(regAssigned,sym->key))
300             addSetHead(&rset,sym);
301     }
302
303     return rset;
304 }
305
306
307 /*-----------------------------------------------------------------*/
308 /* leastUsedLR - given a set determines which is the least used    */
309 /*-----------------------------------------------------------------*/
310 symbol *leastUsedLR (set *sset)
311 {
312     symbol *sym = NULL, *lsym = NULL ;
313     
314     sym = lsym = setFirstItem(sset);
315
316     if (!lsym)
317         return NULL;
318
319     for (; lsym; lsym = setNextItem(sset)) {
320         
321         /* if usage is the same then prefer
322            the spill the smaller of the two */
323         if ( lsym->used == sym->used )
324             if (getSize(lsym->type) < getSize(sym->type))
325                 sym = lsym;
326
327         /* if less usage */
328         if (lsym->used < sym->used )
329             sym = lsym;
330         
331    }
332
333     setToNull((void **)&sset);
334     sym->blockSpil = 0;
335     return sym;
336 }
337
338 /*-----------------------------------------------------------------*/
339 /* noOverLap - will iterate through the list looking for over lap  */
340 /*-----------------------------------------------------------------*/
341 static int noOverLap (set *itmpStack, symbol *fsym)
342 {
343     symbol *sym;
344    
345
346     for (sym = setFirstItem(itmpStack); sym;
347          sym = setNextItem(itmpStack)) {
348         if (sym->liveTo > fsym->liveFrom )
349             return 0;
350             
351     }
352
353     return 1;
354 }
355
356 /*-----------------------------------------------------------------*/
357 /* isFree - will return 1 if the a free spil location is found     */
358 /*-----------------------------------------------------------------*/
359 DEFSETFUNC(isFree)
360 {
361     symbol *sym = item;
362     V_ARG(symbol **,sloc);
363     V_ARG(symbol *,fsym);
364
365     /* if already found */
366     if (*sloc)
367         return 0;
368
369     /* if it is free && and the itmp assigned to
370        this does not have any overlapping live ranges
371        with the one currently being assigned and
372        the size can be accomodated  */
373     if (sym->isFree                        && 
374         noOverLap(sym->usl.itmpStack,fsym) &&
375         getSize(sym->type) >= getSize(fsym->type)) {
376         *sloc = sym;
377         return 1;
378     }
379
380     return 0;
381 }
382
383 /*-----------------------------------------------------------------*/
384 /* spillLRWithPtrReg :- will spil those live ranges which use PTR  */
385 /*-----------------------------------------------------------------*/
386 static void spillLRWithPtrReg (symbol *forSym)
387 {
388     /* Always just return */
389 }
390
391 /*-----------------------------------------------------------------*/
392 /* createStackSpil - create a location on the stack to spil        */
393 /*-----------------------------------------------------------------*/
394 symbol *createStackSpil (symbol *sym)
395 {
396     symbol *sloc= NULL;
397
398     /* first go try and find a free one that is already 
399        existing on the stack */
400     if (applyToSet(stackSpil,isFree,&sloc, sym)) {
401         /* found a free one : just update & return */
402         sym->usl.spillLoc = sloc;
403         sym->stackSpil= 1;
404         sloc->isFree = 0;
405         addSetHead(&sloc->usl.itmpStack,sym);
406         return sym;
407     }
408
409     /* could not then have to create one , this is the hard part
410        we need to allocate this on the stack : this is really a
411        hack!! but cannot think of anything better at this time */
412         
413     sprintf(buffer,"sloc%d",slocNum++);
414     sloc = newiTemp(buffer);
415
416     /* set the type to the spilling symbol */
417     sloc->type = copyLinkChain(sym->type);
418     sloc->etype = getSpec(sloc->type);
419     SPEC_SCLS(sloc->etype) = S_AUTO ;    
420
421     /* we don't allow it to be allocated`
422        onto the external stack since : so we
423        temporarily turn it off ; we also
424        turn off memory model to prevent
425        the spil from going to the external storage
426        and turn off overlaying 
427     */
428     allocLocal(sloc);
429
430     sloc->isref = 1; /* to prevent compiler warning */
431     
432     /* if it is on the stack then update the stack */
433     if (IN_STACK(sloc->etype)) {
434         currFunc->stack += getSize(sloc->type);
435         stackExtend += getSize(sloc->type);
436     } else
437         dataExtend += getSize(sloc->type);
438
439     /* add it to the stackSpil set */
440     addSetHead(&stackSpil,sloc);
441     sym->usl.spillLoc = sloc;
442     sym->stackSpil = 1;
443     
444     /* add it to the set of itempStack set 
445        of the spill location */
446     addSetHead(&sloc->usl.itmpStack,sym);
447     return sym;
448 }
449
450 /*-----------------------------------------------------------------*/
451 /* isSpiltOnStack - returns true if the spil location is on stack  */
452 /*-----------------------------------------------------------------*/
453 bool isSpiltOnStack (symbol *sym)
454 {
455     link *etype;
456
457     if (!sym)
458         return FALSE ;
459     
460     if (!sym->isspilt)
461         return FALSE ;
462
463 /*     if (sym->stackSpil) */
464 /*      return TRUE; */
465     
466     if (!sym->usl.spillLoc)
467         return FALSE;
468
469     etype = getSpec(sym->usl.spillLoc->type);
470     if (IN_STACK(etype))
471         return TRUE;
472
473     return FALSE ;
474 }
475
476 /*-----------------------------------------------------------------*/
477 /* spillThis - spils a specific operand                            */
478 /*-----------------------------------------------------------------*/
479 static void spillThis (symbol *sym)
480 {
481     int i;
482     /* if this is rematerializable or has a spillLocation
483        we are okay, else we need to create a spillLocation
484        for it */
485     if (!(sym->remat || sym->usl.spillLoc)) 
486         createStackSpil (sym);
487     
488
489     /* mark it has spilt & put it in the spilt set */
490     sym->isspilt = 1;
491     spiltSet = bitVectSetBit(spiltSet,sym->key);
492        
493     bitVectUnSetBit(regAssigned,sym->key);
494
495     for (i = 0 ; i < sym->nRegs ; i++)
496
497         if (sym->regs[i]) {
498             freeReg(sym->regs[i]);
499             sym->regs[i] = NULL;
500         }
501     
502     /* if spilt on stack then free up r0 & r1 
503        if they could have been assigned to some
504        LIVE ranges */
505     if (!ptrRegReq && isSpiltOnStack(sym)) {
506         ptrRegReq++ ;
507         spillLRWithPtrReg(sym);
508     }
509
510     if (sym->usl.spillLoc && !sym->remat)
511         sym->usl.spillLoc->allocreq = 1;
512     return;
513 }
514
515 /** Select a iTemp to spil : rather a simple procedure.
516  */
517 symbol *selectSpil (iCode *ic, eBBlock *ebp, symbol *forSym)
518 {
519     bitVect *lrcs= NULL ; 
520     set *selectS ;
521     symbol *sym;
522
523     /* get the spillable live ranges */
524     lrcs = computeSpillable (ic);
525
526     /* get all live ranges that are rematerizable */
527     if ((selectS = liveRangesWith(lrcs,rematable,ebp,ic))) {
528
529         /* return the least used of these */
530         return leastUsedLR(selectS);
531     }
532
533 #if 0
534     /* get live ranges with spillLocations in direct space */
535     if ((selectS = liveRangesWith(lrcs,directSpilLoc,ebp,ic))) {
536         sym = leastUsedLR(selectS);
537         strcpy(sym->rname,(sym->usl.spillLoc->rname[0] ? 
538                            sym->usl.spillLoc->rname : 
539                            sym->usl.spillLoc->name)); 
540         sym->spildir = 1;
541         /* mark it as allocation required */
542         sym->usl.spillLoc->allocreq = 1;
543         return sym;
544     }
545
546     /* if the symbol is local to the block then */        
547     if (forSym->liveTo < ebp->lSeq ) {       
548
549         /* check if there are any live ranges allocated
550            to registers that are not used in this block */
551         if (!blockSpil && (selectS = liveRangesWith(lrcs,notUsedInBlock,ebp,ic))) {
552             sym = leastUsedLR(selectS);
553             /* if this is not rematerializable */
554             if (!sym->remat) {
555                 blockSpil++;
556                 sym->blockSpil = 1;
557             }
558             return sym;
559         } 
560
561         /* check if there are any live ranges that not
562            used in the remainder of the block */
563         if (!blockSpil && (selectS = liveRangesWith(lrcs,notUsedInRemaining,ebp,ic))) {
564             sym = leastUsedLR (selectS);
565             if (!sym->remat) {
566                 sym->remainSpil = 1;
567                 blockSpil++;
568             }
569             return sym;
570         }
571     }
572     /* find live ranges with spillocation && not used as pointers */
573     if ((selectS = liveRangesWith(lrcs,hasSpilLocnoUptr,ebp,ic))) {
574        
575         sym =  leastUsedLR(selectS);
576         /* mark this as allocation required */
577         sym->usl.spillLoc->allocreq = 1;
578         return sym;
579     }
580 #endif   
581
582     /* find live ranges with spillocation */
583     if ((selectS = liveRangesWith(lrcs,hasSpilLoc,ebp,ic))) {
584         
585         sym = leastUsedLR(selectS);
586         sym->usl.spillLoc->allocreq = 1;
587         return sym;
588     }
589
590     /* couldn't find then we need to create a spil
591        location on the stack , for which one? the least
592        used ofcourse */
593     if ((selectS = liveRangesWith(lrcs,noSpilLoc,ebp,ic))) {
594         /* return a created spil location */
595         sym = createStackSpil(leastUsedLR(selectS));
596         sym->usl.spillLoc->allocreq = 1;
597         return sym;
598     }
599     
600     /* this is an extreme situation we will spill
601        this one : happens very rarely but it does happen */
602     spillThis ( forSym );
603     return forSym;
604    
605 }
606
607 /** Spil some variable & mark registers as free.
608     A spill occurs when an iTemp wont fit into the available registers.
609  */
610 bool spilSomething (iCode *ic, eBBlock *ebp, symbol *forSym)
611 {
612     symbol *ssym;
613     int i ;
614
615     /* get something we can spil */
616     ssym = selectSpil(ic,ebp,forSym);
617     
618     /* mark it as spilt */
619     ssym->isspilt = 1;
620     spiltSet = bitVectSetBit(spiltSet,ssym->key);
621     
622     /* mark it as not register assigned &
623        take it away from the set */   
624     bitVectUnSetBit(regAssigned,ssym->key);
625  
626     /* mark the registers as free */    
627     for (i = 0 ; i < ssym->nRegs ;i++ )
628         if (ssym->regs[i])
629             freeReg(ssym->regs[i]);
630      
631 #if 0
632     /* if spilt on stack then free up r0 & r1 
633        if they could have been assigned to as gprs */
634     if (!ptrRegReq && isSpiltOnStack(ssym) ) {
635         ptrRegReq++ ;
636         spillLRWithPtrReg(ssym);
637     }
638
639     /* if this was a block level spil then insert push & pop 
640        at the start & end of block respectively */
641     if (ssym->blockSpil) {
642         iCode *nic = newiCode(IPUSH,operandFromSymbol(ssym),NULL);
643         /* add push to the start of the block */
644         addiCodeToeBBlock(ebp,nic,( ebp->sch->op == LABEL ? 
645                                     ebp->sch->next : ebp->sch));
646         nic = newiCode(IPOP,operandFromSymbol(ssym),NULL);
647         /* add pop to the end of the block */
648         addiCodeToeBBlock(ebp,nic,NULL);
649     }       
650
651     /* if spilt because not used in the remainder of the
652        block then add a push before this instruction and
653        a pop at the end of the block */
654     if (ssym->remainSpil) {
655
656         iCode *nic = newiCode(IPUSH,operandFromSymbol(ssym),NULL);
657         /* add push just before this instruction */
658         addiCodeToeBBlock(ebp,nic,ic);
659                                     
660         nic = newiCode(IPOP,operandFromSymbol(ssym),NULL);
661         /* add pop to the end of the block */
662         addiCodeToeBBlock(ebp,nic,NULL);    
663     }
664 #endif
665
666     if (ssym == forSym )
667         return FALSE ;
668     else
669         return TRUE ;
670 }
671
672 /** Will try for GPR if not spil.
673  */
674 regs *getRegGpr (iCode *ic, eBBlock *ebp,symbol *sym)
675 {
676     regs *reg;
677
678  tryAgain:
679     /* try for gpr type */
680     if ((reg = allocReg(REG_GPR)))        
681         return reg;    
682
683     if (!ptrRegReq)
684         if ((reg = allocReg(REG_PTR)))
685             return reg ;
686
687     /* we have to spil */
688     if (!spilSomething (ic,ebp,sym))
689         return NULL ;
690
691     /* this looks like an infinite loop but 
692        in really selectSpil will abort  */
693     goto tryAgain ;    
694 }
695
696 /** Symbol has a given register.
697  */
698 static bool symHasReg(symbol *sym,regs *reg)
699 {
700     int i;
701
702     for ( i = 0 ; i < sym->nRegs ; i++)
703         if (sym->regs[i] == reg)
704             return TRUE;
705             
706     return FALSE;
707 }
708
709 /** Check the live to and if they have registers & are not spilt then
710     free up the registers 
711 */
712 static void deassignLRs (iCode *ic, eBBlock *ebp)
713 {
714     symbol *sym;
715     int k;
716     symbol *result;
717
718     for (sym = hTabFirstItem(liveRanges,&k); sym;
719          sym = hTabNextItem(liveRanges,&k)) {
720         
721         symbol *psym= NULL;
722         /* if it does not end here */
723         if (sym->liveTo > ic->seq )
724             continue ;
725
726         /* if it was spilt on stack then we can 
727            mark the stack spil location as free */
728         if (sym->isspilt ) {
729             if (sym->stackSpil) {
730                 sym->usl.spillLoc->isFree = 1;
731                 sym->stackSpil = 0;
732             }
733             continue ;
734         }
735         
736         if (!bitVectBitValue(regAssigned,sym->key))
737             continue;
738         
739         /* special case check if this is an IFX &
740            the privious one was a pop and the 
741            previous one was not spilt then keep track
742            of the symbol */     
743         if (ic->op == IFX && ic->prev &&
744             ic->prev->op == IPOP && 
745             !ic->prev->parmPush  &&
746             !OP_SYMBOL(IC_LEFT(ic->prev))->isspilt) 
747             psym = OP_SYMBOL(IC_LEFT(ic->prev));
748
749         if (sym->nRegs) {
750             int i = 0;
751             
752             bitVectUnSetBit(regAssigned,sym->key);
753
754             /* if the result of this one needs registers
755                and does not have it then assign it right
756                away */
757             if (IC_RESULT(ic) &&
758                 !  (SKIP_IC2(ic) ||               /* not a special icode */
759                     ic->op == JUMPTABLE ||
760                     ic->op == IFX ||
761                     ic->op == IPUSH ||
762                     ic->op == IPOP ||
763                     ic->op == RETURN)   &&
764                 (result = OP_SYMBOL(IC_RESULT(ic))) && /* has a result */
765                 result->liveTo > ic->seq &&            /* and will live beyond this */
766                 result->liveTo <= ebp->lSeq &&         /* does not go beyond this block */
767                 result->regType == sym->regType &&     /* same register types */
768                 result->nRegs            &&            /* which needs registers */
769                 ! result->isspilt        &&            /* and does not already have them */
770                 ! result->remat          &&
771                 ! bitVectBitValue(regAssigned,result->key) &&
772                 /* the number of free regs + number of regs in this LR
773                    can accomodate the what result Needs */
774                 ((nfreeRegsType(result->regType) +
775                   sym->nRegs) >= result->nRegs)
776                 ) {
777                 
778                 for (i = 0 ; i < max(sym->nRegs,result->nRegs) ; i++)
779                     if (i < sym->nRegs )
780                         result->regs[i] = sym->regs[i] ;
781                     else
782                         result->regs[i] = getRegGpr (ic,ebp,result);
783
784                 regAssigned = bitVectSetBit(regAssigned,result->key);
785             }                   
786             
787             /* free the remaining */
788             for (; i < sym->nRegs ; i++) {
789                 if (psym) {
790                     if (!symHasReg(psym,sym->regs[i]))
791                         freeReg(sym->regs[i]);
792                 } else
793                     freeReg(sym->regs[i]);
794             }
795         }
796     }
797 }
798
799
800 /** Reassign this to registers.
801  */
802 static void reassignLR (operand *op)
803 {
804     symbol *sym = OP_SYMBOL(op);
805     int i;
806
807     /* not spilt any more */     
808     sym->isspilt = sym->blockSpil  = sym->remainSpil = 0;
809     bitVectUnSetBit(spiltSet,sym->key);
810       
811     regAssigned = bitVectSetBit(regAssigned,sym->key);
812
813     blockSpil--;
814
815     for (i=0;i<sym->nRegs;i++)
816         sym->regs[i]->isFree = 0;
817 }
818
819 /** Determines if allocating will cause a spill.
820  */
821 static int willCauseSpill ( int nr, int rt)
822 {
823     /* first check if there are any avlb registers
824        of te type required */
825     if (nFreeRegs(0) >= nr)
826         return 0;
827
828     /* it will cause a spil */
829     return 1;
830 }
831
832 /** The allocator can allocate same registers to result and operand,
833     if this happens make sure they are in the same position as the operand
834     otherwise chaos results.
835 */
836 static void positionRegs (symbol *result, symbol *opsym, int lineno)
837 {
838         int count = min(result->nRegs,opsym->nRegs);
839         int i , j = 0, shared = 0;
840
841         /* if the result has been spilt then cannot share */
842         if (opsym->isspilt)
843                 return ;
844  again:
845         shared = 0;
846         /* first make sure that they actually share */
847         for ( i = 0 ; i < count; i++ ) {
848                 for (j = 0 ; j < count ; j++ ) {
849                         if (result->regs[i] == opsym->regs[j] && i !=j) {
850                                 shared = 1;
851                                 goto xchgPositions;
852                         }
853                 }
854         }
855  xchgPositions:
856         if (shared) {
857                 regs *tmp = result->regs[i];
858                 result->regs[i] = result->regs[j];
859                 result->regs[j] = tmp;          
860                 goto again;
861         }
862 }
863
864 /** Try to allocate a pair of registers to the symbol.
865  */
866 bool tryAllocatingRegPair(symbol *sym)
867 {
868     int i;
869     assert(sym->nRegs == 2);
870     for ( i = 0 ; i < MAX_REGS ; i+=2 ) {
871         if ((regsZ80[i].isFree)&&(regsZ80[i+1].isFree)) {
872             regsZ80[i].isFree = 0;
873             sym->regs[0] = &regsZ80[i];
874             regsZ80[i+1].isFree = 0;
875             sym->regs[1] = &regsZ80[i+1];
876             if (currFunc) {
877                 currFunc->regsUsed = 
878                     bitVectSetBit(currFunc->regsUsed,i);
879                 currFunc->regsUsed = 
880                     bitVectSetBit(currFunc->regsUsed,i+1);
881             }
882             return TRUE;
883         }
884     }
885     return FALSE;
886 }
887
888 /** Serially allocate registers to the variables.
889     This is the main register allocation function.  It is called after
890     packing.
891  */
892 static void serialRegAssign (eBBlock **ebbs, int count)
893 {
894     int i;
895
896     /* for all blocks */
897     for (i = 0; i < count ; i++ ) {
898         
899         iCode *ic;
900         
901         if (ebbs[i]->noPath &&
902             (ebbs[i]->entryLabel != entryLabel &&
903              ebbs[i]->entryLabel != returnLabel ))
904             continue ;
905
906         /* of all instructions do */
907         for (ic = ebbs[i]->sch ; ic ; ic = ic->next) {
908          
909             /* if this is an ipop that means some live
910                range will have to be assigned again */
911             if (ic->op == IPOP)
912                 reassignLR (IC_LEFT(ic));
913
914             /* if result is present && is a true symbol */
915             if (IC_RESULT(ic) && ic->op != IFX &&
916                 IS_TRUE_SYMOP(IC_RESULT(ic)))
917                 OP_SYMBOL(IC_RESULT(ic))->allocreq = 1;
918
919             /* take away registers from live
920                ranges that end at this instruction */      
921             deassignLRs (ic, ebbs[i]) ;         
922                     
923             /* some don't need registers */
924             /* MLH: removed RESULT and POINTER_SET condition */
925             if (SKIP_IC2(ic) ||
926                 ic->op == JUMPTABLE ||
927                 ic->op == IFX ||
928                 ic->op == IPUSH ||
929                 ic->op == IPOP)
930                 continue;   
931             
932             /* now we need to allocate registers only for the result */
933             if (IC_RESULT(ic)) {
934                 symbol *sym = OP_SYMBOL(IC_RESULT(ic));
935                 bitVect *spillable;
936                 int willCS ;
937                 int j;
938
939                 /* if it does not need or is spilt 
940                    or is already assigned to registers
941                    or will not live beyond this instructions */
942                 if (!sym->nRegs      || 
943                     sym->isspilt     || 
944                     bitVectBitValue(regAssigned,sym->key) ||
945                     sym->liveTo <= ic->seq)
946                     continue ;
947
948                 /* if some liverange has been spilt at the block level
949                    and this one live beyond this block then spil this
950                    to be safe */
951                 if (blockSpil && sym->liveTo > ebbs[i]->lSeq) {
952                     spillThis (sym);
953                     continue ;
954                 }
955                 /* if trying to allocate this will cause
956                    a spill and there is nothing to spill 
957                    or this one is rematerializable then
958                    spill this one */
959                 willCS = willCauseSpill(sym->nRegs,sym->regType);
960                 spillable = computeSpillable(ic);
961                 if ( sym->remat ||                  
962                     (willCS  && bitVectIsZero(spillable) ) ) {
963
964                     spillThis (sym) ;
965                     continue ;
966
967                 }
968
969                 /* if it has a spillocation & is used less than
970                    all other live ranges then spill this */
971                 if ( willCS && sym->usl.spillLoc ) {
972
973                     symbol *leastUsed = 
974                         leastUsedLR(liveRangesWith (spillable ,
975                                                     allLRs,
976                                                     ebbs[i],
977                                                     ic));
978                     if (leastUsed && 
979                         leastUsed->used > sym->used) {
980                         spillThis (sym);
981                         continue;
982                     }
983                 }               
984
985                 /* else we assign registers to it */            
986                 regAssigned = bitVectSetBit(regAssigned,sym->key);
987
988                 /* Special case:  Try to fit into a reg pair if
989                    available */
990                 if ((sym->nRegs == 2)&&tryAllocatingRegPair(sym)) {
991                 }
992                 else {
993                     for (j = 0 ; j < sym->nRegs ;j++ ) {
994                         sym->regs[j] = getRegGpr(ic,ebbs[i],sym);
995                         
996                         /* if the allocation falied which means
997                            this was spilt then break */
998                         if (!sym->regs[j]) {
999                             break;
1000                         }
1001                     }
1002                 }
1003                 /* if it shares registers with operands make sure
1004                    that they are in the same position */
1005                 if (IC_LEFT(ic) && IS_SYMOP(IC_LEFT(ic)) &&
1006                     OP_SYMBOL(IC_LEFT(ic))->nRegs  && ic->op != '=')
1007                         positionRegs(OP_SYMBOL(IC_RESULT(ic)),
1008                                      OP_SYMBOL(IC_LEFT(ic)),ic->lineno);
1009                 /* do the same for the right operand */
1010                 if (IC_RIGHT(ic) && IS_SYMOP(IC_RIGHT(ic)) &&
1011                     OP_SYMBOL(IC_RIGHT(ic))->nRegs && ic->op != '=')
1012                         positionRegs(OP_SYMBOL(IC_RESULT(ic)),
1013                                      OP_SYMBOL(IC_RIGHT(ic)),ic->lineno);
1014                 
1015             }       
1016         }
1017     }
1018 }
1019
1020 /*-----------------------------------------------------------------*/
1021 /* rUmaskForOp :- returns register mask for an operand             */
1022 /*-----------------------------------------------------------------*/
1023 bitVect *rUmaskForOp (operand *op)
1024 {
1025     bitVect *rumask;
1026     symbol *sym;
1027     int j;
1028     
1029     /* only temporaries are assigned registers */
1030     if (!IS_ITEMP(op)) 
1031         return NULL;
1032
1033     sym = OP_SYMBOL(op);
1034     
1035     /* if spilt or no registers assigned to it
1036        then nothing */
1037     if (sym->isspilt || !sym->nRegs)
1038         return NULL;
1039
1040     rumask = newBitVect(MAX_REGS);
1041
1042     for (j = 0; j < sym->nRegs; j++) {
1043         rumask = bitVectSetBit(rumask,
1044                                sym->regs[j]->rIdx);
1045     }
1046
1047     return rumask;
1048 }
1049
1050 /** Returns bit vector of registers used in iCode.
1051  */
1052 bitVect *regsUsedIniCode (iCode *ic)
1053 {
1054     bitVect *rmask = newBitVect(MAX_REGS);
1055
1056     /* do the special cases first */
1057     if (ic->op == IFX ) {
1058         rmask = bitVectUnion(rmask,
1059                              rUmaskForOp(IC_COND(ic)));
1060         goto ret;
1061     }
1062
1063     /* for the jumptable */
1064     if (ic->op == JUMPTABLE) {
1065         rmask = bitVectUnion(rmask,
1066                              rUmaskForOp(IC_JTCOND(ic)));
1067
1068         goto ret;
1069     }
1070
1071     /* of all other cases */
1072     if (IC_LEFT(ic)) 
1073         rmask = bitVectUnion(rmask,
1074                              rUmaskForOp(IC_LEFT(ic)));
1075         
1076     
1077     if (IC_RIGHT(ic))
1078         rmask = bitVectUnion(rmask,
1079                              rUmaskForOp(IC_RIGHT(ic)));
1080
1081     if (IC_RESULT(ic))
1082         rmask = bitVectUnion(rmask,
1083                              rUmaskForOp(IC_RESULT(ic)));
1084
1085  ret:
1086     return rmask;
1087 }
1088
1089 /** For each instruction will determine the regsUsed.
1090  */
1091 static void createRegMask (eBBlock **ebbs, int count)
1092 {
1093     int i;
1094
1095     /* for all blocks */
1096     for (i = 0; i < count ; i++ ) {
1097         iCode *ic ;
1098
1099         if ( ebbs[i]->noPath &&
1100              ( ebbs[i]->entryLabel != entryLabel &&
1101                ebbs[i]->entryLabel != returnLabel ))
1102             continue ;
1103
1104         /* for all instructions */
1105         for ( ic = ebbs[i]->sch ; ic ; ic = ic->next ) {
1106             
1107             int j;
1108
1109             if (SKIP_IC2(ic) || !ic->rlive)
1110                 continue ;
1111             
1112             /* first mark the registers used in this
1113                instruction */
1114             ic->rUsed = regsUsedIniCode(ic);
1115             funcrUsed = bitVectUnion(funcrUsed,ic->rUsed);
1116
1117             /* now create the register mask for those 
1118                registers that are in use : this is a
1119                super set of ic->rUsed */
1120             ic->rMask = newBitVect(MAX_REGS+1);
1121
1122             /* for all live Ranges alive at this point */
1123             for (j = 1; j < ic->rlive->size; j++ ) {
1124                 symbol *sym;
1125                 int k;
1126
1127                 /* if not alive then continue */
1128                 if (!bitVectBitValue(ic->rlive,j))
1129                     continue ;
1130
1131                 /* find the live range we are interested in */
1132                 if (!(sym = hTabItemWithKey(liveRanges,j))) {
1133                     werror (E_INTERNAL_ERROR,__FILE__,__LINE__,
1134                             "createRegMask cannot find live range");
1135                     exit(0);
1136                 }
1137
1138                 /* if no register assigned to it */
1139                 if (!sym->nRegs || sym->isspilt)
1140                     continue ;
1141
1142                 /* for all the registers allocated to it */
1143                 for (k = 0 ; k < sym->nRegs ;k++)
1144                     if (sym->regs[k])
1145                         ic->rMask =
1146                             bitVectSetBit(ic->rMask,sym->regs[k]->rIdx);
1147             }
1148         }
1149     }
1150 }
1151
1152 /** Returns the rematerialized string for a remat var.
1153  */
1154 char *rematStr (symbol *sym)
1155 {
1156     char *s = buffer;   
1157     iCode *ic = sym->rematiCode;    
1158
1159     while (1) {
1160
1161         /* if plus or minus print the right hand side */
1162         if (ic->op == '+' || ic->op == '-') {
1163             sprintf(s,"0x%04x %c ",(int) operandLitValue(IC_RIGHT(ic)),
1164                     ic->op );
1165             s += strlen(s);
1166             ic = OP_SYMBOL(IC_LEFT(ic))->rematiCode;
1167             continue ;
1168         }
1169         /* we reached the end */
1170         sprintf(s,"%s",OP_SYMBOL(IC_LEFT(ic))->rname);
1171         break;
1172     }
1173
1174     return buffer ;
1175 }
1176
1177 /*-----------------------------------------------------------------*/
1178 /* regTypeNum - computes the type & number of registers required   */
1179 /*-----------------------------------------------------------------*/
1180 static void regTypeNum ()
1181 {
1182     symbol *sym;
1183     int k;
1184
1185     /* for each live range do */
1186     for ( sym = hTabFirstItem(liveRanges,&k); sym ;
1187           sym = hTabNextItem(liveRanges,&k)) {
1188
1189         /* if used zero times then no registers needed */
1190         if ((sym->liveTo - sym->liveFrom) == 0)
1191             continue ;
1192
1193         /* if the live range is a temporary */
1194         if (sym->isitmp) {
1195
1196             /* if the type is marked as a conditional */
1197             if (sym->regType == REG_CND)
1198                 continue ;
1199
1200             /* if used in return only then we don't 
1201                need registers */
1202             if (sym->ruonly || sym->accuse) {
1203                 if (IS_AGGREGATE(sym->type) || sym->isptr)
1204                     sym->type = aggrToPtr(sym->type,FALSE);
1205                 continue ;
1206             }
1207
1208             /* if not then we require registers */
1209             sym->nRegs = ((IS_AGGREGATE(sym->type) || sym->isptr ) ?
1210                           getSize(sym->type = aggrToPtr(sym->type,FALSE)) :
1211                           getSize(sym->type));
1212
1213             if (sym->nRegs > 4) {
1214                 fprintf(stderr,"allocated more than 4 or 0 registers for type ");
1215                 printTypeChain(sym->type,stderr);fprintf(stderr,"\n");
1216             }
1217             
1218             /* determine the type of register required */
1219             /* Always general purpose */
1220             sym->regType = REG_GPR ;
1221             
1222         } else 
1223             /* for the first run we don't provide */
1224             /* registers for true symbols we will */
1225             /* see how things go                  */
1226             sym->nRegs = 0 ;    
1227     }
1228     
1229 }
1230
1231 /** Mark all registers as free.
1232  */
1233 static void freeAllRegs()
1234 {
1235     int i;
1236
1237     for (i=0;i< MAX_REGS;i++ )
1238         regsZ80[i].isFree = 1;
1239 }
1240
1241 /*-----------------------------------------------------------------*/
1242 /* deallocStackSpil - this will set the stack pointer back         */
1243 /*-----------------------------------------------------------------*/
1244 DEFSETFUNC(deallocStackSpil)
1245 {
1246     symbol *sym = item;
1247
1248     deallocLocal(sym);
1249     return 0;
1250 }
1251
1252 /** Register reduction for assignment.
1253  */
1254 static int packRegsForAssign (iCode *ic,eBBlock *ebp)
1255 {
1256     iCode *dic, *sic;
1257     
1258     if (
1259         /*      !IS_TRUE_SYMOP(IC_RESULT(ic)) ||*/
1260         !IS_ITEMP(IC_RIGHT(ic))       ||
1261         OP_LIVETO(IC_RIGHT(ic)) > ic->seq ||
1262         OP_SYMBOL(IC_RIGHT(ic))->isind)
1263         return 0;
1264
1265 #if 0        
1266     /* if the true symbol is defined in far space or on stack
1267        then we should not since this will increase register pressure */
1268     if (isOperandInFarSpace(IC_RESULT(ic))) {
1269         if ((dic = farSpacePackable(ic)))
1270             goto pack;
1271         else
1272             return 0;
1273     }
1274 #endif
1275
1276     /* find the definition of iTempNN scanning backwards if we find a 
1277        a use of the true symbol in before we find the definition then 
1278        we cannot */     
1279     for ( dic = ic->prev ; dic ; dic = dic->prev) {
1280         /* if there is a function call and this is
1281            a parameter & not my parameter then don't pack it */
1282         if ( (dic->op == CALL || dic->op == PCALL) &&
1283              (OP_SYMBOL(IC_RESULT(ic))->_isparm &&
1284               !OP_SYMBOL(IC_RESULT(ic))->ismyparm)) {
1285             dic = NULL;
1286             break;
1287         }
1288
1289         if (SKIP_IC2(dic))
1290                 continue;
1291
1292         if (IS_SYMOP(IC_RESULT(dic)) &&
1293             IC_RESULT(dic)->key == IC_RIGHT(ic)->key) {
1294             break;          
1295         }
1296
1297         if (IS_SYMOP(IC_RIGHT(dic)) && 
1298             (IC_RIGHT(dic)->key == IC_RESULT(ic)->key ||
1299              IC_RIGHT(dic)->key == IC_RIGHT(ic)->key)) {
1300             dic = NULL;
1301             break;
1302         }
1303         
1304         if (IS_SYMOP(IC_LEFT(dic)) && 
1305             (IC_LEFT(dic)->key == IC_RESULT(ic)->key ||
1306              IC_LEFT(dic)->key == IC_RIGHT(ic)->key)) {
1307             dic = NULL;
1308             break;
1309         }
1310         if (POINTER_SET(dic) && 
1311             IC_RESULT(dic)->key == IC_RESULT(ic)->key ) {
1312             dic = NULL ;
1313             break;
1314         }
1315     }
1316     
1317     if (!dic)
1318         return 0 ; /* did not find */
1319             
1320     /* if the result is on stack or iaccess then it must be
1321        the same atleast one of the operands */
1322     if (OP_SYMBOL(IC_RESULT(ic))->onStack  || 
1323         OP_SYMBOL(IC_RESULT(ic))->iaccess ) {
1324
1325         /* the operation has only one symbol
1326            operator then we can pack */
1327         if ((IC_LEFT(dic) && !IS_SYMOP(IC_LEFT(dic))) ||
1328             (IC_RIGHT(dic) && !IS_SYMOP(IC_RIGHT(dic))))
1329             goto pack;
1330
1331         if (!((IC_LEFT(dic) &&
1332              IC_RESULT(ic)->key == IC_LEFT(dic)->key) ||
1333               (IC_RIGHT(dic) &&
1334                IC_RESULT(ic)->key == IC_RIGHT(dic)->key)))
1335             return 0;                
1336     }
1337 pack:
1338     /* found the definition */
1339     /* replace the result with the result of */
1340     /* this assignment and remove this assignment */
1341     IC_RESULT(dic) = IC_RESULT(ic) ;
1342
1343     if (IS_ITEMP(IC_RESULT(dic)) && OP_SYMBOL(IC_RESULT(dic))->liveFrom > dic->seq) {
1344             OP_SYMBOL(IC_RESULT(dic))->liveFrom = dic->seq;
1345     }
1346     /* delete from liverange table also 
1347        delete from all the points inbetween and the new
1348        one */
1349     for ( sic = dic; sic != ic ; sic = sic->next ) {    
1350         bitVectUnSetBit(sic->rlive,IC_RESULT(ic)->key);
1351         if (IS_ITEMP(IC_RESULT(dic)))
1352             bitVectSetBit(sic->rlive,IC_RESULT(dic)->key);
1353     }
1354         
1355     remiCodeFromeBBlock(ebp,ic);
1356     return 1;
1357     
1358 }
1359
1360 /** Scanning backwards looks for first assig found.
1361  */
1362 iCode *findAssignToSym (operand *op,iCode *ic)
1363 {
1364     iCode *dic;
1365
1366     for (dic = ic->prev ; dic ; dic = dic->prev) {
1367         
1368         /* if definition by assignment */
1369         if (dic->op == '='                 && 
1370             !POINTER_SET(dic)              &&
1371             IC_RESULT(dic)->key == op->key)
1372             /*      &&  IS_TRUE_SYMOP(IC_RIGHT(dic))*/
1373             {      
1374
1375             /* we are interested only if defined in far space */
1376             /* or in stack space in case of + & - */
1377
1378             /* if assigned to a non-symbol then return
1379                true */
1380             if (!IS_SYMOP(IC_RIGHT(dic)))
1381                 break ;
1382
1383             /* if the symbol is in far space then
1384                we should not */
1385             if (isOperandInFarSpace(IC_RIGHT(dic)))
1386                 return NULL ;
1387
1388             /* for + & - operations make sure that
1389                if it is on the stack it is the same
1390                as one of the three operands */
1391             if ((ic->op == '+' || ic->op == '-') &&
1392                 OP_SYMBOL(IC_RIGHT(dic))->onStack) {
1393
1394                 if ( IC_RESULT(ic)->key != IC_RIGHT(dic)->key &&
1395                      IC_LEFT(ic)->key   != IC_RIGHT(dic)->key &&
1396                      IC_RIGHT(ic)->key  != IC_RIGHT(dic)->key)
1397                     return NULL;
1398             }           
1399
1400             break ;
1401                 
1402         }
1403
1404         /* if we find an usage then we cannot delete it */
1405         if (IC_LEFT(dic) && IC_LEFT(dic)->key == op->key)
1406             return NULL;
1407             
1408         if (IC_RIGHT(dic) && IC_RIGHT(dic)->key == op->key)
1409             return NULL;
1410
1411         if (POINTER_SET(dic) && IC_RESULT(dic)->key == op->key)
1412             return NULL;
1413     }
1414
1415     /* now make sure that the right side of dic
1416        is not defined between ic & dic */       
1417     if (dic) {
1418         iCode *sic = dic->next ;
1419
1420         for (; sic != ic ; sic = sic->next)
1421             if (IC_RESULT(sic) &&
1422                 IC_RESULT(sic)->key == IC_RIGHT(dic)->key)
1423                 return NULL;
1424     }
1425
1426     return dic;
1427         
1428         
1429 }
1430
1431 /*-----------------------------------------------------------------*/
1432 /* packRegsForSupport :- reduce some registers for support calls   */
1433 /*-----------------------------------------------------------------*/
1434 static int packRegsForSupport (iCode *ic, eBBlock *ebp)
1435 {
1436     int change = 0 ;
1437     /* for the left & right operand :- look to see if the
1438        left was assigned a true symbol in far space in that
1439        case replace them */
1440     if (IS_ITEMP(IC_LEFT(ic)) && 
1441         OP_SYMBOL(IC_LEFT(ic))->liveTo <= ic->seq) {
1442         iCode *dic = findAssignToSym(IC_LEFT(ic),ic);
1443         iCode *sic;
1444
1445         if (!dic)
1446             goto right ;
1447
1448         /* found it we need to remove it from the
1449            block */
1450         for ( sic = dic; sic != ic ; sic = sic->next )
1451             bitVectUnSetBit(sic->rlive,IC_LEFT(ic)->key);
1452
1453         IC_LEFT(ic)->operand.symOperand =
1454             IC_RIGHT(dic)->operand.symOperand;
1455         IC_LEFT(ic)->key = IC_RIGHT(dic)->operand.symOperand->key;
1456         remiCodeFromeBBlock(ebp,dic);   
1457         change++;      
1458     }
1459     
1460     /* do the same for the right operand */
1461  right:    
1462     if (!change && 
1463         IS_ITEMP(IC_RIGHT(ic)) &&
1464         OP_SYMBOL(IC_RIGHT(ic))->liveTo <= ic->seq) {
1465         iCode *dic = findAssignToSym(IC_RIGHT(ic),ic);
1466         iCode *sic;
1467         
1468         if (!dic)
1469             return change ;
1470
1471         /* found it we need to remove it from the block */
1472         for ( sic = dic; sic != ic ; sic = sic->next )
1473             bitVectUnSetBit(sic->rlive,IC_RIGHT(ic)->key);
1474         
1475         IC_RIGHT(ic)->operand.symOperand =
1476             IC_RIGHT(dic)->operand.symOperand;
1477         IC_RIGHT(ic)->key = IC_RIGHT(dic)->operand.symOperand->key;
1478         
1479         remiCodeFromeBBlock(ebp,dic);
1480         change ++;
1481     }
1482    
1483     return change ;
1484 }
1485
1486 #define IS_OP_RUONLY(x) (x && IS_SYMOP(x) && OP_SYMBOL(x)->ruonly)
1487
1488 /** Will reduce some registers for single use.
1489  */
1490 static iCode *packRegsForOneuse (iCode *ic, operand *op , eBBlock *ebp)
1491 {
1492     bitVect *uses ;
1493     iCode *dic, *sic;
1494
1495     /* if returning a literal then do nothing */
1496     if (!IS_SYMOP(op))
1497         return NULL;
1498     
1499     /* only upto 2 bytes since we cannot predict
1500        the usage of b, & acc */
1501     if (getSize(operandType(op)) > 2 && 
1502         ic->op != RETURN             &&
1503         ic->op != SEND)
1504         return NULL;
1505
1506     /* this routine will mark the a symbol as used in one 
1507        instruction use only && if the defintion is local 
1508        (ie. within the basic block) && has only one definition &&
1509        that definiion is either a return value from a 
1510        function or does not contain any variables in
1511        far space */
1512     uses = bitVectCopy(OP_USES(op));
1513     bitVectUnSetBit(uses,ic->key); /* take away this iCode */
1514     if (!bitVectIsZero(uses)) /* has other uses */
1515         return NULL ;
1516     
1517     /* if it has only one defintion */
1518     if (bitVectnBitsOn(OP_DEFS(op)) > 1)
1519         return NULL ; /* has more than one definition */
1520
1521     /* get the that definition */
1522     if (!(dic = 
1523           hTabItemWithKey(iCodehTab,
1524                           bitVectFirstBit(OP_DEFS(op)))))
1525         return NULL ;
1526
1527     /* found the definition now check if it is local */
1528     if (dic->seq < ebp->fSeq ||
1529         dic->seq > ebp->lSeq)
1530         return NULL ; /* non-local */
1531
1532     /* now check if it is the return from a function call */
1533     if (dic->op == CALL || dic->op == PCALL ) {
1534         if (ic->op != SEND && ic->op != RETURN) {
1535             OP_SYMBOL(op)->ruonly = 1;
1536             return dic;
1537         }
1538         dic = dic->next ;
1539     }
1540         
1541     /* otherwise check that the definition does
1542        not contain any symbols in far space */
1543     if (isOperandInFarSpace(IC_LEFT(dic))  ||
1544         isOperandInFarSpace(IC_RIGHT(dic)) ||
1545         IS_OP_RUONLY(IC_LEFT(ic))          ||
1546         IS_OP_RUONLY(IC_RIGHT(ic)) )        {
1547         return NULL;
1548     }
1549     
1550     /* if pointer set then make sure the pointer is one byte */
1551     if (POINTER_SET(dic))
1552       return NULL;
1553
1554     if (POINTER_GET(dic))
1555       return NULL;
1556     
1557     sic = dic;
1558
1559     /* also make sure the intervenening instructions
1560        don't have any thing in far space */
1561     for (dic = dic->next ; dic && dic != ic ; dic = dic->next) {
1562         /* if there is an intervening function call then no */
1563         if (dic->op == CALL || dic->op == PCALL)
1564                 return NULL;
1565         /* if pointer set then make sure the pointer
1566            is one byte */
1567         if (POINTER_SET(dic))
1568             return NULL ;
1569         
1570         if (POINTER_GET(dic))
1571             return NULL ;
1572
1573         /* if address of & the result is remat the okay */
1574         if (dic->op == ADDRESS_OF &&
1575             OP_SYMBOL(IC_RESULT(dic))->remat)
1576             continue ;
1577            
1578         /* if left or right or result is in far space */
1579         if (isOperandInFarSpace(IC_LEFT(dic))   ||
1580             isOperandInFarSpace(IC_RIGHT(dic))  ||
1581             isOperandInFarSpace(IC_RESULT(dic)) ||
1582             IS_OP_RUONLY(IC_LEFT(dic))          ||
1583             IS_OP_RUONLY(IC_RIGHT(dic))         ||
1584             IS_OP_RUONLY(IC_RESULT(dic))            ) {
1585             return NULL;
1586         }
1587     }
1588                 
1589     OP_SYMBOL(op)->ruonly = 1;
1590     return sic;
1591 }
1592
1593 /*-----------------------------------------------------------------*/
1594 /* isBitwiseOptimizable - requirements of JEAN LOUIS VERN          */
1595 /*-----------------------------------------------------------------*/
1596 static bool isBitwiseOptimizable (iCode *ic)
1597 {
1598     link *rtype = getSpec(operandType(IC_RIGHT(ic)));
1599
1600     /* bitwise operations are considered optimizable
1601        under the following conditions (Jean-Louis VERN) 
1602        
1603        x & lit
1604        bit & bit
1605        bit & x
1606        bit ^ bit
1607        bit ^ x
1608        x   ^ lit
1609        x   | lit
1610        bit | bit
1611        bit | x
1612     */    
1613     if (IS_LITERAL(rtype))
1614         return TRUE;
1615     return FALSE; 
1616 }
1617
1618 /** Optimisations:
1619     Certian assignments involving pointers can be temporarly stored
1620     in HL.  Esp.
1621 genAssign
1622     ld  iy,#_Blah
1623     ld  bc,(iy)
1624 genAssign (ptr)
1625     ld  hl,bc
1626     ld  iy,#_Blah2
1627     ld  (iy),(hl)
1628 */
1629
1630 /** Pack registers for acc use.
1631     When the result of this operation is small and short lived it may
1632     be able to be stored in the accumelator.
1633  */
1634 static void packRegsForAccUse (iCode *ic)
1635 {
1636     iCode *uic;
1637     
1638     /* if + or - then it has to be one byte result */
1639     if ((ic->op == '+' || ic->op == '-')
1640         && getSize(operandType(IC_RESULT(ic))) > 1)
1641         return ;
1642     
1643     /* if shift operation make sure right side is not a literal */
1644     if (ic->op == RIGHT_OP  &&
1645         (isOperandLiteral(IC_RIGHT(ic)) ||
1646           getSize(operandType(IC_RESULT(ic))) > 1))
1647         return ;
1648         
1649     if (ic->op == LEFT_OP &&        
1650         ( isOperandLiteral(IC_RIGHT(ic)) ||
1651           getSize(operandType(IC_RESULT(ic))) > 1))
1652         return ;
1653         
1654     /* has only one definition */
1655     if (bitVectnBitsOn(OP_DEFS(IC_RESULT(ic))) > 1)
1656         return ;
1657
1658     /* has only one use */
1659     if (bitVectnBitsOn(OP_USES(IC_RESULT(ic))) > 1)
1660         return ;
1661
1662     /* and the usage immediately follows this iCode */
1663     if (!(uic = hTabItemWithKey(iCodehTab,
1664                                 bitVectFirstBit(OP_USES(IC_RESULT(ic))))))
1665         return ;
1666
1667     if (ic->next != uic)
1668         return ;
1669     
1670     /* if it is a conditional branch then we definitely can */
1671     if (uic->op == IFX  ) 
1672         goto accuse;
1673
1674     if ( uic->op == JUMPTABLE )
1675         return ;
1676
1677 #if 0
1678     /* if the usage is not is an assignment or an 
1679        arithmetic / bitwise / shift operation then not */
1680     if (POINTER_SET(uic) && 
1681         getSize(aggrToPtr(operandType(IC_RESULT(uic)),FALSE)) > 1)
1682         return;
1683 #endif
1684
1685     if (uic->op != '=' && 
1686         !IS_ARITHMETIC_OP(uic) &&
1687         !IS_BITWISE_OP(uic)    &&
1688         uic->op != LEFT_OP &&
1689         uic->op != RIGHT_OP )
1690         return;
1691
1692     /* if used in ^ operation then make sure right is not a 
1693        literl */
1694     if (uic->op == '^' && isOperandLiteral(IC_RIGHT(uic)))
1695         return ;
1696
1697     /* if shift operation make sure right side is not a literal */
1698     if (uic->op == RIGHT_OP  &&
1699         ( isOperandLiteral(IC_RIGHT(uic)) ||
1700           getSize(operandType(IC_RESULT(uic))) > 1))
1701         return ;
1702
1703     if (uic->op == LEFT_OP &&        
1704         ( isOperandLiteral(IC_RIGHT(uic)) ||
1705           getSize(operandType(IC_RESULT(uic))) > 1))
1706         return ;
1707             
1708 #if 0
1709     /* make sure that the result of this icode is not on the
1710        stack, since acc is used to compute stack offset */
1711     if (IS_TRUE_SYMOP(IC_RESULT(uic)) &&
1712         OP_SYMBOL(IC_RESULT(uic))->onStack)
1713         return ;
1714 #endif
1715
1716 #if 0
1717     /* if either one of them in far space then we cannot */
1718     if ((IS_TRUE_SYMOP(IC_LEFT(uic)) &&
1719          isOperandInFarSpace(IC_LEFT(uic))) ||
1720         (IS_TRUE_SYMOP(IC_RIGHT(uic)) &&
1721          isOperandInFarSpace(IC_RIGHT(uic))))
1722         return ;
1723 #endif
1724
1725     /* if the usage has only one operand then we can */
1726     if (IC_LEFT(uic) == NULL ||
1727         IC_RIGHT(uic) == NULL) 
1728         goto accuse;
1729
1730     /* make sure this is on the left side if not
1731        a '+' since '+' is commutative */
1732     if (ic->op != '+' &&
1733         IC_LEFT(uic)->key != IC_RESULT(ic)->key)
1734         return;
1735
1736     /* if one of them is a literal then we can */
1737     if ((IC_LEFT(uic) && IS_OP_LITERAL(IC_LEFT(uic))) ||
1738         (IC_RIGHT(uic) && IS_OP_LITERAL(IC_RIGHT(uic)))) {
1739         OP_SYMBOL(IC_RESULT(ic))->accuse = 1;
1740         return ;
1741     }
1742
1743     /** This is confusing :)  Guess for now */
1744     if (IC_LEFT(uic)->key == IC_RESULT(ic)->key &&
1745         (IS_ITEMP(IC_RIGHT(uic)) ||
1746          (IS_TRUE_SYMOP(IC_RIGHT(uic)))))
1747         goto accuse;
1748     
1749     if (IC_RIGHT(uic)->key == IC_RESULT(ic)->key &&
1750         (IS_ITEMP(IC_LEFT(uic)) ||
1751          (IS_TRUE_SYMOP(IC_LEFT(uic)))))
1752         goto accuse ;
1753     return ;
1754  accuse:
1755     OP_SYMBOL(IC_RESULT(ic))->accuse = 1;
1756 }
1757
1758 bool opPreservesA(iCode *ic, iCode *uic)
1759 {
1760     /* if the usage has only one operand then we can */
1761     if (IC_LEFT(ic) == NULL ||
1762         IC_RIGHT(ic) == NULL) 
1763         return TRUE;
1764
1765     if (uic->op != '=' && 
1766         !IS_ARITHMETIC_OP(uic) &&
1767         !IS_BITWISE_OP(uic)    &&
1768         uic->op != EQ_OP &&
1769         uic->op != LEFT_OP &&
1770         uic->op != RIGHT_OP ) {
1771         return FALSE;
1772     }
1773
1774     /* PENDING */
1775     if (!IC_LEFT(uic) || !IC_RESULT(ic))
1776         return FALSE;
1777
1778     /** This is confusing :)  Guess for now */
1779     if (IC_LEFT(uic)->key == IC_RESULT(ic)->key &&
1780         (IS_ITEMP(IC_RIGHT(uic)) ||
1781          (IS_TRUE_SYMOP(IC_RIGHT(uic)))))
1782         return TRUE;
1783     
1784     if (IC_RIGHT(uic)->key == IC_RESULT(ic)->key &&
1785         (IS_ITEMP(IC_LEFT(uic)) ||
1786          (IS_TRUE_SYMOP(IC_LEFT(uic)))))
1787         return TRUE;
1788
1789     return FALSE;
1790 }
1791
1792 /** Pack registers for acc use.
1793     When the result of this operation is small and short lived it may
1794     be able to be stored in the accumelator.
1795  */
1796 static void packRegsForAccUse2(iCode *ic)
1797 {
1798     iCode *uic;
1799     
1800     /* if + or - then it has to be one byte result.
1801        MLH: Ok.
1802      */
1803     if ((ic->op == '+' || ic->op == '-')
1804         && getSize(operandType(IC_RESULT(ic))) > 1)
1805         return ;
1806     
1807     /* if shift operation make sure right side is not a literal.
1808        MLH: depends.
1809      */
1810 #if 0
1811     if (ic->op == RIGHT_OP  &&
1812         (isOperandLiteral(IC_RIGHT(ic)) ||
1813           getSize(operandType(IC_RESULT(ic))) > 1))
1814         return ;
1815         
1816     if (ic->op == LEFT_OP &&        
1817         ( isOperandLiteral(IC_RIGHT(ic)) ||
1818           getSize(operandType(IC_RESULT(ic))) > 1))
1819         return ;
1820 #endif
1821         
1822     /* has only one definition */
1823     if (bitVectnBitsOn(OP_DEFS(IC_RESULT(ic))) > 1) {
1824         return;
1825     }
1826
1827     /* Right.  We may be able to propagate it through if:
1828        For each in the chain of uses the intermediate is OK.
1829     */
1830     /* Get next with 'uses result' bit on
1831        If this->next == next
1832          Validate use of next
1833          If OK, increase count
1834     */
1835     /* and the usage immediately follows this iCode */
1836     if (!(uic = hTabItemWithKey(iCodehTab,
1837                                 bitVectFirstBit(OP_USES(IC_RESULT(ic)))))) {
1838         return;
1839     }
1840
1841     {
1842         /* Create a copy of the OP_USES bit vect */
1843         bitVect *uses = bitVectCopy(OP_USES(IC_RESULT(ic)));
1844         int setBit;
1845         iCode *scan = ic, *next;
1846
1847         do {
1848             setBit = bitVectFirstBit(uses);
1849             next = hTabItemWithKey(iCodehTab, setBit);
1850             if (scan->next == next) {
1851                 bitVectUnSetBit(uses, setBit);
1852                 /* Still contigous. */
1853                 if (!opPreservesA(ic, next)) {
1854                     return;
1855                 }
1856                 scan = next;
1857             }
1858             else {
1859                 return;
1860             }
1861         } while (!bitVectIsZero(uses));
1862         OP_SYMBOL(IC_RESULT(ic))->accuse = 1;
1863         return;
1864     }
1865
1866     /* OLD CODE FOLLOWS */
1867     /* if it is a conditional branch then we definitely can
1868        MLH: Depends.
1869      */
1870 #if 0    
1871     if (uic->op == IFX ) 
1872         goto accuse;
1873
1874     /* MLH: Depends. */
1875     if ( uic->op == JUMPTABLE )
1876         return ;
1877 #endif
1878
1879     /* if the usage is not is an assignment or an 
1880        arithmetic / bitwise / shift operation then not.
1881        MLH: Pending:  Invalid.  Our pointer sets are always peechy.
1882  */
1883 #if 0
1884     if (POINTER_SET(uic) && 
1885         getSize(aggrToPtr(operandType(IC_RESULT(uic)),FALSE)) > 1) {
1886         printf("e5 %u\n", getSize(aggrToPtr(operandType(IC_RESULT(uic)),FALSE)));
1887         return;
1888     }
1889 #endif
1890
1891     printf("1\n");
1892     if (uic->op != '=' && 
1893         !IS_ARITHMETIC_OP(uic) &&
1894         !IS_BITWISE_OP(uic)    &&
1895         uic->op != LEFT_OP &&
1896         uic->op != RIGHT_OP ) {
1897         printf("e6\n");
1898         return;
1899     }
1900
1901     /* if used in ^ operation then make sure right is not a 
1902        literl */
1903     if (uic->op == '^' && isOperandLiteral(IC_RIGHT(uic)))
1904         return ;
1905
1906     /* if shift operation make sure right side is not a literal */
1907     if (uic->op == RIGHT_OP  &&
1908         ( isOperandLiteral(IC_RIGHT(uic)) ||
1909           getSize(operandType(IC_RESULT(uic))) > 1))
1910         return ;
1911
1912     if (uic->op == LEFT_OP &&        
1913         ( isOperandLiteral(IC_RIGHT(uic)) ||
1914           getSize(operandType(IC_RESULT(uic))) > 1))
1915         return ;
1916             
1917 #if 0
1918     /* make sure that the result of this icode is not on the
1919        stack, since acc is used to compute stack offset */
1920     if (IS_TRUE_SYMOP(IC_RESULT(uic)) &&
1921         OP_SYMBOL(IC_RESULT(uic))->onStack)
1922         return ;
1923 #endif
1924
1925 #if 0
1926     /* if either one of them in far space then we cannot */
1927     if ((IS_TRUE_SYMOP(IC_LEFT(uic)) &&
1928          isOperandInFarSpace(IC_LEFT(uic))) ||
1929         (IS_TRUE_SYMOP(IC_RIGHT(uic)) &&
1930          isOperandInFarSpace(IC_RIGHT(uic))))
1931         return ;
1932 #endif
1933
1934     /* if the usage has only one operand then we can */
1935     if (IC_LEFT(uic) == NULL ||
1936         IC_RIGHT(uic) == NULL) 
1937         goto accuse;
1938
1939     /* make sure this is on the left side if not
1940        a '+' since '+' is commutative */
1941     if (ic->op != '+' &&
1942         IC_LEFT(uic)->key != IC_RESULT(ic)->key)
1943         return;
1944
1945     /* if one of them is a literal then we can */
1946     if ((IC_LEFT(uic) && IS_OP_LITERAL(IC_LEFT(uic))) ||
1947         (IC_RIGHT(uic) && IS_OP_LITERAL(IC_RIGHT(uic)))) {
1948         OP_SYMBOL(IC_RESULT(ic))->accuse = 1;
1949         return ;
1950     }
1951
1952     /** This is confusing :)  Guess for now */
1953     if (IC_LEFT(uic)->key == IC_RESULT(ic)->key &&
1954         (IS_ITEMP(IC_RIGHT(uic)) ||
1955          (IS_TRUE_SYMOP(IC_RIGHT(uic)))))
1956         goto accuse;
1957     
1958     if (IC_RIGHT(uic)->key == IC_RESULT(ic)->key &&
1959         (IS_ITEMP(IC_LEFT(uic)) ||
1960          (IS_TRUE_SYMOP(IC_LEFT(uic)))))
1961         goto accuse ;
1962     return ;
1963  accuse:
1964     printf("acc ok!\n");
1965     OP_SYMBOL(IC_RESULT(ic))->accuse = 1;
1966 }
1967
1968 /** Does some transformations to reduce register pressure.
1969  */
1970 static void packRegisters (eBBlock *ebp)
1971 {
1972     iCode *ic ;
1973     int change = 0 ;
1974     
1975     while (1) {
1976         change = 0;
1977         /* look for assignments of the form */
1978         /* iTempNN = TRueSym (someoperation) SomeOperand */
1979         /*       ....                       */
1980         /* TrueSym := iTempNN:1             */
1981         for ( ic = ebp->sch ; ic ; ic = ic->next ) {
1982             /* find assignment of the form TrueSym := iTempNN:1 */
1983             if (ic->op == '=' && !POINTER_SET(ic))
1984                 change += packRegsForAssign(ic,ebp);
1985         }
1986         if (!change)
1987             break;
1988     }
1989
1990     for ( ic = ebp->sch ; ic ; ic = ic->next ) {
1991         /* Safe: address of a true sym is always constant. */
1992         /* if this is an itemp & result of a address of a true sym 
1993            then mark this as rematerialisable   */
1994         if (ic->op == ADDRESS_OF && 
1995             IS_ITEMP(IC_RESULT(ic)) &&
1996             IS_TRUE_SYMOP(IC_LEFT(ic)) &&
1997             bitVectnBitsOn(OP_DEFS(IC_RESULT(ic))) == 1 &&
1998             !OP_SYMBOL(IC_LEFT(ic))->onStack ) {
1999
2000             OP_SYMBOL(IC_RESULT(ic))->remat = 1;
2001             OP_SYMBOL(IC_RESULT(ic))->rematiCode = ic;
2002             OP_SYMBOL(IC_RESULT(ic))->usl.spillLoc = NULL;
2003         }
2004
2005         /* Safe: just propagates the remat flag */
2006         /* if straight assignment then carry remat flag if this is the
2007            only definition */
2008         if (ic->op == '='    && 
2009             !POINTER_SET(ic) &&
2010             IS_SYMOP(IC_RIGHT(ic)) && 
2011             OP_SYMBOL(IC_RIGHT(ic))->remat &&
2012             bitVectnBitsOn(OP_SYMBOL(IC_RESULT(ic))->defs) <= 1) {
2013
2014             OP_SYMBOL(IC_RESULT(ic))->remat = 
2015                 OP_SYMBOL(IC_RIGHT(ic))->remat;
2016             OP_SYMBOL(IC_RESULT(ic))->rematiCode = 
2017                 OP_SYMBOL(IC_RIGHT(ic))->rematiCode ;
2018         }
2019
2020         /* if the condition of an if instruction is defined in the
2021            previous instruction then mark the itemp as a conditional */
2022         if ((IS_CONDITIONAL(ic) ||
2023              ( ( ic->op == BITWISEAND      ||
2024                  ic->op == '|'             ||
2025                  ic->op == '^' ) &&
2026                isBitwiseOptimizable(ic))) &&        
2027             ic->next && ic->next->op == IFX &&
2028             isOperandEqual(IC_RESULT(ic),IC_COND(ic->next)) &&
2029             OP_SYMBOL(IC_RESULT(ic))->liveTo <= ic->next->seq) {
2030             
2031             OP_SYMBOL(IC_RESULT(ic))->regType = REG_CND;            
2032             continue ;
2033         }
2034
2035 #if 0
2036         /* reduce for support function calls */
2037         if (ic->supportRtn || ic->op == '+' || ic->op == '-' )
2038             packRegsForSupport(ic,ebp); 
2039 #endif
2040
2041 #if 0
2042         /* some cases the redundant moves can
2043            can be eliminated for return statements */
2044         if ((ic->op == RETURN || ic->op == SEND) &&
2045             !isOperandInFarSpace(IC_LEFT(ic))    &&
2046             !options.model)
2047             packRegsForOneuse (ic,IC_LEFT(ic),ebp);     
2048 #endif
2049
2050         /* if pointer set & left has a size more than
2051            one and right is not in far space */
2052         if (POINTER_SET(ic)                    &&
2053             /* MLH: no such thing.
2054                !isOperandInFarSpace(IC_RIGHT(ic)) && */
2055             !OP_SYMBOL(IC_RESULT(ic))->remat   &&
2056             !IS_OP_RUONLY(IC_RIGHT(ic))        &&
2057             getSize(aggrToPtr(operandType(IC_RESULT(ic)),FALSE)) > 1 )
2058
2059             packRegsForOneuse (ic,IC_RESULT(ic),ebp);
2060
2061         /* if pointer get */
2062         if (POINTER_GET(ic)                    &&
2063             /* MLH: dont have far space
2064                !isOperandInFarSpace(IC_RESULT(ic))&& */
2065             !OP_SYMBOL(IC_LEFT(ic))->remat     &&
2066             !IS_OP_RUONLY(IC_RESULT(ic))         &&
2067             getSize(aggrToPtr(operandType(IC_LEFT(ic)),FALSE)) > 1 )
2068             packRegsForOneuse (ic,IC_LEFT(ic),ebp);
2069
2070         /* pack registers for accumulator use, when the result of an
2071            arithmetic or bit wise operation has only one use, that use is
2072            immediately following the defintion and the using iCode has
2073            only one operand or has two operands but one is literal & the
2074            result of that operation is not on stack then we can leave the
2075            result of this operation in acc:b combination */
2076 #if 0
2077         if ((IS_ARITHMETIC_OP(ic) 
2078              || IS_BITWISE_OP(ic)
2079              || ic->op == LEFT_OP || ic->op == RIGHT_OP
2080              ) &&
2081             IS_ITEMP(IC_RESULT(ic)) &&
2082             getSize(operandType(IC_RESULT(ic))) <= 2)
2083             packRegsForAccUse (ic);
2084 #else
2085         if ((POINTER_GET(ic) ||
2086              IS_ARITHMETIC_OP(ic) ||
2087              IS_BITWISE_OP(ic) ||
2088              ic->op == LEFT_OP ||
2089              ic->op == RIGHT_OP
2090              ) &&
2091             IS_ITEMP(IC_RESULT(ic)) &&
2092             getSize(operandType(IC_RESULT(ic))) == 1)
2093             packRegsForAccUse2(ic);
2094 #endif
2095     }
2096 }
2097   
2098 /*-----------------------------------------------------------------*/
2099 /* assignRegisters - assigns registers to each live range as need  */
2100 /*-----------------------------------------------------------------*/
2101 void z80_assignRegisters (eBBlock **ebbs, int count)
2102 {
2103     iCode *ic;
2104     int i ;
2105
2106     setToNull((void *)&funcrUsed);
2107     ptrRegReq = stackExtend = dataExtend = 0;
2108
2109     /* change assignments this will remove some
2110        live ranges reducing some register pressure */
2111     for (i = 0 ; i < count ;i++ )
2112         packRegisters (ebbs[i]);
2113
2114     if (options.dump_pack)
2115         dumpEbbsToFileExt(".dumppack",ebbs,count);
2116
2117     /* first determine for each live range the number of 
2118        registers & the type of registers required for each */
2119     regTypeNum ();
2120     
2121     /* and serially allocate registers */ 
2122     serialRegAssign(ebbs,count);
2123
2124     /* if stack was extended then tell the user */
2125     if (stackExtend) {
2126 /*      werror(W_TOOMANY_SPILS,"stack", */
2127 /*             stackExtend,currFunc->name,""); */
2128         stackExtend = 0 ;
2129     }
2130
2131     if (dataExtend) {
2132 /*      werror(W_TOOMANY_SPILS,"data space", */
2133 /*             dataExtend,currFunc->name,""); */
2134         dataExtend = 0 ;
2135     }
2136
2137     if (options.dump_rassgn)
2138         dumpEbbsToFileExt(".dumprassgn",ebbs,count);
2139
2140     /* after that create the register mask
2141        for each of the instruction */
2142     createRegMask (ebbs,count);
2143
2144     /* now get back the chain */
2145     ic = iCodeLabelOptimize(iCodeFromeBBlock (ebbs,count));
2146
2147     /* redo that offsets for stacked automatic variables */
2148     redoStackOffsets ();
2149
2150     genZ80Code(ic);
2151
2152     /* free up any stackSpil locations allocated */   
2153     applyToSet(stackSpil,deallocStackSpil);
2154     slocNum = 0;
2155     setToNull((void **)&stackSpil);
2156     setToNull((void **)&spiltSet);
2157     /* mark all registers as free */
2158     freeAllRegs();
2159
2160     return ;
2161 }