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