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