PIC Port - Indirection works better. instrumented pic/ralloc.c to dump
[fw/sdcc] / src / pic / ralloc.c
1 /*------------------------------------------------------------------------
2
3   SDCCralloc.c - source file for register allocation. (8051) specific
4
5                 Written By -  Sandeep Dutta . sandeep.dutta@usa.net (1998)
6                 Added Pic Port T.scott Dattalo scott@dattalo.com (2000)
7
8    This program is free software; you can redistribute it and/or modify it
9    under the terms of the GNU General Public License as published by the
10    Free Software Foundation; either version 2, or (at your option) any
11    later version.
12    
13    This program is distributed in the hope that it will be useful,
14    but WITHOUT ANY WARRANTY; without even the implied warranty of
15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16    GNU General Public License for more details.
17    
18    You should have received a copy of the GNU General Public License
19    along with this program; if not, write to the Free Software
20    Foundation, 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
21    
22    In other words, you are welcome to use, share and improve this program.
23    You are forbidden to forbid anyone else to use, share and improve
24    what you give them.   Help stamp out software-hoarding!  
25 -------------------------------------------------------------------------*/
26
27 #include "common.h"
28 #include "ralloc.h"
29 #include "gen.h"
30
31 /*-----------------------------------------------------------------*/
32 /* At this point we start getting processor specific although      */
33 /* some routines are non-processor specific & can be reused when   */
34 /* targetting other processors. The decision for this will have    */
35 /* to be made on a routine by routine basis                        */
36 /* routines used to pack registers are most definitely not reusable*/
37 /* since the pack the registers depending strictly on the MCU      */
38 /*-----------------------------------------------------------------*/
39
40 extern void genpic14Code(iCode *);
41
42 /* Global data */
43 static struct {
44     bitVect *spiltSet;
45     set *stackSpil;
46     bitVect *regAssigned;
47     short blockSpil;
48     int slocNum;
49     bitVect *funcrUsed; /* registers used in a function */
50     int stackExtend;
51     int dataExtend;
52 } _G;
53
54 /* Shared with gen.c */
55 int pic14_ptrRegReq; /* one byte pointer register required */
56
57 /* pic14 registers */
58 regs regspic14[] = 
59 {
60
61   {REG_GPR,  0x0C, "r0x0C", "r0x0C", 0x0C, 1, 0},
62   {REG_GPR,  0x0D, "r0x0D", "r0x0C", 0x0D, 1, 0},
63   {REG_GPR,  0x0E, "r0x0E", "r0x0C", 0x0E, 1, 0},
64   {REG_GPR,  0x0F, "r0x0F", "r0x0C", 0x0F, 1, 0},
65   {REG_GPR,  0x10, "r0x10", "r0x10", 0x10, 1, 0},
66   {REG_GPR,  0x11, "r0x11", "r0x11", 0x11, 1, 0},
67   {REG_GPR,  0x12, "r0x12", "r0x12", 0x12, 1, 0},
68   {REG_GPR,  0x13, "r0x13", "r0x13", 0x13, 1, 0},
69   {REG_GPR,  0x14, "r0x14", "r0x14", 0x14, 1, 0},
70   {REG_GPR,  0x15, "r0x15", "r0x15", 0x15, 1, 0},
71   {REG_GPR,  0x16, "r0x16", "r0x16", 0x16, 1, 0},
72   {REG_GPR,  0x17, "r0x17", "r0x17", 0x17, 1, 0},
73   {REG_GPR,  0x18, "r0x18", "r0x18", 0x18, 1, 0},
74   {REG_GPR,  0x19, "r0x19", "r0x19", 0x19, 1, 0},
75   {REG_GPR,  0x1A, "r0x1A", "r0x1A", 0x1A, 1, 0},
76   {REG_GPR,  0x1B, "r0x1B", "r0x1B", 0x1B, 1, 0},
77   {REG_GPR,  0x1C, "r0x1C", "r0x1C", 0x1C, 1, 0},
78   {REG_GPR,  0x1D, "r0x1D", "r0x1D", 0x1D, 1, 0},
79   {REG_GPR,  0x1E, "r0x1E", "r0x1E", 0x1E, 1, 0},
80   {REG_GPR,  0x1F, "r0x1F", "r0x1F", 0x1F, 1, 0},
81   {REG_PTR,  4, "FSR", "FSR", 4, 1,0},
82
83 };
84
85 int pic14_nRegs = sizeof(regspic14) / sizeof(regs);
86 static void spillThis (symbol *);
87 static int debug=1;
88 static FILE *debugF=NULL;
89 /*-----------------------------------------------------------------*/
90 /* debugLog - open a file for debugging information                */
91 /*-----------------------------------------------------------------*/
92 //static void debugLog(char *inst,char *fmt, ...)
93 static void debugLog(char *fmt, ...)
94 {
95   static int append = 0;   // First time through, open the file without append.
96   char buffer[256];
97   //char *bufferP=buffer;
98   va_list ap;
99
100   if(!debug)
101     return;
102
103
104   if (!debugF) {
105     /* create the file name */
106     strcpy(buffer,srcFileName);
107     strcat(buffer,".d");
108
109     if( !(debugF = fopen(buffer, (append ? "a+" : "w") ))) {
110       werror(E_FILE_OPEN_ERR,buffer);
111       exit(1);
112     }
113     append = 1;  // Next time debubLog is called, we'll append the debug info
114   }
115
116   va_start(ap,fmt);   
117
118   vsprintf(buffer,fmt,ap);
119
120   fprintf(debugF,"%s",buffer);
121 /*
122   while (isspace(*bufferP)) bufferP++;
123
124   if (bufferP && *bufferP) 
125     lineCurr = (lineCurr ?
126                 connectLine(lineCurr,newLineNode(lb)) :
127                 (lineHead = newLineNode(lb)));
128   lineCurr->isInline = _G.inLine;
129   lineCurr->isDebug  = _G.debugLine;
130 */
131   va_end(ap);
132
133 }
134
135 static void debugNewLine(void)
136 {
137   if(debugF)
138     fputc('\n',debugF);
139 }
140 /*-----------------------------------------------------------------*/
141 /* debugLogClose - closes the debug log file (if opened)           */
142 /*-----------------------------------------------------------------*/
143 static void debugLogClose(void)
144 {
145   if(debugF) {
146     fclose(debugF);
147     debugF = NULL;
148   }
149 }
150 #define AOP(op) op->aop
151
152 static char *debugAopGet(char *str,operand *op)
153 {
154   if(str)
155     debugLog(str);
156
157   printOperand(op,debugF);debugNewLine();
158
159   return NULL;
160
161 }
162
163 static char * decodeOp(unsigned int op)
164 {
165
166   if(op<128 && op>' ') {
167     buffer[0] = (op & 0xff);
168     buffer[1] = 0;
169     return buffer;
170   }
171
172   switch(op) {
173   case IDENTIFIER:
174     return "IDENTIFIER";
175   case TYPE_NAME:
176     return "TYPE_NAME";
177   case CONSTANT:
178     return "CONSTANT";
179   case STRING_LITERAL:
180     return "STRING_LITERAL";
181   case SIZEOF:
182     return "SIZEOF";
183   case PTR_OP:
184     return "PTR_OP";
185   case INC_OP:
186     return "INC_OP";
187   case DEC_OP:
188     return "DEC_OP";
189   case LEFT_OP:
190     return "LEFT_OP";
191   case RIGHT_OP:
192     return "RIGHT_OP";
193   case LE_OP:
194     return "LE_OP";
195   case GE_OP:
196     return "GE_OP";
197   case EQ_OP:
198     return "EQ_OP";
199   case NE_OP:
200     return "NE_OP";
201   case AND_OP:
202     return "AND_OP";
203   case OR_OP:
204     return "OR_OP";
205   case MUL_ASSIGN:
206     return "MUL_ASSIGN";
207   case DIV_ASSIGN:
208     return "DIV_ASSIGN";
209   case MOD_ASSIGN:
210     return "MOD_ASSIGN";
211   case ADD_ASSIGN:
212     return "ADD_ASSIGN";
213   case SUB_ASSIGN:
214     return "SUB_ASSIGN";
215   case LEFT_ASSIGN:
216     return "LEFT_ASSIGN";
217   case RIGHT_ASSIGN:
218     return "RIGHT_ASSIGN";
219   case AND_ASSIGN:
220     return "AND_ASSIGN";
221   case XOR_ASSIGN:
222     return "XOR_ASSIGN";
223   case OR_ASSIGN:
224     return "OR_ASSIGN";
225   case TYPEDEF:
226     return "TYPEDEF";
227   case EXTERN:
228     return "EXTERN";
229   case STATIC:
230     return "STATIC";
231   case AUTO:
232     return "AUTO";
233   case REGISTER:
234     return "REGISTER";
235   case CODE:
236     return "CODE";
237   case EEPROM:
238     return "EEPROM";
239   case INTERRUPT:
240     return "INTERRUPT";
241   case SFR:
242     return "SFR";
243   case AT:
244     return "AT";
245   case SBIT:
246     return "SBIT";
247   case REENTRANT:
248     return "REENTRANT";
249   case USING:
250     return "USING";
251   case XDATA:
252     return "XDATA";
253   case DATA:
254     return "DATA";
255   case IDATA:
256     return "IDATA";
257   case PDATA:
258     return "PDATA";
259   case VAR_ARGS:
260     return "VAR_ARGS";
261   case CRITICAL:
262     return "CRITICAL";
263   case NONBANKED:
264     return "NONBANKED";
265   case BANKED:
266     return "BANKED";
267   case CHAR:
268     return "CHAR";
269   case SHORT:
270     return "SHORT";
271   case INT:
272     return "INT";
273   case LONG:
274     return "LONG";
275   case SIGNED:
276     return "SIGNED";
277   case UNSIGNED:
278     return "UNSIGNED";
279   case FLOAT:
280     return "FLOAT";
281   case DOUBLE:
282     return "DOUBLE";
283   case CONST:
284     return "CONST";
285   case VOLATILE:
286     return "VOLATILE";
287   case VOID:
288     return "VOID";
289   case BIT:
290     return "BIT";
291   case STRUCT:
292     return "STRUCT";
293   case UNION:
294     return "UNION";
295   case ENUM:
296     return "ENUM";
297   case ELIPSIS:
298     return "ELIPSIS";
299   case RANGE:
300     return "RANGE";
301   case FAR:
302     return "FAR";
303   case _XDATA:
304     return "_XDATA";
305   case _CODE:
306     return "_CODE";
307   case _GENERIC:
308     return "_GENERIC";
309   case _NEAR:
310     return "_NEAR";
311   case _PDATA:
312     return "_PDATA";
313   case _IDATA:
314     return "_IDATA";
315   case _EEPROM:
316     return "_EEPROM";
317   case CASE:
318     return "CASE";
319   case DEFAULT:
320     return "DEFAULT";
321   case IF:
322     return "IF";
323   case ELSE:
324     return "ELSE";
325   case SWITCH:
326     return "SWITCH";
327   case WHILE:
328     return "WHILE";
329   case DO:
330     return "DO";
331   case FOR:
332     return "FOR";
333   case GOTO:
334     return "GOTO";
335   case CONTINUE:
336     return "CONTINUE";
337   case BREAK:
338     return "BREAK";
339   case RETURN:
340     return "RETURN";
341   case INLINEASM:
342     return "INLINEASM";
343   case IFX:
344     return "IFX";
345   case ADDRESS_OF:
346     return "ADDRESS_OF";
347   case GET_VALUE_AT_ADDRESS:
348     return "GET_VALUE_AT_ADDRESS";
349   case SPIL:
350     return "SPIL";
351   case UNSPIL:
352     return "UNSPIL";
353   case GETHBIT:
354     return "GETHBIT";
355   case BITWISEAND:
356     return "BITWISEAND";
357   case UNARYMINUS:
358     return "UNARYMINUS";
359   case IPUSH:
360     return "IPUSH";
361   case IPOP:
362     return "IPOP";
363   case PCALL:
364     return "PCALL";
365   case ENDFUNCTION:
366     return "ENDFUNCTION";
367   case JUMPTABLE:
368     return "JUMPTABLE";
369   case RRC:
370     return "RRC";
371   case RLC:
372     return "RLC";
373   case CAST:
374     return "CAST";
375   case CALL:
376     return "CALL";
377   case PARAM:
378     return "PARAM  ";
379   case NULLOP:
380     return "NULLOP";
381   case BLOCK:
382     return "BLOCK";
383   case LABEL:
384     return "LABEL";
385   case RECEIVE:
386     return "RECEIVE";
387   case SEND:
388     return "SEND";
389   }
390   sprintf(buffer,"unkown op %d %c",op, op&0xff);
391   return buffer;
392 }
393 /*-----------------------------------------------------------------*/
394 /*-----------------------------------------------------------------*/
395 static char * debugLogRegType(short type)
396 {
397
398   switch(type) {
399   case REG_GPR:
400     return "REG_GPR";
401   case REG_PTR:
402     return "REG_PTR";
403   case REG_CND:
404     return "REG_CND";
405   }
406
407   sprintf(buffer,"unkown reg type %d",type);
408   return buffer;
409 }
410
411 /*-----------------------------------------------------------------*/
412 /* allocReg - allocates register of given type                     */
413 /*-----------------------------------------------------------------*/
414 static regs *allocReg (short type)
415 {
416     int i;
417
418     debugLog("%s of type %s\n",__FUNCTION__,debugLogRegType(type));
419
420     for ( i = 0 ; i < pic14_nRegs ; i++ ) {
421
422         /* if type is given as 0 then any
423            free register will do */
424         if (!type &&
425             regspic14[i].isFree ) {
426             regspic14[i].isFree = 0;
427             regspic14[i].wasUsed = 1;
428             if (currFunc)
429                 currFunc->regsUsed = 
430                     bitVectSetBit(currFunc->regsUsed,i);
431             debugLog("  returning %s\n",regspic14[i].name);
432             return &regspic14[i];
433         }
434         /* other wise look for specific type
435            of register */
436         if (regspic14[i].isFree && 
437             regspic14[i].type == type) {
438             regspic14[i].isFree = 0;
439             regspic14[i].wasUsed = 1;
440             if (currFunc)
441                 currFunc->regsUsed = 
442                     bitVectSetBit(currFunc->regsUsed,i);
443             debugLog("  returning %s\n",regspic14[i].name);
444             return &regspic14[i];
445         }
446     }
447     return NULL;
448 }
449
450 /*-----------------------------------------------------------------*/
451 /* pic14_regWithIdx - returns pointer to register wit index number       */
452 /*-----------------------------------------------------------------*/
453 regs *pic14_regWithIdx (int idx)
454 {
455     int i ;
456     
457     debugLog("%s\n",__FUNCTION__);
458
459     for (i=0;i < pic14_nRegs;i++)
460         if (regspic14[i].rIdx == idx)
461             return &regspic14[i];
462
463     return &regspic14[0];
464
465     werror(E_INTERNAL_ERROR,__FILE__,__LINE__,
466            "regWithIdx not found");
467     exit(1);
468 }
469
470 /*-----------------------------------------------------------------*/
471 /* freeReg - frees a register                                      */
472 /*-----------------------------------------------------------------*/
473 static void freeReg (regs *reg)
474 {
475     debugLog("%s\n",__FUNCTION__);
476     reg->isFree = 1;
477 }
478
479
480 /*-----------------------------------------------------------------*/
481 /* nFreeRegs - returns number of free registers                    */
482 /*-----------------------------------------------------------------*/
483 static int nFreeRegs (int type)
484 {
485     int i;
486     int nfr=0;
487     
488     debugLog("%s\n",__FUNCTION__);
489     for (i = 0 ; i < pic14_nRegs; i++ )
490         if (regspic14[i].isFree && regspic14[i].type == type)
491             nfr++;
492     return nfr;
493 }
494
495 /*-----------------------------------------------------------------*/
496 /* nfreeRegsType - free registers with type                         */
497 /*-----------------------------------------------------------------*/
498 static int nfreeRegsType (int type)
499 {
500     int nfr ;
501     debugLog("%s\n",__FUNCTION__);
502     if (type == REG_PTR) {
503         if ((nfr = nFreeRegs(type)) == 0)
504             return nFreeRegs(REG_GPR);
505     } 
506     
507     return nFreeRegs(type);
508 }
509
510
511 /*-----------------------------------------------------------------*/
512 /* allDefsOutOfRange - all definitions are out of a range          */
513 /*-----------------------------------------------------------------*/
514 static bool allDefsOutOfRange (bitVect *defs,int fseq, int toseq) 
515 {
516     int i ;
517
518     debugLog("%s\n",__FUNCTION__);
519     if (!defs)
520         return TRUE ;
521
522     for ( i = 0 ;i < defs->size ; i++ ) {
523         iCode *ic;
524
525         if (bitVectBitValue(defs,i)             &&
526             (ic = hTabItemWithKey(iCodehTab,i)) &&
527             ( ic->seq >= fseq  && ic->seq <= toseq))
528             
529             return FALSE;
530         
531     }
532     
533     return TRUE;
534 }
535   
536 /*-----------------------------------------------------------------*/
537 /* computeSpillable - given a point find the spillable live ranges */
538 /*-----------------------------------------------------------------*/
539 static bitVect *computeSpillable (iCode *ic)
540 {
541     bitVect *spillable ;
542
543     debugLog("%s\n",__FUNCTION__);
544     /* spillable live ranges are those that are live at this 
545        point . the following categories need to be subtracted
546        from this set. 
547        a) - those that are already spilt
548        b) - if being used by this one
549        c) - defined by this one */
550     
551     spillable = bitVectCopy(ic->rlive);
552     spillable = 
553         bitVectCplAnd(spillable,_G.spiltSet); /* those already spilt */
554     spillable = 
555         bitVectCplAnd(spillable,ic->uses); /* used in this one */    
556     bitVectUnSetBit(spillable,ic->defKey);
557     spillable = bitVectIntersect(spillable,_G.regAssigned);
558     return spillable;
559     
560 }
561
562 /*-----------------------------------------------------------------*/
563 /* noSpilLoc - return true if a variable has no spil location      */
564 /*-----------------------------------------------------------------*/
565 static int noSpilLoc (symbol *sym, eBBlock *ebp,iCode *ic)
566 {
567     debugLog("%s\n",__FUNCTION__);
568     return (sym->usl.spillLoc ? 0 : 1);
569 }
570
571 /*-----------------------------------------------------------------*/
572 /* hasSpilLoc - will return 1 if the symbol has spil location      */
573 /*-----------------------------------------------------------------*/
574 static int hasSpilLoc (symbol *sym, eBBlock *ebp, iCode *ic)
575 {
576     debugLog("%s\n",__FUNCTION__);
577     return (sym->usl.spillLoc ? 1 : 0);
578 }
579
580 /*-----------------------------------------------------------------*/
581 /* directSpilLoc - will return 1 if the splilocation is in direct  */
582 /*-----------------------------------------------------------------*/
583 static int directSpilLoc (symbol *sym, eBBlock *ebp, iCode *ic)
584 {
585     debugLog("%s\n",__FUNCTION__);
586     if ( sym->usl.spillLoc &&
587          (IN_DIRSPACE(SPEC_OCLS(sym->usl.spillLoc->etype))))
588         return 1;
589     else
590         return 0;
591 }
592
593 /*-----------------------------------------------------------------*/
594 /* hasSpilLocnoUptr - will return 1 if the symbol has spil location*/
595 /*                    but is not used as a pointer                 */
596 /*-----------------------------------------------------------------*/
597 static int hasSpilLocnoUptr (symbol *sym, eBBlock *ebp, iCode *ic)
598 {
599     debugLog("%s\n",__FUNCTION__);
600     return ((sym->usl.spillLoc && !sym->uptr) ? 1 : 0);
601 }
602
603 /*-----------------------------------------------------------------*/
604 /* rematable - will return 1 if the remat flag is set              */
605 /*-----------------------------------------------------------------*/
606 static int rematable (symbol *sym, eBBlock *ebp, iCode *ic)
607 {
608     debugLog("%s\n",__FUNCTION__);
609     return sym->remat;
610 }
611
612 /*-----------------------------------------------------------------*/
613 /* notUsedInBlock - not used in this block                         */
614 /*-----------------------------------------------------------------*/
615 static int notUsedInBlock (symbol *sym, eBBlock *ebp, iCode *ic)
616 {   
617     debugLog("%s\n",__FUNCTION__);
618     return (!bitVectBitsInCommon(sym->defs,ebp->usesDefs) &&
619             allDefsOutOfRange (sym->defs,ebp->fSeq,ebp->lSeq));
620 /*     return (!bitVectBitsInCommon(sym->defs,ebp->usesDefs)); */
621 }
622
623 /*-----------------------------------------------------------------*/
624 /* notUsedInRemaining - not used or defined in remain of the block */
625 /*-----------------------------------------------------------------*/
626 static int notUsedInRemaining (symbol *sym, eBBlock *ebp, iCode *ic)
627 {
628     debugLog("%s\n",__FUNCTION__);
629     return ((usedInRemaining (operandFromSymbol(sym),ic) ? 0 : 1) &&
630             allDefsOutOfRange (sym->defs,ebp->fSeq,ebp->lSeq));
631 }
632
633 /*-----------------------------------------------------------------*/
634 /* allLRs - return true for all                                    */
635 /*-----------------------------------------------------------------*/
636 static int allLRs (symbol *sym, eBBlock *ebp, iCode *ic)
637 {
638     debugLog("%s\n",__FUNCTION__);
639     return 1;
640 }
641
642 /*-----------------------------------------------------------------*/
643 /* liveRangesWith - applies function to a given set of live range  */
644 /*-----------------------------------------------------------------*/
645 static set *liveRangesWith (bitVect *lrs, int (func)(symbol *,eBBlock *, iCode *),
646                      eBBlock *ebp, iCode *ic)
647 {
648     set *rset = NULL;
649     int i;
650
651     debugLog("%s\n",__FUNCTION__);
652     if (!lrs || !lrs->size)
653         return NULL;
654
655     for ( i = 1 ; i < lrs->size ; i++ ) {
656         symbol *sym;
657         if (!bitVectBitValue(lrs,i))
658             continue ;
659
660         /* if we don't find it in the live range 
661            hash table we are in serious trouble */
662         if (!(sym = hTabItemWithKey(liveRanges,i))) {
663             werror(E_INTERNAL_ERROR,__FILE__,__LINE__,
664                    "liveRangesWith could not find liveRange");
665             exit(1);
666         }
667         
668         if (func(sym,ebp,ic) && bitVectBitValue(_G.regAssigned,sym->key))
669             addSetHead(&rset,sym);
670     }
671
672     return rset;
673 }
674
675
676 /*-----------------------------------------------------------------*/
677 /* leastUsedLR - given a set determines which is the least used    */
678 /*-----------------------------------------------------------------*/
679 static symbol *leastUsedLR (set *sset)
680 {
681     symbol *sym = NULL, *lsym = NULL ;
682     
683     debugLog("%s\n",__FUNCTION__);
684     sym = lsym = setFirstItem(sset);
685
686     if (!lsym)
687         return NULL;
688
689     for (; lsym; lsym = setNextItem(sset)) {
690         
691         /* if usage is the same then prefer
692            the spill the smaller of the two */
693         if ( lsym->used == sym->used )
694             if (getSize(lsym->type) < getSize(sym->type))
695                 sym = lsym;
696
697         /* if less usage */
698         if (lsym->used < sym->used )
699             sym = lsym;
700         
701    }
702
703     setToNull((void **)&sset);
704     sym->blockSpil = 0;
705     return sym;
706 }
707
708 /*-----------------------------------------------------------------*/
709 /* noOverLap - will iterate through the list looking for over lap  */
710 /*-----------------------------------------------------------------*/
711 static int noOverLap (set *itmpStack, symbol *fsym)
712 {
713     symbol *sym;
714     debugLog("%s\n",__FUNCTION__);
715    
716
717     for (sym = setFirstItem(itmpStack); sym;
718          sym = setNextItem(itmpStack)) {
719         if (sym->liveTo > fsym->liveFrom )
720             return 0;
721             
722     }
723
724     return 1;
725 }
726
727 /*-----------------------------------------------------------------*/
728 /* isFree - will return 1 if the a free spil location is found     */
729 /*-----------------------------------------------------------------*/
730 static DEFSETFUNC(isFree)
731 {
732     symbol *sym = item;
733     V_ARG(symbol **,sloc);
734     V_ARG(symbol *,fsym);
735
736     debugLog("%s\n",__FUNCTION__);
737     /* if already found */
738     if (*sloc)
739         return 0;
740
741     /* if it is free && and the itmp assigned to
742        this does not have any overlapping live ranges
743        with the one currently being assigned and
744        the size can be accomodated  */
745     if (sym->isFree                        && 
746         noOverLap(sym->usl.itmpStack,fsym) &&
747         getSize(sym->type) >= getSize(fsym->type)) {
748         *sloc = sym;
749         return 1;
750     }
751
752     return 0;
753 }
754
755 /*-----------------------------------------------------------------*/
756 /* spillLRWithPtrReg :- will spil those live ranges which use PTR  */
757 /*-----------------------------------------------------------------*/
758 static void spillLRWithPtrReg (symbol *forSym)
759 {
760     symbol *lrsym;
761     regs *r0,*r1;
762     int k;
763
764     debugLog("%s\n",__FUNCTION__);
765     if (!_G.regAssigned ||
766         bitVectIsZero(_G.regAssigned))
767         return;
768
769     r0 = pic14_regWithIdx(R0_IDX);
770     r1 = pic14_regWithIdx(R1_IDX);
771
772     /* for all live ranges */
773     for (lrsym = hTabFirstItem(liveRanges,&k) ; lrsym ; 
774          lrsym = hTabNextItem(liveRanges,&k) ) {
775         int j;       
776
777         /* if no registers assigned to it or
778            spilt */
779         /* if it does not overlap with this then 
780            not need to spill it */
781
782         if (lrsym->isspilt || !lrsym->nRegs ||
783             (lrsym->liveTo < forSym->liveFrom))
784             continue ;
785
786         /* go thru the registers : if it is either
787            r0 or r1 then spil it */
788         for (j = 0 ; j < lrsym->nRegs ; j++ ) 
789             if (lrsym->regs[j] == r0 ||
790                 lrsym->regs[j] == r1 ) {
791                 spillThis (lrsym);
792                 break;
793             }
794     }
795
796 }
797
798 /*-----------------------------------------------------------------*/
799 /* createStackSpil - create a location on the stack to spil        */
800 /*-----------------------------------------------------------------*/
801 static symbol *createStackSpil (symbol *sym)
802 {
803     symbol *sloc= NULL;
804     int useXstack, model, noOverlay;
805
806     char slocBuffer[30];
807     debugLog("%s\n",__FUNCTION__);
808
809     /* first go try and find a free one that is already 
810        existing on the stack */
811     if (applyToSet(_G.stackSpil,isFree,&sloc, sym)) {
812         /* found a free one : just update & return */
813         sym->usl.spillLoc = sloc;
814         sym->stackSpil= 1;
815         sloc->isFree = 0;
816         addSetHead(&sloc->usl.itmpStack,sym);
817         return sym;
818     }
819
820     /* could not then have to create one , this is the hard part
821        we need to allocate this on the stack : this is really a
822        hack!! but cannot think of anything better at this time */
823         
824     if (sprintf(slocBuffer,"sloc%d",_G.slocNum++) >= sizeof(slocBuffer))
825     {
826         fprintf(stderr, "kkkInternal error: slocBuffer overflowed: %s:%d\n",
827                 __FILE__, __LINE__);
828         exit(1);        
829     }
830
831     sloc = newiTemp(slocBuffer);
832
833     /* set the type to the spilling symbol */
834     sloc->type = copyLinkChain(sym->type);
835     sloc->etype = getSpec(sloc->type);
836     SPEC_SCLS(sloc->etype) = S_DATA ;
837     SPEC_EXTR(sloc->etype) = 0;
838
839     /* we don't allow it to be allocated`
840        onto the external stack since : so we
841        temporarily turn it off ; we also
842        turn off memory model to prevent
843        the spil from going to the external storage
844        and turn off overlaying 
845     */
846     
847     useXstack = options.useXstack;
848     model = options.model;
849     noOverlay = options.noOverlay;
850     options.noOverlay = 1;
851     options.model = options.useXstack = 0;
852
853     allocLocal(sloc);
854
855     options.useXstack = useXstack;
856     options.model     = model;
857     options.noOverlay = noOverlay;
858     sloc->isref = 1; /* to prevent compiler warning */
859     
860     /* if it is on the stack then update the stack */
861     if (IN_STACK(sloc->etype)) {
862         currFunc->stack += getSize(sloc->type);
863         _G.stackExtend += getSize(sloc->type);
864     } else
865         _G.dataExtend += getSize(sloc->type);
866
867     /* add it to the _G.stackSpil set */
868     addSetHead(&_G.stackSpil,sloc);
869     sym->usl.spillLoc = sloc;
870     sym->stackSpil = 1;
871     
872     /* add it to the set of itempStack set 
873        of the spill location */
874     addSetHead(&sloc->usl.itmpStack,sym);
875     return sym;
876 }
877
878 /*-----------------------------------------------------------------*/
879 /* isSpiltOnStack - returns true if the spil location is on stack  */
880 /*-----------------------------------------------------------------*/
881 static bool isSpiltOnStack (symbol *sym)
882 {
883     sym_link *etype;
884
885     debugLog("%s\n",__FUNCTION__);
886     if (!sym)
887         return FALSE ;
888     
889     if (!sym->isspilt)
890         return FALSE ;
891
892 /*     if (sym->_G.stackSpil) */
893 /*      return TRUE; */
894     
895     if (!sym->usl.spillLoc)
896         return FALSE;
897
898     etype = getSpec(sym->usl.spillLoc->type);
899     if (IN_STACK(etype))
900         return TRUE;
901
902     return FALSE ;
903 }
904
905 /*-----------------------------------------------------------------*/
906 /* spillThis - spils a specific operand                            */
907 /*-----------------------------------------------------------------*/
908 static void spillThis (symbol *sym)
909 {
910     int i;
911     debugLog("%s : %s\n",__FUNCTION__, sym->rname);
912
913     /* if this is rematerializable or has a spillLocation
914        we are okay, else we need to create a spillLocation
915        for it */
916     if (!(sym->remat || sym->usl.spillLoc)) 
917         createStackSpil (sym);
918     
919
920     /* mark it has spilt & put it in the spilt set */
921     sym->isspilt = 1;
922     _G.spiltSet = bitVectSetBit(_G.spiltSet,sym->key);
923        
924     bitVectUnSetBit(_G.regAssigned,sym->key);
925
926     for (i = 0 ; i < sym->nRegs ; i++)
927
928         if (sym->regs[i]) {
929             freeReg(sym->regs[i]);
930             sym->regs[i] = NULL;
931         }
932     
933     /* if spilt on stack then free up r0 & r1 
934        if they could have been assigned to some
935        LIVE ranges */
936     if (!pic14_ptrRegReq && isSpiltOnStack(sym)) {
937         pic14_ptrRegReq++ ;
938         spillLRWithPtrReg(sym);
939     }
940
941     if (sym->usl.spillLoc && !sym->remat)
942         sym->usl.spillLoc->allocreq = 1;
943     return;
944 }
945
946 /*-----------------------------------------------------------------*/
947 /* selectSpil - select a iTemp to spil : rather a simple procedure */
948 /*-----------------------------------------------------------------*/
949 static symbol *selectSpil (iCode *ic, eBBlock *ebp, symbol *forSym)
950 {
951     bitVect *lrcs= NULL ; 
952     set *selectS ;
953     symbol *sym;
954
955     debugLog("%s\n",__FUNCTION__);
956     /* get the spillable live ranges */
957     lrcs = computeSpillable (ic);
958
959     /* get all live ranges that are rematerizable */
960     if ((selectS = liveRangesWith(lrcs,rematable,ebp,ic))) {
961
962         /* return the least used of these */
963         return leastUsedLR(selectS);
964     }
965
966     /* get live ranges with spillLocations in direct space */
967     if ((selectS = liveRangesWith(lrcs,directSpilLoc,ebp,ic))) {
968         sym = leastUsedLR(selectS);
969         strcpy(sym->rname,(sym->usl.spillLoc->rname[0] ? 
970                            sym->usl.spillLoc->rname : 
971                            sym->usl.spillLoc->name)); 
972         sym->spildir = 1;
973         /* mark it as allocation required */
974         sym->usl.spillLoc->allocreq = 1;
975         return sym;
976     }
977
978     /* if the symbol is local to the block then */
979     if (forSym->liveTo < ebp->lSeq) {       
980
981         /* check if there are any live ranges allocated
982            to registers that are not used in this block */
983         if (!_G.blockSpil && (selectS = liveRangesWith(lrcs,notUsedInBlock,ebp,ic))) {
984             sym = leastUsedLR(selectS);
985             /* if this is not rematerializable */
986             if (!sym->remat) {
987                 _G.blockSpil++;
988                 sym->blockSpil = 1;
989             }
990             return sym;
991         } 
992
993         /* check if there are any live ranges that not
994            used in the remainder of the block */
995         if (!_G.blockSpil && (selectS = liveRangesWith(lrcs,notUsedInRemaining,ebp,ic))) {
996             sym = leastUsedLR (selectS);
997             if (!sym->remat) {
998                 sym->remainSpil = 1;
999                 _G.blockSpil++;
1000             }
1001             return sym;
1002         }
1003     }   
1004
1005     /* find live ranges with spillocation && not used as pointers */
1006     if ((selectS = liveRangesWith(lrcs,hasSpilLocnoUptr,ebp,ic))) {
1007        
1008         sym =  leastUsedLR(selectS);
1009         /* mark this as allocation required */
1010         sym->usl.spillLoc->allocreq = 1;
1011         return sym;
1012     }
1013
1014     /* find live ranges with spillocation */
1015     if ((selectS = liveRangesWith(lrcs,hasSpilLoc,ebp,ic))) {
1016         
1017         sym = leastUsedLR(selectS);
1018         sym->usl.spillLoc->allocreq = 1;
1019         return sym;
1020     }
1021
1022     /* couldn't find then we need to create a spil
1023        location on the stack , for which one? the least
1024        used ofcourse */
1025     if ((selectS = liveRangesWith(lrcs,noSpilLoc,ebp,ic))) {
1026         
1027         /* return a created spil location */
1028         sym = createStackSpil(leastUsedLR(selectS));
1029         sym->usl.spillLoc->allocreq = 1;
1030         return sym;
1031     }
1032     
1033     /* this is an extreme situation we will spill
1034        this one : happens very rarely but it does happen */
1035     spillThis ( forSym );
1036     return forSym ;
1037    
1038 }
1039
1040 /*-----------------------------------------------------------------*/
1041 /* spilSomething - spil some variable & mark registers as free     */
1042 /*-----------------------------------------------------------------*/
1043 static bool spilSomething (iCode *ic, eBBlock *ebp, symbol *forSym)
1044 {
1045     symbol *ssym;
1046     int i ;
1047
1048     debugLog("%s\n",__FUNCTION__);
1049     /* get something we can spil */
1050     ssym = selectSpil(ic,ebp,forSym);
1051     
1052     /* mark it as spilt */
1053     ssym->isspilt = 1;
1054     _G.spiltSet = bitVectSetBit(_G.spiltSet,ssym->key);
1055     
1056     /* mark it as not register assigned &
1057        take it away from the set */   
1058     bitVectUnSetBit(_G.regAssigned,ssym->key);
1059  
1060     /* mark the registers as free */    
1061     for (i = 0 ; i < ssym->nRegs ;i++ )
1062         if (ssym->regs[i])
1063             freeReg(ssym->regs[i]);
1064      
1065     /* if spilt on stack then free up r0 & r1 
1066        if they could have been assigned to as gprs */
1067     if (!pic14_ptrRegReq && isSpiltOnStack(ssym) ) {
1068         pic14_ptrRegReq++ ;
1069         spillLRWithPtrReg(ssym);
1070     }
1071
1072     /* if this was a block level spil then insert push & pop 
1073        at the start & end of block respectively */
1074     if (ssym->blockSpil) {
1075         iCode *nic = newiCode(IPUSH,operandFromSymbol(ssym),NULL);
1076         /* add push to the start of the block */
1077         addiCodeToeBBlock(ebp,nic,( ebp->sch->op == LABEL ? 
1078                                     ebp->sch->next : ebp->sch));
1079         nic = newiCode(IPOP,operandFromSymbol(ssym),NULL);
1080         /* add pop to the end of the block */
1081         addiCodeToeBBlock(ebp,nic,NULL);
1082     }       
1083
1084     /* if spilt because not used in the remainder of the
1085        block then add a push before this instruction and
1086        a pop at the end of the block */
1087     if (ssym->remainSpil) {
1088
1089         iCode *nic = newiCode(IPUSH,operandFromSymbol(ssym),NULL);
1090         /* add push just before this instruction */
1091         addiCodeToeBBlock(ebp,nic,ic);
1092                                     
1093         nic = newiCode(IPOP,operandFromSymbol(ssym),NULL);
1094         /* add pop to the end of the block */
1095         addiCodeToeBBlock(ebp,nic,NULL);    
1096     }
1097
1098     if (ssym == forSym )
1099         return FALSE ;
1100     else
1101         return TRUE ;
1102 }
1103
1104 /*-----------------------------------------------------------------*/
1105 /* getRegPtr - will try for PTR if not a GPR type if not spil      */
1106 /*-----------------------------------------------------------------*/
1107 static regs *getRegPtr (iCode *ic, eBBlock *ebp, symbol *sym)
1108 {
1109     regs *reg;
1110
1111     debugLog("%s\n",__FUNCTION__);
1112  tryAgain:
1113     /* try for a ptr type */
1114     if ((reg = allocReg(REG_PTR))) 
1115         return reg;    
1116
1117     /* try for gpr type */
1118     if ((reg = allocReg(REG_GPR)))        
1119         return reg;    
1120
1121     /* we have to spil */
1122     if (!spilSomething (ic,ebp,sym))
1123         return NULL ;
1124
1125     /* this looks like an infinite loop but 
1126        in really selectSpil will abort  */
1127     goto tryAgain ;    
1128 }
1129
1130 /*-----------------------------------------------------------------*/
1131 /* getRegGpr - will try for GPR if not spil                        */
1132 /*-----------------------------------------------------------------*/
1133 static regs *getRegGpr (iCode *ic, eBBlock *ebp,symbol *sym)
1134 {
1135     regs *reg;
1136
1137     debugLog("%s\n",__FUNCTION__);
1138  tryAgain:
1139     /* try for gpr type */
1140     if ((reg = allocReg(REG_GPR)))        
1141         return reg;    
1142
1143     if (!pic14_ptrRegReq)
1144         if ((reg = allocReg(REG_PTR)))
1145             return reg ;
1146         
1147     /* we have to spil */
1148     if (!spilSomething (ic,ebp,sym))
1149         return NULL ;
1150
1151     /* this looks like an infinite loop but 
1152        in really selectSpil will abort  */
1153     goto tryAgain ;    
1154 }
1155
1156 /*-----------------------------------------------------------------*/
1157 /* symHasReg - symbol has a given register                         */
1158 /*-----------------------------------------------------------------*/
1159 static bool symHasReg(symbol *sym,regs *reg)
1160 {
1161     int i;
1162
1163     debugLog("%s\n",__FUNCTION__);
1164     for ( i = 0 ; i < sym->nRegs ; i++)
1165         if (sym->regs[i] == reg)
1166             return TRUE;
1167             
1168     return FALSE;
1169 }
1170
1171 /*-----------------------------------------------------------------*/
1172 /* deassignLRs - check the live to and if they have registers & are*/
1173 /*               not spilt then free up the registers              */
1174 /*-----------------------------------------------------------------*/
1175 static void deassignLRs (iCode *ic, eBBlock *ebp)
1176 {
1177     symbol *sym;
1178     int k;
1179     symbol *result;
1180
1181     debugLog("%s\n",__FUNCTION__);
1182     for (sym = hTabFirstItem(liveRanges,&k); sym;
1183          sym = hTabNextItem(liveRanges,&k)) {
1184         
1185         symbol *psym= NULL;
1186         /* if it does not end here */
1187         if (sym->liveTo > ic->seq )
1188             continue ;
1189
1190         /* if it was spilt on stack then we can 
1191            mark the stack spil location as free */
1192         if (sym->isspilt ) {
1193             if (sym->stackSpil) {
1194                 sym->usl.spillLoc->isFree = 1;
1195                 sym->stackSpil = 0;
1196             }
1197             continue ;
1198         }
1199         
1200         if (!bitVectBitValue(_G.regAssigned,sym->key))
1201             continue;
1202         
1203         /* special case check if this is an IFX &
1204            the privious one was a pop and the 
1205            previous one was not spilt then keep track
1206            of the symbol */     
1207         if (ic->op == IFX && ic->prev &&
1208             ic->prev->op == IPOP && 
1209             !ic->prev->parmPush  &&
1210             !OP_SYMBOL(IC_LEFT(ic->prev))->isspilt) 
1211             psym = OP_SYMBOL(IC_LEFT(ic->prev));
1212
1213         if (sym->nRegs) {
1214             int i = 0;
1215             
1216             bitVectUnSetBit(_G.regAssigned,sym->key);
1217
1218             /* if the result of this one needs registers
1219                and does not have it then assign it right
1220                away */
1221             if (IC_RESULT(ic) &&
1222                 !  (SKIP_IC2(ic) ||               /* not a special icode */
1223                     ic->op == JUMPTABLE ||
1224                     ic->op == IFX ||
1225                     ic->op == IPUSH ||
1226                     ic->op == IPOP ||
1227                     ic->op == RETURN ||
1228                     POINTER_SET(ic))     &&             
1229                 (result = OP_SYMBOL(IC_RESULT(ic))) && /* has a result */
1230                 result->liveTo > ic->seq &&            /* and will live beyond this */
1231                 result->liveTo <= ebp->lSeq &&         /* does not go beyond this block */
1232                 result->regType == sym->regType &&     /* same register types */
1233                 result->nRegs            &&            /* which needs registers */
1234                 ! result->isspilt        &&            /* and does not already have them */
1235                 ! result->remat          &&
1236                 ! bitVectBitValue(_G.regAssigned,result->key) &&
1237                 /* the number of free regs + number of regs in this LR
1238                    can accomodate the what result Needs */
1239                 ((nfreeRegsType(result->regType) +
1240                   sym->nRegs) >= result->nRegs)
1241                 ) {
1242                 
1243                 for (i = 0 ; i < max(sym->nRegs,result->nRegs) ; i++)
1244                     if (i < sym->nRegs )
1245                         result->regs[i] = sym->regs[i] ;
1246                     else
1247                         result->regs[i] = getRegGpr (ic,ebp,result);
1248
1249                 _G.regAssigned = bitVectSetBit(_G.regAssigned,result->key);
1250                 
1251             }                   
1252             
1253             /* free the remaining */
1254             for (; i < sym->nRegs ; i++) {
1255                 if (psym) {
1256                     if (!symHasReg(psym,sym->regs[i]))
1257                         freeReg(sym->regs[i]);
1258                 } else
1259                     freeReg(sym->regs[i]);
1260             }
1261         }
1262     }
1263 }
1264
1265
1266 /*-----------------------------------------------------------------*/
1267 /* reassignLR - reassign this to registers                         */
1268 /*-----------------------------------------------------------------*/
1269 static void reassignLR (operand *op)
1270 {
1271     symbol *sym = OP_SYMBOL(op);
1272     int i;
1273
1274     debugLog("%s\n",__FUNCTION__);
1275     /* not spilt any more */     
1276     sym->isspilt = sym->blockSpil  = sym->remainSpil = 0;
1277     bitVectUnSetBit(_G.spiltSet,sym->key);
1278       
1279     _G.regAssigned = bitVectSetBit(_G.regAssigned,sym->key);
1280
1281     _G.blockSpil--;
1282
1283     for (i=0;i<sym->nRegs;i++)
1284         sym->regs[i]->isFree = 0;
1285 }
1286
1287 /*-----------------------------------------------------------------*/
1288 /* willCauseSpill - determines if allocating will cause a spill    */
1289 /*-----------------------------------------------------------------*/
1290 static int willCauseSpill ( int nr, int rt)
1291 {
1292     debugLog("%s\n",__FUNCTION__);
1293     /* first check if there are any avlb registers
1294        of te type required */
1295     if (rt == REG_PTR) {
1296         /* special case for pointer type 
1297            if pointer type not avlb then 
1298            check for type gpr */
1299         if (nFreeRegs(rt) >= nr)
1300             return 0;
1301         if (nFreeRegs(REG_GPR) >= nr)
1302             return 0;
1303     } else {
1304         if (pic14_ptrRegReq) {
1305             if (nFreeRegs(rt) >= nr)
1306                 return 0;
1307         } else {
1308             if (nFreeRegs(REG_PTR) +
1309                 nFreeRegs(REG_GPR) >= nr)
1310                 return 0;
1311         }
1312     }
1313
1314     debugLog(" ... yep it will (cause a spill)\n");
1315     /* it will cause a spil */
1316     return 1;
1317 }
1318
1319 /*-----------------------------------------------------------------*/
1320 /* positionRegs - the allocator can allocate same registers to res-*/
1321 /* ult and operand, if this happens make sure they are in the same */
1322 /* position as the operand otherwise chaos results                 */
1323 /*-----------------------------------------------------------------*/
1324 static void positionRegs (symbol *result, symbol *opsym, int lineno)
1325 {
1326         int count = min(result->nRegs,opsym->nRegs);
1327         int i , j = 0, shared = 0;
1328
1329     debugLog("%s\n",__FUNCTION__);
1330         /* if the result has been spilt then cannot share */
1331         if (opsym->isspilt)
1332                 return ;
1333  again:
1334         shared = 0;
1335         /* first make sure that they actually share */
1336         for ( i = 0 ; i < count; i++ ) {
1337                 for (j = 0 ; j < count ; j++ ) {
1338                         if (result->regs[i] == opsym->regs[j] && i !=j) {
1339                                 shared = 1;
1340                                 goto xchgPositions;
1341                         }
1342                 }
1343         }
1344  xchgPositions:
1345         if (shared) {
1346                 regs *tmp = result->regs[i];
1347                 result->regs[i] = result->regs[j];
1348                 result->regs[j] = tmp;          
1349                 goto again;
1350         }
1351 }
1352
1353 /*-----------------------------------------------------------------*/
1354 /* serialRegAssign - serially allocate registers to the variables  */
1355 /*-----------------------------------------------------------------*/
1356 static void serialRegAssign (eBBlock **ebbs, int count)
1357 {
1358     int i;
1359
1360     debugLog("%s\n",__FUNCTION__);
1361     /* for all blocks */
1362     for (i = 0; i < count ; i++ ) {
1363         
1364         iCode *ic;
1365         
1366         if (ebbs[i]->noPath &&
1367             (ebbs[i]->entryLabel != entryLabel &&
1368              ebbs[i]->entryLabel != returnLabel ))
1369             continue ;
1370
1371         /* of all instructions do */
1372         for (ic = ebbs[i]->sch ; ic ; ic = ic->next) {
1373          
1374           debugLog("  op: %s\n", decodeOp(ic->op));
1375
1376             /* if this is an ipop that means some live
1377                range will have to be assigned again */
1378             if (ic->op == IPOP)
1379                 reassignLR (IC_LEFT(ic));
1380
1381             /* if result is present && is a true symbol */
1382             if (IC_RESULT(ic) && ic->op != IFX &&
1383                 IS_TRUE_SYMOP(IC_RESULT(ic)))
1384                 OP_SYMBOL(IC_RESULT(ic))->allocreq = 1;
1385
1386             /* take away registers from live
1387                ranges that end at this instruction */      
1388             deassignLRs (ic, ebbs[i]) ;         
1389                     
1390             /* some don't need registers */
1391             if (SKIP_IC2(ic) ||
1392                 ic->op == JUMPTABLE ||
1393                 ic->op == IFX ||
1394                 ic->op == IPUSH ||
1395                 ic->op == IPOP ||
1396                 (IC_RESULT(ic) &&POINTER_SET(ic)) )
1397                 continue;   
1398             
1399             /* now we need to allocate registers
1400                only for the result */
1401             if (IC_RESULT(ic)) {
1402                 symbol *sym = OP_SYMBOL(IC_RESULT(ic));
1403                 bitVect *spillable;
1404                 int willCS ;
1405                 int j;
1406                 int ptrRegSet = 0;
1407                                
1408                 /* if it does not need or is spilt 
1409                    or is already assigned to registers
1410                    or will not live beyond this instructions */
1411                 if (!sym->nRegs      || 
1412                     sym->isspilt     || 
1413                     bitVectBitValue(_G.regAssigned,sym->key) ||
1414                     sym->liveTo <= ic->seq)
1415                     continue ;
1416
1417                 /* if some liverange has been spilt at the block level
1418                    and this one live beyond this block then spil this
1419                    to be safe */
1420                 if (_G.blockSpil && sym->liveTo > ebbs[i]->lSeq) {
1421                     spillThis (sym);
1422                     continue ;
1423                 }
1424                 /* if trying to allocate this will cause
1425                    a spill and there is nothing to spill 
1426                    or this one is rematerializable then
1427                    spill this one */
1428                 willCS = willCauseSpill(sym->nRegs,sym->regType);
1429                 spillable = computeSpillable(ic);
1430                 if ( sym->remat ||                  
1431                     (willCS  && bitVectIsZero(spillable) ) ) {
1432
1433                     spillThis (sym) ;
1434                     continue ;
1435
1436                 }
1437
1438                 /* if it has a spillocation & is used less than
1439                    all other live ranges then spill this */
1440                 if ( willCS && sym->usl.spillLoc ) {
1441
1442                     symbol *leastUsed = 
1443                         leastUsedLR(liveRangesWith (spillable ,
1444                                                     allLRs,
1445                                                     ebbs[i],
1446                                                     ic));
1447                     if (leastUsed && 
1448                         leastUsed->used > sym->used) {
1449                         spillThis (sym);
1450                         continue;
1451                     }
1452                 }               
1453                 
1454                 if(ic->op == RECEIVE)
1455                   debugLog("When I get clever, I'll optimize the receive logic\n");
1456
1457                 /* if we need ptr regs for the right side
1458                    then mark it */
1459                 if (POINTER_GET(ic) && getSize(OP_SYMBOL(IC_LEFT(ic))->type) 
1460                     <= PTRSIZE) 
1461                 {
1462                     pic14_ptrRegReq++;
1463                     ptrRegSet = 1;
1464                 }
1465                 /* else we assign registers to it */            
1466                 _G.regAssigned = bitVectSetBit(_G.regAssigned,sym->key);
1467
1468           debugLog("  %d - \n",__LINE__);
1469
1470                 for (j = 0 ; j < sym->nRegs ;j++ ) {
1471                     if (sym->regType == REG_PTR)
1472                         sym->regs[j] = getRegPtr(ic,ebbs[i],sym);
1473                     else
1474                         sym->regs[j] = getRegGpr(ic,ebbs[i],sym);
1475
1476                     /* if the allocation falied which means
1477                        this was spilt then break */
1478                     if (!sym->regs[j])
1479                         break;
1480                 }
1481           debugLog("  %d - \n",__LINE__);
1482
1483                 /* if it shares registers with operands make sure
1484                    that they are in the same position */
1485                 if (IC_LEFT(ic) && IS_SYMOP(IC_LEFT(ic)) &&
1486                     OP_SYMBOL(IC_LEFT(ic))->nRegs  && ic->op != '=')
1487                         positionRegs(OP_SYMBOL(IC_RESULT(ic)),
1488                                      OP_SYMBOL(IC_LEFT(ic)),ic->lineno);
1489                 /* do the same for the right operand */
1490                 if (IC_RIGHT(ic) && IS_SYMOP(IC_RIGHT(ic)) &&
1491                     OP_SYMBOL(IC_RIGHT(ic))->nRegs && ic->op != '=')
1492                         positionRegs(OP_SYMBOL(IC_RESULT(ic)),
1493                                      OP_SYMBOL(IC_RIGHT(ic)),ic->lineno);
1494                 
1495           debugLog("  %d - \n",__LINE__);
1496                 if (ptrRegSet) {
1497           debugLog("  %d - \n",__LINE__);
1498                     pic14_ptrRegReq--;
1499                     ptrRegSet = 0;
1500                 }
1501                                 
1502             }       
1503         }
1504     }
1505 }
1506
1507 /*-----------------------------------------------------------------*/
1508 /* rUmaskForOp :- returns register mask for an operand             */
1509 /*-----------------------------------------------------------------*/
1510 static bitVect *rUmaskForOp (operand *op)
1511 {
1512     bitVect *rumask;
1513     symbol *sym;
1514     int j;
1515     
1516     debugLog("%s\n",__FUNCTION__);
1517     /* only temporaries are assigned registers */
1518     if (!IS_ITEMP(op)) 
1519         return NULL;
1520
1521     sym = OP_SYMBOL(op);
1522     
1523     /* if spilt or no registers assigned to it
1524        then nothing */
1525     if (sym->isspilt || !sym->nRegs)
1526         return NULL;
1527
1528     rumask = newBitVect(pic14_nRegs);
1529
1530     for (j = 0; j < sym->nRegs; j++) {  
1531         rumask = bitVectSetBit(rumask,
1532                                sym->regs[j]->rIdx);
1533     }
1534
1535     return rumask;
1536 }
1537
1538 /*-----------------------------------------------------------------*/
1539 /* regsUsedIniCode :- returns bit vector of registers used in iCode*/
1540 /*-----------------------------------------------------------------*/
1541 static bitVect *regsUsedIniCode (iCode *ic)
1542 {
1543     bitVect *rmask = newBitVect(pic14_nRegs);
1544
1545     debugLog("%s\n",__FUNCTION__);
1546     /* do the special cases first */
1547     if (ic->op == IFX ) {
1548         rmask = bitVectUnion(rmask,
1549                              rUmaskForOp(IC_COND(ic)));
1550         goto ret;
1551     }
1552
1553     /* for the jumptable */
1554     if (ic->op == JUMPTABLE) {
1555         rmask = bitVectUnion(rmask,
1556                              rUmaskForOp(IC_JTCOND(ic)));
1557
1558         goto ret;
1559     }
1560
1561     /* of all other cases */
1562     if (IC_LEFT(ic)) 
1563         rmask = bitVectUnion(rmask,
1564                              rUmaskForOp(IC_LEFT(ic)));
1565         
1566     
1567     if (IC_RIGHT(ic))
1568         rmask = bitVectUnion(rmask,
1569                              rUmaskForOp(IC_RIGHT(ic)));
1570
1571     if (IC_RESULT(ic))
1572         rmask = bitVectUnion(rmask,
1573                              rUmaskForOp(IC_RESULT(ic)));
1574
1575  ret:
1576     return rmask;
1577 }
1578
1579 /*-----------------------------------------------------------------*/
1580 /* createRegMask - for each instruction will determine the regsUsed*/
1581 /*-----------------------------------------------------------------*/
1582 static void createRegMask (eBBlock **ebbs, int count)
1583 {
1584     int i;
1585
1586     debugLog("%s\n",__FUNCTION__);
1587     /* for all blocks */
1588     for (i = 0; i < count ; i++ ) {
1589         iCode *ic ;
1590
1591         if ( ebbs[i]->noPath &&
1592              ( ebbs[i]->entryLabel != entryLabel &&
1593                ebbs[i]->entryLabel != returnLabel ))
1594             continue ;
1595
1596         /* for all instructions */
1597         for ( ic = ebbs[i]->sch ; ic ; ic = ic->next ) {
1598             
1599             int j;
1600
1601             if (SKIP_IC2(ic) || !ic->rlive)
1602                 continue ;
1603             
1604             /* first mark the registers used in this
1605                instruction */
1606             ic->rUsed = regsUsedIniCode(ic);
1607             _G.funcrUsed = bitVectUnion(_G.funcrUsed,ic->rUsed);
1608
1609             /* now create the register mask for those 
1610                registers that are in use : this is a
1611                super set of ic->rUsed */
1612             ic->rMask = newBitVect(pic14_nRegs+1);
1613
1614             /* for all live Ranges alive at this point */
1615             for (j = 1; j < ic->rlive->size; j++ ) {
1616                 symbol *sym;
1617                 int k;
1618
1619                 /* if not alive then continue */
1620                 if (!bitVectBitValue(ic->rlive,j))
1621                     continue ;
1622
1623                 /* find the live range we are interested in */
1624                 if (!(sym = hTabItemWithKey(liveRanges,j))) {
1625                     werror (E_INTERNAL_ERROR,__FILE__,__LINE__,
1626                             "createRegMask cannot find live range");
1627                     exit(0);
1628                 }
1629
1630                 /* if no register assigned to it */
1631                 if (!sym->nRegs || sym->isspilt)
1632                     continue ;
1633
1634                 /* for all the registers allocated to it */
1635                 for (k = 0 ; k < sym->nRegs ;k++)
1636                     if (sym->regs[k])
1637                         ic->rMask =
1638                             bitVectSetBit(ic->rMask,sym->regs[k]->rIdx);
1639             }
1640         }
1641     }
1642 }
1643
1644 /*-----------------------------------------------------------------*/
1645 /* rematStr - returns the rematerialized string for a remat var    */
1646 /*-----------------------------------------------------------------*/
1647 static char *rematStr (symbol *sym)
1648 {
1649     char *s = buffer;   
1650     iCode *ic = sym->rematiCode;    
1651
1652     debugLog("%s\n",__FUNCTION__);
1653     while (1) {
1654
1655         printf("%s\n",s);
1656         /* if plus or minus print the right hand side */
1657 /*
1658         if (ic->op == '+' || ic->op == '-') {
1659             sprintf(s,"0x%04x %c ",(int) operandLitValue(IC_RIGHT(ic)),
1660                     ic->op );
1661             s += strlen(s);
1662             ic = OP_SYMBOL(IC_LEFT(ic))->rematiCode;
1663             continue ;
1664         }
1665 */
1666         if (ic->op == '+' || ic->op == '-') {
1667             iCode *ric = OP_SYMBOL(IC_LEFT(ic))->rematiCode;
1668             sprintf(s,"(%s %c 0x%04x)",
1669                     OP_SYMBOL(IC_LEFT(ric))->rname,
1670                     ic->op,
1671                     (int) operandLitValue(IC_RIGHT(ic)));
1672
1673             //s += strlen(s);
1674             //ic = OP_SYMBOL(IC_LEFT(ic))->rematiCode;
1675             //continue ;
1676             return buffer;
1677         }
1678
1679         /* we reached the end */
1680         sprintf(s,"%s\n",OP_SYMBOL(IC_LEFT(ic))->rname);
1681         break;
1682     }
1683
1684         printf("%s\n",buffer);
1685     return buffer ;
1686 }
1687
1688 /*-----------------------------------------------------------------*/
1689 /* regTypeNum - computes the type & number of registers required   */
1690 /*-----------------------------------------------------------------*/
1691 static void regTypeNum ()
1692 {
1693     symbol *sym;
1694     int k;
1695     iCode *ic;
1696
1697     debugLog("%s\n",__FUNCTION__);
1698     /* for each live range do */
1699     for ( sym = hTabFirstItem(liveRanges,&k); sym ;
1700           sym = hTabNextItem(liveRanges,&k)) {
1701
1702           debugLog("  %d - %s\n",__LINE__ , sym->rname);
1703
1704         /* if used zero times then no registers needed */
1705         if ((sym->liveTo - sym->liveFrom) == 0)
1706             continue ;
1707
1708
1709         /* if the live range is a temporary */
1710         if (sym->isitmp) {
1711
1712           debugLog("  %d - \n",__LINE__);
1713
1714             /* if the type is marked as a conditional */
1715             if (sym->regType == REG_CND)
1716                 continue ;
1717
1718             /* if used in return only then we don't 
1719                need registers */
1720             if (sym->ruonly || sym->accuse) {
1721                 if (IS_AGGREGATE(sym->type) || sym->isptr)
1722                     sym->type = aggrToPtr(sym->type,FALSE);
1723           debugLog("  %d - \n",__LINE__);
1724
1725                 continue ;
1726             }
1727             
1728             /* if the symbol has only one definition &
1729                that definition is a get_pointer and the
1730                pointer we are getting is rematerializable and
1731                in "data" space */
1732                
1733             if (bitVectnBitsOn(sym->defs) == 1 &&
1734                 (ic = hTabItemWithKey(iCodehTab,
1735                                       bitVectFirstBit(sym->defs))) &&
1736                 POINTER_GET(ic) && 
1737                 !IS_BITVAR(sym->etype)) {
1738                 
1739           debugLog("  %d - \n",__LINE__);
1740                                 
1741                 /* if remat in data space */
1742                 if (OP_SYMBOL(IC_LEFT(ic))->remat &&
1743                     DCL_TYPE(aggrToPtr(sym->type,FALSE)) == POINTER) {
1744                 
1745                     /* create a psuedo symbol & force a spil */
1746                     symbol *psym = newSymbol(rematStr(OP_SYMBOL(IC_LEFT(ic))),1);
1747                     psym->type = sym->type;
1748                     psym->etype = sym->etype;
1749                     strcpy(psym->rname,psym->name);
1750                     sym->isspilt = 1;
1751                     sym->usl.spillLoc = psym;
1752                     continue ;
1753                 }
1754
1755                 /* if in data space or idata space then try to
1756                    allocate pointer register */
1757                    
1758             }
1759                 
1760             /* if not then we require registers */
1761             sym->nRegs = ((IS_AGGREGATE(sym->type) || sym->isptr ) ?
1762                           getSize(sym->type = aggrToPtr(sym->type,FALSE)) :
1763                           getSize(sym->type));
1764
1765             if (sym->nRegs > 4) {
1766                 fprintf(stderr,"allocated more than 4 or 0 registers for type ");
1767                 printTypeChain(sym->type,stderr);fprintf(stderr,"\n");
1768             }
1769             
1770           debugLog("  %d - \n",__LINE__);
1771
1772             /* determine the type of register required */
1773             if (sym->nRegs == 1   && 
1774                 IS_PTR(sym->type) && 
1775                 sym->uptr) 
1776                 sym->regType = REG_PTR ;            
1777             else 
1778                 sym->regType = REG_GPR ;
1779             debugLog("  reg type %s\n",debugLogRegType(sym->regType));
1780
1781         } else 
1782             /* for the first run we don't provide */
1783             /* registers for true symbols we will */
1784             /* see how things go                  */
1785             sym->nRegs = 0 ;    
1786     }
1787     
1788 }
1789
1790 /*-----------------------------------------------------------------*/
1791 /* freeAllRegs - mark all registers as free                        */
1792 /*-----------------------------------------------------------------*/
1793 static void freeAllRegs()
1794 {
1795     int i;
1796
1797     debugLog("%s\n",__FUNCTION__);
1798     for (i=0;i< pic14_nRegs;i++ )
1799         regspic14[i].isFree = 1;
1800 }
1801
1802 /*-----------------------------------------------------------------*/
1803 /* deallocStackSpil - this will set the stack pointer back         */
1804 /*-----------------------------------------------------------------*/
1805 static DEFSETFUNC(deallocStackSpil)
1806 {
1807     symbol *sym = item;
1808
1809     debugLog("%s\n",__FUNCTION__);
1810     deallocLocal(sym);
1811     return 0;
1812 }
1813
1814 /*-----------------------------------------------------------------*/
1815 /* farSpacePackable - returns the packable icode for far variables */
1816 /*-----------------------------------------------------------------*/
1817 static iCode *farSpacePackable (iCode *ic)
1818 {
1819     iCode *dic ;
1820
1821     debugLog("%s\n",__FUNCTION__);
1822     /* go thru till we find a definition for the
1823        symbol on the right */
1824     for ( dic = ic->prev ; dic ; dic = dic->prev) {
1825                 
1826         /* if the definition is a call then no */
1827         if ((dic->op == CALL || dic->op == PCALL) &&
1828             IC_RESULT(dic)->key == IC_RIGHT(ic)->key) {
1829             return NULL;
1830         }
1831         
1832         /* if shift by unknown amount then not */
1833         if ((dic->op == LEFT_OP || dic->op == RIGHT_OP) &&
1834             IC_RESULT(dic)->key == IC_RIGHT(ic)->key)
1835             return NULL;
1836
1837         /* if pointer get and size > 1 */
1838         if (POINTER_GET(dic) &&
1839             getSize(aggrToPtr(operandType(IC_LEFT(dic)),FALSE)) > 1)
1840             return NULL ;
1841
1842         if (POINTER_SET(dic) &&
1843             getSize(aggrToPtr(operandType(IC_RESULT(dic)),FALSE)) > 1)
1844             return NULL ;
1845
1846         /* if any three is a true symbol in far space */
1847         if (IC_RESULT(dic) &&
1848             IS_TRUE_SYMOP(IC_RESULT(dic)) &&
1849             isOperandInFarSpace(IC_RESULT(dic)))         
1850             return NULL;
1851
1852         if (IC_RIGHT(dic) &&
1853             IS_TRUE_SYMOP(IC_RIGHT(dic)) &&
1854             isOperandInFarSpace(IC_RIGHT(dic)) &&
1855             !isOperandEqual(IC_RIGHT(dic),IC_RESULT(ic)))
1856             return NULL;
1857
1858         if (IC_LEFT(dic) &&
1859             IS_TRUE_SYMOP(IC_LEFT(dic)) &&
1860             isOperandInFarSpace(IC_LEFT(dic)) &&
1861             !isOperandEqual(IC_LEFT(dic),IC_RESULT(ic)))
1862             return NULL;
1863         
1864         if (isOperandEqual(IC_RIGHT(ic),IC_RESULT(dic))) {
1865             if ( (dic->op == LEFT_OP  ||
1866                   dic->op == RIGHT_OP ||
1867                   dic->op == '-') &&
1868                  IS_OP_LITERAL(IC_RIGHT(dic)))
1869                 return NULL;
1870             else
1871                 return dic;
1872         }
1873     }
1874
1875     return NULL;
1876 }
1877
1878 /*-----------------------------------------------------------------*/
1879 /* packRegsForAssign - register reduction for assignment           */
1880 /*-----------------------------------------------------------------*/
1881 static int packRegsForAssign (iCode *ic,eBBlock *ebp)
1882 {
1883
1884     iCode *dic, *sic;
1885     
1886     debugLog("%s\n",__FUNCTION__);
1887
1888     debugAopGet("  result:",IC_RESULT(ic));
1889     debugAopGet("  left:",IC_LEFT(ic));
1890     debugAopGet("  right:",IC_RIGHT(ic));
1891
1892     if (!IS_ITEMP(IC_RIGHT(ic))       ||        
1893         OP_SYMBOL(IC_RIGHT(ic))->isind ||
1894         OP_LIVETO(IC_RIGHT(ic)) > ic->seq) {
1895         return 0;
1896     }
1897         
1898     /* if the true symbol is defined in far space or on stack
1899        then we should not since this will increase register pressure */
1900     if (isOperandInFarSpace(IC_RESULT(ic))) {
1901         if ((dic = farSpacePackable(ic)))
1902             goto pack;
1903         else
1904             return 0;
1905         
1906     }
1907     /* find the definition of iTempNN scanning backwards if we find a 
1908        a use of the true symbol before we find the definition then 
1909        we cannot pack */        
1910     for ( dic = ic->prev ; dic ; dic = dic->prev) {
1911
1912         /* if there is a function call and this is
1913            a parameter & not my parameter then don't pack it */
1914         if ( (dic->op == CALL || dic->op == PCALL) &&
1915              (OP_SYMBOL(IC_RESULT(ic))->_isparm &&
1916               !OP_SYMBOL(IC_RESULT(ic))->ismyparm)) {
1917           debugLog("  %d - \n",__LINE__);
1918             dic = NULL;
1919             break;
1920         }
1921
1922         if (SKIP_IC2(dic))
1923             continue;
1924
1925         if (IS_TRUE_SYMOP(IC_RESULT(dic)) &&
1926             IS_OP_VOLATILE(IC_RESULT(dic))) {
1927           debugLog("  %d - \n",__LINE__);
1928                 dic = NULL;
1929                 break;
1930         }
1931
1932         if (IS_SYMOP(IC_RESULT(dic)) &&
1933             IC_RESULT(dic)->key == IC_RIGHT(ic)->key) {
1934           debugLog("  %d - dic key == ic key -- pointer set=%c\n",__LINE__,((POINTER_SET(dic)) ? 'Y' :'N') );
1935             if (POINTER_SET(dic))
1936                 dic = NULL;
1937
1938             break;          
1939         }
1940
1941         if (IS_SYMOP(IC_RIGHT(dic)) && 
1942             (IC_RIGHT(dic)->key == IC_RESULT(ic)->key ||
1943              IC_RIGHT(dic)->key == IC_RIGHT(ic)->key)) {
1944           debugLog("  %d - \n",__LINE__);
1945             dic = NULL;
1946             break;
1947         }
1948         
1949         if (IS_SYMOP(IC_LEFT(dic)) && 
1950             (IC_LEFT(dic)->key == IC_RESULT(ic)->key ||
1951              IC_LEFT(dic)->key == IC_RIGHT(ic)->key)) {
1952           debugLog("  %d - \n",__LINE__);
1953             dic = NULL;
1954             break;
1955         }
1956
1957         if (POINTER_SET(dic) && 
1958             IC_RESULT(dic)->key == IC_RESULT(ic)->key ) {
1959           debugLog("  %d - \n",__LINE__);
1960             dic = NULL ;
1961             break;
1962         }
1963     }
1964     
1965     if (!dic)
1966         return 0 ; /* did not find */
1967             
1968     /* if the result is on stack or iaccess then it must be
1969        the same atleast one of the operands */
1970     if (OP_SYMBOL(IC_RESULT(ic))->onStack  || 
1971         OP_SYMBOL(IC_RESULT(ic))->iaccess ) {
1972         
1973         /* the operation has only one symbol
1974            operator then we can pack */
1975         if ((IC_LEFT(dic) && !IS_SYMOP(IC_LEFT(dic))) ||
1976             (IC_RIGHT(dic) && !IS_SYMOP(IC_RIGHT(dic))))
1977             goto pack;
1978
1979         if (!((IC_LEFT(dic) &&
1980              IC_RESULT(ic)->key == IC_LEFT(dic)->key) ||
1981               (IC_RIGHT(dic) &&
1982                IC_RESULT(ic)->key == IC_RIGHT(dic)->key)))
1983             return 0;                
1984     }
1985 pack:
1986     debugLog("  packing. removing %s\n",OP_SYMBOL(IC_RIGHT(ic))->rname);
1987     /* found the definition */
1988     /* replace the result with the result of */
1989     /* this assignment and remove this assignment */
1990     IC_RESULT(dic) = IC_RESULT(ic) ;
1991
1992     if (IS_ITEMP(IC_RESULT(dic)) && OP_SYMBOL(IC_RESULT(dic))->liveFrom > dic->seq) {
1993             OP_SYMBOL(IC_RESULT(dic))->liveFrom = dic->seq;
1994     }
1995     /* delete from liverange table also 
1996        delete from all the points inbetween and the new
1997        one */
1998     for ( sic = dic; sic != ic ; sic = sic->next ) {    
1999         bitVectUnSetBit(sic->rlive,IC_RESULT(ic)->key);
2000         if (IS_ITEMP(IC_RESULT(dic)))
2001             bitVectSetBit(sic->rlive,IC_RESULT(dic)->key);
2002     }
2003         
2004     remiCodeFromeBBlock(ebp,ic);
2005     hTabDeleteItem (&iCodehTab,ic->key,ic,DELETE_ITEM,NULL);
2006     OP_DEFS(IC_RESULT(dic)) = bitVectSetBit(OP_DEFS(IC_RESULT(dic)),dic->key);
2007     return 1;
2008
2009     
2010 }
2011
2012 /*-----------------------------------------------------------------*/
2013 /* findAssignToSym : scanning backwards looks for first assig found*/
2014 /*-----------------------------------------------------------------*/
2015 static iCode *findAssignToSym (operand *op,iCode *ic)
2016 {
2017     iCode *dic;
2018
2019     debugLog("%s\n",__FUNCTION__);
2020     for (dic = ic->prev ; dic ; dic = dic->prev) {
2021         
2022         /* if definition by assignment */
2023         if (dic->op == '='                 && 
2024             !POINTER_SET(dic)              &&
2025             IC_RESULT(dic)->key == op->key
2026 /*          &&  IS_TRUE_SYMOP(IC_RIGHT(dic)) */
2027             ) {    
2028
2029             /* we are interested only if defined in far space */
2030             /* or in stack space in case of + & - */
2031
2032             /* if assigned to a non-symbol then return
2033                true */
2034             if (!IS_SYMOP(IC_RIGHT(dic)))
2035                 break ;
2036
2037             /* if the symbol is in far space then
2038                we should not */
2039             if (isOperandInFarSpace(IC_RIGHT(dic)))
2040                 return NULL ;
2041
2042             /* for + & - operations make sure that
2043                if it is on the stack it is the same
2044                as one of the three operands */
2045             if ((ic->op == '+' || ic->op == '-') &&
2046                 OP_SYMBOL(IC_RIGHT(dic))->onStack) {
2047
2048                 if ( IC_RESULT(ic)->key != IC_RIGHT(dic)->key &&
2049                      IC_LEFT(ic)->key   != IC_RIGHT(dic)->key &&
2050                      IC_RIGHT(ic)->key  != IC_RIGHT(dic)->key)
2051                     return NULL;
2052             }           
2053
2054             break ;
2055                 
2056         }
2057
2058         /* if we find an usage then we cannot delete it */
2059         if (IC_LEFT(dic) && IC_LEFT(dic)->key == op->key)
2060             return NULL;
2061             
2062         if (IC_RIGHT(dic) && IC_RIGHT(dic)->key == op->key)
2063             return NULL;
2064
2065         if (POINTER_SET(dic) && IC_RESULT(dic)->key == op->key)
2066             return NULL;
2067     }
2068
2069     /* now make sure that the right side of dic
2070        is not defined between ic & dic */       
2071     if (dic) {
2072         iCode *sic = dic->next ;
2073
2074         for (; sic != ic ; sic = sic->next)
2075             if (IC_RESULT(sic) &&
2076                 IC_RESULT(sic)->key == IC_RIGHT(dic)->key)
2077                 return NULL;
2078     }
2079
2080     return dic;
2081         
2082         
2083 }
2084
2085 /*-----------------------------------------------------------------*/
2086 /* packRegsForSupport :- reduce some registers for support calls   */
2087 /*-----------------------------------------------------------------*/
2088 static int packRegsForSupport (iCode *ic, eBBlock *ebp)
2089 {
2090     int change = 0 ;
2091
2092     debugLog("%s\n",__FUNCTION__);
2093     /* for the left & right operand :- look to see if the
2094        left was assigned a true symbol in far space in that
2095        case replace them */
2096     if (IS_ITEMP(IC_LEFT(ic)) && 
2097         OP_SYMBOL(IC_LEFT(ic))->liveTo <= ic->seq) {
2098         iCode *dic = findAssignToSym(IC_LEFT(ic),ic);
2099         iCode *sic;
2100
2101         if (!dic)
2102             goto right ;
2103
2104         debugAopGet("removing left:",IC_LEFT(ic));
2105
2106         /* found it we need to remove it from the
2107            block */
2108         for ( sic = dic; sic != ic ; sic = sic->next )
2109             bitVectUnSetBit(sic->rlive,IC_LEFT(ic)->key);
2110
2111         IC_LEFT(ic)->operand.symOperand =
2112             IC_RIGHT(dic)->operand.symOperand;
2113         IC_LEFT(ic)->key = IC_RIGHT(dic)->operand.symOperand->key;
2114         remiCodeFromeBBlock(ebp,dic);
2115         hTabDeleteItem (&iCodehTab,dic->key,dic,DELETE_ITEM,NULL);
2116         change++;      
2117     }
2118     
2119     /* do the same for the right operand */
2120  right:    
2121     if (!change && 
2122         IS_ITEMP(IC_RIGHT(ic)) &&
2123         OP_SYMBOL(IC_RIGHT(ic))->liveTo <= ic->seq) {
2124         iCode *dic = findAssignToSym(IC_RIGHT(ic),ic);
2125         iCode *sic;
2126         
2127         if (!dic)
2128             return change ;
2129
2130         /* if this is a subtraction & the result
2131            is a true symbol in far space then don't pack */
2132         if (ic->op == '-' && IS_TRUE_SYMOP(IC_RESULT(dic))) {
2133             sym_link *etype =getSpec(operandType(IC_RESULT(dic)));
2134             if (IN_FARSPACE(SPEC_OCLS(etype)))
2135                 return change ;
2136         }
2137
2138         debugAopGet("removing right:",IC_RIGHT(ic));
2139
2140         /* found it we need to remove it from the
2141            block */
2142         for ( sic = dic; sic != ic ; sic = sic->next )
2143             bitVectUnSetBit(sic->rlive,IC_RIGHT(ic)->key);
2144         
2145         IC_RIGHT(ic)->operand.symOperand =
2146             IC_RIGHT(dic)->operand.symOperand;
2147         IC_RIGHT(ic)->key = IC_RIGHT(dic)->operand.symOperand->key;
2148         
2149         remiCodeFromeBBlock(ebp,dic);
2150         hTabDeleteItem (&iCodehTab,dic->key,dic,DELETE_ITEM,NULL);
2151         change ++;
2152     }
2153    
2154     return change ;
2155 }
2156
2157 #define IS_OP_RUONLY(x) (x && IS_SYMOP(x) && OP_SYMBOL(x)->ruonly)
2158
2159
2160 /*-----------------------------------------------------------------*/
2161 /* packRegsForOneuse : - will reduce some registers for single Use */ 
2162 /*-----------------------------------------------------------------*/
2163 static iCode *packRegsForOneuse (iCode *ic, operand *op , eBBlock *ebp)
2164 {
2165     bitVect *uses ;
2166     iCode *dic, *sic;
2167
2168     debugLog("%s\n",__FUNCTION__);
2169     /* if returning a literal then do nothing */
2170     if (!IS_SYMOP(op))
2171         return NULL;
2172     
2173     /* only upto 2 bytes since we cannot predict
2174        the usage of b, & acc */
2175     if (getSize(operandType(op)) >  (fReturnSize - 2) &&
2176         ic->op != RETURN             &&
2177         ic->op != SEND)
2178         return NULL;
2179
2180     /* this routine will mark the a symbol as used in one 
2181        instruction use only && if the definition is local 
2182        (ie. within the basic block) && has only one definition &&
2183        that definition is either a return value from a 
2184        function or does not contain any variables in
2185        far space */
2186     uses = bitVectCopy(OP_USES(op));
2187     bitVectUnSetBit(uses,ic->key); /* take away this iCode */
2188     if (!bitVectIsZero(uses)) /* has other uses */
2189         return NULL ;
2190     
2191     /* if it has only one defintion */
2192     if (bitVectnBitsOn(OP_DEFS(op)) > 1)
2193         return NULL ; /* has more than one definition */
2194
2195     /* get that definition */
2196     if (!(dic = 
2197           hTabItemWithKey(iCodehTab,
2198                           bitVectFirstBit(OP_DEFS(op)))))
2199         return NULL ;
2200
2201     /* found the definition now check if it is local */
2202     if (dic->seq < ebp->fSeq ||
2203         dic->seq > ebp->lSeq)
2204         return NULL ; /* non-local */
2205
2206     /* now check if it is the return from
2207        a function call */
2208     if (dic->op == CALL || dic->op == PCALL ) {
2209         if (ic->op != SEND && ic->op != RETURN) {
2210             OP_SYMBOL(op)->ruonly = 1;
2211             return dic;
2212         }
2213         dic = dic->next ;
2214     }
2215         
2216     
2217     /* otherwise check that the definition does
2218        not contain any symbols in far space */
2219     if (isOperandInFarSpace(IC_LEFT(dic))  ||
2220         isOperandInFarSpace(IC_RIGHT(dic)) ||
2221         IS_OP_RUONLY(IC_LEFT(ic))          ||
2222         IS_OP_RUONLY(IC_RIGHT(ic)) )        {
2223         return NULL;
2224     }
2225     
2226     /* if pointer set then make sure the pointer
2227        is one byte */
2228     if (POINTER_SET(dic) && 
2229         !IS_DATA_PTR(aggrToPtr(operandType(IC_RESULT(dic)),FALSE)))
2230         return NULL ;
2231
2232     if (POINTER_GET(dic) && 
2233         !IS_DATA_PTR(aggrToPtr(operandType(IC_LEFT(dic)),FALSE)))
2234         return NULL ;
2235     
2236     sic = dic;
2237
2238     /* also make sure the intervenening instructions
2239        don't have any thing in far space */
2240     for (dic = dic->next ; dic && dic != ic ; dic = dic->next) {
2241                 
2242         /* if there is an intervening function call then no */
2243         if (dic->op == CALL || dic->op == PCALL)
2244                 return NULL;
2245         /* if pointer set then make sure the pointer
2246            is one byte */
2247         if (POINTER_SET(dic) && 
2248             !IS_DATA_PTR(aggrToPtr(operandType(IC_RESULT(dic)),FALSE)))
2249             return NULL ;
2250         
2251         if (POINTER_GET(dic) && 
2252             !IS_DATA_PTR(aggrToPtr(operandType(IC_LEFT(dic)),FALSE)))
2253             return NULL ;
2254
2255         /* if address of & the result is remat then okay */
2256         if (dic->op == ADDRESS_OF &&
2257             OP_SYMBOL(IC_RESULT(dic))->remat)
2258             continue ;
2259            
2260         /* if operand has size of three or more & this
2261            operation is a '*','/' or '%' then 'b' may
2262            cause a problem */
2263         if (( dic->op == '%' || dic->op == '/' || dic->op == '*') &&
2264             getSize(operandType(op)) >= 3)
2265                 return NULL;
2266
2267         /* if left or right or result is in far space */
2268         if (isOperandInFarSpace(IC_LEFT(dic))   ||
2269             isOperandInFarSpace(IC_RIGHT(dic))  ||
2270             isOperandInFarSpace(IC_RESULT(dic)) ||
2271             IS_OP_RUONLY(IC_LEFT(dic))          ||
2272             IS_OP_RUONLY(IC_RIGHT(dic))         ||
2273             IS_OP_RUONLY(IC_RESULT(dic))            ) {
2274             return NULL;
2275         }
2276     }
2277                 
2278     OP_SYMBOL(op)->ruonly = 1;
2279     return sic;
2280         
2281 }
2282
2283 /*-----------------------------------------------------------------*/
2284 /* isBitwiseOptimizable - requirements of JEAN LOUIS VERN          */
2285 /*-----------------------------------------------------------------*/
2286 static bool isBitwiseOptimizable (iCode *ic)
2287 {
2288     sym_link *ltype = getSpec(operandType(IC_LEFT(ic)));
2289     sym_link *rtype = getSpec(operandType(IC_RIGHT(ic)));
2290
2291     debugLog("%s\n",__FUNCTION__);
2292     /* bitwise operations are considered optimizable
2293        under the following conditions (Jean-Louis VERN) 
2294        
2295        x & lit
2296        bit & bit
2297        bit & x
2298        bit ^ bit
2299        bit ^ x
2300        x   ^ lit
2301        x   | lit
2302        bit | bit
2303        bit | x
2304     */    
2305     if ( IS_LITERAL(rtype) ||
2306          (IS_BITVAR(ltype) && IN_BITSPACE(SPEC_OCLS(ltype))))
2307         return TRUE ;
2308     else
2309         return FALSE ;    
2310 }
2311
2312 /*-----------------------------------------------------------------*/
2313 /* packRegsForAccUse - pack registers for acc use                  */
2314 /*-----------------------------------------------------------------*/
2315 static void packRegsForAccUse (iCode *ic)
2316 {
2317     iCode *uic;
2318     
2319     debugLog("%s\n",__FUNCTION__);
2320     /* if + or - then it has to be one byte result */
2321     if ((ic->op == '+' || ic->op == '-')
2322         && getSize(operandType(IC_RESULT(ic))) > 1)
2323         return ;
2324     
2325     /* if shift operation make sure right side is not a literal */
2326     if (ic->op == RIGHT_OP  &&
2327         ( isOperandLiteral(IC_RIGHT(ic)) ||
2328           getSize(operandType(IC_RESULT(ic))) > 1))
2329         return ;
2330         
2331     if (ic->op == LEFT_OP &&        
2332         ( isOperandLiteral(IC_RIGHT(ic)) ||
2333           getSize(operandType(IC_RESULT(ic))) > 1))
2334         return ;
2335         
2336     if (IS_BITWISE_OP(ic) &&
2337         getSize(operandType(IC_RESULT(ic))) > 1)
2338         return ;
2339             
2340         
2341     /* has only one definition */
2342     if (bitVectnBitsOn(OP_DEFS(IC_RESULT(ic))) > 1)
2343         return ;
2344
2345     /* has only one use */
2346     if (bitVectnBitsOn(OP_USES(IC_RESULT(ic))) > 1)
2347         return ;
2348
2349     /* and the usage immediately follows this iCode */
2350     if (!(uic = hTabItemWithKey(iCodehTab,
2351                                 bitVectFirstBit(OP_USES(IC_RESULT(ic))))))
2352         return ;
2353
2354     if (ic->next != uic)
2355         return ;
2356     
2357     /* if it is a conditional branch then we definitely can */
2358     if (uic->op == IFX  ) 
2359         goto accuse;
2360
2361     if ( uic->op == JUMPTABLE )
2362         return ;
2363
2364     /* if the usage is not is an assignment
2365        or an arithmetic / bitwise / shift operation then not */
2366     if (POINTER_SET(uic) && 
2367         getSize(aggrToPtr(operandType(IC_RESULT(uic)),FALSE)) > 1)
2368         return;
2369
2370     if (uic->op != '=' && 
2371         !IS_ARITHMETIC_OP(uic) &&
2372         !IS_BITWISE_OP(uic)    &&
2373         uic->op != LEFT_OP &&
2374         uic->op != RIGHT_OP )
2375         return;
2376
2377     /* if used in ^ operation then make sure right is not a 
2378        literl */
2379     if (uic->op == '^' && isOperandLiteral(IC_RIGHT(uic)))
2380         return ;
2381
2382     /* if shift operation make sure right side is not a literal */
2383     if (uic->op == RIGHT_OP  &&
2384         ( isOperandLiteral(IC_RIGHT(uic)) ||
2385           getSize(operandType(IC_RESULT(uic))) > 1))
2386         return ;
2387
2388     if (uic->op == LEFT_OP &&        
2389         ( isOperandLiteral(IC_RIGHT(uic)) ||
2390           getSize(operandType(IC_RESULT(uic))) > 1))
2391         return ;
2392             
2393     /* make sure that the result of this icode is not on the
2394        stack, since acc is used to compute stack offset */
2395     if (IS_TRUE_SYMOP(IC_RESULT(uic)) &&
2396         OP_SYMBOL(IC_RESULT(uic))->onStack)
2397         return ;
2398
2399     /* if either one of them in far space then we cannot */
2400     if ((IS_TRUE_SYMOP(IC_LEFT(uic)) &&
2401          isOperandInFarSpace(IC_LEFT(uic))) ||
2402         (IS_TRUE_SYMOP(IC_RIGHT(uic)) &&
2403          isOperandInFarSpace(IC_RIGHT(uic))))
2404         return ;
2405
2406     /* if the usage has only one operand then we can */
2407     if (IC_LEFT(uic) == NULL ||
2408         IC_RIGHT(uic) == NULL) 
2409         goto accuse;
2410
2411     /* make sure this is on the left side if not
2412        a '+' since '+' is commutative */
2413     if (ic->op != '+' &&
2414         IC_LEFT(uic)->key != IC_RESULT(ic)->key)
2415         return;
2416
2417     /* if one of them is a literal then we can */
2418     if ((IC_LEFT(uic) && IS_OP_LITERAL(IC_LEFT(uic))) ||
2419         (IC_RIGHT(uic) && IS_OP_LITERAL(IC_RIGHT(uic)))) {
2420         OP_SYMBOL(IC_RESULT(ic))->accuse = 1;
2421         return ;
2422     }
2423
2424     /* if the other one is not on stack then we can */
2425     if (IC_LEFT(uic)->key == IC_RESULT(ic)->key &&
2426         (IS_ITEMP(IC_RIGHT(uic)) ||
2427          (IS_TRUE_SYMOP(IC_RIGHT(uic)) &&
2428           !OP_SYMBOL(IC_RIGHT(uic))->onStack))) 
2429         goto accuse;
2430     
2431     if (IC_RIGHT(uic)->key == IC_RESULT(ic)->key &&
2432         (IS_ITEMP(IC_LEFT(uic)) ||
2433          (IS_TRUE_SYMOP(IC_LEFT(uic)) &&
2434           !OP_SYMBOL(IC_LEFT(uic))->onStack))) 
2435         goto accuse ;
2436
2437     return ;
2438
2439  accuse:
2440     OP_SYMBOL(IC_RESULT(ic))->accuse = 1;
2441     
2442         
2443 }
2444
2445 /*-----------------------------------------------------------------*/
2446 /* packForPush - hueristics to reduce iCode for pushing            */
2447 /*-----------------------------------------------------------------*/
2448 static void packForReceive(iCode *ic, eBBlock *ebp)
2449 {
2450   iCode *dic;
2451   bool can_remove=1;    // assume that we can remove temporary
2452
2453   debugLog("%s\n",__FUNCTION__);
2454   debugAopGet("  result:",IC_RESULT(ic));
2455   debugAopGet("  left:",IC_LEFT(ic));
2456   debugAopGet("  right:",IC_RIGHT(ic));
2457
2458   if(!ic->next)
2459     return;
2460
2461   for ( dic = ic->next ; dic ; dic = dic->next ) {
2462
2463
2464
2465     if(IC_LEFT(dic) && (IC_RESULT(ic)->key == IC_LEFT(dic)->key) )
2466       debugLog("    used on left\n");
2467     if(IC_RIGHT(dic) && IC_RESULT(ic)->key == IC_RIGHT(dic)->key) 
2468       debugLog("    used on right\n");
2469     if(IC_RESULT(dic) && IC_RESULT(ic)->key == IC_RESULT(dic)->key) 
2470       debugLog("    used on result\n");
2471
2472     if( (IC_LEFT(dic) && (IC_RESULT(ic)->key == IC_LEFT(dic)->key) ) ||
2473         (IC_RESULT(dic) && IC_RESULT(ic)->key == IC_RESULT(dic)->key) )
2474       return;
2475
2476   }
2477
2478   debugLog("  hey we can remove this unnecessary assign\n");
2479 }
2480 /*-----------------------------------------------------------------*/
2481 /* packForPush - hueristics to reduce iCode for pushing            */
2482 /*-----------------------------------------------------------------*/
2483 static void packForPush(iCode *ic, eBBlock *ebp)
2484 {
2485     iCode *dic;
2486
2487     debugLog("%s\n",__FUNCTION__);
2488     if (ic->op != IPUSH || !IS_ITEMP(IC_LEFT(ic)))
2489         return ;
2490
2491     /* must have only definition & one usage */
2492     if (bitVectnBitsOn(OP_DEFS(IC_LEFT(ic))) != 1 ||
2493         bitVectnBitsOn(OP_USES(IC_LEFT(ic))) != 1 )     
2494         return ;
2495     
2496     /* find the definition */
2497     if (!(dic = hTabItemWithKey(iCodehTab,
2498                                 bitVectFirstBit(OP_DEFS(IC_LEFT(ic))))))
2499         return ;
2500
2501     if (dic->op != '=' || POINTER_SET(dic))
2502         return;
2503
2504     /* we now we know that it has one & only one def & use
2505        and the that the definition is an assignment */
2506     IC_LEFT(ic) = IC_RIGHT(dic);
2507
2508     remiCodeFromeBBlock(ebp,dic);
2509     hTabDeleteItem (&iCodehTab,dic->key,dic,DELETE_ITEM,NULL);
2510 }
2511
2512 /*-----------------------------------------------------------------*/
2513 /* packRegisters - does some transformations to reduce register    */
2514 /*                   pressure                                      */
2515 /*-----------------------------------------------------------------*/
2516 static void packRegisters (eBBlock *ebp)
2517 {
2518     iCode *ic ;
2519     int change = 0 ;
2520     
2521     debugLog("%s\n",__FUNCTION__);
2522
2523     while (1) {
2524
2525         change = 0;
2526         
2527         /* look for assignments of the form */
2528         /* iTempNN = TRueSym (someoperation) SomeOperand */
2529         /*       ....                       */
2530         /* TrueSym := iTempNN:1             */
2531         for ( ic = ebp->sch ; ic ; ic = ic->next ) {
2532             
2533             /* find assignment of the form TrueSym := iTempNN:1 */
2534             if (ic->op == '=' && !POINTER_SET(ic))
2535                 change += packRegsForAssign(ic,ebp);
2536             /* debug stuff */
2537             if (ic->op == '=') {
2538               if(POINTER_SET(ic))
2539                 debugLog("pointer is set\n");
2540               debugAopGet("  result:",IC_RESULT(ic));
2541               debugAopGet("  left:",IC_LEFT(ic));
2542               debugAopGet("  right:",IC_RIGHT(ic));
2543             }
2544
2545         }
2546
2547         if (!change)
2548             break;
2549     }
2550     
2551     for ( ic = ebp->sch ; ic ; ic = ic->next ) {
2552                 
2553         /* if this is an itemp & result of a address of a true sym 
2554            then mark this as rematerialisable   */
2555         if (ic->op == ADDRESS_OF && 
2556             IS_ITEMP(IC_RESULT(ic)) &&
2557             IS_TRUE_SYMOP(IC_LEFT(ic)) &&
2558             bitVectnBitsOn(OP_DEFS(IC_RESULT(ic))) == 1 &&
2559             !OP_SYMBOL(IC_LEFT(ic))->onStack ) {
2560
2561             OP_SYMBOL(IC_RESULT(ic))->remat = 1;
2562             OP_SYMBOL(IC_RESULT(ic))->rematiCode = ic;
2563             OP_SYMBOL(IC_RESULT(ic))->usl.spillLoc = NULL;
2564
2565         }
2566         
2567         /* if straight assignment then carry remat flag if
2568            this is the only definition */
2569         if (ic->op == '='    && 
2570             !POINTER_SET(ic) &&
2571             IS_SYMOP(IC_RIGHT(ic)) && 
2572             OP_SYMBOL(IC_RIGHT(ic))->remat &&
2573             bitVectnBitsOn(OP_SYMBOL(IC_RESULT(ic))->defs) <= 1) {
2574
2575             OP_SYMBOL(IC_RESULT(ic))->remat = 
2576                 OP_SYMBOL(IC_RIGHT(ic))->remat;
2577             OP_SYMBOL(IC_RESULT(ic))->rematiCode = 
2578                 OP_SYMBOL(IC_RIGHT(ic))->rematiCode ;
2579         }
2580
2581         /* if this is a +/- operation with a rematerizable 
2582            then mark this as rematerializable as well */
2583         if ((ic->op == '+' || ic->op == '-') &&
2584             (IS_SYMOP(IC_LEFT(ic)) && 
2585              IS_ITEMP(IC_RESULT(ic)) &&
2586              OP_SYMBOL(IC_LEFT(ic))->remat &&
2587              bitVectnBitsOn(OP_DEFS(IC_RESULT(ic))) == 1 &&
2588              IS_OP_LITERAL(IC_RIGHT(ic))) ) {
2589
2590           //int i = 
2591             operandLitValue(IC_RIGHT(ic));
2592             OP_SYMBOL(IC_RESULT(ic))->remat = 1;
2593             OP_SYMBOL(IC_RESULT(ic))->rematiCode = ic;
2594             OP_SYMBOL(IC_RESULT(ic))->usl.spillLoc = NULL;
2595         }
2596
2597         /* mark the pointer usages */
2598         if (POINTER_SET(ic)) {
2599             OP_SYMBOL(IC_RESULT(ic))->uptr = 1;
2600             debugLog("  marking as a pointer (set)\n");
2601         }
2602         if (POINTER_GET(ic)) {
2603             OP_SYMBOL(IC_LEFT(ic))->uptr = 1;
2604             debugLog("  marking as a pointer (get)\n");
2605         }
2606
2607         if (!SKIP_IC2(ic)) {
2608             /* if we are using a symbol on the stack
2609                then we should say pic14_ptrRegReq */
2610             if (ic->op == IFX && IS_SYMOP(IC_COND(ic)))
2611                 pic14_ptrRegReq += ((OP_SYMBOL(IC_COND(ic))->onStack ||
2612                                OP_SYMBOL(IC_COND(ic))->iaccess) ? 1 : 0);
2613             else
2614                 if (ic->op == JUMPTABLE && IS_SYMOP(IC_JTCOND(ic)))
2615                     pic14_ptrRegReq += ((OP_SYMBOL(IC_JTCOND(ic))->onStack ||
2616                                    OP_SYMBOL(IC_JTCOND(ic))->iaccess) ? 1 : 0);
2617                 else {
2618                     if (IS_SYMOP(IC_LEFT(ic)))
2619                         pic14_ptrRegReq += ((OP_SYMBOL(IC_LEFT(ic))->onStack ||
2620                                        OP_SYMBOL(IC_LEFT(ic))->iaccess) ? 1 : 0);
2621                     if (IS_SYMOP(IC_RIGHT(ic)))
2622                         pic14_ptrRegReq += ((OP_SYMBOL(IC_RIGHT(ic))->onStack ||
2623                                        OP_SYMBOL(IC_RIGHT(ic))->iaccess) ? 1 : 0);
2624                     if (IS_SYMOP(IC_RESULT(ic)))
2625                         pic14_ptrRegReq += ((OP_SYMBOL(IC_RESULT(ic))->onStack ||
2626                                        OP_SYMBOL(IC_RESULT(ic))->iaccess) ? 1 : 0);    
2627                 }
2628         }
2629
2630         /* if the condition of an if instruction
2631            is defined in the previous instruction then
2632            mark the itemp as a conditional */
2633         if ((IS_CONDITIONAL(ic) ||
2634              ( ( ic->op == BITWISEAND      ||
2635                  ic->op == '|'             ||
2636                  ic->op == '^' ) &&
2637                isBitwiseOptimizable(ic))) &&        
2638             ic->next && ic->next->op == IFX &&
2639             isOperandEqual(IC_RESULT(ic),IC_COND(ic->next)) &&
2640             OP_SYMBOL(IC_RESULT(ic))->liveTo <= ic->next->seq) {
2641             
2642             OP_SYMBOL(IC_RESULT(ic))->regType = REG_CND;            
2643             continue ;
2644         }
2645         
2646         /* reduce for support function calls */
2647         if (ic->supportRtn || ic->op == '+' || ic->op == '-' )
2648             packRegsForSupport (ic,ebp);        
2649
2650         /* if a parameter is passed, it's in W, so we may not
2651            need to place a copy in a register */
2652         if(ic->op == RECEIVE)
2653           packForReceive(ic,ebp);
2654
2655         /* some cases the redundant moves can
2656            can be eliminated for return statements */
2657         if ((ic->op == RETURN || ic->op == SEND) &&
2658             !isOperandInFarSpace(IC_LEFT(ic))    &&
2659             !options.model)
2660             packRegsForOneuse (ic,IC_LEFT(ic),ebp);     
2661
2662         /* if pointer set & left has a size more than
2663            one and right is not in far space */
2664         if (POINTER_SET(ic)                    &&
2665             !isOperandInFarSpace(IC_RIGHT(ic)) &&
2666             !OP_SYMBOL(IC_RESULT(ic))->remat   &&
2667             !IS_OP_RUONLY(IC_RIGHT(ic))        &&
2668             getSize(aggrToPtr(operandType(IC_RESULT(ic)),FALSE)) > 1 )
2669
2670             packRegsForOneuse (ic,IC_RESULT(ic),ebp);
2671
2672         /* if pointer get */
2673         if (POINTER_GET(ic)                    &&
2674             !isOperandInFarSpace(IC_RESULT(ic))&&
2675             !OP_SYMBOL(IC_LEFT(ic))->remat     &&
2676             !IS_OP_RUONLY(IC_RESULT(ic))         &&
2677             getSize(aggrToPtr(operandType(IC_LEFT(ic)),FALSE)) > 1 )
2678
2679             packRegsForOneuse (ic,IC_LEFT(ic),ebp);
2680
2681
2682         /* if this is cast for intergral promotion then
2683            check if only use of  the definition of the 
2684            operand being casted/ if yes then replace
2685            the result of that arithmetic operation with 
2686            this result and get rid of the cast */
2687         if (ic->op == CAST) {
2688             sym_link *fromType = operandType(IC_RIGHT(ic));
2689             sym_link *toType = operandType(IC_LEFT(ic));
2690
2691             if (IS_INTEGRAL(fromType) && IS_INTEGRAL(toType) &&
2692                 getSize(fromType) != getSize(toType) ) {
2693
2694                 iCode *dic = packRegsForOneuse(ic,IC_RIGHT(ic),ebp);
2695                 if (dic) {
2696                     if (IS_ARITHMETIC_OP(dic)) {
2697                         IC_RESULT(dic) = IC_RESULT(ic);
2698                         remiCodeFromeBBlock(ebp,ic);
2699                         hTabDeleteItem (&iCodehTab,ic->key,ic,DELETE_ITEM,NULL);
2700                         OP_DEFS(IC_RESULT(dic)) = bitVectSetBit(OP_DEFS(IC_RESULT(dic)),dic->key);
2701                         ic = ic->prev;
2702                     } else
2703                         OP_SYMBOL(IC_RIGHT(ic))->ruonly =  0;
2704                 }               
2705             } else {
2706                 
2707                 /* if the type from and type to are the same
2708                    then if this is the only use then packit */
2709                 if (checkType(operandType(IC_RIGHT(ic)),
2710                               operandType(IC_LEFT(ic))) == 1) {
2711                     iCode *dic = packRegsForOneuse (ic,IC_RIGHT(ic),ebp);
2712                     if (dic) {
2713                         IC_RESULT(dic) = IC_RESULT(ic);
2714                         remiCodeFromeBBlock(ebp,ic);
2715                         hTabDeleteItem (&iCodehTab,ic->key,ic,DELETE_ITEM,NULL);
2716                         OP_DEFS(IC_RESULT(dic)) = bitVectSetBit(OP_DEFS(IC_RESULT(dic)),dic->key);
2717                         ic = ic->prev;
2718                     }
2719                 }
2720             }
2721         }
2722         
2723         /* pack for PUSH 
2724            iTempNN := (some variable in farspace) V1
2725            push iTempNN ;
2726            -------------
2727            push V1
2728         */
2729         if (ic->op == IPUSH ) {
2730             packForPush(ic,ebp);
2731         }
2732           
2733         
2734         /* pack registers for accumulator use, when the
2735            result of an arithmetic or bit wise operation
2736            has only one use, that use is immediately following
2737            the defintion and the using iCode has only one
2738            operand or has two operands but one is literal &
2739            the result of that operation is not on stack then
2740            we can leave the result of this operation in acc:b
2741            combination */
2742         if ((IS_ARITHMETIC_OP(ic) 
2743              
2744              || IS_BITWISE_OP(ic) 
2745              
2746              || ic->op == LEFT_OP || ic->op == RIGHT_OP
2747              
2748              ) &&
2749             IS_ITEMP(IC_RESULT(ic)) &&
2750             getSize(operandType(IC_RESULT(ic))) <= 2)
2751
2752             packRegsForAccUse (ic);
2753
2754     }
2755 }
2756
2757 static void dumpEbbsToDebug(eBBlock **ebbs, int count)
2758 {
2759   int i;
2760
2761   if(!debug || !debugF)
2762     return;
2763
2764   for (i=0; i < count ; i++ ) {
2765     fprintf(debugF,"\n----------------------------------------------------------------\n");
2766     fprintf(debugF,"Basic Block %s : loop Depth = %d noPath = %d , lastinLoop = %d\n",
2767             ebbs[i]->entryLabel->name, 
2768             ebbs[i]->depth,
2769             ebbs[i]->noPath,
2770             ebbs[i]->isLastInLoop);
2771     fprintf(debugF,"depth 1st num %d : bbnum = %d 1st iCode = %d , last iCode = %d\n",
2772             ebbs[i]->dfnum, 
2773             ebbs[i]->bbnum,
2774             ebbs[i]->fSeq,
2775             ebbs[i]->lSeq);
2776     fprintf(debugF,"visited %d : hasFcall = %d\n",
2777             ebbs[i]->visited, 
2778             ebbs[i]->hasFcall);
2779
2780     fprintf(debugF,"\ndefines bitVector :");
2781     bitVectDebugOn(ebbs[i]->defSet,debugF);
2782     fprintf(debugF,"\nlocal defines bitVector :");
2783     bitVectDebugOn(ebbs[i]->ldefs,debugF);
2784     fprintf(debugF,"\npointers Set bitvector :");
2785     bitVectDebugOn(ebbs[i]->ptrsSet,debugF);
2786     fprintf(debugF,"\nin pointers Set bitvector :");
2787     bitVectDebugOn(ebbs[i]->inPtrsSet,debugF);
2788     fprintf(debugF,"\ninDefs Set bitvector :");
2789     bitVectDebugOn(ebbs[i]->inDefs,debugF);
2790     fprintf(debugF,"\noutDefs Set bitvector :");
2791     bitVectDebugOn(ebbs[i]->outDefs,debugF);
2792     fprintf(debugF,"\nusesDefs Set bitvector :");
2793     bitVectDebugOn(ebbs[i]->usesDefs,debugF);
2794     fprintf(debugF,"\n----------------------------------------------------------------\n");
2795     printiCChain(ebbs[i]->sch,debugF);
2796   }
2797 }
2798 /*-----------------------------------------------------------------*/
2799 /* assignRegisters - assigns registers to each live range as need  */
2800 /*-----------------------------------------------------------------*/
2801 void pic14_assignRegisters (eBBlock **ebbs, int count)
2802 {
2803     iCode *ic;
2804     int i ;
2805
2806     debugLog("<><><><><><><><><><><><><><><><><>\nstarting\t%s:%s",__FILE__,__FUNCTION__);
2807     debugLog("ebbs before optimizing:\n");
2808     dumpEbbsToDebug(ebbs,count);
2809
2810     setToNull((void *)&_G.funcrUsed);
2811     pic14_ptrRegReq = _G.stackExtend = _G.dataExtend = 0;
2812
2813
2814     /* change assignments this will remove some
2815        live ranges reducing some register pressure */
2816     for (i = 0 ; i < count ;i++ )
2817         packRegisters (ebbs[i]);
2818     
2819     if (options.dump_pack)
2820         dumpEbbsToFileExt(".dumppack",ebbs,count);
2821
2822     /* first determine for each live range the number of 
2823        registers & the type of registers required for each */
2824     regTypeNum ();
2825     
2826     /* and serially allocate registers */ 
2827     serialRegAssign(ebbs,count);
2828
2829     /* if stack was extended then tell the user */
2830     if (_G.stackExtend) {
2831 /*      werror(W_TOOMANY_SPILS,"stack", */
2832 /*             _G.stackExtend,currFunc->name,""); */
2833         _G.stackExtend = 0 ;
2834     }
2835
2836     if (_G.dataExtend) {
2837 /*      werror(W_TOOMANY_SPILS,"data space", */
2838 /*             _G.dataExtend,currFunc->name,""); */
2839         _G.dataExtend = 0 ;
2840     }  
2841
2842     /* after that create the register mask
2843        for each of the instruction */
2844     createRegMask (ebbs,count);
2845
2846     /* redo that offsets for stacked automatic variables */
2847     redoStackOffsets ();
2848
2849     if (options.dump_rassgn)
2850         dumpEbbsToFileExt(".dumprassgn",ebbs,count);
2851
2852     /* now get back the chain */
2853     ic = iCodeLabelOptimize(iCodeFromeBBlock (ebbs,count));
2854
2855     debugLog("ebbs after optimizing:\n");
2856     dumpEbbsToDebug(ebbs,count);
2857
2858
2859     genpic14Code(ic);
2860
2861     /* free up any _G.stackSpil locations allocated */   
2862     applyToSet(_G.stackSpil,deallocStackSpil);
2863     _G.slocNum = 0;
2864     setToNull((void **)&_G.stackSpil);
2865     setToNull((void **)&_G.spiltSet);
2866     /* mark all registers as free */
2867     freeAllRegs();
2868
2869     debugLog("leaving\n<><><><><><><><><><><><><><><><><>\n");
2870     debugLogClose();
2871     return ;
2872 }