File: DFS.hs

package info (click to toggle)
haskell-fgl 5.8.3.0-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 348 kB
  • sloc: haskell: 3,121; makefile: 3
file content (249 lines) | stat: -rw-r--r-- 7,730 bytes parent folder | download | duplicates (3)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
-- (c) 2000 - 2005 by Martin Erwig [see file COPYRIGHT]

-- | Depth-first search algorithms.
--
-- Names consist of:
--
--   1. 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
--
--   2. "df" for depth-first
--   3. A structure parameter, specifying the type of the result.
--
--       [@s@] Flat list of results
--       [@f@] Structured 'Tree' of results
--
--   4. An optional \"With\", which instead of putting the found nodes directly
--      into the result, adds the result of a computation on them into it.
--   5. An optional prime character, in which case all nodes of the graph will
--      be visited, instead of a user-given subset.
module Data.Graph.Inductive.Query.DFS (

    CFun,

    -- * Standard
    dfs, dfs', dff, dff',
    dfsWith,  dfsWith', dffWith, dffWith',
    xdfsWith, xdfWith, xdffWith,

    -- * Undirected
    udfs, udfs', udff, udff',
    udffWith, udffWith',

    -- * Reversed
    rdff, rdff', rdfs, rdfs',
    rdffWith, rdffWith',

    -- * Applications of depth first search/forest
    topsort, topsort', scc, reachable,

    -- * Applications of undirected depth first search/forest
    components, noComponents, isConnected, condensation

) where

import Data.Graph.Inductive.Basic
import Data.Graph.Inductive.Graph
import Data.Tree
import qualified Data.Map as Map
import Control.Monad (liftM2)
import Data.Tuple (swap)


-- | Many functions take a list of nodes to visit as an explicit argument.
--   fixNodes is a convenience function that adds all the nodes present in a
--   graph as that list.
fixNodes :: (Graph gr) => ([Node] -> gr a b -> c) -> gr a b -> c
fixNodes f g = f (nodes g) g


type CFun a b c = Context a b -> c

-- | Most general DFS algorithm to create a list of results. The other
--   list-returning functions such as 'dfs' are all defined in terms of this
--   one.
--
-- @
-- 'xdfsWith' d f vs = 'preorderF' . 'xdffWith' d f vs
-- @
xdfsWith :: (Graph gr)
    => CFun a b [Node] -- ^ Mapping from a node to its neighbours to be visited
                       --   as well. 'suc'' for example makes 'xdfsWith'
                       --   traverse the graph following the edge directions,
                       --   while 'pre'' means reversed directions.
    -> CFun a b c      -- ^ Mapping from the 'Context' of a node to a result
                       --   value.
    -> [Node]          -- ^ Nodes to be visited.
    -> gr a b
    -> [c]
