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