92efc4a1d324e08e7219c6b7f8eb6c4c7d6dc6a7
[ghc-hetmet.git] / compiler / nativeGen / RegAllocColor.hs
1 -- | Graph coloring register allocator.
2 --
3 -- TODO:
4 --      Live range splitting:
5 --              At the moment regs that are spilled are spilled for all time, even though
6 --              we might be able to allocate them a hardreg in different parts of the code.
7 --
8 --      As we're aggressively coalescing before register allocation proper we're not currently
9 --      using the coalescence information present in the graph.
10 --
11 --      The function that choosing the potential spills could be a bit cleverer.
12 --
13 --      Colors in graphviz graphs could be nicer.
14 --
15
16 module RegAllocColor ( 
17         regAlloc,
18         regDotColor
19
20
21 where
22
23 import qualified GraphColor     as Color
24 import RegLiveness
25 import RegSpill
26 import RegAllocStats
27 import MachRegs
28 import MachInstrs
29 import RegCoalesce
30 import PprMach
31
32 import UniqSupply
33 import UniqSet
34 import UniqFM
35 import Bag
36 import Outputable
37
38 import Data.List
39 import Data.Maybe
40 import Control.Monad
41
42 -- | The maximum number of build/spill cycles we'll allow.
43 --      We should only need 3 or 4 cycles tops.
44 --      If we run for any longer than this we're probably in an infinite loop,
45 --      It's probably better just to bail out and report a bug at this stage.
46 maxSpinCount    :: Int
47 maxSpinCount    = 10
48
49
50 -- | The top level of the graph coloring register allocator.
51 --      
52 regAlloc
53         :: UniqFM (UniqSet Reg)         -- ^ the registers we can use for allocation
54         -> UniqSet Int                  -- ^ the set of available spill slots.
55         -> [LiveCmmTop]                 -- ^ code annotated with liveness information.
56         -> UniqSM 
57                 ( [NatCmmTop]           -- ^ code with registers allocated.
58                 , [RegAllocStats] )     -- ^ stats for each stage of allocation
59                 
60 regAlloc regsFree slotsFree code
61  = do
62         (code_final, debug_codeGraphs, graph_final)
63                 <- regAlloc_spin 0 trivColorable regsFree slotsFree [] code
64         
65         return  ( code_final
66                 , reverse debug_codeGraphs )
67
68 regAlloc_spin (spinCount :: Int) triv regsFree slotsFree debug_codeGraphs code 
69  = do
70         -- check that we're not running off down the garden path.
71         when (spinCount > maxSpinCount)
72          $ pprPanic "regAlloc_spin: max build/spill cycle count exceeded."
73                 (  text "It looks like the register allocator is stuck in an infinite loop."
74                 $$ text "max cycles  = " <> int maxSpinCount
75                 $$ text "regsFree    = " <> (hcat       $ punctuate space $ map (docToSDoc . pprUserReg)
76                                                 $ uniqSetToList $ unionManyUniqSets $ eltsUFM regsFree)
77                 $$ text "slotsFree   = " <> ppr (sizeUniqSet slotsFree))
78
79         -- build a conflict graph from the code.
80         graph           <- buildGraph code
81
82         -- build a map of how many instructions each reg lives for.
83         --      this is lazy, it won't be computed unless we need to spill
84         let fmLife      = plusUFMs_C (\(r1, l1) (r2, l2) -> (r1, l1 + l2))
85                         $ map lifetimeCount code
86
87         -- record startup state
88         let stat1       =
89                 if spinCount == 0
90                  then   Just $ RegAllocStatsStart
91                         { raLiveCmm     = code
92                         , raGraph       = graph
93                         , raLifetimes   = fmLife }
94                  else   Nothing
95
96
97         -- the function to choose regs to leave uncolored
98         let spill       = chooseSpill_maxLife fmLife
99         
100         -- try and color the graph 
101         let (graph_colored, rsSpill)    
102                         = Color.colorGraph regsFree triv spill graph
103
104         -- see if we've found a coloring
105         if isEmptyUniqSet rsSpill
106          then do
107                 -- patch the registers using the info in the graph
108                 --      also rewrite SPILL/REALOAD pseudos into real instructions
109                 let code_patched        = map (patchRegsFromGraph graph_colored) code
110
111                 let spillNatTop         = mapGenBlockTop spillNatBlock
112                 let code_nat            = map (spillNatTop . stripLive) code_patched
113
114                 
115                 -- record what happened in this stage for debugging
116                 let stat                =
117                         RegAllocStatsColored
118                         { raGraph       = graph_colored
119                         , raPatchedCmm  = code_patched }
120
121                 return  ( code_nat
122                         , [stat] ++ maybeToList stat1 ++ debug_codeGraphs
123                         , graph_colored)
124
125          else do
126                 -- spill the uncolored regs
127                 (code_spilled, slotsFree', spillStats)
128                         <- regSpill code slotsFree rsSpill
129                         
130                 -- recalculate liveness
131                 let code_nat    = map stripLive code_spilled
132                 code_relive     <- mapM regLiveness code_nat
133
134                 -- record what happened in this stage for debugging
135                 let stat        =
136                         RegAllocStatsSpill
137                         { raGraph       = graph_colored
138                         , raSpillStats  = spillStats
139                         , raLifetimes   = fmLife
140                         , raSpilled     = code_spilled }
141                                 
142                 -- try again
143                 regAlloc_spin (spinCount + 1) triv regsFree slotsFree' 
144                         ([stat] ++ maybeToList stat1 ++ debug_codeGraphs)
145                         code_relive
146
147  
148 -----
149 -- Simple maxconflicts isn't always good, because we
150 --      can naievely end up spilling vregs that only live for one or two instrs.
151 --      
152 {-
153 chooseSpill_maxConflicts
154         :: Color.Graph Reg RegClass Reg
155         -> Reg
156         
157 chooseSpill_maxConflicts graph
158  = let  node    = maximumBy 
159                         (\n1 n2 -> compare 
160                                 (sizeUniqSet $ Color.nodeConflicts n1) 
161                                 (sizeUniqSet $ Color.nodeConflicts n2))
162                 $ eltsUFM $ Color.graphMap graph
163                 
164    in   Color.nodeId node
165 -} 
166    
167 -----
168 chooseSpill_maxLife
169         :: UniqFM (Reg, Int)
170         -> Color.Graph Reg RegClass Reg
171         -> Reg
172
173 chooseSpill_maxLife life graph
174  = let  node    = maximumBy (\n1 n2 -> compare (getLife n1) (getLife n2))
175                 $ eltsUFM $ Color.graphMap graph
176
177         -- Orphan vregs die in the same instruction they are born in.
178         --      They will be in the graph, but not in the liveness map.
179         --      Their liveness is 0.
180         getLife n
181          = case lookupUFM life (Color.nodeId n) of
182                 Just (_, l)     -> l
183                 Nothing         -> 0
184
185    in   Color.nodeId node
186    
187
188 -- | Build a graph from the liveness and coalesce information in this code.
189
190 buildGraph 
191         :: [LiveCmmTop]
192         -> UniqSM (Color.Graph Reg RegClass Reg)
193         
194 buildGraph code
195  = do
196         -- Add the reg-reg conflicts to the graph
197         let conflictSets        = unionManyBags (map slurpConflicts code)
198         let graph_conflict      = foldrBag graphAddConflictSet Color.initGraph conflictSets
199
200
201         -- Add the coalescences edges to the graph.
202         let coalesce            = unionManyBags (map slurpJoinMovs code)
203         let graph_coalesce      = foldrBag graphAddCoalesce graph_conflict coalesce
204                         
205         return  $ graph_coalesce
206
207
208 -- | Add some conflict edges to the graph.
209 --      Conflicts between virtual and real regs are recorded as exclusions.
210 --
211 graphAddConflictSet 
212         :: UniqSet Reg
213         -> Color.Graph Reg RegClass Reg
214         -> Color.Graph Reg RegClass Reg
215         
216 graphAddConflictSet set graph
217  = let  reals           = filterUFM isRealReg set
218         virtuals        = filterUFM (not . isRealReg) set
219  
220         graph1  = Color.addConflicts virtuals regClass graph
221         graph2  = foldr (\(r1, r2) -> Color.addExclusion r1 regClass r2)
222                         graph1
223                         [ (a, b) 
224                                 | a <- uniqSetToList virtuals
225                                 , b <- uniqSetToList reals]
226
227    in   graph2
228         
229
230 -- | Add some coalesence edges to the graph
231 --      Coalesences between virtual and real regs are recorded as preferences.
232 --
233 graphAddCoalesce 
234         :: (Reg, Reg) 
235         -> Color.Graph Reg RegClass Reg
236         -> Color.Graph Reg RegClass Reg
237         
238 graphAddCoalesce (r1, r2) graph
239         | RealReg regno <- r1
240         = Color.addPreference (regWithClass r2) r1 graph
241         
242         | RealReg regno <- r2
243         = Color.addPreference (regWithClass r1) r2 graph
244         
245         | otherwise
246         = Color.addCoalesce (regWithClass r1) (regWithClass r2) graph
247
248         where   regWithClass r  = (r, regClass r)
249
250
251 -- | Patch registers in code using the reg -> reg mapping in this graph.
252 patchRegsFromGraph 
253         :: Color.Graph Reg RegClass Reg
254         -> LiveCmmTop -> LiveCmmTop
255
256 patchRegsFromGraph graph code
257  = let
258         -- a function to lookup the hardreg for a virtual reg from the graph.
259         patchF reg
260                 -- leave real regs alone.
261                 | isRealReg reg
262                 = reg
263
264                 -- this virtual has a regular node in the graph.
265                 | Just node     <- Color.lookupNode graph reg
266                 = case Color.nodeColor node of
267                         Just color      -> color
268                         Nothing         -> reg
269                         
270                 -- no node in the graph for this virtual, bad news.
271                 | otherwise
272                 = pprPanic "patchRegsFromGraph: register mapping failed." 
273                         (  text "There is no node in the graph for register " <> ppr reg
274                         $$ ppr code
275                         $$ Color.dotGraph (\x -> text "white") trivColorable graph)
276         
277    in   patchEraseLive patchF code
278    
279
280 plusUFMs_C  :: (elt -> elt -> elt) -> [UniqFM elt] -> UniqFM elt
281 plusUFMs_C f maps
282         = foldl (plusUFM_C f) emptyUFM maps
283