Add iterative coalescing to graph coloring allocator
[ghc-hetmet.git] / compiler / nativeGen / GraphColor.hs
1
2 -- | Graph Coloring.
3 --      This is a generic graph coloring library, abstracted over the type of
4 --      the node keys, nodes and colors.
5 --
6 {-# OPTIONS -fno-warn-missing-signatures #-}
7
8 module GraphColor ( 
9         module GraphBase,
10         module GraphOps,
11         module GraphPpr,
12         colorGraph
13 )
14
15 where
16
17 import GraphBase
18 import GraphOps
19 import GraphPpr
20
21 import Unique
22 import UniqFM
23 import UniqSet
24 import Outputable       
25
26 import Data.Maybe
27 import Data.List
28         
29
30 -- | Try to color a graph with this set of colors.
31 --      Uses Chaitin's algorithm to color the graph.
32 --      The graph is scanned for nodes which are deamed 'trivially colorable'. These nodes
33 --      are pushed onto a stack and removed from the graph.
34 --      Once this process is complete the graph can be colored by removing nodes from
35 --      the stack (ie in reverse order) and assigning them colors different to their neighbors.
36 --
37 colorGraph
38         :: ( Uniquable  k, Uniquable cls,  Uniquable  color
39            , Eq color, Eq cls, Ord k
40            , Outputable k, Outputable cls, Outputable color)
41         => Bool                         -- ^ whether to do iterative coalescing
42         -> UniqFM (UniqSet color)       -- ^ map of (node class -> set of colors available for this class).
43         -> Triv   k cls color           -- ^ fn to decide whether a node is trivially colorable.
44         -> (Graph k cls color -> k)     -- ^ fn to choose a node to potentially leave uncolored if nothing is trivially colorable.
45         -> Graph  k cls color           -- ^ the graph to color.
46
47         -> ( Graph k cls color          -- the colored graph.
48            , UniqSet k                  -- the set of nodes that we couldn't find a color for.
49            , UniqFM  k )                -- map of regs (r1 -> r2) that were coaleced
50                                         --       r1 should be replaced by r2 in the source
51
52 colorGraph iterative colors triv spill graph0
53  = let
54         -- if we're not doing iterative coalescing, then just do a single coalescing
55         --      pass at the front. This won't be as good but should still eat up a
56         --      lot of the reg-reg moves.
57         (graph_coalesced, kksCoalesce1)
58                 = if not iterative
59                         then coalesceGraph False triv graph0
60                         else (graph0, [])
61
62         -- run the scanner to slurp out all the trivially colorable nodes
63         --      (and do coalescing if iterative coalescing is enabled)
64         (ksTriv, ksProblems, kksCoalesce2)
65                 = colorScan iterative triv spill graph_coalesced
66
67         -- If iterative coalescing is enabled, the scanner will coalesce the graph as does its business.
68         --      We need to apply all the coalescences found by the scanner to the original
69         --      graph before doing assignColors.
70         (graph_scan_coalesced, _)
71                 = mapAccumL (coalesceNodes False triv) graph_coalesced kksCoalesce2
72  
73         -- color the trivially colorable nodes
74         --      during scanning, keys of triv nodes were added to the front of the list as they were found
75         --      this colors them in the reverse order, as required by the algorithm.
76         (graph_triv, ksNoTriv)
77                 = assignColors colors graph_scan_coalesced ksTriv
78
79         -- try and color the problem nodes
80         --      problem nodes are the ones that were left uncolored because they weren't triv.
81         --      theres a change we can color them here anyway.
82         (graph_prob, ksNoColor)
83                 = assignColors colors graph_triv ksProblems
84
85         -- if the trivially colorable nodes didn't color then something is probably wrong
86         --      with the provided triv function.
87         --
88    in   if not $ null ksNoTriv
89          then   pprPanic "colorGraph: trivially colorable nodes didn't color!" empty
90 {-                      (  empty
91                         $$ text "ksTriv    = " <> ppr ksTriv
92                         $$ text "ksNoTriv  = " <> ppr ksNoTriv
93                         $$ empty
94                         $$ dotGraph (\x -> text "white") triv graph1) -}
95
96          else   ( graph_prob
97                 , mkUniqSet ksNoColor   -- the nodes that didn't color (spills)
98                 , if iterative
99                         then (listToUFM kksCoalesce2)
100                         else (listToUFM kksCoalesce1))
101         
102
103 -- | Scan through the conflict graph separating out trivially colorable and
104 --      potentially uncolorable (problem) nodes.
105 --
106 --      Checking whether a node is trivially colorable or not is a resonably expensive operation,
107 --      so after a triv node is found and removed from the graph it's no good to return to the 'start'
108 --      of the graph and recheck a bunch of nodes that will probably still be non-trivially colorable.
109 --
110 --      To ward against this, during each pass through the graph we collect up a list of triv nodes
111 --      that were found, and only remove them once we've finished the pass. The more nodes we can delete
112 --      at once the more likely it is that nodes we've already checked will become trivially colorable
113 --      for the next pass.
114 --
115 --      TODO:   add work lists to finding triv nodes is easier.
116 --              If we've just scanned the graph, and removed triv nodes, then the only
117 --              nodes that we need to rescan are the ones we've removed edges from.
118
119 colorScan
120         :: ( Uniquable k, Uniquable cls, Uniquable color
121            , Ord k,       Eq cls
122            , Outputable k, Outputable color)
123         => Bool                         -- ^ whether to do iterative coalescing
124         -> Triv k cls color             -- ^ fn to decide whether a node is trivially colorable
125         -> (Graph k cls color -> k)     -- ^ fn to choose a node to potentially leave uncolored if nothing is trivially colorable.
126         -> Graph k cls color            -- ^ the graph to scan
127
128         -> ([k], [k], [(k, k)])         --  triv colorable nodes, problem nodes, pairs of nodes to coalesce
129
130 colorScan iterative triv spill graph
131         = colorScan_spin iterative triv spill graph [] [] []
132
133 colorScan_spin iterative triv spill graph
134         ksTriv ksSpill kksCoalesce
135
136         -- if the graph is empty then we're done
137         | isNullUFM $ graphMap graph
138         = (ksTriv, ksSpill, kksCoalesce)
139
140         -- Simplify:
141         --      Look for trivially colorable nodes.
142         --      If we can find some then remove them from the graph and go back for more.
143         --
144         | nsTrivFound@(_:_)
145                 <-  scanGraph   (\node -> triv  (nodeClass node) (nodeConflicts node) (nodeExclusions node)
146
147                                   -- for iterative coalescing we only want non-move related
148                                   --    nodes here
149                                   && (not iterative || isEmptyUniqSet (nodeCoalesce node)))
150                         $ graph
151
152         , ksTrivFound   <- map nodeId nsTrivFound
153         , graph3        <- foldr delNode graph ksTrivFound
154         = colorScan_spin iterative triv spill graph3
155                 (ksTrivFound ++ ksTriv)
156                 ksSpill
157                 kksCoalesce
158
159         -- Coalesce:
160         --      If we're doing iterative coalescing and no triv nodes are avaliable
161         --      then it's type for a coalescing pass.
162         | iterative
163         = case coalesceGraph False triv graph of
164
165                 -- we were able to coalesce something
166                 --      go back and see if this frees up more nodes to be trivially colorable.
167                 (graph2, kksCoalesceFound @(_:_))
168                  -> colorScan_spin iterative triv spill graph2
169                         ksTriv ksSpill (kksCoalesceFound ++ kksCoalesce)
170
171                 -- Freeze:
172                 -- nothing could be coalesced (or was triv),
173                 --      time to choose a node to freeze and give up on ever coalescing it.
174                 (graph2, [])
175                  -> case freezeOneInGraph graph2 of
176
177                         -- we were able to freeze something
178                         --      hopefully this will free up something for Simplify
179                         (graph3, True)
180                          -> colorScan_spin iterative triv spill graph3
181                                 ksTriv ksSpill kksCoalesce
182
183                         -- we couldn't find something to freeze either
184                         --      time for a spill
185                         (graph3, False)
186                          -> colorScan_spill iterative triv spill graph3
187                                 ksTriv ksSpill kksCoalesce
188
189         -- spill time
190         | otherwise
191         = colorScan_spill iterative triv spill graph
192                 ksTriv ksSpill kksCoalesce
193
194
195 -- Select:
196 -- we couldn't find any triv nodes or things to freeze or coalesce,
197 --      and the graph isn't empty yet.. We'll have to choose a spill
198 --      candidate and leave it uncolored.
199 --
200 colorScan_spill iterative triv spill graph
201         ksTriv ksSpill kksCoalesce
202
203  = let  kSpill  = spill graph
204         graph'  = delNode kSpill graph
205    in   colorScan_spin iterative triv spill graph'
206                 ksTriv (kSpill : ksSpill) kksCoalesce
207         
208
209 -- | Try to assign a color to all these nodes.
210
211 assignColors 
212         :: ( Uniquable k, Uniquable cls, Uniquable color, Eq color )
213         => UniqFM (UniqSet color)       -- ^ map of (node class -> set of colors available for this class).
214         -> Graph k cls color            -- ^ the graph
215         -> [k]                          -- ^ nodes to assign a color to.
216         -> ( Graph k cls color          -- the colored graph
217            , [k])                       -- the nodes that didn't color.
218
219 assignColors colors graph ks 
220         = assignColors' colors graph [] ks
221
222  where  assignColors' _ graph prob []
223                 = (graph, prob)
224
225         assignColors' colors graph prob (k:ks)
226          = case assignColor colors k graph of
227
228                 -- couldn't color this node
229                 Nothing         -> assignColors' colors graph (k : prob) ks
230
231                 -- this node colored ok, so do the rest
232                 Just graph'     -> assignColors' colors graph' prob ks
233
234
235         assignColor colors u graph
236                 | Just c        <- selectColor colors graph u
237                 = Just (setColor u c graph)
238
239                 | otherwise
240                 = Nothing
241
242         
243         
244 -- | Select a color for a certain node
245 --      taking into account preferences, neighbors and exclusions.
246 --      returns Nothing if no color can be assigned to this node.
247 --
248 selectColor
249         :: ( Uniquable k, Uniquable cls, Uniquable color, Eq color)
250         => UniqFM (UniqSet color)       -- ^ map of (node class -> set of colors available for this class).
251         -> Graph k cls color            -- ^ the graph
252         -> k                            -- ^ key of the node to select a color for.
253         -> Maybe color
254         
255 selectColor colors graph u 
256  = let  -- lookup the node
257         Just node       = lookupNode graph u
258
259         -- lookup the available colors for the class of this node.
260         Just colors_avail
261                         = lookupUFM colors (nodeClass node)
262
263         -- find colors we can't use because they're already being used
264         --      by a node that conflicts with this one.
265         Just nsConflicts        
266                         = sequence
267                         $ map (lookupNode graph)
268                         $ uniqSetToList 
269                         $ nodeConflicts node
270                 
271         colors_conflict = mkUniqSet 
272                         $ catMaybes 
273                         $ map nodeColor nsConflicts
274         
275         -- the prefs of our neighbors
276         colors_neighbor_prefs
277                         = mkUniqSet
278                         $ concat $ map nodePreference nsConflicts
279
280         -- colors that are still valid for us
281         colors_ok_ex    = minusUniqSet colors_avail (nodeExclusions node)
282         colors_ok       = minusUniqSet colors_ok_ex colors_conflict
283                                 
284         -- the colors that we prefer, and are still ok
285         colors_ok_pref  = intersectUniqSets
286                                 (mkUniqSet $ nodePreference node) colors_ok
287
288         -- the colors that we could choose while being nice to our neighbors
289         colors_ok_nice  = minusUniqSet
290                                 colors_ok colors_neighbor_prefs
291
292         -- the best of all possible worlds..
293         colors_ok_pref_nice
294                         = intersectUniqSets
295                                 colors_ok_nice colors_ok_pref
296
297         -- make the decision
298         chooseColor
299
300                 -- everyone is happy, yay!
301                 | not $ isEmptyUniqSet colors_ok_pref_nice
302                 , c : _         <- filter (\x -> elementOfUniqSet x colors_ok_pref_nice)
303                                         (nodePreference node)
304                 = Just c
305
306                 -- we've got one of our preferences
307                 | not $ isEmptyUniqSet colors_ok_pref   
308                 , c : _         <- filter (\x -> elementOfUniqSet x colors_ok_pref)
309                                         (nodePreference node)
310                 = Just c
311                 
312                 -- it wasn't a preference, but it was still ok
313                 | not $ isEmptyUniqSet colors_ok
314                 , c : _         <- uniqSetToList colors_ok
315                 = Just c
316                 
317                 -- no colors were available for us this time.
318                 --      looks like we're going around the loop again..
319                 | otherwise
320                 = Nothing
321                 
322    in   chooseColor 
323
324
325