graph-wrapper-0.2.4: A wrapper around the standard Data.Graph with a less awkward interface

Data.Graph.Wrapper

Description

A wrapper around the types and functions from Data.Graph to make programming with them less painful. Also implements some extra useful goodies such as successors and sccGraph, and improves the documentation of the behaviour of some functions.

As it wraps Data.Graph, this module only supports directed graphs with unlabelled edges.

Incorporates code from the containers package which is (c) The University of Glasgow 2002 and based on code described in:

Lazy Depth-First Search and Linear Graph Algorithms in Haskell, by David King and John Launchbury

Synopsis

Documentation

type Edge i = (i, i)Source

An edge from the first vertex to the second

data Graph i v Source

A directed graph

Instances

Functor (Graph i) 
Foldable (Graph i) 
Traversable (Graph i) 
(Ord i, Show i, Show v) => Show (Graph i v) 

vertex :: Ord i => Graph i v -> i -> vSource

Retrieve data associated with the vertex

fromListSimple :: Ord v => [(v, [v])] -> Graph v vSource

Construct a Graph where the vertex data double up as the indices.

Unlike Data.Graph.graphFromEdges, vertex data that is listed as edges that are not actually themselves present in the input list are reported as an error.

fromList :: Ord i => [(i, v, [i])] -> Graph i vSource

Construct a Graph that contains the given vertex data, linked up according to the supplied index and edge list.

Unlike Data.Graph.graphFromEdges, indexes in the edge list that do not correspond to the index of some item in the input list are reported as an error.

fromListLenient :: Ord i => [(i, v, [i])] -> Graph i vSource

Construct a Graph that contains the given vertex data, linked up according to the supplied index and edge list.

Like Data.Graph.graphFromEdges, indexes in the edge list that do not correspond to the index of some item in the input list are silently ignored.

fromListBy :: Ord i => (v -> i) -> [(v, [i])] -> Graph i vSource

Construct a Graph that contains the given vertex data, linked up according to the supplied key extraction function and edge list.

Unlike Data.Graph.graphFromEdges, indexes in the edge list that do not correspond to the index of some item in the input list are reported as an error.

fromVerticesEdges :: Ord i => [(i, v)] -> [Edge i] -> Graph i vSource

Construct a Graph directly from a list of vertices (and vertex data).

If either end of an Edge does not correspond to a supplied vertex, an error will be raised.

toList :: Ord i => Graph i v -> [(i, v, [i])]Source

Morally, the inverse of fromList. The order of the elements in the output list is unspecified, as is the order of the edges in each node's adjacency list. For this reason, toList . fromList is not necessarily the identity function.

vertices :: Graph i v -> [i]Source

Exhaustive list of vertices in the graph

edges :: Graph i v -> [Edge i]Source

Exhaustive list of edges in the graph

successors :: Ord i => Graph i v -> i -> [i]Source

Find the vertices we can reach from a vertex with the given indentity

outdegree :: Ord i => Graph i v -> i -> IntSource

Number of edges going out of the vertex.

It is worth sharing a partial application of outdegree to the Graph argument if you intend to query for the outdegrees of a number of vertices.

indegree :: Ord i => Graph i v -> i -> IntSource

Number of edges going in to the vertex.

It is worth sharing a partial application of indegree to the Graph argument if you intend to query for the indegrees of a number of vertices.

transpose :: Graph i v -> Graph i vSource

The graph formed by flipping all the edges, so edges from i to j now go from j to i

reachableVertices :: Ord i => Graph i v -> i -> [i]Source

List all of the vertices reachable from the given starting point

hasPath :: Ord i => Graph i v -> i -> i -> BoolSource

Is the second vertex reachable by following edges from the first vertex?

It is worth sharing a partial application of hasPath to the first vertex if you are testing for several vertices being reachable from it.

topologicalSort :: Graph i v -> [i]Source

Topological sort of of the graph (http://en.wikipedia.org/wiki/Topological_sort). If the graph is acyclic, vertices will only appear in the list once all of those vertices with arrows to them have already appeared.

Vertex i precedes j in the output whenever j is reachable from i but not vice versa.

depthNumbering :: Ord i => Graph i v -> [i] -> Graph i (v, Maybe Int)Source

Number the vertices in the graph by how far away they are from the given roots. The roots themselves have depth 0, and every subsequent link we traverse adds 1 to the depth. If a vertex is not reachable it will have a depth of Nothing.

data SCC i Source

Constructors

AcyclicSCC i 
CyclicSCC [i] 

Instances

stronglyConnectedComponents :: Graph i v -> [SCC i]Source

Strongly connected components (http://en.wikipedia.org/wiki/Strongly_connected_component).

The SCCs are listed in a *reverse topological order*. That is to say, any edges *to* a node in the SCC originate either *from*:

1) Within the SCC itself (in the case of a CyclicSCC only) 2) Or from a node in a SCC later on in the list

Vertex i strictly precedes j in the output whenever i is reachable from j but not vice versa. Vertex i occurs in the same SCC as j whenever both i is reachable from j and j is reachable from i.

sccGraph :: Ord i => Graph i v -> Graph (Set i) (Map i v)Source

The graph formed by the strongly connected components of the input graph. Each node in the resulting graph is indexed by the set of vertex indices from the input graph that it contains.

traverseWithKey :: Applicative t => (i -> a -> t b) -> Graph i a -> t (Graph i b)Source