| Copyright | (c) Edward Z. Yang 2016 | 
|---|---|
| License | BSD3 | 
| Maintainer | cabal-dev@haskell.org | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Distribution.Compat.Graph
Description
A data type representing directed graphs, backed by Data.Graph. It is strict in the node type.
This is an alternative interface to Data.Graph.  In this interface,
 nodes (identified by the IsNode type class) are associated with a
 key and record the keys of their neighbors.  This interface is more
 convenient than Graph, which requires vertices to be
 explicitly handled by integer indexes.
The current implementation has somewhat peculiar performance characteristics. The asymptotics of all map-like operations mirror their counterparts in Data.Map. However, to perform a graph operation, we first must build the Data.Graph representation, an operation that takes O(V + E log V). However, this operation can be amortized across all queries on that particular graph.
Some nodes may be broken, i.e., refer to neighbors which are not
 stored in the graph.  In our graph algorithms, we transparently
 ignore such edges; however, you can easily query for the broken
 vertices of a graph using broken (and should, e.g., to ensure that
 a closure of a graph is well-formed.)  It's possible to take a closed
 subset of a broken graph and get a well-formed graph.
Synopsis
- data Graph a
- class Ord (Key a) => IsNode a where- type Key a
- nodeKey :: a -> Key a
- nodeNeighbors :: a -> [Key a]
 
- null :: Graph a -> Bool
- size :: Graph a -> Int
- member :: IsNode a => Key a -> Graph a -> Bool
- lookup :: IsNode a => Key a -> Graph a -> Maybe a
- empty :: IsNode a => Graph a
- insert :: IsNode a => a -> Graph a -> Graph a
- deleteKey :: IsNode a => Key a -> Graph a -> Graph a
- deleteLookup :: IsNode a => Key a -> Graph a -> (Maybe a, Graph a)
- unionLeft :: IsNode a => Graph a -> Graph a -> Graph a
- unionRight :: IsNode a => Graph a -> Graph a -> Graph a
- stronglyConnComp :: Graph a -> [SCC a]
- data SCC vertex- = AcyclicSCC vertex
- | CyclicSCC [vertex]
 
- cycles :: Graph a -> [[a]]
- broken :: Graph a -> [(a, [Key a])]
- neighbors :: Graph a -> Key a -> Maybe [a]
- revNeighbors :: Graph a -> Key a -> Maybe [a]
- closure :: Graph a -> [Key a] -> Maybe [a]
- revClosure :: Graph a -> [Key a] -> Maybe [a]
- topSort :: Graph a -> [a]
- revTopSort :: Graph a -> [a]
- toMap :: Graph a -> Map (Key a) a
- fromDistinctList :: (IsNode a, Show (Key a)) => [a] -> Graph a
- toList :: Graph a -> [a]
- keys :: Graph a -> [Key a]
- keysSet :: Graph a -> Set (Key a)
- toGraph :: Graph a -> (Graph, Vertex -> a, Key a -> Maybe Vertex)
- data Node k a = N a k [k]
- nodeValue :: Node k a -> a
Graph type
A graph of nodes a.  The nodes are expected to have instance
 of class IsNode.
Instances
| Foldable Graph Source # | |
| Defined in Distribution.Compat.Graph Methods fold :: Monoid m => Graph m -> m # foldMap :: Monoid m => (a -> m) -> Graph a -> m # foldMap' :: Monoid m => (a -> m) -> Graph a -> m # foldr :: (a -> b -> b) -> b -> Graph a -> b # foldr' :: (a -> b -> b) -> b -> Graph a -> b # foldl :: (b -> a -> b) -> b -> Graph a -> b # foldl' :: (b -> a -> b) -> b -> Graph a -> b # foldr1 :: (a -> a -> a) -> Graph a -> a # foldl1 :: (a -> a -> a) -> Graph a -> a # elem :: Eq a => a -> Graph a -> Bool # maximum :: Ord a => Graph a -> a # minimum :: Ord a => Graph a -> a # | |
| (Eq (Key a), Eq a) => Eq (Graph a) Source # | |
| (IsNode a, Read a, Show (Key a)) => Read (Graph a) Source # | |
| Show a => Show (Graph a) Source # | |
| (IsNode a, Binary a, Show (Key a)) => Binary (Graph a) Source # | |
| (NFData a, NFData (Key a)) => NFData (Graph a) Source # | |
| Defined in Distribution.Compat.Graph | |
| Structured a => Structured (Graph a) Source # | |
| Defined in Distribution.Compat.Graph | |
class Ord (Key a) => IsNode a where Source #
The IsNode class is used for datatypes which represent directed
 graph nodes.  A node of type a is associated with some unique key of
 type Key anodeKey)
 and the keys of its neighbors (nodeNeighbors).
