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