3 -- The above warning supression flag is a temporary kludge.
4 -- While working on this module you are encouraged to remove it and fix
5 -- any warnings in the module. See
6 -- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
17 #include "HsVersions.h"
36 -- | Spill all these virtual regs to memory
37 -- TODO: see if we can split some of the live ranges instead of just globally
38 -- spilling the virtual reg.
40 -- TODO: On ciscy x86 and x86_64 we don't nessesarally have to add a mov instruction
41 -- when making spills. If an instr is using a spilled virtual we may be able to
42 -- address the spill slot directly.
45 :: [LiveCmmTop] -- ^ the code
46 -> UniqSet Int -- ^ available stack slots
47 -> UniqSet Reg -- ^ the regs to spill
49 ([LiveCmmTop] -- code will spill instructions
50 , UniqSet Int -- left over slots
51 , SpillStats ) -- stats about what happened during spilling
53 regSpill code slotsFree regs
55 -- not enough slots to spill these regs
56 | sizeUniqSet slotsFree < sizeUniqSet regs
57 = pprPanic "regSpill: out of spill slots!"
58 ( text " regs to spill = " <> ppr (sizeUniqSet regs)
59 $$ text " slots left = " <> ppr (sizeUniqSet slotsFree))
63 -- allocate a slot for each of the spilled regs
64 let slots = take (sizeUniqSet regs) $ uniqSetToList slotsFree
65 let regSlotMap = listToUFM
66 $ zip (uniqSetToList regs) slots
68 -- grab the unique supply from the monad
71 -- run the spiller on all the blocks
73 runState (mapM (mapBlockTopM (regSpill_block regSlotMap)) code)
77 , minusUniqSet slotsFree (mkUniqSet slots)
78 , makeSpillStats state')
81 regSpill_block regSlotMap (BasicBlock i instrs)
82 = do instrss' <- mapM (regSpill_instr regSlotMap) instrs
83 return $ BasicBlock i (concat instrss')
85 regSpill_instr _ li@(Instr _ Nothing)
88 regSpill_instr regSlotMap
89 (Instr instr (Just live))
91 -- work out which regs are read and written in this instr
92 let RU rlRead rlWritten = regUsage instr
94 -- sometimes a register is listed as being read more than once,
95 -- nub this so we don't end up inserting two lots of spill code.
96 let rsRead_ = nub rlRead
97 let rsWritten_ = nub rlWritten
99 -- if a reg is modified, it appears in both lists, want to undo this..
100 let rsRead = rsRead_ \\ rsWritten_
101 let rsWritten = rsWritten_ \\ rsRead_
102 let rsModify = intersect rsRead_ rsWritten_
104 -- work out if any of the regs being used are currently being spilled.
105 let rsSpillRead = filter (\r -> elemUFM r regSlotMap) rsRead
106 let rsSpillWritten = filter (\r -> elemUFM r regSlotMap) rsWritten
107 let rsSpillModify = filter (\r -> elemUFM r regSlotMap) rsModify
109 -- rewrite the instr and work out spill code.
110 (instr1, prepost1) <- mapAccumLM (spillRead regSlotMap) instr rsSpillRead
111 (instr2, prepost2) <- mapAccumLM (spillWrite regSlotMap) instr1 rsSpillWritten
112 (instr3, prepost3) <- mapAccumLM (spillModify regSlotMap) instr2 rsSpillModify
114 let (mPrefixes, mPostfixes) = unzip (prepost1 ++ prepost2 ++ prepost3)
115 let prefixes = concat mPrefixes
116 let postfixes = concat mPostfixes
119 let instrs' = map (\i -> Instr i Nothing) prefixes
120 ++ [ Instr instr3 Nothing ]
121 ++ map (\i -> Instr i Nothing) postfixes
124 {- $ pprTrace "* regSpill_instr spill"
125 ( text "instr = " <> ppr instr
126 $$ text "read = " <> ppr rsSpillRead
127 $$ text "write = " <> ppr rsSpillWritten
128 $$ text "mod = " <> ppr rsSpillModify
130 $$ (vcat $ map ppr instrs')
136 spillRead regSlotMap instr reg
137 | Just slot <- lookupUFM regSlotMap reg
138 = do (instr', nReg) <- patchInstr reg instr
141 { stateSpillSL = addToUFM_C accSpillSL (stateSpillSL s) reg (reg, 0, 1) }
144 , ( [RELOAD slot nReg]
147 | otherwise = panic "RegSpill.spillRead: no slot defined for spilled reg"
149 spillWrite regSlotMap instr reg
150 | Just slot <- lookupUFM regSlotMap reg
151 = do (instr', nReg) <- patchInstr reg instr
154 { stateSpillSL = addToUFM_C accSpillSL (stateSpillSL s) reg (reg, 1, 0) }
158 , [SPILL nReg slot]))
160 | otherwise = panic "RegSpill.spillWrite: no slot defined for spilled reg"
162 spillModify regSlotMap instr reg
163 | Just slot <- lookupUFM regSlotMap reg
164 = do (instr', nReg) <- patchInstr reg instr
167 { stateSpillSL = addToUFM_C accSpillSL (stateSpillSL s) reg (reg, 1, 1) }
170 , ( [RELOAD slot nReg]
171 , [SPILL nReg slot]))
173 | otherwise = panic "RegSpill.spillModify: no slot defined for spilled reg"
177 -- | rewrite uses of this virtual reg in an instr to use a different virtual reg
178 patchInstr :: Reg -> Instr -> SpillM (Instr, Reg)
180 = do nUnique <- newUnique
181 let nReg = renameVirtualReg nUnique reg
182 let instr' = patchReg1 reg nReg instr
183 return (instr', nReg)
185 patchReg1 :: Reg -> Reg -> Instr -> Instr
186 patchReg1 old new instr
190 in patchRegs instr patchF
193 ------------------------------------------------------
198 { stateUS :: UniqSupply
199 , stateSpillSL :: UniqFM (Reg, Int, Int) } -- ^ spilled reg vs number of times vreg was loaded, stored
201 initSpillS uniqueSupply
203 { stateUS = uniqueSupply
204 , stateSpillSL = emptyUFM }
206 type SpillM a = State SpillS a
208 newUnique :: SpillM Unique
210 = do us <- gets stateUS
211 case splitUniqSupply us of
213 -> do let uniq = uniqFromSupply us1
214 modify $ \s -> s { stateUS = us2 }
217 accSpillSL (r1, s1, l1) (r2, s2, l2)
218 = (r1, s1 + s2, l1 + l2)
221 ----------------------------------------------------
226 { spillStoreLoad :: UniqFM (Reg, Int, Int) }
228 makeSpillStats :: SpillS -> SpillStats
231 { spillStoreLoad = stateSpillSL s }
233 instance Outputable SpillStats where
235 = (vcat $ map (\(r, s, l) -> ppr r <+> int s <+> int l)
236 $ eltsUFM (spillStoreLoad stats))