| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell98 | 
Reactive.Banana.Prim.Low.Graph
Synopsis
- data Graph v e
 - empty :: Graph v e
 - getOutgoing :: (Eq v, Hashable v) => Graph v e -> v -> [(e, v)]
 - getIncoming :: (Eq v, Hashable v) => Graph v e -> v -> [(v, e)]
 - size :: (Eq v, Hashable v) => Graph v e -> Int
 - edgeCount :: (Eq v, Hashable v) => Graph v e -> Int
 - listConnectedVertices :: (Eq v, Hashable v) => Graph v e -> [v]
 - deleteVertex :: (Eq v, Hashable v) => v -> Graph v e -> Graph v e
 - insertEdge :: (Eq v, Hashable v) => (v, v) -> e -> Graph v e -> Graph v e
 - deleteEdge :: (Eq v, Hashable v) => (v, v) -> Graph v e -> Graph v e
 - clearPredecessors :: (Eq v, Hashable v) => v -> Graph v e -> Graph v e
 - collectGarbage :: (Eq v, Hashable v) => [v] -> Graph v e -> Graph v e
 - topologicalSort :: (Eq v, Hashable v) => Graph v e -> [v]
 - data Step
 - walkSuccessors :: forall v e m. (Monad m, Eq v, Hashable v) => [v] -> (v -> m Step) -> Graph v e -> m [v]
 - walkSuccessors_ :: (Monad m, Eq v, Hashable v) => [v] -> (v -> m Step) -> Graph v e -> m ()
 - type Level = Int
 - getLevel :: (Eq v, Hashable v) => Graph v e -> v -> Level
 - showDot :: (Eq v, Hashable v) => (v -> String) -> Graph v e -> String
 
Documentation
A directed graph
whose set of vertices is the set of all values of the type v
and whose edges are associated with data of type e.
Note that a Graph does not have a notion of vertex membership
— by design, all values of the type v are vertices of the Graph.
The main purpose of Graph is to keep track of directed edges between
vertices; a vertex with at least one edge incident on it is called
a connected vertex.
For efficiency, only the connected vertices are stored.
getOutgoing :: (Eq v, Hashable v) => Graph v e -> v -> [(e, v)] Source #
Get all direct successors of a vertex in a Graph.
getIncoming :: (Eq v, Hashable v) => Graph v e -> v -> [(v, e)] Source #
Get all direct predecessors of a vertex in a Graph.
size :: (Eq v, Hashable v) => Graph v e -> Int Source #
Number of connected vertices, i.e. vertices on which at least one edge is incident.
listConnectedVertices :: (Eq v, Hashable v) => Graph v e -> [v] Source #
List all connected vertices, i.e. vertices on which at least one edge is incident.
deleteVertex :: (Eq v, Hashable v) => v -> Graph v e -> Graph v e Source #
Remove all edges incident on this vertex from the Graph.
insertEdge :: (Eq v, Hashable v) => (v, v) -> e -> Graph v e -> Graph v e Source #
Insert an edge from the first to the second vertex into the Graph.
clearPredecessors :: (Eq v, Hashable v) => v -> Graph v e -> Graph v e Source #
Remove all the edges that connect the given vertex to its predecessors.
collectGarbage :: (Eq v, Hashable v) => [v] -> Graph v e -> Graph v e Source #
Apply deleteVertex to all vertices which are not predecessors
 of any of the vertices in the given list.
topologicalSort :: (Eq v, Hashable v) => Graph v e -> [v] Source #
If the Graph is acyclic, return a topological sort,
 that is a linear ordering of its connected vertices such that
 each vertex occurs before its successors.
(Vertices that are not connected are not listed in the topological sort.)
walkSuccessors :: forall v e m. (Monad m, Eq v, Hashable v) => [v] -> (v -> m Step) -> Graph v e -> m [v] Source #
Starting from a list of vertices without predecessors,
 walk through all successors, but in such a way that every vertex
 is visited before its predecessors.
 For every vertex, if the function returns Next, then
 the successors are visited, otherwise the walk at the vertex
 stops prematurely.
topologicalSort g =
    runIdentity $ walkSuccessors (roots g) (pure Next) gwalkSuccessors_ :: (Monad m, Eq v, Hashable v) => [v] -> (v -> m Step) -> Graph v e -> m () Source #
Internal
Levels are used to keep track of the order of vertices —
 Lower levels come first.