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