1 {-# OPTIONS -fno-warn-missing-signatures #-}
2 -- | Graph coloring register allocator.
4 -- TODO: The colors in graphviz graphs for x86_64 and ppc could be nicer.
7 module RegAlloc.Graph.Main (
13 import qualified GraphColor as Color
14 import RegAlloc.Liveness
15 import RegAlloc.Graph.Spill
16 import RegAlloc.Graph.SpillClean
17 import RegAlloc.Graph.SpillCost
18 import RegAlloc.Graph.Stats
19 import RegAlloc.Graph.TrivColorable
37 -- | The maximum number of build\/spill cycles we'll allow.
38 -- We should only need 3 or 4 cycles tops.
39 -- If we run for any longer than this we're probably in an infinite loop,
40 -- It's probably better just to bail out and report a bug at this stage.
45 -- | The top level of the graph coloring register allocator.
48 :: (Outputable instr, Instruction instr)
50 -> UniqFM (UniqSet RealReg) -- ^ the registers we can use for allocation
51 -> UniqSet Int -- ^ the set of available spill slots.
52 -> [LiveCmmTop instr] -- ^ code annotated with liveness information.
53 -> UniqSM ( [NatCmmTop instr], [RegAllocStats instr] )
54 -- ^ code with registers allocated and stats for each stage of
57 regAlloc dflags regsFree slotsFree code
59 -- TODO: the regClass function is currently hard coded to the default target
60 -- architecture. Would prefer to determine this from dflags.
61 -- There are other uses of targetRegClass later in this module.
62 let triv = trivColorable
63 targetVirtualRegSqueeze
66 (code_final, debug_codeGraphs, _)
67 <- regAlloc_spin dflags 0
69 regsFree slotsFree [] code
72 , reverse debug_codeGraphs )
77 (triv :: Color.Triv VirtualReg RegClass RealReg)
78 (regsFree :: UniqFM (UniqSet RealReg))
83 -- if any of these dump flags are turned on we want to hang on to
84 -- intermediate structures in the allocator - otherwise tell the
85 -- allocator to ditch them early so we don't end up creating space leaks.
87 [ dopt Opt_D_dump_asm_regalloc_stages dflags
88 , dopt Opt_D_dump_asm_stats dflags
89 , dopt Opt_D_dump_asm_conflicts dflags ]
91 -- check that we're not running off down the garden path.
92 when (spinCount > maxSpinCount)
93 $ pprPanic "regAlloc_spin: max build/spill cycle count exceeded."
94 ( text "It looks like the register allocator is stuck in an infinite loop."
95 $$ text "max cycles = " <> int maxSpinCount
96 $$ text "regsFree = " <> (hcat $ punctuate space $ map ppr
97 $ uniqSetToList $ unionManyUniqSets $ eltsUFM regsFree)
98 $$ text "slotsFree = " <> ppr (sizeUniqSet slotsFree))
100 -- build a conflict graph from the code.
101 (graph :: Color.Graph VirtualReg RegClass RealReg)
102 <- {-# SCC "BuildGraph" #-} buildGraph code
105 -- We really do want the graph to be fully evaluated _before_ we start coloring.
106 -- If we don't do this now then when the call to Color.colorGraph forces bits of it,
107 -- the heap will be filled with half evaluated pieces of graph and zillions of apply thunks.
109 seqGraph graph `seq` return ()
112 -- build a map of the cost of spilling each instruction
113 -- this will only actually be computed if we have to spill something.
114 let spillCosts = foldl' plusSpillCostInfo zeroSpillCostInfo
115 $ map slurpSpillCostInfo code
117 -- the function to choose regs to leave uncolored
118 let spill = chooseSpill spillCosts
120 -- record startup state
123 then Just $ RegAllocStatsStart
126 , raSpillCosts = spillCosts }
129 -- try and color the graph
130 let (graph_colored, rsSpill, rmCoalesce)
131 = {-# SCC "ColorGraph" #-}
133 (dopt Opt_RegsIterative dflags)
135 regsFree triv spill graph
137 -- rewrite regs in the code that have been coalesced
139 | RegVirtual vr <- reg
140 = case lookupUFM rmCoalesce vr of
141 Just vr' -> patchF (RegVirtual vr')
148 = map (patchEraseLive patchF) code
151 -- see if we've found a coloring
152 if isEmptyUniqSet rsSpill
154 -- if -fasm-lint is turned on then validate the graph
155 let graph_colored_lint =
156 if dopt Opt_DoAsmLinting dflags
157 then Color.validateGraph (text "")
158 True -- require all nodes to be colored
162 -- patch the registers using the info in the graph
163 let code_patched = map (patchRegsFromGraph graph_colored_lint) code_coalesced
165 -- clean out unneeded SPILL/RELOADs
166 let code_spillclean = map cleanSpills code_patched
168 -- strip off liveness information,
169 -- and rewrite SPILL/RELOAD pseudos into real instructions along the way
170 let code_final = map stripLive code_spillclean
172 -- let spillNatTop = mapGenBlockTop spillNatBlock
173 -- let code_final = map spillNatTop code_nat
175 -- record what happened in this stage for debugging
179 , raGraphColored = graph_colored_lint
180 , raCoalesced = rmCoalesce
181 , raCodeCoalesced = code_coalesced
182 , raPatched = code_patched
183 , raSpillClean = code_spillclean
184 , raFinal = code_final
185 , raSRMs = foldl' addSRM (0, 0, 0) $ map countSRMs code_spillclean }
189 if dump then [stat] ++ maybeToList stat1 ++ debug_codeGraphs
192 -- space leak avoidance
193 seqList statList `seq` return ()
197 , graph_colored_lint)
199 -- we couldn't find a coloring, time to spill something
201 -- if -fasm-lint is turned on then validate the graph
202 let graph_colored_lint =
203 if dopt Opt_DoAsmLinting dflags
204 then Color.validateGraph (text "")
205 False -- don't require nodes to be colored
209 -- spill the uncolored regs
210 (code_spilled, slotsFree', spillStats)
211 <- regSpill code_coalesced slotsFree rsSpill
213 -- recalculate liveness
214 -- let code_nat = map stripLive code_spilled
215 code_relive <- mapM regLiveness code_spilled
217 -- record what happened in this stage for debugging
220 { raGraph = graph_colored_lint
221 , raCoalesced = rmCoalesce
222 , raSpillStats = spillStats
223 , raSpillCosts = spillCosts
224 , raSpilled = code_spilled }
228 then [stat] ++ maybeToList stat1 ++ debug_codeGraphs
231 -- space leak avoidance
232 seqList statList `seq` return ()
234 regAlloc_spin dflags (spinCount + 1) triv regsFree slotsFree'
240 -- | Build a graph from the liveness and coalesce information in this code.
244 => [LiveCmmTop instr]
245 -> UniqSM (Color.Graph VirtualReg RegClass RealReg)
249 -- Slurp out the conflicts and reg->reg moves from this code
250 let (conflictList, moveList) =
251 unzip $ map slurpConflicts code
253 -- Slurp out the spill/reload coalesces
254 let moveList2 = map slurpReloadCoalesce code
256 -- Add the reg-reg conflicts to the graph
257 let conflictBag = unionManyBags conflictList
258 let graph_conflict = foldrBag graphAddConflictSet Color.initGraph conflictBag
260 -- Add the coalescences edges to the graph.
261 let moveBag = unionBags (unionManyBags moveList2) (unionManyBags moveList)
262 let graph_coalesce = foldrBag graphAddCoalesce graph_conflict moveBag
264 return graph_coalesce
267 -- | Add some conflict edges to the graph.
268 -- Conflicts between virtual and real regs are recorded as exclusions.
272 -> Color.Graph VirtualReg RegClass RealReg
273 -> Color.Graph VirtualReg RegClass RealReg
275 graphAddConflictSet set graph
276 = let virtuals = mkUniqSet
277 [ vr | RegVirtual vr <- uniqSetToList set ]
279 graph1 = Color.addConflicts virtuals classOfVirtualReg graph
281 graph2 = foldr (\(r1, r2) -> Color.addExclusion r1 classOfVirtualReg r2)
284 | RegVirtual vr <- uniqSetToList set
285 , RegReal rr <- uniqSetToList set]
290 -- | Add some coalesence edges to the graph
291 -- Coalesences between virtual and real regs are recorded as preferences.
295 -> Color.Graph VirtualReg RegClass RealReg
296 -> Color.Graph VirtualReg RegClass RealReg
298 graphAddCoalesce (r1, r2) graph
300 , RegVirtual vr <- r2
301 = Color.addPreference (vr, classOfVirtualReg vr) rr graph
304 , RegVirtual vr <- r1
305 = Color.addPreference (vr, classOfVirtualReg vr) rr graph
307 | RegVirtual vr1 <- r1
308 , RegVirtual vr2 <- r2
310 (vr1, classOfVirtualReg vr1)
311 (vr2, classOfVirtualReg vr2)
314 -- We can't coalesce two real regs, but there could well be existing
315 -- hreg,hreg moves in the input code. We'll just ignore these
316 -- for coalescing purposes.
322 = panic "graphAddCoalesce: bogus"
325 -- | Patch registers in code using the reg -> reg mapping in this graph.
327 :: (Outputable instr, Instruction instr)
328 => Color.Graph VirtualReg RegClass RealReg
329 -> LiveCmmTop instr -> LiveCmmTop instr
331 patchRegsFromGraph graph code
333 -- a function to lookup the hardreg for a virtual reg from the graph.
335 -- leave real regs alone.
339 -- this virtual has a regular node in the graph.
340 | RegVirtual vr <- reg
341 , Just node <- Color.lookupNode graph vr
342 = case Color.nodeColor node of
343 Just color -> RegReal color
344 Nothing -> RegVirtual vr
346 -- no node in the graph for this virtual, bad news.
348 = pprPanic "patchRegsFromGraph: register mapping failed."
349 ( text "There is no node in the graph for register " <> ppr reg
354 targetVirtualRegSqueeze
355 targetRealRegSqueeze)
358 in patchEraseLive patchF code
362 -- for when laziness just isn't what you wanted...
364 seqGraph :: Color.Graph VirtualReg RegClass RealReg -> ()
365 seqGraph graph = seqNodes (eltsUFM (Color.graphMap graph))
367 seqNodes :: [Color.Node VirtualReg RegClass RealReg] -> ()
371 (n : ns) -> seqNode n `seq` seqNodes ns
373 seqNode :: Color.Node VirtualReg RegClass RealReg -> ()
375 = seqVirtualReg (Color.nodeId node)
376 `seq` seqRegClass (Color.nodeClass node)
377 `seq` seqMaybeRealReg (Color.nodeColor node)
378 `seq` (seqVirtualRegList (uniqSetToList (Color.nodeConflicts node)))
379 `seq` (seqRealRegList (uniqSetToList (Color.nodeExclusions node)))
380 `seq` (seqRealRegList (Color.nodePreference node))
381 `seq` (seqVirtualRegList (uniqSetToList (Color.nodeCoalesce node)))
383 seqVirtualReg :: VirtualReg -> ()
384 seqVirtualReg reg = reg `seq` ()
386 seqRealReg :: RealReg -> ()
387 seqRealReg reg = reg `seq` ()
389 seqRegClass :: RegClass -> ()
390 seqRegClass c = c `seq` ()
392 seqMaybeRealReg :: Maybe RealReg -> ()
396 Just r -> seqRealReg r
398 seqVirtualRegList :: [VirtualReg] -> ()
402 (r : rs) -> seqVirtualReg r `seq` seqVirtualRegList rs
404 seqRealRegList :: [RealReg] -> ()
408 (r : rs) -> seqRealReg r `seq` seqRealRegList rs
414 (r : rs) -> r `seq` seqList rs