xdfsWith _ _ []     _             = []
xdfsWith _ _ _      g | isEmpty g = []
xdfsWith d f (v:vs) g = case match v g of
                         (Just c,g')  -> f c:xdfsWith d f (d c++vs) g'
                         (Nothing,g') -> xdfsWith d f vs g'


-- | Depth-first search.
dfs :: (Graph gr) => [Node] -> gr a b -> [Node]
dfs = dfsWith node'

dfsWith :: (Graph gr) => CFun a b c -> [Node] -> gr a b -> [c]
dfsWith = xdfsWith suc'

dfsWith' :: (Graph gr) => CFun a b c -> gr a b -> [c]
dfsWith' f = fixNodes (dfsWith f)

dfs' :: (Graph gr) => gr a b -> [Node]
dfs' = dfsWith' node'


-- | Undirected depth-first search, obtained by following edges regardless
--   of their direction.
udfs :: (Graph gr) => [Node] -> gr a b -> [Node]
udfs = xdfsWith neighbors' node'

udfs' :: (Graph gr) => gr a b -> [Node]
udfs' = fixNodes udfs


-- | Reverse depth-first search, obtained by following predecessors.
rdfs :: (Graph gr) => [Node] -> gr a b -> [Node]
rdfs = xdfsWith pre' node'

rdfs' :: (Graph gr) => gr a b -> [Node]
rdfs' = fixNodes rdfs


-- | Most general DFS algorithm to create a forest of results, otherwise very
--   similar to 'xdfsWith'. The other forest-returning functions such as 'dff'
--   are all defined in terms of this one.
xdfWith :: (Graph gr)
    => CFun a b [Node]
    -> CFun a b c
    -> [Node]
    -> gr a b
    -> ([Tree c],gr a b)
xdfWith _ _ []     g             = ([],g)
xdfWith _ _ _      g | isEmpty g = ([],g)
xdfWith d f (v:vs) g = case match v g of
                        (Nothing,g1) -> xdfWith d f vs g1
                        (Just c,g1)  -> (Node (f c) ts:ts',g3)
                                 where (ts,g2)  = xdfWith d f (d c) g1
                                       (ts',g3) = xdfWith d f vs g2

-- | Discard the graph part of the result of 'xdfWith'.
--
-- @
-- xdffWith d f vs g = fst (xdfWith d f vs g)
-- @
xdffWith :: (Graph gr)
    => CFun a b [Node]
    -> CFun a b c
    -> [Node]
    -> gr a b
    -> [Tree c]
xdffWith d f vs g = fst (xdfWith d f vs g)



-- | Directed depth-first forest.
dff :: (Graph gr) => [Node] -> gr a b -> [Tree Node]
dff = dffWith node'

dffWith :: (Graph gr) => CFun a b c -> [Node] -> gr a b -> [Tree c]
dffWith = xdffWith suc'

dffWith' :: (Graph gr) => CFun a b c -> gr a b -> [Tree c]
dffWith' f = fixNodes (dffWith f)

dff' :: (Graph gr) => gr a b -> [Tree Node]
dff' = dffWith' node'



-- | Undirected depth-first forest, obtained by following edges regardless
--   of their direction.
udff :: (Graph gr) => [Node] -> gr a b -> [Tree Node]
udff = udffWith node'

udffWith :: (Graph gr) => CFun a b c -> [Node] -> gr a b -> [Tree c]
udffWith = xdffWith neighbors'

udffWith' :: (Graph gr) => CFun a b c -> gr a b -> [Tree c]
udffWith' f = fixNodes (udffWith f)

udff' :: (Graph gr) => gr a b -> [Tree Node]
udff' = udffWith' node'


-- | Reverse depth-first forest, obtained by following predecessors.
rdff :: (Graph gr) => [Node] -> gr a b -> [Tree Node]
rdff = rdffWith node'

rdffWith :: (Graph gr) => CFun a b c -> [Node] -> gr a b -> [Tree c]
rdffWith = xdffWith pre'

rdffWith' :: (Graph gr) => CFun a b c -> gr a b -> [Tree c]
rdffWith' f = fixNodes (rdffWith f)

rdff' :: (Graph gr) => gr a b -> [Tree Node]
rdff' = rdffWith' node'


----------------------------------------------------------------------
-- ALGORITHMS BASED ON DFS
----------------------------------------------------------------------

-- | Collection of connected components
components :: (Graph gr) => gr a b -> [[Node]]
components = map preorder . udff'

-- | Number of connected components
noComponents :: (Graph gr) => gr a b -> Int
noComponents = length . components

-- | Is the graph connected?
isConnected :: (Graph gr) => gr a b -> Bool
isConnected = (==1) . noComponents

-- | Flatten a 'Tree' in reverse order
postflatten :: Tree a -> [a]
postflatten (Node v ts) = postflattenF ts ++ [v]

-- | Flatten a forest in reverse order
postflattenF :: [Tree a] -> [a]
postflattenF = concatMap postflatten

-- | <http://en.wikipedia.org/wiki/Topological_sorting Topological sorting>,
--   i.e. a list of 'Node's so that if there's an edge between a source and a
--   target node, the source appears earlier in the result.
topsort :: (Graph gr) => gr a b -> [Node]
topsort = reverse . postflattenF . dff'

-- | 'topsort', returning only the labels of the nodes.
topsort' :: (Graph gr) => gr a b -> [a]
topsort' = reverse . postorderF . dffWith' lab'

-- | Collection of strongly connected components
scc :: (Graph gr) => gr a b -> [[Node]]
scc g = map preorder (rdff (topsort g) g)

-- | Collection of nodes reachable from a starting point.
reachable :: (Graph gr) => Node -> gr a b -> [Node]
reachable v g = preorderF (dff [v] g)

-- | The condensation of the given graph, i.e., the graph of its
-- strongly connected components.
condensation :: Graph gr => gr a b -> gr [Node] ()
condensation gr = mkGraph vs es
  where
    sccs = scc gr
    vs = zip [1..] sccs
    vMap = Map.fromList $ map swap vs

    getN = (vMap Map.!)
    es = [ (getN c1, getN c2, ()) | c1 <- sccs, c2 <- sccs
                                  , (c1 /= c2) && any (hasEdge gr) (liftM2 (,) c1 c2) ]