/compiler/Eta/Utils/UnVarGraph.hs

https://github.com/typelead/eta · Haskell · 136 lines · 76 code · 26 blank · 34 comment · 7 complexity · 2a222454d756bf707b72714774135a81 MD5 · raw file

  1. {-
  2. Copyright (c) 2014 Joachim Breitner
  3. A data structure for undirected graphs of variables
  4. (or in plain terms: Sets of unordered pairs of numbers)
  5. This is very specifically tailored for the use in CallArity. In particular it
  6. stores the graph as a union of complete and complete bipartite graph, which
  7. would be very expensive to store as sets of edges or as adjanceny lists.
  8. It does not normalize the graphs. This means that g `unionUnVarGraph` g is
  9. equal to g, but twice as expensive and large.
  10. -}
  11. module Eta.Utils.UnVarGraph
  12. ( UnVarSet
  13. , emptyUnVarSet, mkUnVarSet, varEnvDom, unionUnVarSet, unionUnVarSets
  14. , delUnVarSet
  15. , elemUnVarSet, isEmptyUnVarSet
  16. , UnVarGraph
  17. , emptyUnVarGraph
  18. , unionUnVarGraph, unionUnVarGraphs
  19. , completeGraph, completeBipartiteGraph
  20. , neighbors
  21. , delNode
  22. ) where
  23. import Eta.BasicTypes.Id
  24. import Eta.BasicTypes.VarEnv
  25. import Eta.Utils.UniqFM
  26. import Eta.Utils.Outputable
  27. import Data.List
  28. import Eta.Utils.Bag
  29. import Eta.BasicTypes.Unique
  30. import qualified Data.IntSet as S
  31. -- We need a type for sets of variables (UnVarSet).
  32. -- We do not use VarSet, because for that we need to have the actual variable
  33. -- at hand, and we do not have that when we turn the domain of a VarEnv into a UnVarSet.
  34. -- Therefore, use a IntSet directly (which is likely also a bit more efficient).
  35. -- Set of uniques, i.e. for adjancet nodes
  36. newtype UnVarSet = UnVarSet (S.IntSet)
  37. deriving Eq
  38. k :: Var -> Int
  39. k v = getKey (getUnique v)
  40. emptyUnVarSet :: UnVarSet
  41. emptyUnVarSet = UnVarSet S.empty
  42. elemUnVarSet :: Var -> UnVarSet -> Bool
  43. elemUnVarSet v (UnVarSet s) = k v `S.member` s
  44. isEmptyUnVarSet :: UnVarSet -> Bool
  45. isEmptyUnVarSet (UnVarSet s) = S.null s
  46. delUnVarSet :: UnVarSet -> Var -> UnVarSet
  47. delUnVarSet (UnVarSet s) v = UnVarSet $ k v `S.delete` s
  48. mkUnVarSet :: [Var] -> UnVarSet
  49. mkUnVarSet vs = UnVarSet $ S.fromList $ map k vs
  50. varEnvDom :: VarEnv a -> UnVarSet
  51. varEnvDom ae = UnVarSet $ ufmToSet_Directly ae
  52. unionUnVarSet :: UnVarSet -> UnVarSet -> UnVarSet
  53. unionUnVarSet (UnVarSet set1) (UnVarSet set2) = UnVarSet (set1 `S.union` set2)
  54. unionUnVarSets :: [UnVarSet] -> UnVarSet
  55. unionUnVarSets = foldr unionUnVarSet emptyUnVarSet
  56. instance Outputable UnVarSet where
  57. ppr (UnVarSet s) = braces $
  58. hcat $ punctuate comma [ ppr (getUnique i) | i <- S.toList s]
  59. -- The graph type. A list of complete bipartite graphs
  60. data Gen = CBPG UnVarSet UnVarSet -- complete bipartite
  61. | CG UnVarSet -- complete
  62. newtype UnVarGraph = UnVarGraph (Bag Gen)
  63. emptyUnVarGraph :: UnVarGraph
  64. emptyUnVarGraph = UnVarGraph emptyBag
  65. unionUnVarGraph :: UnVarGraph -> UnVarGraph -> UnVarGraph
  66. {-
  67. Premature optimisation, it seems.
  68. unionUnVarGraph (UnVarGraph [CBPG s1 s2]) (UnVarGraph [CG s3, CG s4])
  69. | s1 == s3 && s2 == s4
  70. = pprTrace "unionUnVarGraph fired" empty $
  71. completeGraph (s1 `unionUnVarSet` s2)
  72. unionUnVarGraph (UnVarGraph [CBPG s1 s2]) (UnVarGraph [CG s3, CG s4])
  73. | s2 == s3 && s1 == s4
  74. = pprTrace "unionUnVarGraph fired2" empty $
  75. completeGraph (s1 `unionUnVarSet` s2)
  76. -}
  77. unionUnVarGraph (UnVarGraph g1) (UnVarGraph g2)
  78. = -- pprTrace "unionUnVarGraph" (ppr (length g1, length g2)) $
  79. UnVarGraph (g1 `unionBags` g2)
  80. unionUnVarGraphs :: [UnVarGraph] -> UnVarGraph
  81. unionUnVarGraphs = foldl' unionUnVarGraph emptyUnVarGraph
  82. -- completeBipartiteGraph A B = { {a,b} | a A, b B }
  83. completeBipartiteGraph :: UnVarSet -> UnVarSet -> UnVarGraph
  84. completeBipartiteGraph s1 s2 = prune $ UnVarGraph $ unitBag $ CBPG s1 s2
  85. completeGraph :: UnVarSet -> UnVarGraph
  86. completeGraph s = prune $ UnVarGraph $ unitBag $ CG s
  87. neighbors :: UnVarGraph -> Var -> UnVarSet
  88. neighbors (UnVarGraph g) v = unionUnVarSets $ concatMap go $ bagToList g
  89. where go (CG s) = (if v `elemUnVarSet` s then [s] else [])
  90. go (CBPG s1 s2) = (if v `elemUnVarSet` s1 then [s2] else []) ++
  91. (if v `elemUnVarSet` s2 then [s1] else [])
  92. delNode :: UnVarGraph -> Var -> UnVarGraph
  93. delNode (UnVarGraph g) v = prune $ UnVarGraph $ mapBag go g
  94. where go (CG s) = CG (s `delUnVarSet` v)
  95. go (CBPG s1 s2) = CBPG (s1 `delUnVarSet` v) (s2 `delUnVarSet` v)
  96. prune :: UnVarGraph -> UnVarGraph
  97. prune (UnVarGraph g) = UnVarGraph $ filterBag go g
  98. where go (CG s) = not (isEmptyUnVarSet s)
  99. go (CBPG s1 s2) = not (isEmptyUnVarSet s1) && not (isEmptyUnVarSet s2)
  100. instance Outputable Gen where
  101. ppr (CG s) = ppr s <> char '²'
  102. ppr (CBPG s1 s2) = ppr s1 <+> char 'x' <+> ppr s2
  103. instance Outputable UnVarGraph where
  104. ppr (UnVarGraph g) = ppr g