warning police
[ghc-hetmet.git] / compiler / nativeGen / RegAllocColor.hs
1 -- | Graph coloring register allocator.
2 --
3 -- TODO:
4 --      The function that choosing the potential spills could be a bit cleverer.
5 --      Colors in graphviz graphs could be nicer.
6 --
7 {-# OPTIONS -fno-warn-missing-signatures #-}
8
9 module RegAllocColor ( 
10         regAlloc,
11         regDotColor
12
13
14 where
15
16 import qualified GraphColor     as Color
17 import RegLiveness
18 import RegSpill
19 import RegSpillClean
20 import RegSpillCost
21 import RegAllocStats
22 -- import RegCoalesce
23 import MachRegs
24 import MachInstrs
25 import PprMach
26
27 import UniqSupply
28 import UniqSet
29 import UniqFM
30 import Bag
31 import Outputable
32 import DynFlags
33
34 import Data.List
35 import Data.Maybe
36 import Control.Monad
37
38 -- | The maximum number of build/spill cycles we'll allow.
39 --      We should only need 3 or 4 cycles tops.
40 --      If we run for any longer than this we're probably in an infinite loop,
41 --      It's probably better just to bail out and report a bug at this stage.
42 maxSpinCount    :: Int
43 maxSpinCount    = 10
44
45
46 -- | The top level of the graph coloring register allocator.
47 --      
48 regAlloc
49         :: DynFlags
50         -> UniqFM (UniqSet Reg)         -- ^ the registers we can use for allocation
51         -> UniqSet Int                  -- ^ the set of available spill slots.
52         -> [LiveCmmTop]                 -- ^ code annotated with liveness information.
53         -> UniqSM 
54                 ( [NatCmmTop]           -- ^ code with registers allocated.
55                 , [RegAllocStats] )     -- ^ stats for each stage of allocation
56                 
57 regAlloc dflags regsFree slotsFree code
58  = do
59         (code_final, debug_codeGraphs, _)
60                 <- regAlloc_spin dflags 0 trivColorable regsFree slotsFree [] code
61         
62         return  ( code_final
63                 , reverse debug_codeGraphs )
64
65 regAlloc_spin dflags (spinCount :: Int) triv regsFree slotsFree debug_codeGraphs code
66  = do
67         -- if any of these dump flags are turned on we want to hang on to
68         --      intermediate structures in the allocator - otherwise tell the
69         --      allocator to ditch them early so we don't end up creating space leaks.
70         let dump = or
71                 [ dopt Opt_D_dump_asm_regalloc_stages dflags
72                 , dopt Opt_D_dump_asm_stats dflags
73                 , dopt Opt_D_dump_asm_conflicts dflags ]
74
75         -- check that we're not running off down the garden path.
76         when (spinCount > maxSpinCount)
77          $ pprPanic "regAlloc_spin: max build/spill cycle count exceeded."
78                 (  text "It looks like the register allocator is stuck in an infinite loop."
79                 $$ text "max cycles  = " <> int maxSpinCount
80                 $$ text "regsFree    = " <> (hcat       $ punctuate space $ map (docToSDoc . pprUserReg)
81                                                 $ uniqSetToList $ unionManyUniqSets $ eltsUFM regsFree)
82                 $$ text "slotsFree   = " <> ppr (sizeUniqSet slotsFree))
83
84
85         -- Brig's algorithm does reckless coalescing for all but the first allocation stage
86         --      Doing this seems to reduce the number of reg-reg moves, but at the cost-
87         --      of creating more spills. Probably better just to stick with conservative 
88         --      coalescing in Color.colorGraph for now.
89         --
90         {- code_coalesced1      <- if (spinCount > 0) 
91                                 then regCoalesce code
92                                 else return code -}
93
94         let code_coalesced1     = code
95
96         -- build a conflict graph from the code.
97         graph           <- {-# SCC "BuildGraph" #-} buildGraph code_coalesced1
98
99         -- VERY IMPORTANT:
100         --      We really do want the graph to be fully evaluated _before_ we start coloring.
101         --      If we don't do this now then when the call to Color.colorGraph forces bits of it,
102         --      the heap will be filled with half evaluated pieces of graph and zillions of apply thunks.
103         --
104         seqGraph graph `seq` return ()
105
106
107         -- build a map of the cost of spilling each instruction
108         --      this will only actually be computed if we have to spill something.
109         let spillCosts  = foldl' plusSpillCostInfo zeroSpillCostInfo
110                         $ map slurpSpillCostInfo code_coalesced1
111
112         -- the function to choose regs to leave uncolored
113         let spill       = chooseSpill spillCosts
114
115         -- record startup state
116         let stat1       =
117                 if spinCount == 0
118                  then   Just $ RegAllocStatsStart
119                         { raLiveCmm     = code
120                         , raGraph       = graph
121                         , raSpillCosts  = spillCosts }
122                  else   Nothing
123         
124         -- try and color the graph 
125         let (graph_colored, rsSpill, rmCoalesce)
126                         = {-# SCC "ColorGraph" #-}
127                            Color.colorGraph
128                                 (dopt Opt_RegsIterative dflags)
129                                 regsFree triv spill graph
130
131         -- rewrite regs in the code that have been coalesced
132         let patchF reg  = case lookupUFM rmCoalesce reg of
133                                 Just reg'       -> patchF reg'
134                                 Nothing         -> reg
135         let code_coalesced2
136                         = map (patchEraseLive patchF) code_coalesced1
137
138
139         -- see if we've found a coloring
140         if isEmptyUniqSet rsSpill
141          then do
142                 -- patch the registers using the info in the graph
143                 let code_patched        = map (patchRegsFromGraph graph_colored) code_coalesced2
144
145                 -- clean out unneeded SPILL/RELOADs
146                 let code_spillclean     = map cleanSpills code_patched
147
148                 -- strip off liveness information
149                 let code_nat            = map stripLive code_spillclean
150
151                 -- rewrite SPILL/RELOAD pseudos into real instructions
152                 let spillNatTop         = mapGenBlockTop spillNatBlock
153                 let code_final          = map spillNatTop code_nat
154                 
155                 -- record what happened in this stage for debugging
156                 let stat                =
157                         RegAllocStatsColored
158                         { raGraph       = graph_colored
159                         , raCoalesced   = rmCoalesce
160                         , raPatched     = code_patched
161                         , raSpillClean  = code_spillclean
162                         , raFinal       = code_final
163                         , raSRMs        = foldl' addSRM (0, 0, 0) $ map countSRMs code_spillclean }
164
165
166                 let statList =
167                         if dump then [stat] ++ maybeToList stat1 ++ debug_codeGraphs
168                                 else []
169
170                 -- space leak avoidance
171                 seqList statList `seq` return ()
172
173                 return  ( code_final
174                         , statList
175                         , graph_colored)
176
177          -- we couldn't find a coloring, time to spill something
178          else do
179                 -- spill the uncolored regs
180                 (code_spilled, slotsFree', spillStats)
181                         <- regSpill code_coalesced2 slotsFree rsSpill
182
183                 -- recalculate liveness
184                 let code_nat    = map stripLive code_spilled
185                 code_relive     <- mapM regLiveness code_nat
186
187                 -- record what happened in this stage for debugging
188                 let stat        =
189                         RegAllocStatsSpill
190                         { raGraph       = graph_colored
191                         , raCoalesced   = rmCoalesce
192                         , raSpillStats  = spillStats
193                         , raSpillCosts  = spillCosts
194                         , raSpilled     = code_spilled }
195                                 
196                 let statList =
197                         if dump
198                                 then [stat] ++ maybeToList stat1 ++ debug_codeGraphs
199                                 else []
200
201                 -- space leak avoidance
202                 seqList statList `seq` return ()
203
204                 regAlloc_spin dflags (spinCount + 1) triv regsFree slotsFree'
205                         statList
206                         code_relive
207
208
209
210 -- | Build a graph from the liveness and coalesce information in this code.
211
212 buildGraph 
213         :: [LiveCmmTop]
214         -> UniqSM (Color.Graph Reg RegClass Reg)
215         
216 buildGraph code
217  = do
218         -- Slurp out the conflicts and reg->reg moves from this code
219         let (conflictList, moveList) =
220                 unzip $ map slurpConflicts code
221
222         -- Slurp out the spill/reload coalesces
223         let moveList2           = map slurpReloadCoalesce code
224
225         -- Add the reg-reg conflicts to the graph
226         let conflictBag         = unionManyBags conflictList
227         let graph_conflict      = foldrBag graphAddConflictSet Color.initGraph conflictBag
228
229         -- Add the coalescences edges to the graph.
230         let moveBag             = unionBags (unionManyBags moveList2) (unionManyBags moveList)
231         let graph_coalesce      = foldrBag graphAddCoalesce graph_conflict moveBag
232                         
233         return  graph_coalesce
234
235
236 -- | Add some conflict edges to the graph.
237 --      Conflicts between virtual and real regs are recorded as exclusions.
238 --
239 graphAddConflictSet 
240         :: UniqSet Reg
241         -> Color.Graph Reg RegClass Reg
242         -> Color.Graph Reg RegClass Reg
243         
244 graphAddConflictSet set graph
245  = let  reals           = filterUFM isRealReg set
246         virtuals        = filterUFM (not . isRealReg) set
247  
248         graph1  = Color.addConflicts virtuals regClass graph
249         graph2  = foldr (\(r1, r2) -> Color.addExclusion r1 regClass r2)
250                         graph1
251                         [ (a, b) 
252                                 | a <- uniqSetToList virtuals
253                                 , b <- uniqSetToList reals]
254
255    in   graph2
256         
257
258 -- | Add some coalesence edges to the graph
259 --      Coalesences between virtual and real regs are recorded as preferences.
260 --
261 graphAddCoalesce 
262         :: (Reg, Reg) 
263         -> Color.Graph Reg RegClass Reg
264         -> Color.Graph Reg RegClass Reg
265         
266 graphAddCoalesce (r1, r2) graph
267         | RealReg _ <- r1
268         = Color.addPreference (regWithClass r2) r1 graph
269         
270         | RealReg _ <- r2
271         = Color.addPreference (regWithClass r1) r2 graph
272         
273         | otherwise
274         = Color.addCoalesce (regWithClass r1) (regWithClass r2) graph
275
276         where   regWithClass r  = (r, regClass r)
277
278
279 -- | Patch registers in code using the reg -> reg mapping in this graph.
280 patchRegsFromGraph 
281         :: Color.Graph Reg RegClass Reg
282         -> LiveCmmTop -> LiveCmmTop
283
284 patchRegsFromGraph graph code
285  = let
286         -- a function to lookup the hardreg for a virtual reg from the graph.
287         patchF reg
288                 -- leave real regs alone.
289                 | isRealReg reg
290                 = reg
291
292                 -- this virtual has a regular node in the graph.
293                 | Just node     <- Color.lookupNode graph reg
294                 = case Color.nodeColor node of
295                         Just color      -> color
296                         Nothing         -> reg
297                         
298                 -- no node in the graph for this virtual, bad news.
299                 | otherwise
300                 = pprPanic "patchRegsFromGraph: register mapping failed." 
301                         (  text "There is no node in the graph for register " <> ppr reg
302                         $$ ppr code
303                         $$ Color.dotGraph (\_ -> text "white") trivColorable graph)
304
305    in   patchEraseLive patchF code
306    
307
308 -----
309 -- for when laziness just isn't what you wanted...
310 --
311 seqGraph :: Color.Graph Reg RegClass Reg -> ()
312 seqGraph graph          = seqNodes (eltsUFM (Color.graphMap graph))
313
314 seqNodes :: [Color.Node Reg RegClass Reg] -> ()
315 seqNodes ns
316  = case ns of
317         []              -> ()
318         (n : ns)        -> seqNode n `seq` seqNodes ns
319
320 seqNode :: Color.Node Reg RegClass Reg -> ()
321 seqNode node
322         =     seqReg      (Color.nodeId node)
323         `seq` seqRegClass (Color.nodeClass node)
324         `seq` seqMaybeReg (Color.nodeColor node)
325         `seq` (seqRegList (uniqSetToList (Color.nodeConflicts node)))
326         `seq` (seqRegList (uniqSetToList (Color.nodeExclusions node)))
327         `seq` (seqRegList (Color.nodePreference node))
328         `seq` (seqRegList (uniqSetToList (Color.nodeCoalesce node)))
329
330 seqReg :: Reg -> ()
331 seqReg reg
332  = case reg of
333         RealReg _       -> ()
334         VirtualRegI _   -> ()
335         VirtualRegHi _  -> ()
336         VirtualRegF _   -> ()
337         VirtualRegD _   -> ()
338
339 seqRegClass :: RegClass -> ()
340 seqRegClass c
341  = case c of
342         RcInteger       -> ()
343         RcFloat         -> ()
344         RcDouble        -> ()
345
346 seqMaybeReg :: Maybe Reg -> ()
347 seqMaybeReg mr
348  = case mr of
349         Nothing         -> ()
350         Just r          -> seqReg r
351
352 seqRegList :: [Reg] -> ()
353 seqRegList rs
354  = case rs of
355         []              -> ()
356         (r : rs)        -> seqReg r `seq` seqRegList rs
357
358 seqList :: [a] -> ()
359 seqList ls
360  = case ls of
361         []              -> ()
362         (r : rs)        -> r `seq` seqList rs
363
364