X-Git-Url: https://git.gag.com/?a=blobdiff_plain;f=src%2Fds390%2Fralloc.c;h=527ffeb81fe9271031efea44ec6dc4b906d862d8;hb=43759cb53bb9b21248d5541b8b2579fc33506750;hp=c9307ee386f160d783808e269621af4067bbb86e;hpb=f6943692bcb9620217f07b81187d618817c9757c;p=fw%2Fsdcc diff --git a/src/ds390/ralloc.c b/src/ds390/ralloc.c index c9307ee3..527ffeb8 100644 --- a/src/ds390/ralloc.c +++ b/src/ds390/ralloc.c @@ -36,12 +36,15 @@ /* since the pack the registers depending strictly on the MCU */ /*-----------------------------------------------------------------*/ +#define D(x) + /* Global data */ static struct { bitVect *spiltSet; set *stackSpil; bitVect *regAssigned; + bitVect *totRegAssigned; /* final set of LRs that got into registers */ short blockSpil; int slocNum; bitVect *funcrUsed; /* registers used in a function */ @@ -57,23 +60,29 @@ int ds390_ptrRegReq; /* one byte pointer register required */ regs regs390[] = { - {REG_GPR, R2_IDX, REG_GPR, "r2", "ar2", "0", 2, 1}, - {REG_GPR, R3_IDX, REG_GPR, "r3", "ar3", "0", 3, 1}, - {REG_GPR, R4_IDX, REG_GPR, "r4", "ar4", "0", 4, 1}, - {REG_GPR, R5_IDX, REG_GPR, "r5", "ar5", "0", 5, 1}, - {REG_GPR, R6_IDX, REG_GPR, "r6", "ar6", "0", 6, 1}, - {REG_GPR, R7_IDX, REG_GPR, "r7", "ar7", "0", 7, 1}, - {REG_PTR, R0_IDX, REG_PTR, "r0", "ar0", "0", 0, 1}, - {REG_PTR, R1_IDX, REG_PTR, "r1", "ar1", "0", 1, 1}, - {REG_GPR, X8_IDX, REG_GPR, "x8", "x8", "xreg", 0, 1}, - {REG_GPR, X9_IDX, REG_GPR, "x9", "x9", "xreg", 1, 1}, - {REG_GPR, X10_IDX, REG_GPR, "x10", "x10", "xreg", 2, 1}, - {REG_GPR, X11_IDX, REG_GPR, "x11", "x11", "xreg", 3, 1}, - {REG_GPR, X12_IDX, REG_GPR, "x12", "x12", "xreg", 4, 1}, - {REG_CND, CND_IDX, REG_CND, "C", "C", "xreg", 0, 1}, + {REG_GPR, R2_IDX, REG_GPR, "r2", "ar2", "0", 2, 1, 1}, + {REG_GPR, R3_IDX, REG_GPR, "r3", "ar3", "0", 3, 1, 1}, + {REG_GPR, R4_IDX, REG_GPR, "r4", "ar4", "0", 4, 1, 1}, + {REG_GPR, R5_IDX, REG_GPR, "r5", "ar5", "0", 5, 1, 1}, + {REG_GPR, R6_IDX, REG_GPR, "r6", "ar6", "0", 6, 1, 1}, + {REG_GPR, R7_IDX, REG_GPR, "r7", "ar7", "0", 7, 1, 1}, + {REG_PTR, R0_IDX, REG_PTR, "r0", "ar0", "0", 0, 1, 1}, + {REG_PTR, R1_IDX, REG_PTR, "r1", "ar1", "0", 1, 1, 1}, + {REG_GPR, DPL_IDX, REG_GPR, "dpl", "dpl", "dpl", 0, 0, 0}, + {REG_GPR, DPH_IDX, REG_GPR, "dph", "dph", "dph", 0, 0, 0}, + {REG_GPR, DPX_IDX, REG_GPR, "dpx", "dpx", "dpx", 0, 0, 0}, + {REG_GPR, B_IDX, REG_GPR, "b", "b", "b", 0, 0, 0}, + {REG_GPR, X8_IDX, REG_GPR, "x8", "x8", "xreg", 0, 0, 0}, + {REG_GPR, X9_IDX, REG_GPR, "x9", "x9", "xreg", 1, 0, 0}, + {REG_GPR, X10_IDX, REG_GPR, "x10", "x10", "xreg", 2, 0, 0}, + {REG_GPR, X11_IDX, REG_GPR, "x11", "x11", "xreg", 3, 0, 0}, + {REG_GPR, X12_IDX, REG_GPR, "x12", "x12", "xreg", 4, 0, 0}, + {REG_CND, CND_IDX, REG_GPR, "C", "C", "xreg", 0, 0, 0}, }; int ds390_nRegs = 13; static void spillThis (symbol *); +static void freeAllRegs (); +static iCode * packRegsDPTRuse (operand *); /*-----------------------------------------------------------------*/ /* allocReg - allocates register of given type */ @@ -138,6 +147,15 @@ freeReg (regs * reg) reg->isFree = 1; } +/*-----------------------------------------------------------------*/ +/* useReg - marks a register as used */ +/*-----------------------------------------------------------------*/ +static void +useReg (regs * reg) +{ + reg->isFree = 0; +} + /*-----------------------------------------------------------------*/ /* nFreeRegs - returns number of free registers */ @@ -197,6 +215,16 @@ allDefsOutOfRange (bitVect * defs, int fseq, int toseq) return TRUE; } +/*-----------------------------------------------------------------*/ +/* isOperandInReg - returns true if operand is currently in regs */ +/*-----------------------------------------------------------------*/ +static int isOperandInReg(operand *op) +{ + if (!IS_SYMOP(op)) return 0; + + return bitVectBitValue(_G.totRegAssigned,OP_SYMBOL(op)->key); +} + /*-----------------------------------------------------------------*/ /* computeSpillable - given a point find the spillable live ranges */ /*-----------------------------------------------------------------*/ @@ -383,14 +411,7 @@ noOverLap (set * itmpStack, symbol * fsym) for (sym = setFirstItem (itmpStack); sym; sym = setNextItem (itmpStack)) { - // if sym starts before (or on) our end point - // and ends after (or on) our start point, - // it is an overlap. - if (sym->liveFrom <= fsym->liveTo && - sym->liveTo >= fsym->liveFrom) - { - return 0; - } + if (bitVectBitValue(sym->clashes,fsym->key)) return 0; } return 1; } @@ -485,7 +506,7 @@ createStackSpil (symbol * sym) if (applyToSet (_G.stackSpil, isFree, &sloc, sym)) { /* found a free one : just update & return */ - sym->usl.spillLoc = sloc; + sym->usl.spillLoc = sloc; sym->stackSpil = 1; sloc->isFree = 0; addSetHead (&sloc->usl.itmpStack, sym); @@ -508,8 +529,14 @@ createStackSpil (symbol * sym) /* set the type to the spilling symbol */ sloc->type = copyLinkChain (sym->type); sloc->etype = getSpec (sloc->type); - SPEC_SCLS (sloc->etype) = options.model ? S_XDATA : S_DATA; + if (options.model == MODEL_SMALL) { + SPEC_SCLS (sloc->etype) = S_DATA; + } else { + SPEC_SCLS (sloc->etype) = S_XDATA; + } SPEC_EXTR (sloc->etype) = 0; + SPEC_STAT (sloc->etype) = 0; + SPEC_VOLATILE(sloc->etype) = 0; /* we don't allow it to be allocated` onto the external stack since : so we @@ -595,10 +622,11 @@ spillThis (symbol * sym) /* mark it has spilt & put it in the spilt set */ - sym->isspilt = 1; + sym->isspilt = sym->spillA = 1; _G.spiltSet = bitVectSetBit (_G.spiltSet, sym->key); bitVectUnSetBit (_G.regAssigned, sym->key); + bitVectUnSetBit (_G.totRegAssigned, sym->key); for (i = 0; i < sym->nRegs; i++) @@ -613,12 +641,12 @@ spillThis (symbol * sym) LIVE ranges */ if (!ds390_ptrRegReq && isSpiltOnStack (sym)) { - ds390_ptrRegReq++; + ds390_ptrRegReq += !options.stack10bit; spillLRWithPtrReg (sym); } if (sym->usl.spillLoc && !sym->remat) - sym->usl.spillLoc->allocreq = 1; + sym->usl.spillLoc->allocreq++; return; } @@ -652,7 +680,7 @@ selectSpil (iCode * ic, eBBlock * ebp, symbol * forSym) sym->usl.spillLoc->name)); sym->spildir = 1; /* mark it as allocation required */ - sym->usl.spillLoc->allocreq = 1; + sym->usl.spillLoc->allocreq++; return sym; } @@ -697,7 +725,7 @@ selectSpil (iCode * ic, eBBlock * ebp, symbol * forSym) sym = leastUsedLR (selectS); /* mark this as allocation required */ - sym->usl.spillLoc->allocreq = 1; + sym->usl.spillLoc->allocreq++; return sym; } @@ -706,7 +734,7 @@ selectSpil (iCode * ic, eBBlock * ebp, symbol * forSym) { sym = leastUsedLR (selectS); - sym->usl.spillLoc->allocreq = 1; + sym->usl.spillLoc->allocreq++; return sym; } @@ -718,7 +746,7 @@ selectSpil (iCode * ic, eBBlock * ebp, symbol * forSym) /* return a created spil location */ sym = createStackSpil (leastUsedLR (selectS)); - sym->usl.spillLoc->allocreq = 1; + sym->usl.spillLoc->allocreq++; return sym; } @@ -742,12 +770,13 @@ spilSomething (iCode * ic, eBBlock * ebp, symbol * forSym) ssym = selectSpil (ic, ebp, forSym); /* mark it as spilt */ - ssym->isspilt = 1; + ssym->isspilt = ssym->spillA = 1; _G.spiltSet = bitVectSetBit (_G.spiltSet, ssym->key); /* mark it as not register assigned & take it away from the set */ bitVectUnSetBit (_G.regAssigned, ssym->key); + bitVectUnSetBit (_G.totRegAssigned, ssym->key); /* mark the registers as free */ for (i = 0; i < ssym->nRegs; i++) @@ -756,9 +785,9 @@ spilSomething (iCode * ic, eBBlock * ebp, symbol * forSym) /* if spilt on stack then free up r0 & r1 if they could have been assigned to as gprs */ - if (!ds390_ptrRegReq && isSpiltOnStack (ssym)) + if (!ds390_ptrRegReq && isSpiltOnStack (ssym) && !options.stack10bit) { - ds390_ptrRegReq++; + ds390_ptrRegReq++; spillLRWithPtrReg (ssym); } @@ -848,6 +877,41 @@ tryAgain: goto tryAgain; } +/*-----------------------------------------------------------------*/ +/* getRegPtrNoSpil - get it cannot split */ +/*-----------------------------------------------------------------*/ +static regs *getRegPtrNoSpil() +{ + regs *reg; + + /* try for a ptr type */ + if ((reg = allocReg (REG_PTR))) + return reg; + + /* try for gpr type */ + if ((reg = allocReg (REG_GPR))) + return reg; + + assert(0); +} + +/*-----------------------------------------------------------------*/ +/* getRegGprNoSpil - get it cannot split */ +/*-----------------------------------------------------------------*/ +static regs *getRegGprNoSpil() +{ + + regs *reg; + if ((reg = allocReg (REG_GPR))) + return reg; + + if (!ds390_ptrRegReq) + if ((reg = allocReg (REG_PTR))) + return reg; + + assert(0); +} + /*-----------------------------------------------------------------*/ /* symHasReg - symbol has a given register */ /*-----------------------------------------------------------------*/ @@ -947,6 +1011,7 @@ deassignLRs (iCode * ic, eBBlock * ebp) result->regs[i] = getRegGpr (ic, ebp, result); _G.regAssigned = bitVectSetBit (_G.regAssigned, result->key); + _G.totRegAssigned = bitVectSetBit (_G.totRegAssigned, result->key); } @@ -976,10 +1041,11 @@ reassignLR (operand * op) int i; /* not spilt any more */ - sym->isspilt = sym->blockSpil = sym->remainSpil = 0; + sym->isspilt = sym->spillA = sym->blockSpil = sym->remainSpil = 0; bitVectUnSetBit (_G.spiltSet, sym->key); _G.regAssigned = bitVectSetBit (_G.regAssigned, sym->key); + _G.totRegAssigned = bitVectSetBit (_G.totRegAssigned, sym->key); _G.blockSpil--; @@ -1029,15 +1095,16 @@ willCauseSpill (int nr, int rt) /* ult and operand, if this happens make sure they are in the same */ /* position as the operand otherwise chaos results */ /*-----------------------------------------------------------------*/ -static void -positionRegs (symbol * result, symbol * opsym, int lineno) +static int +positionRegs (symbol * result, symbol * opsym) { int count = min (result->nRegs, opsym->nRegs); int i, j = 0, shared = 0; + int change = 0; /* if the result has been spilt then cannot share */ if (opsym->isspilt) - return; + return 0; again: shared = 0; /* first make sure that they actually share */ @@ -1058,8 +1125,10 @@ xchgPositions: regs *tmp = result->regs[i]; result->regs[i] = result->regs[j]; result->regs[j] = tmp; + change ++; goto again; } + return change ; } /*-----------------------------------------------------------------*/ @@ -1093,7 +1162,7 @@ serialRegAssign (eBBlock ** ebbs, int count) /* if result is present && is a true symbol */ if (IC_RESULT (ic) && ic->op != IFX && IS_TRUE_SYMOP (IC_RESULT (ic))) - OP_SYMBOL (IC_RESULT (ic))->allocreq = 1; + OP_SYMBOL (IC_RESULT (ic))->allocreq++; /* take away registers from live ranges that end at this instruction */ @@ -1164,8 +1233,11 @@ serialRegAssign (eBBlock ** ebbs, int count) /* if none of the liveRanges have a spillLocation then better to spill this one than anything else already assigned to registers */ if (liveRangesWith(spillable,noSpilLoc,ebbs[i],ic)) { - spillThis (sym); - continue; + /* if this is local to this block then we might find a block spil */ + if (!(sym->liveFrom >= ebbs[i]->fSeq && sym->liveTo <= ebbs[i]->lSeq)) { + spillThis (sym); + continue; + } } } } @@ -1181,6 +1253,7 @@ serialRegAssign (eBBlock ** ebbs, int count) } /* else we assign registers to it */ _G.regAssigned = bitVectSetBit (_G.regAssigned, sym->key); + _G.totRegAssigned = bitVectSetBit (_G.totRegAssigned, sym->key); for (j = 0; j < sym->nRegs; j++) { @@ -1199,12 +1272,12 @@ serialRegAssign (eBBlock ** ebbs, int count) if (IC_LEFT (ic) && IS_SYMOP (IC_LEFT (ic)) && OP_SYMBOL (IC_LEFT (ic))->nRegs && ic->op != '=') positionRegs (OP_SYMBOL (IC_RESULT (ic)), - OP_SYMBOL (IC_LEFT (ic)), ic->lineno); + OP_SYMBOL (IC_LEFT (ic))); /* do the same for the right operand */ if (IC_RIGHT (ic) && IS_SYMOP (IC_RIGHT (ic)) && OP_SYMBOL (IC_RIGHT (ic))->nRegs) positionRegs (OP_SYMBOL (IC_RESULT (ic)), - OP_SYMBOL (IC_RIGHT (ic)), ic->lineno); + OP_SYMBOL (IC_RIGHT (ic))); if (ptrRegSet) { @@ -1217,11 +1290,131 @@ serialRegAssign (eBBlock ** ebbs, int count) } } +/*-----------------------------------------------------------------*/ +/* fillGaps - Try to fill in the Gaps left by Pass1 */ +/*-----------------------------------------------------------------*/ +static void fillGaps() +{ + symbol *sym =NULL; + int key =0; + + if (getenv("DISABLE_FILL_GAPS")) return; + + /* First try to do DPTRuse once more since now we know what got into + registers */ + + for (sym = hTabFirstItem(liveRanges,&key) ; sym ; + sym = hTabNextItem(liveRanges,&key)) { + + if (sym->uptr && !sym->ruonly && getSize(sym->type) < 4) { + if (packRegsDPTRuse(operandFromSymbol(sym))) { + + D (fprintf (stderr, "FILL GAPS: found more DPTR use for " + "%s in func %s\n", + sym->name, currFunc ? currFunc->name : "UNKNOWN")); + /* if this was ssigned to registers then */ + if (bitVectBitValue(_G.totRegAssigned,sym->key)) { + + /* take it out of the register assigned set */ + bitVectUnSetBit(_G.totRegAssigned,sym->key); + sym->nRegs = 0; + } else if (sym->usl.spillLoc) sym->usl.spillLoc->allocreq--; + + sym->isspilt = sym->spillA = 0; + } + } + } + + /* look for livernages that was spilt by the allocator */ + for (sym = hTabFirstItem(liveRanges,&key) ; sym ; + sym = hTabNextItem(liveRanges,&key)) { + + int i; + int pdone = 0; + + if (!sym->spillA || !sym->clashes || sym->remat) continue ; + + /* find the liveRanges this one clashes with, that are + still assigned to registers & mark the registers as used*/ + for ( i = 0 ; i < sym->clashes->size ; i ++) { + int k; + symbol *clr; + + if (bitVectBitValue(sym->clashes,i) == 0 || /* those that clash with this */ + bitVectBitValue(_G.totRegAssigned,i) == 0) /* and are still assigned to registers */ + continue ; + + assert (clr = hTabItemWithKey(liveRanges,i)); + + /* mark these registers as used */ + for (k = 0 ; k < clr->nRegs ; k++ ) + useReg(clr->regs[k]); + } + + if (willCauseSpill(sym->nRegs,sym->regType)) { + /* NOPE :( clear all registers & and continue */ + freeAllRegs(); + continue ; + } + + /* THERE IS HOPE !!!! */ + for (i=0; i < sym->nRegs ; i++ ) { + if (sym->regType == REG_PTR) + sym->regs[i] = getRegPtrNoSpil (); + else + sym->regs[i] = getRegGprNoSpil (); + } + + /* for all its definitions check if the registers + allocated needs positioning NOTE: we can position + only ONCE if more than One positioning required + then give up */ + sym->isspilt = 0; + for (i = 0 ; i < sym->defs->size ; i++ ) { + if (bitVectBitValue(sym->defs,i)) { + iCode *ic; + if (!(ic = hTabItemWithKey(iCodehTab,i))) continue ; + if (SKIP_IC(ic)) continue; + assert(isSymbolEqual(sym,OP_SYMBOL(IC_RESULT(ic)))); /* just making sure */ + /* if left is assigned to registers */ + if (IS_SYMOP(IC_LEFT(ic)) && + bitVectBitValue(_G.totRegAssigned,OP_SYMBOL(IC_LEFT(ic))->key)) { + pdone += positionRegs(sym,OP_SYMBOL(IC_LEFT(ic))); + } + if (IS_SYMOP(IC_RIGHT(ic)) && + bitVectBitValue(_G.totRegAssigned,OP_SYMBOL(IC_RIGHT(ic))->key)) { + pdone += positionRegs(sym,OP_SYMBOL(IC_RIGHT(ic))); + } + if (pdone > 1) break; + } + } + /* had to position more than once GIVE UP */ + if (pdone > 1) { + /* UNDO all the changes we made to try this */ + sym->isspilt = 0; + for (i=0; i < sym->nRegs ; i++ ) { + sym->regs[i] = NULL; + } + freeAllRegs(); + D (fprintf (stderr, "Fill Gap gave up due to positioning for " + "%s in function %s\n", + sym->name, currFunc ? currFunc->name : "UNKNOWN")); + continue ; + } + D (fprintf (stderr, "FILLED GAP for %s in function %s\n", + sym->name, currFunc ? currFunc->name : "UNKNOWN")); + _G.totRegAssigned = bitVectSetBit(_G.totRegAssigned,sym->key); + sym->isspilt = sym->spillA = 0 ; + sym->usl.spillLoc->allocreq--; + freeAllRegs(); + } +} + /*-----------------------------------------------------------------*/ /* rUmaskForOp :- returns register mask for an operand */ /*-----------------------------------------------------------------*/ -static bitVect * -rUmaskForOp (operand * op) +bitVect * +ds390_rUmaskForOp (operand * op) { bitVect *rumask; symbol *sym; @@ -1261,7 +1454,7 @@ regsUsedIniCode (iCode * ic) if (ic->op == IFX) { rmask = bitVectUnion (rmask, - rUmaskForOp (IC_COND (ic))); + ds390_rUmaskForOp (IC_COND (ic))); goto ret; } @@ -1269,7 +1462,7 @@ regsUsedIniCode (iCode * ic) if (ic->op == JUMPTABLE) { rmask = bitVectUnion (rmask, - rUmaskForOp (IC_JTCOND (ic))); + ds390_rUmaskForOp (IC_JTCOND (ic))); goto ret; } @@ -1277,16 +1470,16 @@ regsUsedIniCode (iCode * ic) /* of all other cases */ if (IC_LEFT (ic)) rmask = bitVectUnion (rmask, - rUmaskForOp (IC_LEFT (ic))); + ds390_rUmaskForOp (IC_LEFT (ic))); if (IC_RIGHT (ic)) rmask = bitVectUnion (rmask, - rUmaskForOp (IC_RIGHT (ic))); + ds390_rUmaskForOp (IC_RIGHT (ic))); if (IC_RESULT (ic)) rmask = bitVectUnion (rmask, - rUmaskForOp (IC_RESULT (ic))); + ds390_rUmaskForOp (IC_RESULT (ic))); ret: return rmask; @@ -1346,7 +1539,15 @@ createRegMask (eBBlock ** ebbs, int count) "createRegMask cannot find live range"); exit (0); } - + + /* special case for ruonly */ + if (sym->ruonly && sym->liveFrom != sym->liveTo) { + int size = getSize(sym->type); + int j = DPL_IDX; + for (k = 0 ; k < size; k++ ) + ic->rMask = bitVectSetBit (ic->rMask, j++); + continue ; + } /* if no register assigned to it */ if (!sym->nRegs || sym->isspilt) continue; @@ -1382,7 +1583,11 @@ rematStr (symbol * sym) ic = OP_SYMBOL (IC_LEFT (ic))->rematiCode; continue; } - + /* cast then continue */ + if (IS_CAST_ICODE(ic)) { + ic = OP_SYMBOL (IC_RIGHT (ic))->rematiCode; + continue; + } /* we reached the end */ sprintf (s, "%s", OP_SYMBOL (IC_LEFT (ic))->rname); break; @@ -1437,13 +1642,14 @@ regTypeNum () (ic = hTabItemWithKey (iCodehTab, bitVectFirstBit (sym->defs))) && POINTER_GET (ic) && + !sym->noSpilLoc && !IS_BITVAR (sym->etype)) { /* if remat in data space */ if (OP_SYMBOL (IC_LEFT (ic))->remat && - // sym->type && + !IS_CAST_ICODE(OP_SYMBOL (IC_LEFT (ic))->rematiCode) && DCL_TYPE (aggrToPtr (sym->type, FALSE)) == POINTER) { @@ -1694,6 +1900,7 @@ pack: /* found the definition */ /* replace the result with the result of */ /* this assignment and remove this assignment */ + bitVectUnSetBit(OP_SYMBOL(IC_RESULT(dic))->defs,dic->key); IC_RESULT (dic) = IC_RESULT (ic); if (IS_ITEMP (IC_RESULT (dic)) && OP_SYMBOL (IC_RESULT (dic))->liveFrom > dic->seq) @@ -1711,6 +1918,7 @@ pack: } remiCodeFromeBBlock (ebp, ic); + bitVectUnSetBit(OP_SYMBOL(IC_RESULT(ic))->defs,ic->key); hTabDeleteItem (&iCodehTab, ic->key, ic, DELETE_ITEM, NULL); OP_DEFS (IC_RESULT (dic)) = bitVectSetBit (OP_DEFS (IC_RESULT (dic)), dic->key); return 1; @@ -1740,9 +1948,9 @@ findAssignToSym (operand * op, iCode * ic) /* or in stack space in case of + & - */ /* if assigned to a non-symbol then return - true */ + FALSE */ if (!IS_SYMOP (IC_RIGHT (dic))) - break; + return NULL; /* if the symbol is in far space then we should not */ @@ -1821,6 +2029,7 @@ packRegsForSupport (iCode * ic, eBBlock * ebp) IC_LEFT (ic)->operand.symOperand = IC_RIGHT (dic)->operand.symOperand; IC_LEFT (ic)->key = IC_RIGHT (dic)->operand.symOperand->key; + bitVectUnSetBit(OP_SYMBOL(IC_RESULT(dic))->defs,dic->key); remiCodeFromeBBlock (ebp, dic); hTabDeleteItem (&iCodehTab, dic->key, dic, DELETE_ITEM, NULL); change++; @@ -1856,6 +2065,7 @@ right: IC_RIGHT (ic)->key = IC_RIGHT (dic)->operand.symOperand->key; remiCodeFromeBBlock (ebp, dic); + bitVectUnSetBit(OP_SYMBOL(IC_RESULT(dic))->defs,dic->key); hTabDeleteItem (&iCodehTab, dic->key, dic, DELETE_ITEM, NULL); change++; } @@ -1867,154 +2077,106 @@ right: /*-----------------------------------------------------------------*/ -/* packRegsForOneuse : - will reduce some registers for single Use */ +/* packRegsDPTRuse : - will reduce some registers for single Use */ /*-----------------------------------------------------------------*/ static iCode * -packRegsForOneuse (iCode * ic, operand * op, eBBlock * ebp) +packRegsDPTRuse (operand * op) { -#if 1 - - /* I can't figure out how to make this safe yet. */ - if ((int)ic+(int)op+(int)ebp) { - return 0; - } else { - return 0; - } - return NULL; - -#else - bitVect *uses; - iCode *dic, *sic; - - /* if returning a literal then do nothing */ - if (!IS_SYMOP (op)) - return NULL; - - /* only upto 2 bytes since we cannot predict - the usage of b, & acc */ - if (getSize (operandType (op)) > (fReturnSizeDS390 - 2) && - ic->op != RETURN && - ic->op != SEND && - !POINTER_SET (ic) && - !POINTER_GET (ic)) - return NULL; - - /* this routine will mark the a symbol as used in one - instruction use only && if the defintion is local - (ie. within the basic block) && has only one definition && - that definiion is either a return value from a - function or does not contain any variables in - far space */ - uses = bitVectCopy (OP_USES (op)); - bitVectUnSetBit (uses, ic->key); /* take away this iCode */ - if (!bitVectIsZero (uses)) /* has other uses */ - return NULL; - - /* if it has only one defintion */ - if (bitVectnBitsOn (OP_DEFS (op)) > 1) - return NULL; /* has more than one definition */ - - /* get the that definition */ - if (!(dic = - hTabItemWithKey (iCodehTab, - bitVectFirstBit (OP_DEFS (op))))) - return NULL; - - /* if that only usage is a cast */ - if (dic->op == CAST) { - /* to a bigger type */ - if (getSize(OP_SYM_TYPE(IC_RESULT(dic))) > - getSize(OP_SYM_TYPE(IC_RIGHT(dic)))) { - /* than we can not, since we cannot predict the usage of b & acc */ - return NULL; - } - } - - /* found the definition now check if it is local */ - if (dic->seq < ebp->fSeq || - dic->seq > ebp->lSeq) - return NULL; /* non-local */ - - /* now check if it is the return from - a function call */ - if (dic->op == CALL || dic->op == PCALL) - { - if (ic->op != SEND && ic->op != RETURN) - { - OP_SYMBOL (op)->ruonly = 1; - return dic; + /* go thru entire liveRange of this variable & check for + other possible usage of DPTR , if we don't find it the + assign this to DPTR (ruonly) + */ + int i, key; + symbol *sym; + iCode *ic, *dic; + sym_link *type, *etype; + + if (!IS_SYMOP(op) || !IS_ITEMP(op)) return NULL; + if (OP_SYMBOL(op)->remat || OP_SYMBOL(op)->ruonly) return NULL; + + /* first check if any overlapping liverange has already been + assigned to DPTR */ + if (OP_SYMBOL(op)->clashes) { + for (i = 0 ; i < OP_SYMBOL(op)->clashes->size ; i++ ) { + if (bitVectBitValue(OP_SYMBOL(op)->clashes,i)) { + sym = hTabItemWithKey(liveRanges,i); + if (sym->ruonly) return NULL ; + } } - dic = dic->next; } - - /* otherwise check that the definition does - not contain any symbols in far space */ - if (isOperandInFarSpace (IC_LEFT (dic)) || - isOperandInFarSpace (IC_RIGHT (dic)) || - IS_OP_RUONLY (IC_LEFT (ic)) || - IS_OP_RUONLY (IC_RIGHT (ic))) - { - return NULL; - } - - /* if pointer set then make sure the pointer - is one byte */ - if (POINTER_SET (dic) && - !IS_DATA_PTR (aggrToPtr (operandType (IC_RESULT (dic)), FALSE))) - return NULL; - - if (POINTER_GET (dic) && - !IS_DATA_PTR (aggrToPtr (operandType (IC_LEFT (dic)), FALSE))) - return NULL; - - sic = dic; - - /* also make sure the intervenening instructions - don't have any thing in far space */ - for (dic = dic->next; dic && dic != ic; dic = dic->next) - { - - /* if there is an intervening function call then no */ - if (dic->op == CALL || dic->op == PCALL) - return NULL; - /* if pointer set then make sure the pointer - is one byte */ - if (POINTER_SET (dic) && - !IS_DATA_PTR (aggrToPtr (operandType (IC_RESULT (dic)), FALSE))) - return NULL; - - if (POINTER_GET (dic) && - !IS_DATA_PTR (aggrToPtr (operandType (IC_LEFT (dic)), FALSE))) - return NULL; - - /* if address of & the result is remat the okay */ - if (dic->op == ADDRESS_OF && - OP_SYMBOL (IC_RESULT (dic))->remat) - continue; - - /* if operand has size of three or more & this - operation is a '*','/' or '%' then 'b' may - cause a problem */ - if ((dic->op == '%' || dic->op == '/' || dic->op == '*') && - getSize (operandType (op)) >= 3) - return NULL; - - /* if left or right or result is in far space */ - if (isOperandInFarSpace (IC_LEFT (dic)) || - isOperandInFarSpace (IC_RIGHT (dic)) || - isOperandInFarSpace (IC_RESULT (dic)) || - IS_OP_RUONLY (IC_LEFT (dic)) || - IS_OP_RUONLY (IC_RIGHT (dic)) || - IS_OP_RUONLY (IC_RESULT (dic))) - { - return NULL; + /* no then go thru this guys live range */ + dic = ic = hTabFirstItemWK(iCodeSeqhTab,OP_SYMBOL(op)->liveFrom); + for (; ic && ic->seq <= OP_SYMBOL(op)->liveTo; + ic = hTabNextItem(iCodeSeqhTab,&key)) { + + if (SKIP_IC3(ic)) continue; + + /* if PCALL cannot be sure give up */ + if (ic->op == PCALL) return NULL; + + /* if CALL then make sure it is VOID || return value not used + or the return value is assigned to this one */ + if (ic->op == CALL) { + if (OP_SYMBOL(IC_RESULT(ic))->liveTo == + OP_SYMBOL(IC_RESULT(ic))->liveFrom) continue ; + etype = getSpec(type = operandType(IC_RESULT(ic))); + //if (getSize(type) == 0 || isOperandEqual(op,IC_RESULT(ic))) + if (getSize(type) == 0) + continue ; + return NULL ; } - } - OP_SYMBOL (op)->ruonly = 1; - return sic; -#endif + /* special case of add with a [remat] */ + if (ic->op == '+' && + OP_SYMBOL(IC_LEFT(ic))->remat && + (isOperandInFarSpace(IC_RIGHT(ic)) && + !isOperandInReg(IC_RIGHT(ic)))) return NULL ; + + /* special cases */ + /* pointerGet */ + if (POINTER_GET(ic) && !isOperandEqual(IC_LEFT(ic),op) && + getSize(operandType(IC_LEFT(ic))) > 1 ) return NULL ; + + /* pointerSet */ + if (POINTER_SET(ic) && !isOperandEqual(IC_RESULT(ic),op) && + getSize(operandType(IC_RESULT(ic))) > 1 ) return NULL; + + /* conditionals can destroy 'b' - make sure B wont be used in this one*/ + if ((IS_CONDITIONAL(ic) || ic->op == '*' || ic->op == '/' ) && + getSize(operandType(op)) > 3) return NULL; + + /* general case */ + if (IC_RESULT(ic) && IS_SYMOP(IC_RESULT(ic)) && + !isOperandEqual(IC_RESULT(ic),op) && + ((isOperandInFarSpace(IC_RESULT(ic)) && !isOperandInReg(IC_RESULT(ic))) || + OP_SYMBOL(IC_RESULT(ic))->ruonly || + OP_SYMBOL(IC_RESULT(ic))->onStack)) return NULL; + + if (IC_RIGHT(ic) && IS_SYMOP(IC_RIGHT(ic)) && + !isOperandEqual(IC_RIGHT(ic),op) && + (OP_SYMBOL(IC_RIGHT(ic))->liveTo > ic->seq || + IS_TRUE_SYMOP(IC_RIGHT(ic)) || + OP_SYMBOL(IC_RIGHT(ic))->ruonly) && + ((isOperandInFarSpace(IC_RIGHT(ic)) && !isOperandInReg(IC_RIGHT(ic)))|| + OP_SYMBOL(IC_RIGHT(ic))->onStack)) return NULL; + + if (IC_LEFT(ic) && IS_SYMOP(IC_LEFT(ic)) && + !isOperandEqual(IC_LEFT(ic),op) && + (OP_SYMBOL(IC_LEFT(ic))->liveTo > ic->seq || + IS_TRUE_SYMOP(IC_LEFT(ic)) || + OP_SYMBOL(IC_LEFT(ic))->ruonly) && + ((isOperandInFarSpace(IC_LEFT(ic)) && !isOperandInReg(IC_LEFT(ic)))|| + OP_SYMBOL(IC_LEFT(ic))->onStack)) return NULL; + + if (IC_LEFT(ic) && IC_RIGHT(ic) && + IS_ITEMP(IC_LEFT(ic)) && IS_ITEMP(IC_RIGHT(ic)) && + (isOperandInFarSpace(IC_LEFT(ic)) && !isOperandInReg(IC_LEFT(ic))) && + (isOperandInFarSpace(IC_RIGHT(ic)) && !isOperandInReg(IC_RIGHT(ic)))) + return NULL; + } + OP_SYMBOL(op)->ruonly = 1; + return dic; } /*-----------------------------------------------------------------*/ @@ -2054,6 +2216,11 @@ packRegsForAccUse (iCode * ic) { iCode *uic; + /* if this is an aggregate, e.g. a one byte char array */ + if (IS_AGGREGATE(operandType(IC_RESULT(ic)))) { + return; + } + /* if + or - then it has to be one byte result */ if ((ic->op == '+' || ic->op == '-') && getSize (operandType (IC_RESULT (ic))) > 1) @@ -2129,9 +2296,14 @@ packRegsForAccUse (iCode * ic) /* make sure that the result of this icode is not on the stack, since acc is used to compute stack offset */ +#if 0 if (IS_TRUE_SYMOP (IC_RESULT (uic)) && OP_SYMBOL (IC_RESULT (uic))->onStack) return; +#else + if (isOperandOnStack(IC_RESULT(uic))) + return; +#endif /* if either one of them in far space then we cannot */ if ((IS_TRUE_SYMOP (IC_LEFT (uic)) && @@ -2151,6 +2323,10 @@ packRegsForAccUse (iCode * ic) IC_LEFT (uic)->key != IC_RESULT (ic)->key) return; +#if 0 + // this is too dangerous and need further restrictions + // see bug #447547 + /* if one of them is a literal then we can */ if ((IC_LEFT (uic) && IS_OP_LITERAL (IC_LEFT (uic))) || (IC_RIGHT (uic) && IS_OP_LITERAL (IC_RIGHT (uic)))) @@ -2158,6 +2334,7 @@ packRegsForAccUse (iCode * ic) OP_SYMBOL (IC_RESULT (ic))->accuse = 1; return; } +#endif /* if the other one is not on stack then we can */ if (IC_LEFT (uic)->key == IC_RESULT (ic)->key && @@ -2229,6 +2406,7 @@ packForPush (iCode * ic, eBBlock * ebp) IC_LEFT (ic) = IC_RIGHT (dic); remiCodeFromeBBlock (ebp, dic); + bitVectUnSetBit(OP_SYMBOL(IC_RESULT(dic))->defs,dic->key); hTabDeleteItem (&iCodehTab, dic->key, dic, DELETE_ITEM, NULL); } @@ -2288,6 +2466,7 @@ packRegisters (eBBlock * ebp) !POINTER_SET (ic) && IS_SYMOP (IC_RIGHT (ic)) && OP_SYMBOL (IC_RIGHT (ic))->remat && + !IS_CAST_ICODE(OP_SYMBOL (IC_RIGHT (ic))->rematiCode) && bitVectnBitsOn (OP_SYMBOL (IC_RESULT (ic))->defs) <= 1) { @@ -2296,6 +2475,20 @@ packRegisters (eBBlock * ebp) OP_SYMBOL (IC_RESULT (ic))->rematiCode = OP_SYMBOL (IC_RIGHT (ic))->rematiCode; } + + /* if cast to a generic pointer & the pointer being + cast is remat, then we can remat this cast as well */ + if (ic->op == CAST && + IS_SYMOP(IC_RIGHT(ic)) && + OP_SYMBOL(IC_RIGHT(ic))->remat ) { + sym_link *to_type = operandType(IC_LEFT(ic)); + sym_link *from_type = operandType(IC_RIGHT(ic)); + if (IS_GENPTR(to_type) && IS_PTR(from_type)) { + OP_SYMBOL (IC_RESULT (ic))->remat = 1; + OP_SYMBOL (IC_RESULT (ic))->rematiCode = ic; + OP_SYMBOL (IC_RESULT (ic))->usl.spillLoc = NULL; + } + } /* if this is a +/- operation with a rematerizable then mark this as rematerializable as well */ @@ -2303,6 +2496,7 @@ packRegisters (eBBlock * ebp) (IS_SYMOP (IC_LEFT (ic)) && IS_ITEMP (IC_RESULT (ic)) && OP_SYMBOL (IC_LEFT (ic))->remat && + (!IS_SYMOP (IC_RIGHT (ic)) || !IS_CAST_ICODE(OP_SYMBOL (IC_RIGHT (ic))->rematiCode)) && bitVectnBitsOn (OP_DEFS (IC_RESULT (ic))) == 1 && IS_OP_LITERAL (IC_RIGHT (ic)))) { @@ -2320,27 +2514,30 @@ packRegisters (eBBlock * ebp) if (POINTER_GET (ic)) OP_SYMBOL (IC_LEFT (ic))->uptr = 1; + if (ic->op == RETURN && IS_SYMOP (IC_LEFT(ic))) + OP_SYMBOL (IC_LEFT (ic))->uptr = 1; + if (!SKIP_IC2 (ic)) { /* if we are using a symbol on the stack then we should say ds390_ptrRegReq */ if (ic->op == IFX && IS_SYMOP (IC_COND (ic))) - ds390_ptrRegReq += ((OP_SYMBOL (IC_COND (ic))->onStack || - OP_SYMBOL (IC_COND (ic))->iaccess) ? 1 : 0); + ds390_ptrRegReq += ((OP_SYMBOL (IC_COND (ic))->onStack ? !options.stack10bit : 0) + + OP_SYMBOL (IC_COND (ic))->iaccess); else if (ic->op == JUMPTABLE && IS_SYMOP (IC_JTCOND (ic))) - ds390_ptrRegReq += ((OP_SYMBOL (IC_JTCOND (ic))->onStack || - OP_SYMBOL (IC_JTCOND (ic))->iaccess) ? 1 : 0); + ds390_ptrRegReq += ((OP_SYMBOL (IC_JTCOND (ic))->onStack ? !options.stack10bit : 0) + + OP_SYMBOL (IC_JTCOND (ic))->iaccess); else { if (IS_SYMOP (IC_LEFT (ic))) - ds390_ptrRegReq += ((OP_SYMBOL (IC_LEFT (ic))->onStack || - OP_SYMBOL (IC_LEFT (ic))->iaccess) ? 1 : 0); + ds390_ptrRegReq += ((OP_SYMBOL (IC_LEFT (ic))->onStack ? !options.stack10bit : 0) + + OP_SYMBOL (IC_LEFT (ic))->iaccess); if (IS_SYMOP (IC_RIGHT (ic))) - ds390_ptrRegReq += ((OP_SYMBOL (IC_RIGHT (ic))->onStack || - OP_SYMBOL (IC_RIGHT (ic))->iaccess) ? 1 : 0); + ds390_ptrRegReq += ((OP_SYMBOL (IC_RIGHT (ic))->onStack ? !options.stack10bit : 0) + + OP_SYMBOL (IC_RIGHT (ic))->iaccess); if (IS_SYMOP (IC_RESULT (ic))) - ds390_ptrRegReq += ((OP_SYMBOL (IC_RESULT (ic))->onStack || - OP_SYMBOL (IC_RESULT (ic))->iaccess) ? 1 : 0); + ds390_ptrRegReq += ((OP_SYMBOL (IC_RESULT (ic))->onStack ? !options.stack10bit : 0) + + OP_SYMBOL (IC_RESULT (ic))->iaccess); } } @@ -2381,10 +2578,16 @@ packRegisters (eBBlock * ebp) /* some cases the redundant moves can can be eliminated for return statements */ - if ((ic->op == RETURN || ic->op == SEND) && + if ((ic->op == RETURN || ic->op == SEND) && !isOperandInFarSpace (IC_LEFT (ic)) && - !options.model) - packRegsForOneuse (ic, IC_LEFT (ic), ebp); + !options.model) { + + packRegsDPTRuse (IC_LEFT (ic)); + } + + if ((ic->op == CALL && getSize(operandType(IC_RESULT(ic))) <= 4)) { + packRegsDPTRuse (IC_RESULT (ic)); + } /* if pointer set & left has a size more than one and right is not in far space */ @@ -2392,19 +2595,20 @@ packRegisters (eBBlock * ebp) !isOperandInFarSpace (IC_RIGHT (ic)) && !OP_SYMBOL (IC_RESULT (ic))->remat && !IS_OP_RUONLY (IC_RIGHT (ic)) && - getSize (aggrToPtr (operandType (IC_RESULT (ic)), FALSE)) > 1) - - packRegsForOneuse (ic, IC_RESULT (ic), ebp); + getSize (aggrToPtr (operandType (IC_RESULT (ic)), FALSE)) > 1) { + + packRegsDPTRuse (IC_RESULT (ic)); + } /* if pointer get */ if (POINTER_GET (ic) && !isOperandInFarSpace (IC_RESULT (ic)) && !OP_SYMBOL (IC_LEFT (ic))->remat && !IS_OP_RUONLY (IC_RESULT (ic)) && - getSize (aggrToPtr (operandType (IC_LEFT (ic)), FALSE)) > 1) - - packRegsForOneuse (ic, IC_LEFT (ic), ebp); + getSize (aggrToPtr (operandType (IC_LEFT (ic)), FALSE)) > 1) { + packRegsDPTRuse (IC_LEFT (ic)); + } /* if this is cast for intergral promotion then check if only use of the definition of the @@ -2421,13 +2625,15 @@ packRegisters (eBBlock * ebp) SPEC_USIGN (fromType) == SPEC_USIGN (toType)) { - iCode *dic = packRegsForOneuse (ic, IC_RIGHT (ic), ebp); + iCode *dic = packRegsDPTRuse (IC_RIGHT (ic)); if (dic) { if (IS_ARITHMETIC_OP (dic)) { + bitVectUnSetBit(OP_SYMBOL(IC_RESULT(dic))->defs,dic->key); IC_RESULT (dic) = IC_RESULT (ic); remiCodeFromeBBlock (ebp, ic); + bitVectUnSetBit(OP_SYMBOL(IC_RESULT(ic))->defs,ic->key); hTabDeleteItem (&iCodehTab, ic->key, ic, DELETE_ITEM, NULL); OP_DEFS (IC_RESULT (dic)) = bitVectSetBit (OP_DEFS (IC_RESULT (dic)), dic->key); ic = ic->prev; @@ -2444,11 +2650,13 @@ packRegisters (eBBlock * ebp) if (compareType (operandType (IC_RIGHT (ic)), operandType (IC_LEFT (ic))) == 1) { - iCode *dic = packRegsForOneuse (ic, IC_RIGHT (ic), ebp); + iCode *dic = packRegsDPTRuse (IC_RIGHT (ic)); if (dic) { + bitVectUnSetBit(OP_SYMBOL(IC_RESULT(ic))->defs,ic->key); IC_RESULT (dic) = IC_RESULT (ic); remiCodeFromeBBlock (ebp, ic); + bitVectUnSetBit(OP_SYMBOL(IC_RESULT(ic))->defs,ic->key); hTabDeleteItem (&iCodehTab, ic->key, ic, DELETE_ITEM, NULL); OP_DEFS (IC_RESULT (dic)) = bitVectSetBit (OP_DEFS (IC_RESULT (dic)), dic->key); ic = ic->prev; @@ -2478,17 +2686,16 @@ packRegisters (eBBlock * ebp) we can leave the result of this operation in acc:b combination */ if ((IS_ARITHMETIC_OP (ic) - + || IS_CONDITIONAL(ic) || IS_BITWISE_OP (ic) - - || ic->op == LEFT_OP || ic->op == RIGHT_OP - + || ic->op == LEFT_OP || ic->op == RIGHT_OP || ic->op == CALL + || (ic->op == ADDRESS_OF && isOperandOnStack (IC_LEFT (ic))) ) && IS_ITEMP (IC_RESULT (ic)) && getSize (operandType (IC_RESULT (ic))) <= 2) packRegsForAccUse (ic); - + } } @@ -2501,10 +2708,13 @@ ds390_assignRegisters (eBBlock ** ebbs, int count) iCode *ic; int i; - setToNull ((void *) &_G.funcrUsed); + setToNull ((void *) &_G.funcrUsed); + setToNull ((void *) &_G.regAssigned); + setToNull ((void *) &_G.totRegAssigned); + setToNull ((void *) &_G.funcrUsed); ds390_ptrRegReq = _G.stackExtend = _G.dataExtend = 0; - ds390_nRegs = 8; - + ds390_nRegs = 12; + if (options.model != MODEL_FLAT24) options.stack10bit = 0; /* change assignments this will remove some live ranges reducing some register pressure */ for (i = 0; i < count; i++) @@ -2520,6 +2730,11 @@ ds390_assignRegisters (eBBlock ** ebbs, int count) /* and serially allocate registers */ serialRegAssign (ebbs, count); + ds390_nRegs = 8; + freeAllRegs (); + fillGaps(); + ds390_nRegs = 12; + /* if stack was extended then tell the user */ if (_G.stackExtend) { @@ -2542,8 +2757,10 @@ ds390_assignRegisters (eBBlock ** ebbs, int count) /* redo that offsets for stacked automatic variables */ redoStackOffsets (); - if (options.dump_rassgn) + if (options.dump_rassgn) { dumpEbbsToFileExt (DUMP_RASSGN, ebbs, count); + dumpLiveRanges (DUMP_LRANGE, liveRanges); + } /* do the overlaysegment stuff SDCCmem.c */ doOverlays (ebbs, count); @@ -2560,6 +2777,7 @@ ds390_assignRegisters (eBBlock ** ebbs, int count) setToNull ((void **) &_G.stackSpil); setToNull ((void **) &_G.spiltSet); /* mark all registers as free */ + ds390_nRegs = 8; freeAllRegs (); return;