| Safe Haskell | Safe | 
|---|---|
| Language | Haskell98 | 
Data.Graph.Inductive.Query.DFS
Contents
Description
Depth-first search algorithms.
Names consist of:
- An optional direction parameter, specifying which nodes to visit next.
- u
- undirectional: ignore edge direction
- r
- reversed: walk edges in reverse
- x
- user defined: speciy which paths to follow
- "df" for depth-first
- A structure parameter, specifying the type of the result. - s
- Flat list of results
- f
- Structured Treeof results
 
- An optional "With", which instead of putting the found nodes directly into the result, adds the result of a computation on them into it.
- An optional prime character, in which case all nodes of the graph will be visited, instead of a user-given subset.
- type CFun a b c = Context a b -> c
- dfs :: Graph gr => [Node] -> gr a b -> [Node]
- dfs' :: Graph gr => gr a b -> [Node]
- dff :: Graph gr => [Node] -> gr a b -> [Tree Node]
- dff' :: Graph gr => gr a b -> [Tree Node]
- dfsWith :: Graph gr => CFun a b c -> [Node] -> gr a b -> [c]
- dfsWith' :: Graph gr => CFun a b c -> gr a b -> [c]
- dffWith :: Graph gr => CFun a b c -> [Node] -> gr a b -> [Tree c]
- dffWith' :: Graph gr => CFun a b c -> gr a b -> [Tree c]
- xdfsWith :: Graph gr => CFun a b [Node] -> CFun a b c -> [Node] -> gr a b -> [c]
- xdfWith :: Graph gr => CFun a b [Node] -> CFun a b c -> [Node] -> gr a b -> ([Tree c], gr a b)
- xdffWith :: Graph gr => CFun a b [Node] -> CFun a b c -> [Node] -> gr a b -> [Tree c]
- udfs :: Graph gr => [Node] -> gr a b -> [Node]
- udfs' :: Graph gr => gr a b -> [Node]
- udff :: Graph gr => [Node] -> gr a b -> [Tree Node]
- udff' :: Graph gr => gr a b -> [Tree Node]
- udffWith :: Graph gr => CFun a b c -> [Node] -> gr a b -> [Tree c]
- udffWith' :: Graph gr => CFun a b c -> gr a b -> [Tree c]
- rdff :: Graph gr => [Node] -> gr a b -> [Tree Node]
- rdff' :: Graph gr => gr a b -> [Tree Node]
- rdfs :: Graph gr => [Node] -> gr a b -> [Node]
- rdfs' :: Graph gr => gr a b -> [Node]
- rdffWith :: Graph gr => CFun a b c -> [Node] -> gr a b -> [Tree c]
- rdffWith' :: Graph gr => CFun a b c -> gr a b -> [Tree c]
- topsort :: Graph gr => gr a b -> [Node]
- topsort' :: Graph gr => gr a b -> [a]
- scc :: Graph gr => gr a b -> [[Node]]
- reachable :: Graph gr => Node -> gr a b -> [Node]
- components :: Graph gr => gr a b -> [[Node]]
- noComponents :: Graph gr => gr a b -> Int
- isConnected :: Graph gr => gr a b -> Bool
- condensation :: Graph gr => gr a b -> gr [Node] ()
Documentation
Standard
Arguments
| :: Graph gr | |
| => CFun a b [Node] | Mapping from a node to its neighbours to be visited
   as well.  | 
| -> CFun a b c | Mapping from the  | 
| -> [Node] | Nodes to be visited. | 
| -> gr a b | |
| -> [c] | 
xdfWith :: Graph gr => CFun a b [Node] -> CFun a b c -> [Node] -> gr a b -> ([Tree c], gr a b) Source #
xdffWith :: Graph gr => CFun a b [Node] -> CFun a b c -> [Node] -> gr a b -> [Tree c] Source #
Discard the graph part of the result of xdfWith.
xdffWith d f vs g = fst (xdfWith d f vs g)
Undirected
udfs :: Graph gr => [Node] -> gr a b -> [Node] Source #
Undirected depth-first search, obtained by following edges regardless of their direction.
udff :: Graph gr => [Node] -> gr a b -> [Tree Node] Source #
Undirected depth-first forest, obtained by following edges regardless of their direction.
Reversed
rdff :: Graph gr => [Node] -> gr a b -> [Tree Node] Source #
Reverse depth-first forest, obtained by following predecessors.
rdfs :: Graph gr => [Node] -> gr a b -> [Node] Source #
Reverse depth-first search, obtained by following predecessors.
Applications of depth first search/forest
topsort :: Graph gr => gr a b -> [Node] Source #
Topological sorting,
   i.e. a list of Nodes so that if there's an edge between a source and a
   target node, the source appears earlier in the result.
reachable :: Graph gr => Node -> gr a b -> [Node] Source #
Collection of nodes reachable from a starting point.
Applications of undirected depth first search/forest
components :: Graph gr => gr a b -> [[Node]] Source #
Collection of connected components
noComponents :: Graph gr => gr a b -> Int Source #
Number of connected components
isConnected :: Graph gr => gr a b -> Bool Source #
Is the graph connected?
condensation :: Graph gr => gr a b -> gr [Node] () Source #
The condensation of the given graph, i.e., the graph of its strongly connected components.