1 {-# OPTIONS -fno-warn-missing-signatures #-}
2 -- | Basic operations on graphs.
6 addNode, delNode, getNode, lookupNode, modNode,
9 addConflict, delConflict, addConflicts,
10 addCoalesce, delCoalesce,
11 addExclusion, addExclusions,
13 coalesceNodes, coalesceGraph,
14 freezeNode, freezeOneInGraph, freezeAllInGraph,
18 slurpNodeConflictCount
29 import Data.List hiding (union)
32 -- | Lookup a node from the graph.
36 -> k -> Maybe (Node k cls color)
39 = lookupUFM (graphMap graph) k
42 -- | Get a node from the graph, throwing an error if it's not there
46 -> k -> Node k cls color
49 = case lookupUFM (graphMap graph) k of
51 Nothing -> panic "ColorOps.getNode: not found"
54 -- | Add a node to the graph, linking up its edges
55 addNode :: Uniquable k
56 => k -> Node k cls color
57 -> Graph k cls color -> Graph k cls color
61 -- add back conflict edges from other nodes to this one
64 (adjustUFM (\n -> n { nodeConflicts = addOneToUniqSet (nodeConflicts n) k}))
68 -- add back coalesce edges from other nodes to this one
71 (adjustUFM (\n -> n { nodeCoalesce = addOneToUniqSet (nodeCoalesce n) k}))
76 { graphMap = addToUFM map_coalesce k node}
79 -- | Delete a node and all its edges from the graph.
80 delNode :: (Uniquable k, Outputable k)
81 => k -> Graph k cls color -> Maybe (Graph k cls color)
84 | Just node <- lookupNode graph k
85 = let -- delete conflict edges from other nodes to this one.
86 graph1 = foldl' (\g k1 -> let Just g' = delConflict k1 k g in g') graph
87 $ uniqSetToList (nodeConflicts node)
89 -- delete coalesce edge from other nodes to this one.
90 graph2 = foldl' (\g k1 -> let Just g' = delCoalesce k1 k g in g') graph1
91 $ uniqSetToList (nodeCoalesce node)
94 graph3 = graphMapModify (\fm -> delFromUFM fm k) graph2
102 -- | Modify a node in the graph.
103 -- returns Nothing if the node isn't present.
105 modNode :: Uniquable k
106 => (Node k cls color -> Node k cls color)
107 -> k -> Graph k cls color -> Maybe (Graph k cls color)
110 = case lookupNode graph k of
114 (\fm -> let Just node = lookupUFM fm k
116 in addToUFM fm k node')
122 -- | Get the size of the graph, O(n)
124 => Graph k cls color -> Int
127 = sizeUFM $ graphMap graph
130 -- | Union two graphs together.
132 => Graph k cls color -> Graph k cls color -> Graph k cls color
136 { graphMap = plusUFM (graphMap graph1) (graphMap graph2) }
139 -- | Add a conflict between nodes to the graph, creating the nodes required.
140 -- Conflicts are virtual regs which need to be colored differently.
143 => (k, cls) -> (k, cls)
144 -> Graph k cls color -> Graph k cls color
146 addConflict (u1, c1) (u2, c2)
147 = let addNeighbor u c u'
148 = adjustWithDefaultUFM
149 (\node -> node { nodeConflicts = addOneToUniqSet (nodeConflicts node) u' })
150 (newNode u c) { nodeConflicts = unitUniqSet u' }
154 ( addNeighbor u1 c1 u2
155 . addNeighbor u2 c2 u1)
158 -- | Delete a conflict edge. k1 -> k2
159 -- returns Nothing if the node isn't in the graph
163 -> Graph k cls color -> Maybe (Graph k cls color)
167 (\node -> node { nodeConflicts = delOneFromUniqSet (nodeConflicts node) k2 })
171 -- | Add some conflicts to the graph, creating nodes if required.
172 -- All the nodes in the set are taken to conflict with each other.
175 => UniqSet k -> (k -> cls)
176 -> Graph k cls color -> Graph k cls color
178 addConflicts conflicts getClass
180 -- just a single node, but no conflicts, create the node anyway.
181 | (u : []) <- uniqSetToList conflicts
183 $ adjustWithDefaultUFM
185 (newNode u (getClass u))
190 $ (\fm -> foldl' (\g u -> addConflictSet1 u getClass conflicts g) fm
191 $ uniqSetToList conflicts)
194 addConflictSet1 u getClass set
195 = case delOneFromUniqSet set u of
196 set' -> adjustWithDefaultUFM
197 (\node -> node { nodeConflicts = unionUniqSets set' (nodeConflicts node) } )
198 (newNode u (getClass u)) { nodeConflicts = set' }
202 -- | Add an exclusion to the graph, creating nodes if required.
203 -- These are extra colors that the node cannot use.
205 :: (Uniquable k, Uniquable color)
206 => k -> (k -> cls) -> color
207 -> Graph k cls color -> Graph k cls color
209 addExclusion u getClass color
211 $ adjustWithDefaultUFM
212 (\node -> node { nodeExclusions = addOneToUniqSet (nodeExclusions node) color })
213 (newNode u (getClass u)) { nodeExclusions = unitUniqSet color }
217 :: (Uniquable k, Uniquable color)
218 => k -> (k -> cls) -> [color]
219 -> Graph k cls color -> Graph k cls color
221 addExclusions u getClass colors graph
222 = foldr (addExclusion u getClass) graph colors
225 -- | Add a coalescence edge to the graph, creating nodes if requried.
226 -- It is considered adventageous to assign the same color to nodes in a coalesence.
229 => (k, cls) -> (k, cls)
230 -> Graph k cls color -> Graph k cls color
232 addCoalesce (u1, c1) (u2, c2)
233 = let addCoalesce u c u'
234 = adjustWithDefaultUFM
235 (\node -> node { nodeCoalesce = addOneToUniqSet (nodeCoalesce node) u' })
236 (newNode u c) { nodeCoalesce = unitUniqSet u' }
240 ( addCoalesce u1 c1 u2
241 . addCoalesce u2 c2 u1)
244 -- | Delete a coalescence edge (k1 -> k2) from the graph.
248 -> Graph k cls color -> Maybe (Graph k cls color)
251 = modNode (\node -> node { nodeCoalesce = delOneFromUniqSet (nodeCoalesce node) k2 })
255 -- | Add a color preference to the graph, creating nodes if required.
256 -- The most recently added preference is the most prefered.
257 -- The algorithm tries to assign a node it's prefered color if possible.
262 -> Graph k cls color -> Graph k cls color
264 addPreference (u, c) color
266 $ adjustWithDefaultUFM
267 (\node -> node { nodePreference = color : (nodePreference node) })
268 (newNode u c) { nodePreference = [color] }
272 -- | Do agressive coalescing on this graph.
273 -- returns the new graph and the list of pairs of nodes that got coaleced together.
274 -- for each pair, the resulting node will have the least key and be second in the pair.
277 :: (Uniquable k, Ord k, Eq cls, Outputable k)
278 => Bool -- ^ If True, coalesce nodes even if this might make the graph
279 -- less colorable (aggressive coalescing)
282 -> ( Graph k cls color
283 , [(k, k)]) -- pairs of nodes that were coalesced, in the order that the
284 -- coalescing was applied.
286 coalesceGraph aggressive triv graph
287 = coalesceGraph' aggressive triv graph []
289 coalesceGraph' aggressive triv graph kkPairsAcc
291 -- find all the nodes that have coalescence edges
292 cNodes = filter (\node -> not $ isEmptyUniqSet (nodeCoalesce node))
293 $ eltsUFM $ graphMap graph
295 -- build a list of pairs of keys for node's we'll try and coalesce
296 -- every pair of nodes will appear twice in this list
297 -- ie [(k1, k2), (k2, k1) ... ]
298 -- This is ok, GrapOps.coalesceNodes handles this and it's convenient for
299 -- build a list of what nodes get coalesced together for later on.
301 cList = [ (nodeId node1, k2)
303 , k2 <- uniqSetToList $ nodeCoalesce node1 ]
305 -- do the coalescing, returning the new graph and a list of pairs of keys
306 -- that got coalesced together.
308 = mapAccumL (coalesceNodes aggressive triv) graph cList
310 -- keep running until there are no more coalesces can be found
311 in case catMaybes mPairs of
312 [] -> (graph', reverse kkPairsAcc)
313 pairs -> coalesceGraph' aggressive triv graph' (reverse pairs ++ kkPairsAcc)
316 -- | Coalesce this pair of nodes unconditionally \/ agressively.
317 -- The resulting node is the one with the least key.
319 -- returns: Just the pair of keys if the nodes were coalesced
320 -- the second element of the pair being the least one
322 -- Nothing if either of the nodes weren't in the graph
325 :: (Uniquable k, Ord k, Eq cls, Outputable k)
326 => Bool -- ^ If True, coalesce nodes even if this might make the graph
327 -- less colorable (aggressive coalescing)
330 -> (k, k) -- ^ keys of the nodes to be coalesced
331 -> (Graph k cls color, Maybe (k, k))
333 coalesceNodes aggressive triv graph (k1, k2)
334 | (kMin, kMax) <- if k1 < k2
338 -- the nodes being coalesced must be in the graph
339 , Just nMin <- lookupNode graph kMin
340 , Just nMax <- lookupNode graph kMax
342 -- can't coalesce conflicting modes
343 , not $ elementOfUniqSet kMin (nodeConflicts nMax)
344 , not $ elementOfUniqSet kMax (nodeConflicts nMin)
346 -- can't coalesce the same node
347 , nodeId nMin /= nodeId nMax
349 = coalesceNodes_merge aggressive triv graph kMin kMax nMin nMax
351 -- don't do the coalescing after all
355 coalesceNodes_merge aggressive triv graph kMin kMax nMin nMax
358 | nodeClass nMin /= nodeClass nMax
359 = error "GraphOps.coalesceNodes: can't coalesce nodes of different classes."
361 | not (isNothing (nodeColor nMin) && isNothing (nodeColor nMax))
362 = error "GraphOps.coalesceNodes: can't coalesce colored nodes."
367 -- the new node gets all the edges from its two components
370 , nodeClass = nodeClass nMin
371 , nodeColor = Nothing
373 -- nodes don't conflict with themselves..
375 = (unionUniqSets (nodeConflicts nMin) (nodeConflicts nMax))
376 `delOneFromUniqSet` kMin
377 `delOneFromUniqSet` kMax
379 , nodeExclusions = unionUniqSets (nodeExclusions nMin) (nodeExclusions nMax)
380 , nodePreference = nodePreference nMin ++ nodePreference nMax
382 -- nodes don't coalesce with themselves..
384 = (unionUniqSets (nodeCoalesce nMin) (nodeCoalesce nMax))
385 `delOneFromUniqSet` kMin
386 `delOneFromUniqSet` kMax
389 in coalesceNodes_check aggressive triv graph kMin kMax node
391 coalesceNodes_check aggressive triv graph kMin kMax node
393 -- Unless we're coalescing aggressively, if the result node is not trivially
394 -- colorable then don't do the coalescing.
396 , not $ triv (nodeClass node) (nodeConflicts node) (nodeExclusions node)
400 = let -- delete the old nodes from the graph and add the new one
401 Just graph1 = delNode kMax graph
402 Just graph2 = delNode kMin graph1
403 graph3 = addNode kMin node graph2
405 in (graph3, Just (kMax, kMin))
409 -- This is for the iterative coalescer.
410 -- By freezing a node we give up on ever coalescing it.
411 -- Move all its coalesce edges into the frozen set - and update
412 -- back edges from other nodes.
416 => k -- ^ key of the node to freeze
417 -> Graph k cls color -- ^ the graph
418 -> Graph k cls color -- ^ graph with that node frozen
424 -- freeze all the edges in the node to be frozen
425 Just node = lookupUFM fm k
427 { nodeCoalesce = emptyUniqSet }
429 fm1 = addToUFM fm k node'
431 -- update back edges pointing to this node
433 = if elementOfUniqSet k (nodeCoalesce node)
435 { nodeCoalesce = delOneFromUniqSet (nodeCoalesce node) k }
436 else panic "GraphOps.freezeNode: edge to freeze wasn't in the coalesce set"
438 fm2 = foldUniqSet (adjustUFM (freezeEdge k)) fm1
444 -- | Freeze one node in the graph
445 -- This if for the iterative coalescer.
446 -- Look for a move related node of low degree and freeze it.
448 -- We probably don't need to scan the whole graph looking for the node of absolute
449 -- lowest degree. Just sample the first few and choose the one with the lowest
450 -- degree out of those. Also, we don't make any distinction between conflicts of different
451 -- classes.. this is just a heuristic, after all.
453 -- IDEA: freezing a node might free it up for Simplify.. would be good to check for triv
454 -- right here, and add it to a worklist if known triv\/non-move nodes.
457 :: (Uniquable k, Outputable k)
459 -> ( Graph k cls color -- the new graph
460 , Bool ) -- whether we found a node to freeze
462 freezeOneInGraph graph
463 = let compareNodeDegree n1 n2
464 = compare (sizeUniqSet $ nodeConflicts n1) (sizeUniqSet $ nodeConflicts n2)
467 = sortBy compareNodeDegree
468 $ take 5 -- 5 isn't special, it's just a small number.
469 $ scanGraph (\node -> not $ isEmptyUniqSet (nodeCoalesce node)) graph
471 in case candidates of
473 -- there wasn't anything available to freeze
476 -- we found something to freeze
478 -> ( freezeNode (nodeId n) graph
482 -- | Freeze all the nodes in the graph
483 -- for debugging the iterative allocator.
486 :: (Uniquable k, Outputable k)
490 freezeAllInGraph graph
491 = foldr freezeNode graph
493 $ eltsUFM $ graphMap graph
496 -- | Find all the nodes in the graph that meet some criteria
500 => (Node k cls color -> Bool)
502 -> [Node k cls color]
504 scanGraph match graph
505 = filter match $ eltsUFM $ graphMap graph
508 -- | validate the internal structure of a graph
509 -- all its edges should point to valid nodes
510 -- If they don't then throw an error
513 :: (Uniquable k, Outputable k, Eq color)
514 => SDoc -- ^ extra debugging info to display on error
515 -> Bool -- ^ whether this graph is supposed to be colored.
516 -> Graph k cls color -- ^ graph to validate
517 -> Graph k cls color -- ^ validated graph
519 validateGraph doc isColored graph
521 -- Check that all edges point to valid nodes.
522 | edges <- unionManyUniqSets
523 ( (map nodeConflicts $ eltsUFM $ graphMap graph)
524 ++ (map nodeCoalesce $ eltsUFM $ graphMap graph))
526 , nodes <- mkUniqSet $ map nodeId $ eltsUFM $ graphMap graph
527 , badEdges <- minusUniqSet edges nodes
528 , not $ isEmptyUniqSet badEdges
529 = pprPanic "GraphOps.validateGraph"
530 ( text "Graph has edges that point to non-existant nodes"
531 $$ text " bad edges: " <> vcat (map ppr $ uniqSetToList badEdges)
534 -- Check that no conflicting nodes have the same color
535 | badNodes <- filter (not . (checkNode graph))
536 $ eltsUFM $ graphMap graph
537 , not $ null badNodes
538 = pprPanic "GraphOps.validateGraph"
539 ( text "Node has same color as one of it's conflicts"
540 $$ text " bad nodes: " <> hcat (map (ppr . nodeId) badNodes)
543 -- If this is supposed to be a colored graph,
544 -- check that all nodes have a color.
546 , badNodes <- filter (\n -> isNothing $ nodeColor n)
547 $ eltsUFM $ graphMap graph
548 , not $ null badNodes
549 = pprPanic "GraphOps.validateGraph"
550 ( text "Supposably colored graph has uncolored nodes."
551 $$ text " uncolored nodes: " <> hcat (map (ppr . nodeId) badNodes)
560 -- | If this node is colored, check that all the nodes which
561 -- conflict with it have different colors.
563 :: (Uniquable k, Eq color)
566 -> Bool -- ^ True if this node is ok
569 | Just color <- nodeColor node
570 , Just neighbors <- sequence $ map (lookupNode graph)
571 $ uniqSetToList $ nodeConflicts node
573 , neighbourColors <- catMaybes $ map nodeColor neighbors
574 , elem color neighbourColors
582 -- | Slurp out a map of how many nodes had a certain number of conflict neighbours
584 slurpNodeConflictCount
587 -> UniqFM (Int, Int) -- ^ (conflict neighbours, num nodes with that many conflicts)
589 slurpNodeConflictCount graph
591 (\(c1, n1) (_, n2) -> (c1, n1 + n2))
594 -> let count = sizeUniqSet $ nodeConflicts node
595 in (count, (count, 1)))
600 -- | Set the color of a certain node
604 -> Graph k cls color -> Graph k cls color
609 (\n -> n { nodeColor = Just color })
613 {-# INLINE adjustWithDefaultUFM #-}
616 => (a -> a) -> a -> k
617 -> UniqFM a -> UniqFM a
619 adjustWithDefaultUFM f def k map
625 {-# INLINE adjustUFM #-}
629 -> k -> UniqFM a -> UniqFM a
632 = case lookupUFM map k of
634 Just a -> addToUFM map k (f a)