Skip to content

Commit 7b66a78

Browse files
m-renaudtreeowl
authored andcommitted
Improve Data.Graph documentation. (#532)
* Improve module docs * Re-orders function documentation order * Adds examples * Don't use Table type alias, use Array Vertex a instead.
1 parent b1a05c3 commit 7b66a78

File tree

1 file changed

+173
-43
lines changed

1 file changed

+173
-43
lines changed

Data/Graph.hs

Lines changed: 173 additions & 43 deletions
Original file line numberDiff line numberDiff line change
@@ -23,53 +23,78 @@
2323
-- Maintainer : [email protected]
2424
-- Portability : portable
2525
--
26-
-- A version of the graph algorithms described in:
26+
-- = Finite Graphs
2727
--
28-
-- /Structuring Depth-First Search Algorithms in Haskell/,
29-
-- by David King and John Launchbury.
28+
-- The @'Graph'@ type is an adjacency list representation of a finite, directed
29+
-- graph with vertices of type @Int@.
30+
--
31+
-- The @'SCC'@ type represents a
32+
-- <https://en.wikipedia.org/wiki/Strongly_connected_component strongly-connected component>
33+
-- of a graph.
34+
--
35+
-- == Implementation
36+
--
37+
-- The implementation is based on
38+
--
39+
-- * /Structuring Depth-First Search Algorithms in Haskell/,
40+
-- by David King and John Launchbury.
3041
--
3142
-----------------------------------------------------------------------------
3243

33-
module Data.Graph(
34-
35-
-- * External interface
44+
module Data.Graph (
3645

37-
-- At present the only one with a "nice" external interface
38-
stronglyConnComp, stronglyConnCompR, SCC(..), flattenSCC, flattenSCCs,
46+
-- * Graphs
47+
Graph
48+
, Bounds
49+
, Edge
50+
, Vertex
51+
, Table
3952

40-
-- * Graphs
53+
-- ** Graph Construction
54+
, graphFromEdges
55+
, graphFromEdges'
56+
, buildG
4157

42-
Graph, Table, Bounds, Edge, Vertex,
58+
-- ** Graph Properties
59+
, vertices
60+
, edges
61+
, outdegree
62+
, indegree
4363

44-
-- ** Building graphs
64+
-- ** Graph Transformations
65+
, transposeG
4566

46-
graphFromEdges, graphFromEdges', buildG, transposeG,
47-
-- reverseE,
67+
-- ** Graph Algorithms
68+
, dfs
69+
, dff
70+
, topSort
71+
, components
72+
, scc
73+
, bcc
74+
, reachable
75+
, path
4876

49-
-- ** Graph properties
5077

51-
vertices, edges,
52-
outdegree, indegree,
78+
-- * Strongly Connected Components
79+
, SCC(..)
5380

54-
-- * Algorithms
81+
-- ** Construction
82+
, stronglyConnComp
83+
, stronglyConnCompR
5584

56-
dfs, dff,
57-
topSort,
58-
components,
59-
scc,
60-
bcc,
61-
-- tree, back, cross, forward,
62-
reachable, path,
85+
-- ** Conversion
86+
, flattenSCC
87+
, flattenSCCs
6388

64-
module Data.Tree
89+
-- * Trees
90+
, module Data.Tree
6591

6692
) where
6793

6894
#if __GLASGOW_HASKELL__
6995
# define USE_ST_MONAD 1
7096
#endif
7197

72-
-- Extensions
7398
#if USE_ST_MONAD
7499
import Control.Monad.ST
75100
import Data.Array.ST (STUArray, newArray, readArray, writeArray)
@@ -108,7 +133,7 @@ import Data.Typeable
108133

109134
-------------------------------------------------------------------------
110135
-- -
111-
-- External interface
136+
-- Strongly Connected Components
112137
-- -
113138
-------------------------------------------------------------------------
114139

@@ -246,44 +271,83 @@ stronglyConnCompR edges0
246271
-- | Abstract representation of vertices.
247272
type Vertex = Int
248273
-- | Table indexed by a contiguous set of vertices.
274+
--
275+
-- /Note: This is included for backwards compatibility./
249276
type Table a = Array Vertex a
250277
-- | Adjacency list representation of a graph, mapping each vertex to its
251278
-- list of successors.
252-
type Graph = Table [Vertex]
253-
-- | The bounds of a 'Table'.
279+
type Graph = Array Vertex [Vertex]
280+
-- | The bounds of an @Array@.
254281
type Bounds = (Vertex, Vertex)
255282
-- | An edge from the first vertex to the second.
256283
type Edge = (Vertex, Vertex)
257284

258-
-- | All vertices of a graph.
285+
-- | Returns the list of vertices in the graph.
286+
--
287+
-- ==== __Examples__
288+
--
289+
-- > vertices (buildG (0,-1) []) == []
290+
--
291+
-- > vertices (buildG (0,2) [(0,1),(1,2)]) == [0,1,2]
259292
vertices :: Graph -> [Vertex]
260293
vertices = indices
261294

262-
-- | All edges of a graph.
295+
-- | Returns the list of edges in the graph.
296+
--
297+
-- ==== __Examples__
298+
--
299+
-- > edges (buildG (0,-1) []) == []
300+
--
301+
-- > edges (buildG (0,2) [(0,1),(1,2)]) == [(0,1),(1,2)]
263302
edges :: Graph -> [Edge]
264303
edges g = [ (v, w) | v <- vertices g, w <- g!v ]
265304

266-
mapT :: (Vertex -> a -> b) -> Table a -> Table b
305+
mapT :: (Vertex -> a -> b) -> Array Vertex a -> Array Vertex b
267306
mapT f t = array (bounds t) [ (,) v (f v (t!v)) | v <- indices t ]
268307

269308
-- | Build a graph from a list of edges.
309+
--
310+
-- Warning: This function will cause a runtime exception if a vertex in the edge
311+
-- list is not within the given @Bounds@.
312+
--
313+
-- ==== __Examples__
314+
--
315+
-- > buildG (0,-1) [] == array (0,-1) []
316+
-- > buildG (0,2) [(0,1), (1,2)] == array (0,1) [(0,[1]),(1,[2])]
317+
-- > buildG (0,2) [(0,1), (0,2), (1,2)] == array (0,2) [(0,[2,1]),(1,[2]),(2,[])]
270318
buildG :: Bounds -> [Edge] -> Graph
271319
buildG bounds0 edges0 = accumArray (flip (:)) [] bounds0 edges0
272320

273321
-- | The graph obtained by reversing all edges.
322+
--
323+
-- ==== __Examples__
324+
--
325+
-- > transposeG (buildG (0,2) [(0,1), (1,2)]) == array (0,2) [(0,[]),(1,[0]),(2,[1])]
274326
transposeG :: Graph -> Graph
275327
transposeG g = buildG (bounds g) (reverseE g)
276328

277329
reverseE :: Graph -> [Edge]
278330
reverseE g = [ (w, v) | (v, w) <- edges g ]
279331

280332
-- | A table of the count of edges from each node.
281-
outdegree :: Graph -> Table Int
333+
--
334+
-- ==== __Examples__
335+
--
336+
-- > outdegree (buildG (0,-1) []) == array (0,-1) []
337+
--
338+
-- > outdegree (buildG (0,2) [(0,1), (1,2)]) == array (0,2) [(0,1),(1,1),(2,0)]
339+
outdegree :: Graph -> Array Vertex Int
282340
outdegree = mapT numEdges
283341
where numEdges _ ws = length ws
284342

285343
-- | A table of the count of edges into each node.
286-
indegree :: Graph -> Table Int
344+
--
345+
-- ==== __Examples__
346+
--
347+
-- > indegree (buildG (0,-1) []) == array (0,-1) []
348+
--
349+
-- > indegree (buildG (0,2) [(0,1), (1,2)]) == array (0,2) [(0,0),(1,1),(2,1)]
350+
indegree :: Graph -> Array Vertex Int
287351
indegree = outdegree . transposeG
288352

289353
-- | Identical to 'graphFromEdges', except that the return value
@@ -298,8 +362,60 @@ graphFromEdges' x = (a,b) where
298362

299363
-- | Build a graph from a list of nodes uniquely identified by keys,
300364
-- with a list of keys of nodes this node should have edges to.
301-
-- The out-list may contain keys that don't correspond to
302-
-- nodes of the graph; they are ignored.
365+
--
366+
-- This function takes an adjacency list representing a graph with vertices of
367+
-- type @key@ labeled by values of type @node@ and produces a @Graph@-based
368+
-- representation of that list. The @Graph@ result represents the /shape/ of the
369+
-- graph, and the functions describe a) how to retrieve the label and adjacent
370+
-- vertices of a given vertex, and b) how to retrive a vertex given a key.
371+
--
372+
-- @(graph, nodeFromVertex, vertexFromKey) = graphFromEdges edgeList@
373+
--
374+
-- * @graph :: Graph@ is the raw, array based adjacency list for the graph.
375+
-- * @nodeFromVertex :: Vertex -> (node, key, [key])@ returns the node
376+
-- associated with the given 0-based @Int@ vertex; see /warning/ below.
377+
-- * @vertexFromKey :: key -> Maybe Vertex@ returns the @Int@ vertex for the
378+
-- key if it exists in the graph, @Nothing@ otherwise.
379+
--
380+
-- To safely use this API you must either extract the list of vertices directly
381+
-- from the graph or first call @vertexFromKey k@ to check if a vertex
382+
-- corresponds to the key @k@. Once it is known that a vertex exists you can use
383+
-- @nodeFromVertex@ to access the labelled node and adjacent vertices. See below
384+
-- for examples.
385+
--
386+
-- Note: The out-list may contain keys that don't correspond to nodes of the
387+
-- graph; they are ignored.
388+
--
389+
-- Warning: The @nodeFromVertex@ function will cause a runtime exception if the
390+
-- given @Vertex@ does not exist.
391+
--
392+
-- ==== __Examples__
393+
--
394+
-- An empty graph.
395+
--
396+
-- > (graph, nodeFromVertex, vertexFromKey) = graphFromEdges []
397+
-- > graph = array (0,-1) []
398+
--
399+
-- A graph where the out-list references unspecified nodes (@'c'@), these are
400+
-- ignored.
401+
--
402+
-- > (graph, _, _) = graphFromEdges [("a", 'a', ['b']), ("b", 'b', ['c'])]
403+
-- > array (0,1) [(0,[1]),(1,[])]
404+
--
405+
--
406+
-- A graph with 3 vertices: ("a") -> ("b") -> ("c")
407+
--
408+
-- > (graph, nodeFromVertex, vertexFromKey) = graphFromEdges [("a", 'a', ['b']), ("b", 'b', ['c']), ("c", 'c', [])]
409+
-- > graph == array (0,2) [(0,[1]),(1,[2]),(2,[])]
410+
-- > nodeFromVertex 0 == ("a",'a',"b")
411+
-- > vertexFromKey 'a' == Just 0
412+
--
413+
-- Get the label for a given key.
414+
--
415+
-- > let getNodePart (n, _, _) = n
416+
-- > (graph, nodeFromVertex, vertexFromKey) = graphFromEdges [("a", 'a', ['b']), ("b", 'b', ['c']), ("c", 'c', [])]
417+
-- > getNodePart . nodeFromVertex <$> vertexFromKey 'a' == Just "A"
418+
--
303419
graphFromEdges
304420
:: Ord key
305421
=> [(node, key, [key])]
@@ -452,10 +568,10 @@ preorderF' ts = foldr (.) id $ map preorder' ts
452568
preorderF :: Forest a -> [a]
453569
preorderF ts = preorderF' ts []
454570

