On this page
Data.Graph
Copyright | (c) The University of Glasgow 2002 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Description
Finite Graphs
The Graph
type is an adjacency list representation of a finite, directed graph with vertices of type Int
.
The SCC
type represents a strongly-connected component of a graph.
Implementation
The implementation is based on
- Structuring Depth-First Search Algorithms in Haskell, by David King and John Launchbury, http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.52.6526
Graphs
type Graph = Array Vertex [Vertex] Source
Adjacency list representation of a graph, mapping each vertex to its list of successors.
type Bounds = (Vertex, Vertex) Source
The bounds of an Array
.
type Edge = (Vertex, Vertex) Source
An edge from the first vertex to the second.
Abstract representation of vertices.
type Table a = Array Vertex a Source
Table indexed by a contiguous set of vertices.
Note: This is included for backwards compatibility.
Graph Construction
graphFromEdges :: Ord key => [(node, key, [key])] -> (Graph, Vertex -> (node, key, [key]), key -> Maybe Vertex) Source
Build a graph from a list of nodes uniquely identified by keys, with a list of keys of nodes this node should have edges to.
This function takes an adjacency list representing a graph with vertices of type key
labeled by values of type node
and produces a Graph
-based representation of that list. The Graph
result represents the shape of the graph, and the functions describe a) how to retrieve the label and adjacent vertices of a given vertex, and b) how to retrieve a vertex given a key.
(graph, nodeFromVertex, vertexFromKey) = graphFromEdges edgeList
graph :: Graph
is the raw, array based adjacency list for the graph.nodeFromVertex :: Vertex -> (node, key, [key])
returns the node associated with the given 0-basedInt
vertex; see warning below.vertexFromKey :: key -> Maybe Vertex
returns theInt
vertex for the key if it exists in the graph,Nothing
otherwise.
To safely use this API you must either extract the list of vertices directly from the graph or first call vertexFromKey k
to check if a vertex corresponds to the key k
. Once it is known that a vertex exists you can use nodeFromVertex
to access the labelled node and adjacent vertices. See below for examples.
Note: The out-list may contain keys that don't correspond to nodes of the graph; they are ignored.
Warning: The nodeFromVertex
function will cause a runtime exception if the given Vertex
does not exist.
Examples
An empty graph.
(graph, nodeFromVertex, vertexFromKey) = graphFromEdges []
graph = array (0,-1) []
A graph where the out-list references unspecified nodes ('c'
), these are ignored.
(graph, _, _) = graphFromEdges [("a", 'a', ['b']), ("b", 'b', ['c'])]
array (0,1) [(0,[1]),(1,[])]
A graph with 3 vertices: ("a") -> ("b") -> ("c")
(graph, nodeFromVertex, vertexFromKey) = graphFromEdges [("a", 'a', ['b']), ("b", 'b', ['c']), ("c", 'c', [])]
graph == array (0,2) [(0,[1]),(1,[2]),(2,[])]
nodeFromVertex 0 == ("a",'a',"b")
vertexFromKey 'a' == Just 0
Get the label for a given key.
let getNodePart (n, _, _) = n
(graph, nodeFromVertex, vertexFromKey) = graphFromEdges [("a", 'a', ['b']), ("b", 'b', ['c']), ("c", 'c', [])]
getNodePart . nodeFromVertex <$> vertexFromKey 'a' == Just "A"
graphFromEdges' :: Ord key => [(node, key, [key])] -> (Graph, Vertex -> (node, key, [key])) Source
Identical to graphFromEdges
, except that the return value does not include the function which maps keys to vertices. This version of graphFromEdges
is for backwards compatibility.
buildG :: Bounds -> [Edge] -> Graph Source
Build a graph from a list of edges.
Warning: This function will cause a runtime exception if a vertex in the edge list is not within the given Bounds
.
Examples
buildG (0,-1) [] == array (0,-1) []
buildG (0,2) [(0,1), (1,2)] == array (0,1) [(0,[1]),(1,[2])]
buildG (0,2) [(0,1), (0,2), (1,2)] == array (0,2) [(0,[2,1]),(1,[2]),(2,[])]
Graph Properties
vertices :: Graph -> [Vertex] Source
Returns the list of vertices in the graph.
Examples
vertices (buildG (0,-1) []) == []
vertices (buildG (0,2) [(0,1),(1,2)]) == [0,1,2]
edges :: Graph -> [Edge] Source
Returns the list of edges in the graph.
Examples
edges (buildG (0,-1) []) == []
edges (buildG (0,2) [(0,1),(1,2)]) == [(0,1),(1,2)]
outdegree :: Graph -> Array Vertex Int Source
A table of the count of edges from each node.
Examples
outdegree (buildG (0,-1) []) == array (0,-1) []
outdegree (buildG (0,2) [(0,1), (1,2)]) == array (0,2) [(0,1),(1,1),(2,0)]
indegree :: Graph -> Array Vertex Int Source
A table of the count of edges into each node.
Examples
indegree (buildG (0,-1) []) == array (0,-1) []
indegree (buildG (0,2) [(0,1), (1,2)]) == array (0,2) [(0,0),(1,1),(2,1)]
Graph Transformations
transposeG :: Graph -> Graph Source
The graph obtained by reversing all edges.
Examples
transposeG (buildG (0,2) [(0,1), (1,2)]) == array (0,2) [(0,[]),(1,[0]),(2,[1])]
Graph Algorithms
dfs :: Graph -> [Vertex] -> Forest Vertex Source
A spanning forest of the part of the graph reachable from the listed vertices, obtained from a depth-first search of the graph starting at each of the listed vertices in order.
dff :: Graph -> Forest Vertex Source
A spanning forest of the graph, obtained from a depth-first search of the graph starting from each vertex in an unspecified order.
topSort :: Graph -> [Vertex] Source
A topological sort of the graph. The order is partially specified by the condition that a vertex i precedes j whenever j is reachable from i but not vice versa.
reverseTopSort :: Graph -> [Vertex] Source
Reverse ordering of topSort
.
Since: containers-0.6.4
components :: Graph -> Forest Vertex Source
The connected components of a graph. Two vertices are connected if there is a path between them, traversing edges in either direction.
scc :: Graph -> Forest Vertex Source
The strongly connected components of a graph, in reverse topological order.
Examples
scc (buildG (0,3) [(3,1),(1,2),(2,0),(0,1)])
== [Node {rootLabel = 0, subForest = [Node {rootLabel = 1, subForest = [Node {rootLabel = 2, subForest = []}]}]}
,Node {rootLabel = 3, subForest = []}]
bcc :: Graph -> Forest [Vertex] Source
The biconnected components of a graph. An undirected graph is biconnected if the deletion of any vertex leaves it connected.
reachable :: Graph -> Vertex -> [Vertex] Source
Returns the list of vertices reachable from a given vertex.
Examples
reachable (buildG (0,0) []) 0 == [0]
reachable (buildG (0,2) [(0,1), (1,2)]) 0 == [0,1,2]
path :: Graph -> Vertex -> Vertex -> Bool Source
Returns True
if the second vertex reachable from the first.
Examples
path (buildG (0,0) []) 0 0 == True
path (buildG (0,2) [(0,1), (1,2)]) 0 2 == True
path (buildG (0,2) [(0,1), (1,2)]) 2 0 == False
Strongly Connected Components
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
Foldable SCC Source | Since: containers-0.5.9 |
Defined in Data.Graph Methodsfold :: Monoid m => SCC m -> m Source foldMap :: Monoid m => (a -> m) -> SCC a -> m Source foldMap' :: Monoid m => (a -> m) -> SCC a -> m Source foldr :: (a -> b -> b) -> b -> SCC a -> b Source foldr' :: (a -> b -> b) -> b -> SCC a -> b Source foldl :: (b -> a -> b) -> b -> SCC a -> b Source foldl' :: (b -> a -> b) -> b -> SCC a -> b Source foldr1 :: (a -> a -> a) -> SCC a -> a Source foldl1 :: (a -> a -> a) -> SCC a -> a Source elem :: Eq a => a -> SCC a -> Bool Source maximum :: Ord a => SCC a -> a Source minimum :: Ord a => SCC a -> a Source |
|
Eq1 SCC Source | Since: containers-0.5.9 |
Read1 SCC Source | Since: containers-0.5.9 |
Defined in Data.Graph |
|
Show1 SCC Source | Since: containers-0.5.9 |
Traversable SCC Source | Since: containers-0.5.9 |
Functor SCC Source | Since: containers-0.5.4 |
Generic1 SCC Source | |
Lift vertex => Lift (SCC vertex :: Type) Source | @since FIXME |
Data vertex => Data (SCC vertex) Source | Since: containers-0.5.9 |
Defined in Data.Graph Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SCC vertex -> c (SCC vertex) Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SCC vertex) Source toConstr :: SCC vertex -> Constr Source dataTypeOf :: SCC vertex -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SCC vertex)) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SCC vertex)) Source gmapT :: (forall b. Data b => b -> b) -> SCC vertex -> SCC vertex Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SCC vertex -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SCC vertex -> r Source gmapQ :: (forall d. Data d => d -> u) -> SCC vertex -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> SCC vertex -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SCC vertex -> m (SCC vertex) Source |
|
Generic (SCC vertex) Source | |
Read vertex => Read (SCC vertex) Source | Since: containers-0.5.9 |
Show vertex => Show (SCC vertex) Source | Since: containers-0.5.9 |
NFData a => NFData (SCC a) Source | |
Defined in Data.Graph |
|
Eq vertex => Eq (SCC vertex) Source | Since: containers-0.5.9 |
type Rep1 SCC Source | Since: containers-0.5.9 |
Defined in Data.Graph
type Rep1 SCC = D1 ('MetaData "SCC" "Data.Graph" "containers-0.6.6" '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 [])))
|
|
type Rep (SCC vertex) Source | Since: containers-0.5.9 |
Defined in Data.Graph
type Rep (SCC vertex) = D1 ('MetaData "SCC" "Data.Graph" "containers-0.6.6" '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])))
|
Construction
Arguments
The strongly connected components of a directed graph, reverse topologically sorted.
Examples
stronglyConnComp [("a",0,[1]),("b",1,[2,3]),("c",2,[1]),("d",3,[3])]
== [CyclicSCC ["d"],CyclicSCC ["b","c"],AcyclicSCC "a"]
Arguments
The strongly connected components of a directed graph, reverse topologically sorted. The function is the same as stronglyConnComp
, except that all the information about each node retained. This interface is used when you expect to apply SCC
to (some of) the result of SCC
, so you don't want to lose the dependency information.
Examples
stronglyConnCompR [("a",0,[1]),("b",1,[2,3]),("c",2,[1]),("d",3,[3])]
== [CyclicSCC [("d",3,[3])],CyclicSCC [("b",1,[2,3]),("c",2,[1])],AcyclicSCC ("a",0,[1])]
Conversion
flattenSCC :: SCC vertex -> [vertex] Source
The vertices of a strongly connected component.
flattenSCCs :: [SCC a] -> [a] Source
The vertices of a list of strongly connected components.
Trees
Non-empty, possibly infinite, multi-way trees; also known as rose trees.
Instances
MonadFix Tree Source | Since: containers-0.5.11 |
MonadZip Tree Source | |
Foldable Tree Source | |
Defined in Data.Tree Methodsfold :: Monoid m => Tree m -> m Source foldMap :: Monoid m => (a -> m) -> Tree a -> m Source foldMap' :: Monoid m => (a -> m) -> Tree a -> m Source foldr :: (a -> b -> b) -> b -> Tree a -> b Source foldr' :: (a -> b -> b) -> b -> Tree a -> b Source foldl :: (b -> a -> b) -> b -> Tree a -> b Source foldl' :: (b -> a -> b) -> b -> Tree a -> b Source foldr1 :: (a -> a -> a) -> Tree a -> a Source foldl1 :: (a -> a -> a) -> Tree a -> a Source toList :: Tree a -> [a] Source length :: Tree a -> Int Source elem :: Eq a => a -> Tree a -> Bool Source maximum :: Ord a => Tree a -> a Source minimum :: Ord a => Tree a -> a Source |
|
Eq1 Tree Source | Since: containers-0.5.9 |
Ord1 Tree Source | Since: containers-0.5.9 |
Read1 Tree Source | Since: containers-0.5.9 |
Defined in Data.Tree MethodsliftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Tree a) Source liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Tree a] Source liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Tree a) Source liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Tree a] Source |
|
Show1 Tree Source | Since: containers-0.5.9 |
Traversable Tree Source | |
Applicative Tree Source | |
Functor Tree Source | |
Monad Tree Source | |
Generic1 Tree Source | |
Lift a => Lift (Tree a :: Type) Source | @since FIXME |
Data a => Data (Tree a) Source | |
Defined in Data.Tree Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tree a -> c (Tree a) Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tree a) Source toConstr :: Tree a -> Constr Source dataTypeOf :: Tree a -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Tree a)) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tree a)) Source gmapT :: (forall b. Data b => b -> b) -> Tree a -> Tree a Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tree a -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tree a -> r Source gmapQ :: (forall d. Data d => d -> u) -> Tree a -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Tree a -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) Source |
|
Generic (Tree a) Source | |
Read a => Read (Tree a) Source | |
Show a => Show (Tree a) Source | |
NFData a => NFData (Tree a) Source | |
Eq a => Eq (Tree a) Source | |
Ord a => Ord (Tree a) Source | Since: containers-0.6.5 |
type Rep1 Tree Source | Since: containers-0.5.8 |
Defined in Data.Tree
type Rep1 Tree = D1 ('MetaData "Tree" "Data.Tree" "containers-0.6.6" 'False) (C1 ('MetaCons "Node" 'PrefixI 'True) (S1 ('MetaSel ('Just "rootLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "subForest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 Tree)))
|
|
type Rep (Tree a) Source | Since: containers-0.5.8 |
Defined in Data.Tree
type Rep (Tree a) = D1 ('MetaData "Tree" "Data.Tree" "containers-0.6.6" 'False) (C1 ('MetaCons "Node" 'PrefixI 'True) (S1 ('MetaSel ('Just "rootLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "subForest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tree a])))
|
type Forest a = [Tree a] Source
This type synonym exists primarily for historical reasons.
© The University of Glasgow and others
Licensed under a BSD-style license (see top of the page).
https://downloads.haskell.org/~ghc/9.4.2/docs/libraries/containers-0.6.6/Data-Graph.html