Instances
| IsNode InstalledPackageInfo Source # | |
| Defined in Distribution.Types.InstalledPackageInfo Associated Types type Key InstalledPackageInfo Source # Methods nodeKey :: InstalledPackageInfo -> Key InstalledPackageInfo Source # nodeNeighbors :: InstalledPackageInfo -> [Key InstalledPackageInfo] Source # | |
| IsNode ComponentLocalBuildInfo Source # | |
| Defined in Distribution.Types.ComponentLocalBuildInfo Associated Types | |
| IsNode TargetInfo Source # | |
| Defined in Distribution.Types.TargetInfo Associated Types type Key TargetInfo Source # Methods nodeKey :: TargetInfo -> Key TargetInfo Source # nodeNeighbors :: TargetInfo -> [Key TargetInfo] Source # | |
| (IsNode a, IsNode b, Key a ~ Key b) => IsNode (Either a b) Source # | |
| Ord k => IsNode (Node k a) Source # | |
Query
lookup :: IsNode a => Key a -> Graph a -> Maybe a Source #
O(log V). Lookup the node at a key in the graph.
Construction
deleteKey :: IsNode a => Key a -> Graph a -> Graph a Source #
O(log V). Delete the node at a key from the graph.
deleteLookup :: IsNode a => Key a -> Graph a -> (Maybe a, Graph a) Source #
O(log V). Lookup and delete. This function returns the deleted value if it existed.
Combine
unionLeft :: IsNode a => Graph a -> Graph a -> Graph a Source #
O(V + V'). Left-biased union, preferring entries from the first map when conflicts occur.
Graph algorithms
stronglyConnComp :: Graph a -> [SCC a] Source #
Ω(V + E). Compute the strongly connected components of a graph. Requires amortized construction of graph.
Strongly connected component.
Constructors
| AcyclicSCC vertex | A single vertex that is not in any cycle. | 
| CyclicSCC [vertex] | A maximal set of mutually reachable vertices. | 
Instances
| Functor SCC | Since: containers-0.5.4 | 
| Foldable SCC | Since: containers-0.5.9 | 
| Defined in Data.Graph Methods fold :: Monoid m => SCC m -> m # foldMap :: Monoid m => (a -> m) -> SCC a -> m # foldMap' :: Monoid m => (a -> m) -> SCC a -> m # foldr :: (a -> b -> b) -> b -> SCC a -> b # foldr' :: (a -> b -> b) -> b -> SCC a -> b # foldl :: (b -> a -> b) -> b -> SCC a -> b # foldl' :: (b -> a -> b) -> b -> SCC a -> b # foldr1 :: (a -> a -> a) -> SCC a -> a # foldl1 :: (a -> a -> a) -> SCC a -> a # elem :: Eq a => a -> SCC a -> Bool # maximum :: Ord a => SCC a -> a # | |
| Traversable SCC | Since: containers-0.5.9 | 
| Eq1 SCC | Since: containers-0.5.9 | 
| Read1 SCC | Since: containers-0.5.9 | 
| Show1 SCC | Since: containers-0.5.9 | 
| Eq vertex => Eq (SCC vertex) | Since: containers-0.5.9 | 
| Data vertex => Data (SCC vertex) | Since: containers-0.5.9 | 
| Defined in Data.Graph Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SCC vertex -> c (SCC vertex) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SCC vertex) # toConstr :: SCC vertex -> Constr # dataTypeOf :: SCC vertex -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SCC vertex)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SCC vertex)) # gmapT :: (forall b. Data b => b -> b) -> SCC vertex -> SCC vertex # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SCC vertex -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SCC vertex -> r # gmapQ :: (forall d. Data d => d -> u) -> SCC vertex -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SCC vertex -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) # | |
| Read vertex => Read (SCC vertex) | Since: containers-0.5.9 | 
| Show vertex => Show (SCC vertex) | Since: containers-0.5.9 | 
| Generic (SCC vertex) | Since: containers-0.5.9 | 
| NFData a => NFData (SCC a) | |
| Defined in Data.Graph | |
| Generic1 SCC | Since: containers-0.5.9 | 
| type Rep (SCC vertex) | |
| Defined in Data.Graph type Rep (SCC vertex) = D1 ('MetaData "SCC" "Data.Graph" "containers-0.6.2.1" 'False) (C1 ('MetaCons "AcyclicSCC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 vertex)) :+: C1 ('MetaCons "CyclicSCC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [vertex]))) | |
| type Rep1 SCC | |
| Defined in Data.Graph type Rep1 SCC = D1 ('MetaData "SCC" "Data.Graph" "containers-0.6.2.1" 'False) (C1 ('MetaCons "AcyclicSCC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1) :+: C1 ('MetaCons "CyclicSCC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))) | |
cycles :: Graph a -> [[a]] Source #
Ω(V + E). Compute the cycles of a graph. Requires amortized construction of graph.
broken :: Graph a -> [(a, [Key a])] Source #
O(1). Return a list of nodes paired with their broken neighbors (i.e., neighbor keys which are not in the graph). Requires amortized construction of graph.
neighbors :: Graph a -> Key a -> Maybe [a] Source #
Lookup the immediate neighbors from a key in the graph. Requires amortized construction of graph.
revNeighbors :: Graph a -> Key a -> Maybe [a] Source #
Lookup the immediate reverse neighbors from a key in the graph. Requires amortized construction of graph.
closure :: Graph a -> [Key a] -> Maybe [a] Source #
Compute the subgraph which is the closure of some set of keys.
 Returns Nothing if one (or more) keys are not present in
 the graph.
 Requires amortized construction of graph.
revClosure :: Graph a -> [Key a] -> Maybe [a] Source #
Compute the reverse closure of a graph from some set
 of keys.  Returns Nothing if one (or more) keys are not present in
 the graph.
 Requires amortized construction of graph.
topSort :: Graph a -> [a] Source #
Topologically sort the nodes of a graph. Requires amortized construction of graph.
revTopSort :: Graph a -> [a] Source #
Reverse topologically sort the nodes of a graph. Requires amortized construction of graph.
Conversions
Maps
Lists
fromDistinctList :: (IsNode a, Show (Key a)) => [a] -> Graph a Source #
O(V log V). Convert a list of nodes (with distinct keys) into a graph.
Sets
Graphs
toGraph :: Graph a -> (Graph, Vertex -> a, Key a -> Maybe Vertex) Source #
O(1). Convert a graph into a Graph.
 Requires amortized construction of graph.
Node type
A simple, trivial data type which admits an IsNode instance.
Constructors
| N a k [k] |