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