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