Portability | portable |
---|---|
Stability | experimental |
Maintainer | libraries@haskell.org |
Safe Haskell | Trustworthy |
A version of the graph algorithms described in:
Lazy Depth-First Search and Linear Graph Algorithms in Haskell, by David King and John Launchbury.
- stronglyConnComp :: Ord key => [(node, key, [key])] -> [SCC node]
- stronglyConnCompR :: Ord key => [(node, key, [key])] -> [SCC (node, key, [key])]
- data SCC vertex
- = AcyclicSCC vertex
- | CyclicSCC [vertex]
- flattenSCC :: SCC vertex -> [vertex]
- flattenSCCs :: [SCC a] -> [a]
- type Graph = Table [Vertex]
- type Table a = Array Vertex a
- type Bounds = (Vertex, Vertex)
- type Edge = (Vertex, Vertex)
- type Vertex = Int
- graphFromEdges :: Ord key => [(node, key, [key])] -> (Graph, Vertex -> (node, key, [key]), key -> Maybe Vertex)
- graphFromEdges' :: Ord key => [(node, key, [key])] -> (Graph, Vertex -> (node, key, [key]))
- buildG :: Bounds -> [Edge] -> Graph
- transposeG :: Graph -> Graph
- vertices :: Graph -> [Vertex]
- edges :: Graph -> [Edge]
- outdegree :: Graph -> Table Int
- indegree :: Graph -> Table Int
- dfs :: Graph -> [Vertex] -> Forest Vertex
- dff :: Graph -> Forest Vertex
- topSort :: Graph -> [Vertex]
- components :: Graph -> Forest Vertex
- scc :: Graph -> Forest Vertex
- bcc :: Graph -> Forest [Vertex]
- reachable :: Graph -> Vertex -> [Vertex]
- path :: Graph -> Vertex -> Vertex -> Bool
- module Data.Tree
External interface
:: Ord key | |
=> [(node, key, [key])] | The graph: a list of nodes uniquely identified by keys, with a list of keys of nodes this node has edges to. The out-list may contain keys that don't correspond to nodes of the graph; such edges are ignored. |
-> [SCC node] |
The strongly connected components of a directed graph, topologically sorted.
:: Ord key | |
=> [(node, key, [key])] | The graph: a list of nodes uniquely identified by keys, with a list of keys of nodes this node has edges to. The out-list may contain keys that don't correspond to nodes of the graph; such edges are ignored. |
-> [SCC (node, key, [key])] | Topologically sorted |
The strongly connected components of a directed graph, 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.
Strongly connected component.
AcyclicSCC vertex | A single vertex that is not in any cycle. |
CyclicSCC [vertex] | A maximal set of mutually reachable vertices. |
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.
Graphs
type Graph = Table [Vertex]Source
Adjacency list representation of a graph, mapping each vertex to its list of successors.
Building graphs
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. The out-list may contain keys that don't correspond to nodes of the graph; they are ignored.
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.
transposeG :: Graph -> GraphSource
The graph obtained by reversing all edges.
Graph properties
Algorithms
dfs :: Graph -> [Vertex] -> Forest VertexSource
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 VertexSource
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.
components :: Graph -> Forest VertexSource
The connected components of a graph. Two vertices are connected if there is a path between them, traversing edges in either direction.
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.
module Data.Tree