ghc-6.10.3: The GHC APIContentsIndex
Digraph
Documentation
data Graph node
show/hide Instances
Outputable node => Outputable (Graph node)
graphFromVerticesAndAdjacency :: Ord key => [(node, key)] -> [(key, key)] -> Graph (node, key)
graphFromEdgedVertices :: Ord key => [(node, key, [key])] -> Graph (node, key, [key])
data SCC vertex
Constructors
AcyclicSCC vertex
CyclicSCC [vertex]
show/hide Instances
flattenSCC :: SCC a -> [a]
flattenSCCs :: [SCC a] -> [a]
stronglyConnCompG :: Graph node -> [SCC node]
topologicalSortG :: Graph node -> [node]
verticesG :: Graph node -> [node]
edgesG :: Graph node -> [Edge node]
hasVertexG :: Graph node -> node -> Bool
reachableG :: Graph node -> node -> [node]
transposeG :: Graph node -> Graph node
outdegreeG :: Graph node -> node -> Maybe Int
indegreeG :: Graph node -> node -> Maybe Int
vertexGroupsG :: Graph node -> [[node]]
emptyG :: Graph node -> Bool
componentsG :: Graph node -> [[node]]
stronglyConnCompFromEdgedVertices :: Ord key => [(node, key, [key])] -> [SCC node]
stronglyConnCompFromEdgedVerticesR :: Ord key => [(node, key, [key])] -> [SCC (node, key, [key])]
tabulate :: Bounds -> [Vertex] -> Table Int
preArr :: Bounds -> Forest Vertex -> Table Int
components :: IntGraph -> Forest Vertex
undirected :: IntGraph -> IntGraph
back :: IntGraph -> Table Int -> IntGraph
cross :: IntGraph -> Table Int -> Table Int -> IntGraph
forward :: IntGraph -> IntGraph -> Table Int -> IntGraph
path :: IntGraph -> Vertex -> Vertex -> Bool
bcc :: IntGraph -> Forest [Vertex]
do_label :: IntGraph -> Table Int -> Tree Vertex -> Tree (Vertex, Int, Int)
bicomps :: Tree (Vertex, Int, Int) -> Forest [Vertex]
collect :: Tree (Vertex, Int, Int) -> (Int, Tree [Vertex])
Produced by Haddock version 2.4.2