module Distribution.Compat.Graph (
Graph,
IsNode(..),
null,
size,
member,
lookup,
empty,
insert,
deleteKey,
deleteLookup,
unionLeft,
unionRight,
stronglyConnComp,
SCC(..),
cycles,
broken,
neighbors,
revNeighbors,
closure,
revClosure,
topSort,
revTopSort,
toMap,
fromDistinctList,
toList,
keys,
keysSet,
toGraph,
Node(..),
nodeValue,
) where
#ifdef MIN_VERSION_containers
#if MIN_VERSION_containers(0,5,0)
#define HAVE_containers_050
#endif
#endif
import Prelude ()
import qualified Distribution.Compat.Prelude as Prelude
import Distribution.Compat.Prelude hiding (lookup, null, empty)
import Data.Graph (SCC(..))
import qualified Data.Graph as G
#ifdef HAVE_containers_050
import qualified Data.Map.Strict as Map
#else
import qualified Data.Map as Map
#endif
import qualified Data.Set as Set
import qualified Data.Array as Array
import Data.Array ((!))
import qualified Data.Tree as Tree
import Data.Either (partitionEithers)
import qualified Data.Foldable as Foldable
data Graph a
= Graph {
graphMap :: !(Map (Key a) a),
graphForward :: G.Graph,
graphAdjoint :: G.Graph,
graphVertexToNode :: G.Vertex -> a,
graphKeyToVertex :: Key a -> Maybe G.Vertex,
graphBroken :: [(a, [Key a])]
}
deriving (Typeable)
instance Show a => Show (Graph a) where
show = show . toList
instance (IsNode a, Read a, Show (Key a)) => Read (Graph a) where
readsPrec d s = map (\(a,r) -> (fromDistinctList a, r)) (readsPrec d s)
instance (IsNode a, Binary a, Show (Key a)) => Binary (Graph a) where
put x = put (toList x)
get = fmap fromDistinctList get
instance (Eq (Key a), Eq a) => Eq (Graph a) where
g1 == g2 = graphMap g1 == graphMap g2
instance Foldable.Foldable Graph where
fold = Foldable.fold . graphMap
foldr f z = Foldable.foldr f z . graphMap
foldl f z = Foldable.foldl f z . graphMap
foldMap f = Foldable.foldMap f . graphMap
#ifdef MIN_VERSION_base
#if MIN_VERSION_base(4,6,0)
foldl' f z = Foldable.foldl' f z . graphMap
foldr' f z = Foldable.foldr' f z . graphMap
#endif
#if MIN_VERSION_base(4,8,0)
length = Foldable.length . graphMap
null = Foldable.null . graphMap
toList = Foldable.toList . graphMap
elem x = Foldable.elem x . graphMap
maximum = Foldable.maximum . graphMap
minimum = Foldable.minimum . graphMap
sum = Foldable.sum . graphMap
product = Foldable.product . graphMap
#endif
#endif
instance (NFData a, NFData (Key a)) => NFData (Graph a) where
rnf Graph {
graphMap = m,
graphForward = gf,
graphAdjoint = ga,
graphVertexToNode = vtn,
graphKeyToVertex = ktv,
graphBroken = b
} = gf `seq` ga `seq` vtn `seq` ktv `seq` b `seq` rnf m
class Ord (Key a) => IsNode a where
type Key a :: *
nodeKey :: a -> Key a
nodeNeighbors :: a -> [Key a]
instance (IsNode a, IsNode b, Key a ~ Key b) => IsNode (Either a b) where
type Key (Either a b) = Key a
nodeKey (Left x) = nodeKey x
nodeKey (Right x) = nodeKey x
nodeNeighbors (Left x) = nodeNeighbors x
nodeNeighbors (Right x) = nodeNeighbors x
data Node k a = N a k [k]
deriving (Show, Eq)
nodeValue :: Node k a -> a
nodeValue (N a _ _) = a
instance Functor (Node k) where
fmap f (N a k ks) = N (f a) k ks
instance Ord k => IsNode (Node k a) where
type Key (Node k a) = k
nodeKey (N _ k _) = k
nodeNeighbors (N _ _ ks) = ks
null :: Graph a -> Bool
null = Map.null . toMap
size :: Graph a -> Int
size = Map.size . toMap
member :: IsNode a => Key a -> Graph a -> Bool
member k g = Map.member k (toMap g)
lookup :: IsNode a => Key a -> Graph a -> Maybe a
lookup k g = Map.lookup k (toMap g)
empty :: IsNode a => Graph a
empty = fromMap Map.empty
insert :: IsNode a => a -> Graph a -> Graph a
insert !n g = fromMap (Map.insert (nodeKey n) n (toMap g))
deleteKey :: IsNode a => Key a -> Graph a -> Graph a
deleteKey k g = fromMap (Map.delete k (toMap g))
deleteLookup :: IsNode a => Key a -> Graph a -> (Maybe a, Graph a)
deleteLookup k g =
let (r, m') = Map.updateLookupWithKey (\_ _ -> Nothing) k (toMap g)
in (r, fromMap m')
unionRight :: IsNode a => Graph a -> Graph a -> Graph a
unionRight g g' = fromMap (Map.union (toMap g') (toMap g))
unionLeft :: IsNode a => Graph a -> Graph a -> Graph a
unionLeft = flip unionRight
stronglyConnComp :: Graph a -> [SCC a]
stronglyConnComp g = map decode forest
where
forest = G.scc (graphForward g)
decode (Tree.Node v [])
| mentions_itself v = CyclicSCC [graphVertexToNode g v]
| otherwise = AcyclicSCC (graphVertexToNode g v)
decode other = CyclicSCC (dec other [])
where dec (Tree.Node v ts) vs
= graphVertexToNode g v : foldr dec vs ts
mentions_itself v = v `elem` (graphForward g ! v)
cycles :: Graph a -> [[a]]
cycles g = [ vs | CyclicSCC vs <- stronglyConnComp g ]
broken :: Graph a -> [(a, [Key a])]
broken g = graphBroken g
neighbors :: Graph a -> Key a -> Maybe [a]
neighbors g k = do
v <- graphKeyToVertex g k
return (map (graphVertexToNode g) (graphForward g ! v))
revNeighbors :: Graph a -> Key a -> Maybe [a]
revNeighbors g k = do
v <- graphKeyToVertex g k
return (map (graphVertexToNode g) (graphAdjoint g ! v))
closure :: Graph a -> [Key a] -> Maybe [a]
closure g ks = do
vs <- traverse (graphKeyToVertex g) ks
return (decodeVertexForest g (G.dfs (graphForward g) vs))
revClosure :: Graph a -> [Key a] -> Maybe [a]
revClosure g ks = do
vs <- traverse (graphKeyToVertex g) ks
return (decodeVertexForest g (G.dfs (graphAdjoint g) vs))
flattenForest :: Tree.Forest a -> [a]
flattenForest = concatMap Tree.flatten
decodeVertexForest :: Graph a -> Tree.Forest G.Vertex -> [a]
decodeVertexForest g = map (graphVertexToNode g) . flattenForest
topSort :: Graph a -> [a]
topSort g = map (graphVertexToNode g) $ G.topSort (graphForward g)
revTopSort :: Graph a -> [a]
revTopSort g = map (graphVertexToNode g) $ G.topSort (graphAdjoint g)
fromMap :: IsNode a => Map (Key a) a -> Graph a
fromMap m
= Graph { graphMap = m
, graphForward = g
, graphAdjoint = G.transposeG g
, graphVertexToNode = vertex_to_node
, graphKeyToVertex = key_to_vertex
, graphBroken = broke
}
where
try_key_to_vertex k = maybe (Left k) Right (key_to_vertex k)
(brokenEdges, edges)
= unzip
$ [ partitionEithers (map try_key_to_vertex (nodeNeighbors n))
| n <- ns ]
broke = filter (not . Prelude.null . snd) (zip ns brokenEdges)
g = Array.listArray bounds edges
ns = Map.elems m
vertices = zip (map nodeKey ns) [0..]
vertex_map = Map.fromAscList vertices
key_to_vertex k = Map.lookup k vertex_map
vertex_to_node vertex = nodeTable ! vertex
nodeTable = Array.listArray bounds ns
bounds = (0, Map.size m 1)
fromDistinctList :: (IsNode a, Show (Key a)) => [a] -> Graph a
fromDistinctList = fromMap
. Map.fromListWith (\_ -> duplicateError)
. map (\n -> n `seq` (nodeKey n, n))
where
duplicateError n = error $ "Graph.fromDistinctList: duplicate key: "
++ show (nodeKey n)
toList :: Graph a -> [a]
toList g = Map.elems (toMap g)
keys :: Graph a -> [Key a]
keys g = Map.keys (toMap g)
keysSet :: Graph a -> Set.Set (Key a)
keysSet g = Map.keysSet (toMap g)
toMap :: Graph a -> Map (Key a) a
toMap = graphMap
toGraph :: Graph a -> (G.Graph, G.Vertex -> a, Key a -> Maybe G.Vertex)
toGraph g = (graphForward g, graphVertexToNode g, graphKeyToVertex g)