Added statics
[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
1281         /* if there is a function call and this is
1282            a parameter & not my parameter then don't pack it */
1283         if ( (dic->op == CALL || dic->op == PCALL) &&
1284              (OP_SYMBOL(IC_RESULT(ic))->_isparm &&
1285               !OP_SYMBOL(IC_RESULT(ic))->ismyparm)) {
1286             dic = NULL;
1287             break;
1288         }
1289
1290         if (SKIP_IC2(dic))
1291             continue;
1292
1293 #if 0   
1294         if (IS_SYMOP(IC_RESULT(dic)) &&
1295             IC_RESULT(dic)->key == IC_RIGHT(ic)->key) {
1296             if (POINTER_SET(dic))
1297                 dic = NULL;
1298             break;          
1299         }
1300
1301         if (IS_SYMOP(IC_RIGHT(dic)) && 
1302             (IC_RIGHT(dic)->key == IC_RESULT(ic)->key ||
1303              IC_RIGHT(dic)->key == IC_RIGHT(ic)->key)) {
1304             dic = NULL;
1305             break;
1306         }
1307         
1308         if (IS_SYMOP(IC_LEFT(dic)) && 
1309             (IC_LEFT(dic)->key == IC_RESULT(ic)->key ||
1310              IC_LEFT(dic)->key == IC_RIGHT(ic)->key)) {
1311             dic = NULL;
1312             break;
1313         }
1314         if (POINTER_SET(dic) && 
1315             IC_RESULT(dic)->key == IC_RESULT(ic)->key ) {
1316             dic = NULL ;
1317             break;
1318         }
1319 #endif
1320     }
1321     
1322     if (!dic)
1323         return 0 ; /* did not find */
1324             
1325     /* if the result is on stack or iaccess then it must be
1326        the same atleast one of the operands */
1327     if (OP_SYMBOL(IC_RESULT(ic))->onStack  || 
1328         OP_SYMBOL(IC_RESULT(ic))->iaccess ) {
1329         
1330         /* the operation has only one symbol
1331            operator then we can pack */
1332         if ((IC_LEFT(dic) && !IS_SYMOP(IC_LEFT(dic))) ||
1333             (IC_RIGHT(dic) && !IS_SYMOP(IC_RIGHT(dic))))
1334             goto pack;
1335
1336         if (!((IC_LEFT(dic) &&
1337              IC_RESULT(ic)->key == IC_LEFT(dic)->key) ||
1338               (IC_RIGHT(dic) &&
1339                IC_RESULT(ic)->key == IC_RIGHT(dic)->key)))
1340             return 0;                
1341     }
1342 pack:
1343     /* found the definition */
1344     /* replace the result with the result of */
1345     /* this assignment and remove this assignment */
1346     IC_RESULT(dic) = IC_RESULT(ic) ;
1347
1348     if (IS_ITEMP(IC_RESULT(dic)) && OP_SYMBOL(IC_RESULT(dic))->liveFrom > dic->seq) {
1349             OP_SYMBOL(IC_RESULT(dic))->liveFrom = dic->seq;
1350     }
1351     /* delete from liverange table also 
1352        delete from all the points inbetween and the new
1353        one */
1354     for ( sic = dic; sic != ic ; sic = sic->next ) {    
1355         bitVectUnSetBit(sic->rlive,IC_RESULT(ic)->key);
1356         if (IS_ITEMP(IC_RESULT(dic)))
1357             bitVectSetBit(sic->rlive,IC_RESULT(dic)->key);
1358     }
1359         
1360     remiCodeFromeBBlock(ebp,ic);
1361     return 1;
1362     
1363 }
1364
1365 /** Scanning backwards looks for first assig found.
1366  */
1367 iCode *findAssignToSym (operand *op,iCode *ic)
1368 {
1369     iCode *dic;
1370
1371     for (dic = ic->prev ; dic ; dic = dic->prev) {
1372         
1373         /* if definition by assignment */
1374         if (dic->op == '='                 && 
1375             !POINTER_SET(dic)              &&
1376             IC_RESULT(dic)->key == op->key)
1377             /*      &&  IS_TRUE_SYMOP(IC_RIGHT(dic))*/
1378             {      
1379
1380             /* we are interested only if defined in far space */
1381             /* or in stack space in case of + & - */
1382
1383             /* if assigned to a non-symbol then return
1384                true */
1385             if (!IS_SYMOP(IC_RIGHT(dic)))
1386                 break ;
1387
1388             /* if the symbol is in far space then
1389                we should not */
1390             if (isOperandInFarSpace(IC_RIGHT(dic)))
1391                 return NULL ;
1392
1393             /* for + & - operations make sure that
1394                if it is on the stack it is the same
1395                as one of the three operands */
1396             if ((ic->op == '+' || ic->op == '-') &&
1397                 OP_SYMBOL(IC_RIGHT(dic))->onStack) {
1398
1399                 if ( IC_RESULT(ic)->key != IC_RIGHT(dic)->key &&
1400                      IC_LEFT(ic)->key   != IC_RIGHT(dic)->key &&
1401                      IC_RIGHT(ic)->key  != IC_RIGHT(dic)->key)
1402                     return NULL;
1403             }           
1404
1405             break ;
1406                 
1407         }
1408
1409         /* if we find an usage then we cannot delete it */
1410         if (IC_LEFT(dic) && IC_LEFT(dic)->key == op->key)
1411             return NULL;
1412             
1413         if (IC_RIGHT(dic) && IC_RIGHT(dic)->key == op->key)
1414             return NULL;
1415
1416         if (POINTER_SET(dic) && IC_RESULT(dic)->key == op->key)
1417             return NULL;
1418     }
1419
1420     /* now make sure that the right side of dic
1421        is not defined between ic & dic */       
1422     if (dic) {
1423         iCode *sic = dic->next ;
1424
1425         for (; sic != ic ; sic = sic->next)
1426             if (IC_RESULT(sic) &&
1427                 IC_RESULT(sic)->key == IC_RIGHT(dic)->key)
1428                 return NULL;
1429     }
1430
1431     return dic;
1432         
1433         
1434 }
1435
1436 #if 0
1437 /*-----------------------------------------------------------------*/
1438 /* packRegsForSupport :- reduce some registers for support calls   */
1439 /*-----------------------------------------------------------------*/
1440 static int packRegsForSupport (iCode *ic, eBBlock *ebp)
1441 {
1442     int change = 0 ;
1443     /* for the left & right operand :- look to see if the
1444        left was assigned a true symbol in far space in that
1445        case replace them */
1446     if (IS_ITEMP(IC_LEFT(ic)) && 
1447         OP_SYMBOL(IC_LEFT(ic))->liveTo <= ic->seq) {
1448         iCode *dic = findAssignToSym(IC_LEFT(ic),ic);
1449         iCode *sic;
1450
1451         if (!dic)
1452             goto right ;
1453
1454         /* found it we need to remove it from the
1455            block */
1456         for ( sic = dic; sic != ic ; sic = sic->next )
1457             bitVectUnSetBit(sic->rlive,IC_LEFT(ic)->key);
1458
1459         IC_LEFT(ic)->operand.symOperand =
1460             IC_RIGHT(dic)->operand.symOperand;
1461         IC_LEFT(ic)->key = IC_RIGHT(dic)->operand.symOperand->key;
1462         remiCodeFromeBBlock(ebp,dic);   
1463         change++;      
1464     }
1465     
1466     /* do the same for the right operand */
1467  right:    
1468     if (!change && 
1469         IS_ITEMP(IC_RIGHT(ic)) &&
1470         OP_SYMBOL(IC_RIGHT(ic))->liveTo <= ic->seq) {
1471         iCode *dic = findAssignToSym(IC_RIGHT(ic),ic);
1472         iCode *sic;
1473         
1474         if (!dic)
1475             return change ;
1476
1477         /* found it we need to remove it from the block */
1478         for ( sic = dic; sic != ic ; sic = sic->next )
1479             bitVectUnSetBit(sic->rlive,IC_RIGHT(ic)->key);
1480         
1481         IC_RIGHT(ic)->operand.symOperand =
1482             IC_RIGHT(dic)->operand.symOperand;
1483         IC_RIGHT(ic)->key = IC_RIGHT(dic)->operand.symOperand->key;
1484         
1485         remiCodeFromeBBlock(ebp,dic);
1486         change ++;
1487     }
1488    
1489     return change ;
1490 }
1491 #endif
1492
1493 #define IS_OP_RUONLY(x) (x && IS_SYMOP(x) && OP_SYMBOL(x)->ruonly)
1494
1495 /** Will reduce some registers for single use.
1496  */
1497 static iCode *packRegsForOneuse (iCode *ic, operand *op , eBBlock *ebp)
1498 {
1499     bitVect *uses ;
1500     iCode *dic, *sic;
1501
1502     /* if returning a literal then do nothing */
1503     if (!IS_SYMOP(op))
1504         return NULL;
1505     
1506     /* only upto 2 bytes since we cannot predict
1507        the usage of b, & acc */
1508     if (getSize(operandType(op)) > 2 && 
1509         ic->op != RETURN             &&
1510         ic->op != SEND)
1511         return NULL;
1512
1513     /* this routine will mark the a symbol as used in one 
1514        instruction use only && if the defintion is local 
1515        (ie. within the basic block) && has only one definition &&
1516        that definiion is either a return value from a 
1517        function or does not contain any variables in
1518        far space */
1519     uses = bitVectCopy(OP_USES(op));
1520     bitVectUnSetBit(uses,ic->key); /* take away this iCode */
1521     if (!bitVectIsZero(uses)) /* has other uses */
1522         return NULL ;
1523     
1524     /* if it has only one defintion */
1525     if (bitVectnBitsOn(OP_DEFS(op)) > 1)
1526         return NULL ; /* has more than one definition */
1527
1528     /* get the that definition */
1529     if (!(dic = 
1530           hTabItemWithKey(iCodehTab,
1531                           bitVectFirstBit(OP_DEFS(op)))))
1532         return NULL ;
1533
1534     /* found the definition now check if it is local */
1535     if (dic->seq < ebp->fSeq ||
1536         dic->seq > ebp->lSeq)
1537         return NULL ; /* non-local */
1538
1539     /* now check if it is the return from a function call */
1540     if (dic->op == CALL || dic->op == PCALL ) {
1541         if (ic->op != SEND && ic->op != RETURN) {
1542             OP_SYMBOL(op)->ruonly = 1;
1543             return dic;
1544         }
1545         dic = dic->next ;
1546     }
1547         
1548     /* otherwise check that the definition does
1549        not contain any symbols in far space */
1550     if (isOperandInFarSpace(IC_LEFT(dic))  ||
1551         isOperandInFarSpace(IC_RIGHT(dic)) ||
1552         IS_OP_RUONLY(IC_LEFT(ic))          ||
1553         IS_OP_RUONLY(IC_RIGHT(ic)) )        {
1554         return NULL;
1555     }
1556     
1557     /* if pointer set then make sure the pointer is one byte */
1558     if (POINTER_SET(dic))
1559       return NULL;
1560
1561     if (POINTER_GET(dic))
1562       return NULL;
1563     
1564     sic = dic;
1565
1566     /* also make sure the intervenening instructions
1567        don't have any thing in far space */
1568     for (dic = dic->next ; dic && dic != ic ; dic = dic->next) {
1569         /* if there is an intervening function call then no */
1570         if (dic->op == CALL || dic->op == PCALL)
1571                 return NULL;
1572         /* if pointer set then make sure the pointer
1573            is one byte */
1574         if (POINTER_SET(dic))
1575             return NULL ;
1576         
1577         if (POINTER_GET(dic))
1578             return NULL ;
1579
1580         /* if address of & the result is remat the okay */
1581         if (dic->op == ADDRESS_OF &&
1582             OP_SYMBOL(IC_RESULT(dic))->remat)
1583             continue ;
1584            
1585         /* if left or right or result is in far space */
1586         if (isOperandInFarSpace(IC_LEFT(dic))   ||
1587             isOperandInFarSpace(IC_RIGHT(dic))  ||
1588             isOperandInFarSpace(IC_RESULT(dic)) ||
1589             IS_OP_RUONLY(IC_LEFT(dic))          ||
1590             IS_OP_RUONLY(IC_RIGHT(dic))         ||
1591             IS_OP_RUONLY(IC_RESULT(dic))            ) {
1592             return NULL;
1593         }
1594     }
1595                 
1596     OP_SYMBOL(op)->ruonly = 1;
1597     return sic;
1598 }
1599
1600 /*-----------------------------------------------------------------*/
1601 /* isBitwiseOptimizable - requirements of JEAN LOUIS VERN          */
1602 /*-----------------------------------------------------------------*/
1603 static bool isBitwiseOptimizable (iCode *ic)
1604 {
1605     link *rtype = getSpec(operandType(IC_RIGHT(ic)));
1606
1607     /* bitwise operations are considered optimizable
1608        under the following conditions (Jean-Louis VERN) 
1609        
1610        x & lit
1611        bit & bit
1612        bit & x
1613        bit ^ bit
1614        bit ^ x
1615        x   ^ lit
1616        x   | lit
1617        bit | bit
1618        bit | x
1619     */    
1620     if (IS_LITERAL(rtype))
1621         return TRUE;
1622     return FALSE; 
1623 }
1624
1625 /** Optimisations:
1626     Certian assignments involving pointers can be temporarly stored
1627     in HL.  Esp.
1628 genAssign
1629     ld  iy,#_Blah
1630     ld  bc,(iy)
1631 genAssign (ptr)
1632     ld  hl,bc
1633     ld  iy,#_Blah2
1634     ld  (iy),(hl)
1635 */
1636
1637 /** Pack registers for acc use.
1638     When the result of this operation is small and short lived it may
1639     be able to be stored in the accumelator.
1640  */
1641 static void packRegsForAccUse (iCode *ic)
1642 {
1643     iCode *uic;
1644     
1645     /* if + or - then it has to be one byte result */
1646     if ((ic->op == '+' || ic->op == '-')
1647         && getSize(operandType(IC_RESULT(ic))) > 1)
1648         return ;
1649     
1650     /* if shift operation make sure right side is not a literal */
1651     if (ic->op == RIGHT_OP  &&
1652         (isOperandLiteral(IC_RIGHT(ic)) ||
1653           getSize(operandType(IC_RESULT(ic))) > 1))
1654         return ;
1655         
1656     if (ic->op == LEFT_OP &&        
1657         ( isOperandLiteral(IC_RIGHT(ic)) ||
1658           getSize(operandType(IC_RESULT(ic))) > 1))
1659         return ;
1660         
1661     /* has only one definition */
1662     if (bitVectnBitsOn(OP_DEFS(IC_RESULT(ic))) > 1)
1663         return ;
1664
1665     /* has only one use */
1666     if (bitVectnBitsOn(OP_USES(IC_RESULT(ic))) > 1)
1667         return ;
1668
1669     /* and the usage immediately follows this iCode */
1670     if (!(uic = hTabItemWithKey(iCodehTab,
1671                                 bitVectFirstBit(OP_USES(IC_RESULT(ic))))))
1672         return ;
1673
1674     if (ic->next != uic)
1675         return ;
1676     
1677     /* if it is a conditional branch then we definitely can */
1678     if (uic->op == IFX  ) 
1679         goto accuse;
1680
1681     if ( uic->op == JUMPTABLE )
1682         return ;
1683
1684 #if 0
1685     /* if the usage is not is an assignment or an 
1686        arithmetic / bitwise / shift operation then not */
1687     if (POINTER_SET(uic) && 
1688         getSize(aggrToPtr(operandType(IC_RESULT(uic)),FALSE)) > 1)
1689         return;
1690 #endif
1691
1692     if (uic->op != '=' && 
1693         !IS_ARITHMETIC_OP(uic) &&
1694         !IS_BITWISE_OP(uic)    &&
1695         uic->op != LEFT_OP &&
1696         uic->op != RIGHT_OP )
1697         return;
1698
1699     /* if used in ^ operation then make sure right is not a 
1700        literl */
1701     if (uic->op == '^' && isOperandLiteral(IC_RIGHT(uic)))
1702         return ;
1703
1704     /* if shift operation make sure right side is not a literal */
1705     if (uic->op == RIGHT_OP  &&
1706         ( isOperandLiteral(IC_RIGHT(uic)) ||
1707           getSize(operandType(IC_RESULT(uic))) > 1))
1708         return ;
1709
1710     if (uic->op == LEFT_OP &&        
1711         ( isOperandLiteral(IC_RIGHT(uic)) ||
1712           getSize(operandType(IC_RESULT(uic))) > 1))
1713         return ;
1714             
1715 #if 0
1716     /* make sure that the result of this icode is not on the
1717        stack, since acc is used to compute stack offset */
1718     if (IS_TRUE_SYMOP(IC_RESULT(uic)) &&
1719         OP_SYMBOL(IC_RESULT(uic))->onStack)
1720         return ;
1721 #endif
1722
1723 #if 0
1724     /* if either one of them in far space then we cannot */
1725     if ((IS_TRUE_SYMOP(IC_LEFT(uic)) &&
1726          isOperandInFarSpace(IC_LEFT(uic))) ||
1727         (IS_TRUE_SYMOP(IC_RIGHT(uic)) &&
1728          isOperandInFarSpace(IC_RIGHT(uic))))
1729         return ;
1730 #endif
1731
1732     /* if the usage has only one operand then we can */
1733     if (IC_LEFT(uic) == NULL ||
1734         IC_RIGHT(uic) == NULL) 
1735         goto accuse;
1736
1737     /* make sure this is on the left side if not
1738        a '+' since '+' is commutative */
1739     if (ic->op != '+' &&
1740         IC_LEFT(uic)->key != IC_RESULT(ic)->key)
1741         return;
1742
1743     /* if one of them is a literal then we can */
1744     if ((IC_LEFT(uic) && IS_OP_LITERAL(IC_LEFT(uic))) ||
1745         (IC_RIGHT(uic) && IS_OP_LITERAL(IC_RIGHT(uic)))) {
1746         OP_SYMBOL(IC_RESULT(ic))->accuse = 1;
1747         return ;
1748     }
1749
1750     /** This is confusing :)  Guess for now */
1751     if (IC_LEFT(uic)->key == IC_RESULT(ic)->key &&
1752         (IS_ITEMP(IC_RIGHT(uic)) ||
1753          (IS_TRUE_SYMOP(IC_RIGHT(uic)))))
1754         goto accuse;
1755     
1756     if (IC_RIGHT(uic)->key == IC_RESULT(ic)->key &&
1757         (IS_ITEMP(IC_LEFT(uic)) ||
1758          (IS_TRUE_SYMOP(IC_LEFT(uic)))))
1759         goto accuse ;
1760     return ;
1761  accuse:
1762     OP_SYMBOL(IC_RESULT(ic))->accuse = 1;
1763 }
1764
1765 /** Does some transformations to reduce register pressure.
1766  */
1767 static void packRegisters (eBBlock *ebp)
1768 {
1769     iCode *ic ;
1770     int change = 0 ;
1771     
1772     while (1) {
1773         change = 0;
1774         /* look for assignments of the form */
1775         /* iTempNN = TRueSym (someoperation) SomeOperand */
1776         /*       ....                       */
1777         /* TrueSym := iTempNN:1             */
1778         for ( ic = ebp->sch ; ic ; ic = ic->next ) {
1779             /* find assignment of the form TrueSym := iTempNN:1 */
1780             if (ic->op == '=' && !POINTER_SET(ic))
1781                 change += packRegsForAssign(ic,ebp);
1782         }
1783         if (!change)
1784             break;
1785     }
1786
1787     for ( ic = ebp->sch ; ic ; ic = ic->next ) {
1788         /* Safe: address of a true sym is always constant. */
1789         /* if this is an itemp & result of a address of a true sym 
1790            then mark this as rematerialisable   */
1791         if (ic->op == ADDRESS_OF && 
1792             IS_ITEMP(IC_RESULT(ic)) &&
1793             IS_TRUE_SYMOP(IC_LEFT(ic)) &&
1794             bitVectnBitsOn(OP_DEFS(IC_RESULT(ic))) == 1 &&
1795             !OP_SYMBOL(IC_LEFT(ic))->onStack ) {
1796
1797             OP_SYMBOL(IC_RESULT(ic))->remat = 1;
1798             OP_SYMBOL(IC_RESULT(ic))->rematiCode = ic;
1799             OP_SYMBOL(IC_RESULT(ic))->usl.spillLoc = NULL;
1800         }
1801
1802         /* Safe: just propagates the remat flag */
1803         /* if straight assignment then carry remat flag if this is the
1804            only definition */
1805         if (ic->op == '='    && 
1806             !POINTER_SET(ic) &&
1807             IS_SYMOP(IC_RIGHT(ic)) && 
1808             OP_SYMBOL(IC_RIGHT(ic))->remat &&
1809             bitVectnBitsOn(OP_SYMBOL(IC_RESULT(ic))->defs) <= 1) {
1810
1811             OP_SYMBOL(IC_RESULT(ic))->remat = 
1812                 OP_SYMBOL(IC_RIGHT(ic))->remat;
1813             OP_SYMBOL(IC_RESULT(ic))->rematiCode = 
1814                 OP_SYMBOL(IC_RIGHT(ic))->rematiCode ;
1815         }
1816
1817         /* if the condition of an if instruction is defined in the
1818            previous instruction then mark the itemp as a conditional */
1819         if ((IS_CONDITIONAL(ic) ||
1820              ( ( ic->op == BITWISEAND      ||
1821                  ic->op == '|'             ||
1822                  ic->op == '^' ) &&
1823                isBitwiseOptimizable(ic))) &&        
1824             ic->next && ic->next->op == IFX &&
1825             isOperandEqual(IC_RESULT(ic),IC_COND(ic->next)) &&
1826             OP_SYMBOL(IC_RESULT(ic))->liveTo <= ic->next->seq) {
1827             
1828             OP_SYMBOL(IC_RESULT(ic))->regType = REG_CND;            
1829             continue ;
1830         }
1831
1832 #if 0
1833         /* reduce for support function calls */
1834         if (ic->supportRtn || ic->op == '+' || ic->op == '-' )
1835             packRegsForSupport(ic,ebp); 
1836 #endif
1837
1838 #if 0
1839         /* some cases the redundant moves can
1840            can be eliminated for return statements */
1841         if ((ic->op == RETURN || ic->op == SEND) &&
1842             !isOperandInFarSpace(IC_LEFT(ic))    &&
1843             !options.model)
1844             packRegsForOneuse (ic,IC_LEFT(ic),ebp);     
1845 #endif
1846
1847         /* if pointer set & left has a size more than
1848            one and right is not in far space */
1849         if (POINTER_SET(ic)                    &&
1850             /* MLH: no such thing.
1851                !isOperandInFarSpace(IC_RIGHT(ic)) && */
1852             !OP_SYMBOL(IC_RESULT(ic))->remat   &&
1853             !IS_OP_RUONLY(IC_RIGHT(ic))        &&
1854             getSize(aggrToPtr(operandType(IC_RESULT(ic)),FALSE)) > 1 )
1855
1856             packRegsForOneuse (ic,IC_RESULT(ic),ebp);
1857
1858         /* if pointer get */
1859         if (POINTER_GET(ic)                    &&
1860             /* MLH: dont have far space
1861                !isOperandInFarSpace(IC_RESULT(ic))&& */
1862             !OP_SYMBOL(IC_LEFT(ic))->remat     &&
1863             !IS_OP_RUONLY(IC_RESULT(ic))         &&
1864             getSize(aggrToPtr(operandType(IC_LEFT(ic)),FALSE)) > 1 )
1865             packRegsForOneuse (ic,IC_LEFT(ic),ebp);
1866
1867         /* pack registers for accumulator use, when the result of an
1868            arithmetic or bit wise operation has only one use, that use is
1869            immediately following the defintion and the using iCode has
1870            only one operand or has two operands but one is literal & the
1871            result of that operation is not on stack then we can leave the
1872            result of this operation in acc:b combination */
1873         if ((IS_ARITHMETIC_OP(ic) 
1874              || IS_BITWISE_OP(ic)
1875              || ic->op == LEFT_OP || ic->op == RIGHT_OP
1876              ) &&
1877             IS_ITEMP(IC_RESULT(ic)) &&
1878             getSize(operandType(IC_RESULT(ic))) <= 2)
1879             packRegsForAccUse (ic);
1880     }
1881 }
1882   
1883 /*-----------------------------------------------------------------*/
1884 /* assignRegisters - assigns registers to each live range as need  */
1885 /*-----------------------------------------------------------------*/
1886 void z80_assignRegisters (eBBlock **ebbs, int count)
1887 {
1888     iCode *ic;
1889     int i ;
1890
1891     setToNull((void *)&funcrUsed);
1892     ptrRegReq = stackExtend = dataExtend = 0;
1893
1894     /* change assignments this will remove some
1895        live ranges reducing some register pressure */
1896     for (i = 0 ; i < count ;i++ )
1897         packRegisters (ebbs[i]);
1898
1899     if (options.dump_pack)
1900         dumpEbbsToFileExt(".dumppack",ebbs,count);
1901
1902     /* first determine for each live range the number of 
1903        registers & the type of registers required for each */
1904     regTypeNum ();
1905     
1906     /* and serially allocate registers */ 
1907     serialRegAssign(ebbs,count);
1908
1909     /* if stack was extended then tell the user */
1910     if (stackExtend) {
1911 /*      werror(W_TOOMANY_SPILS,"stack", */
1912 /*             stackExtend,currFunc->name,""); */
1913         stackExtend = 0 ;
1914     }
1915
1916     if (dataExtend) {
1917 /*      werror(W_TOOMANY_SPILS,"data space", */
1918 /*             dataExtend,currFunc->name,""); */
1919         dataExtend = 0 ;
1920     }
1921
1922     if (options.dump_rassgn)
1923         dumpEbbsToFileExt(".dumprassgn",ebbs,count);
1924
1925     /* after that create the register mask
1926        for each of the instruction */
1927     createRegMask (ebbs,count);
1928
1929     /* now get back the chain */
1930     ic = iCodeLabelOptimize(iCodeFromeBBlock (ebbs,count));
1931
1932     /* redo that offsets for stacked automatic variables */
1933     redoStackOffsets ();
1934
1935     genZ80Code(ic);
1936
1937     /* free up any stackSpil locations allocated */   
1938     applyToSet(stackSpil,deallocStackSpil);
1939     slocNum = 0;
1940     setToNull((void **)&stackSpil);
1941     setToNull((void **)&spiltSet);
1942     /* mark all registers as free */
1943     freeAllRegs();
1944
1945     return ;
1946 }