455-
tabulate :: Bounds -> [Vertex] -> Table Int
571+
tabulate :: Bounds -> [Vertex] -> Array Vertex Int
456572
tabulate bnds vs = array bnds (zipWith (,) vs [1..])
457573

458-
preArr :: Bounds -> Forest Vertex -> Table Int
574+
preArr :: Bounds -> Forest Vertex -> Array Vertex Int
459575
preArr bnds = tabulate bnds . preorderF
460576

461577
------------------------------------------------------------
@@ -525,12 +641,26 @@ forward g tree' pre = mapT select g
525641
-- Algorithm 6: Finding reachable vertices
526642
------------------------------------------------------------
527643

528-
-- | A list of vertices reachable from a given vertex.
529-
reachable :: Graph -> Vertex -> [Vertex]
644+
-- | Returns the list of vertices reachable from a given vertex.
645+
--
646+
-- ==== __Examples__
647+
--
648+
-- > reachable (buildG (0,0) []) 0 == [0]
649+
--
650+
-- > reachable (buildG (0,2) [(0,1), (1,2)]) 0 == [0,1,2]
651+
reachable :: Graph -> Vertex -> [Vertex]
530652
reachable g v = preorderF (dfs g [v])
531653

532-
-- | Is the second vertex reachable from the first?
533-
path :: Graph -> Vertex -> Vertex -> Bool
654+
-- | Returns @True@ if the second vertex reachable from the first.
655+
--
656+
-- ==== __Examples__
657+
--
658+
-- > path (buildG (0,0) []) 0 0 == True
659+
--
660+
-- > path (buildG (0,2) [(0,1), (1,2)]) 0 2 == True
661+
--
662+
-- > path (buildG (0,2) [(0,1), (1,2)]) 2 0 == False
663+
path :: Graph -> Vertex -> Vertex -> Bool
534664
path g v w = w `elem` (reachable g v)
535665

536666
------------------------------------------------------------
@@ -545,7 +675,7 @@ bcc g = (concat . map bicomps . map (do_label g dnum)) forest
545675
where forest = dff g
546676
dnum = preArr (bounds g) forest
547677

548-
do_label :: Graph -> Table Int -> Tree Vertex -> Tree (Vertex,Int,Int)
678+
do_label :: Graph -> Array Vertex Int -> Tree Vertex -> Tree (Vertex,Int,Int)
549679
do_label g dnum (Node v ts) = Node (v,dnum!v,lv) us
550680
where us = map (do_label g dnum) ts
551681
lv = minimum ([dnum!v] ++ [dnum!w | w <- g!v]

0 commit comments

Comments
 (0)