~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/stdlib/doc/src/digraph_utils.xml

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • mto: (3.3.1 squeeze)
  • mto: This revision was merged to the branch mainline in revision 17.
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
<?xml version="1.0" encoding="latin1" ?>
 
2
<!DOCTYPE erlref SYSTEM "erlref.dtd">
 
3
 
 
4
<erlref>
 
5
  <header>
 
6
    <copyright>
 
7
      <year>2000</year>
 
8
      <year>2007</year>
 
9
      <holder>Ericsson AB, All Rights Reserved</holder>
 
10
    </copyright>
 
11
    <legalnotice>
 
12
  The contents of this file are subject to the Erlang Public License,
 
13
  Version 1.1, (the "License"); you may not use this file except in
 
14
  compliance with the License. You should have received a copy of the
 
15
  Erlang Public License along with this software. If not, it can be
 
16
  retrieved online at http://www.erlang.org/.
 
17
 
 
18
  Software distributed under the License is distributed on an "AS IS"
 
19
  basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
20
  the License for the specific language governing rights and limitations
 
21
  under the License.
 
22
 
 
23
  The Initial Developer of the Original Code is Ericsson AB.
 
24
    </legalnotice>
 
25
 
 
26
    <title>digraph_utils</title>
 
27
    <prepared>Hans Bolinder</prepared>
 
28
    <responsible>nobody</responsible>
 
29
    <docno></docno>
 
30
    <approved>nobody</approved>
 
31
    <checked>no</checked>
 
32
    <date>2001-08-27</date>
 
33
    <rev>PA1</rev>
 
34
    <file>digraph_utils.sgml</file>
 
35
  </header>
 
36
  <module>digraph_utils</module>
 
37
  <modulesummary>Algorithms for Directed Graphs</modulesummary>
 
38
  <description>
 
39
    <p>The <c>digraph_utils</c> module implements some algorithms
 
40
      based on depth-first traversal of directed graphs. See the
 
41
      <c>digraph</c> module for basic functions on directed graphs.
 
42
      </p>
 
43
    <p>A <marker id="digraph"></marker><em>directed graph</em> (or 
 
44
       just "digraph") is a pair (V,&nbsp;E) of a finite set V of
 
45
       <marker id="vertex"></marker><em>vertices</em> and a finite set E 
 
46
       of <marker id="edge"></marker><em>directed edges</em> (or just 
 
47
       "edges"). The set of edges E is a subset of V&nbsp;&times;&nbsp;V 
 
48
       (the Cartesian product of V with itself).
 
49
      </p>
 
50
    <p>Digraphs can be annotated with additional information. Such
 
51
      information may be attached to the vertices and to the edges of
 
52
      the digraph. A digraph which has been annotated is called a
 
53
      <em>labeled digraph</em>, and the information attached to a
 
54
      vertex or an edge is called a <marker id="label"></marker>
 
55
      <em>label</em>.</p>
 
56
    <p>An edge e&nbsp;=&nbsp;(v,&nbsp;w) is said 
 
57
      to <marker id="emanate"></marker><em>emanate</em> from vertex v and 
 
58
      to be <marker id="incident"></marker><em>incident</em> on vertex w. 
 
59
      If there is an edge emanating from v and incident on w, then w is 
 
60
      said to be 
 
61
      an <marker id="out_neighbour"></marker><em>out-neighbour</em> of v, 
 
62
      and v is said to be 
 
63
      an <marker id="in_neighbour"></marker><em>in-neighbour</em> of w. 
 
64
      A <marker id="path"></marker><em>path</em> P from v[1] to v[k] in a 
 
65
      digraph (V,&nbsp;E) is a non-empty sequence
 
66
      v[1],&nbsp;v[2],&nbsp;...,&nbsp;v[k] of vertices in V such that
 
67
      there is an edge (v[i],v[i+1]) in E for
 
68
      1&nbsp;&lt;=&nbsp;i&nbsp;&lt;&nbsp;k. 
 
69
      The <marker id="length"></marker><em>length</em> of the path P is k-1. 
 
70
      P is a <marker id="cycle"></marker><em>cycle</em> if the length of P 
 
71
      is not zero and v[1] = v[k]. 
 
72
      A <marker id="loop"></marker><em>loop</em> is a cycle of length one. 
 
73
      An <marker id="acyclic_digraph"></marker><em>acyclic digraph</em> is 
 
74
      a digraph that has no cycles.
 
75
      </p>
 
76
 
 
77
    <p>A <marker id="depth_first_traversal"></marker> <em>depth-first
 
78
      traversal</em> of a directed digraph can be viewed as a process
 
79
      that visits all vertices of the digraph. Initially, all vertices
 
80
      are marked as unvisited. The traversal starts with an
 
81
      arbitrarily chosen vertex, which is marked as visited, and
 
82
      follows an edge to an unmarked vertex, marking that vertex. The
 
83
      search then proceeds from that vertex in the same fashion, until
 
84
      there is no edge leading to an unvisited vertex. At that point
 
85
      the process backtracks, and the traversal continues as long as
 
86
      there are unexamined edges. If there remain unvisited vertices
 
87
      when all edges from the first vertex have been examined, some
 
88
      hitherto unvisited vertex is chosen, and the process is
 
89
      repeated.
 
90
      </p>
 
91
    <p>A <marker id="partial_ordering"></marker><em>partial ordering</em> of 
 
92
      a set S is a transitive, antisymmetric and reflexive relation
 
93
      between the objects of S. The problem 
 
94
      of <marker id="topsort"></marker><em>topological sorting</em> is to 
 
95
      find a total
 
96
      ordering of S that is a superset of the partial ordering. A
 
97
      digraph G&nbsp;=&nbsp;(V,&nbsp;E) is equivalent to a relation E
 
98
      on V (we neglect the fact that the version of directed graphs
 
99
      implemented in the <c>digraph</c> module allows multiple edges
 
100
      between vertices). If the digraph has no cycles of length two or
 
101
      more, then the reflexive and transitive closure of E is a
 
102
      partial ordering.
 
103
      </p>
 
104
    <p>A <marker id="subgraph"></marker><em>subgraph</em> G' of G is a
 
105
      digraph whose vertices and edges form subsets of the vertices
 
106
      and edges of G. G' is <em>maximal</em> with respect to a
 
107
      property P if all other subgraphs that include the vertices of
 
108
      G' do not have the property P. A <marker
 
109
      id="strong_components"></marker> <em>strongly connected
 
110
      component</em> is a maximal subgraph such that there is a path
 
111
      between each pair of vertices. A <marker
 
112
      id="components"></marker><em>connected component</em> is a
 
113
      maximal subgraph such that there is a path between each pair of
 
114
      vertices, considering all edges undirected. An <marker
 
115
      id="arborescence"></marker><em>arborescence</em> is an acyclic
 
116
      digraph with a vertex V, the <marker
 
117
      id="root"></marker><em>root</em>, such that there is a unique
 
118
      path from V to every other vertex of G. A <marker
 
119
      id="tree"></marker><em>tree</em> is an acyclic non-empty digraph
 
120
      such that there is a unique path between every pair of vertices,
 
121
      considering all edges undirected.</p>
 
122
  </description>
 
123
 
 
124
  <funcs>
 
125
    <func>
 
126
      <name>arborescence_root(Digraph) -> no | {yes, Root}</name>
 
127
      <fsummary>Check if a digraph is an arborescence.</fsummary>
 
128
      <type>
 
129
        <v>Digraph = digraph()</v>
 
130
        <v>Root = vertex()</v>
 
131
      </type>
 
132
      <desc>
 
133
 
 
134
        <p>Returns <c>{yes, Root}</c> if <c>Root</c> is 
 
135
          the <seealso marker="#root">root</seealso> of the arborescence
 
136
          <c>Digraph</c>, <c>no</c> otherwise.
 
137
          </p>
 
138
      </desc>
 
139
    </func>
 
140
    <func>
 
141
      <name>components(Digraph) -> [Component]</name>
 
142
      <fsummary>Return the components of a digraph.</fsummary>
 
143
      <type>
 
144
        <v>Digraph = digraph()</v>
 
145
        <v>Component = [vertex()]</v>
 
146
      </type>
 
147
      <desc>
 
148
        <p>Returns a list 
 
149
          of <seealso marker="#components">connected components</seealso>. 
 
150
          Each component is represented by its
 
151
          vertices. The order of the vertices and the order of the
 
152
          components are arbitrary. Each vertex of the digraph
 
153
          <c>Digraph</c> occurs in exactly one component.
 
154
          </p>
 
155
      </desc>
 
156
    </func>
 
157
    <func>
 
158
      <name>condensation(Digraph) -> CondensedDigraph</name>
 
159
      <fsummary>Return a condensed graph of a digraph.</fsummary>
 
160
      <type>
 
161
        <v>Digraph = CondensedDigraph = digraph()</v>
 
162
      </type>
 
163
      <desc>
 
164
        <p>Creates a digraph where the vertices are 
 
165
          the <seealso marker="#strong_components">strongly connected 
 
166
          components</seealso> of <c>Digraph</c> as returned by
 
167
          <c>strong_components/1</c>. If X and Y are strongly
 
168
          connected components, and there exist vertices x and y in X
 
169
          and Y respectively such that there is an 
 
170
          edge <seealso marker="#emanate">emanating</seealso> from x 
 
171
          and <seealso marker="#incident">incident</seealso> on y, then 
 
172
          an edge emanating from X and incident on Y is created.
 
173
          </p>
 
174
        <p>The created digraph has the same type as <c>Digraph</c>.
 
175
          All vertices and edges have the 
 
176
          default <seealso marker="#label">label</seealso> <c>[]</c>.
 
177
          </p>
 
178
        <p>Each and every <seealso marker="#cycle">cycle</seealso> is
 
179
          included in some strongly connected component, which implies
 
180
          that there always exists 
 
181
          a <seealso marker="#topsort">topological ordering</seealso> of the
 
182
          created digraph.</p>
 
183
      </desc>
 
184
    </func>
 
185
    <func>
 
186
      <name>cyclic_strong_components(Digraph) -> [StrongComponent]</name>
 
187
      <fsummary>Return the cyclic strong components of a digraph.</fsummary>
 
188
      <type>
 
189
        <v>Digraph = digraph()</v>
 
190
        <v>StrongComponent = [vertex()]</v>
 
191
      </type>
 
192
      <desc>
 
193
        <p>Returns a list of <seealso marker="#strong_components">strongly 
 
194
          connected components</seealso>. 
 
195
          Each strongly component is represented
 
196
          by its vertices. The order of the vertices and the order of
 
197
          the components are arbitrary. Only vertices that are
 
198
          included in some <seealso marker="#cycle">cycle</seealso> in
 
199
          <c>Digraph</c> are returned, otherwise the returned list is
 
200
          equal to that returned by <c>strong_components/1</c>.
 
201
          </p>
 
202
      </desc>
 
203
    </func>
 
204
    <func>
 
205
      <name>is_acyclic(Digraph) -> bool()</name>
 
206
      <fsummary>Check if a digraph is acyclic.</fsummary>
 
207
      <type>
 
208
        <v>Digraph = digraph()</v>
 
209
      </type>
 
210
      <desc>
 
211
        <p>Returns <c>true</c> if and only if the digraph
 
212
          <c>Digraph</c> is <seealso marker="#acyclic_digraph">acyclic</seealso>.</p>
 
213
      </desc>
 
214
    </func>
 
215
    <func>
 
216
      <name>is_arborescence(Digraph) -> bool()</name>
 
217
      <fsummary>Check if a digraph is an arborescence.</fsummary>
 
218
      <type>
 
219
        <v>Digraph = digraph()</v>
 
220
      </type>
 
221
      <desc>
 
222
        <p>Returns <c>true</c> if and only if the digraph
 
223
          <c>Digraph</c> is 
 
224
          an <seealso marker="#arborescence">arborescence</seealso>.</p>
 
225
      </desc>
 
226
    </func>
 
227
    <func>
 
228
      <name>is_tree(Digraph) -> bool()</name>
 
229
      <fsummary>Check if a digraph is a tree.</fsummary>
 
230
      <type>
 
231
        <v>Digraph = digraph()</v>
 
232
      </type>
 
233
      <desc>
 
234
        <p>Returns <c>true</c> if and only if the digraph
 
235
          <c>Digraph</c> is 
 
236
          a <seealso marker="#tree">tree</seealso>.</p>
 
237
      </desc>
 
238
    </func>
 
239
    <func>
 
240
      <name>loop_vertices(Digraph) -> Vertices</name>
 
241
      <fsummary>Return the vertices of a digraph included in  some loop.</fsummary>
 
242
      <type>
 
243
        <v>Digraph = digraph()</v>
 
244
        <v>Vertices = [vertex()]</v>
 
245
      </type>
 
246
      <desc>
 
247
        <p>Returns a list of all vertices of <c>Digraph</c> that are
 
248
          included in some <seealso marker="#loop">loop</seealso>.</p>
 
249
      </desc>
 
250
    </func>
 
251
    <func>
 
252
      <name>postorder(Digraph) -> Vertices</name>
 
253
      <fsummary>Return the vertices of a digraph in post-order.</fsummary>
 
254
      <type>
 
255
        <v>Digraph = digraph()</v>
 
256
        <v>Vertices = [vertex()]</v>
 
257
      </type>
 
258
      <desc>
 
259
        <p>Returns all vertices of the digraph <c>Digraph</c>. The
 
260
          order is given by 
 
261
          a <seealso marker="#depth_first_traversal">depth-first 
 
262
          traversal</seealso> of the digraph, collecting visited
 
263
          vertices in postorder. More precisely, the vertices visited
 
264
          while searching from an arbitrarily chosen vertex are
 
265
          collected in postorder, and all those collected vertices are
 
266
          placed before the subsequently visited vertices.
 
267
          </p>
 
268
      </desc>
 
269
    </func>
 
270
    <func>
 
271
      <name>preorder(Digraph) -> Vertices</name>
 
272
      <fsummary>Return the vertices of a digraph in pre-order.</fsummary>
 
273
      <type>
 
274
        <v>Digraph = digraph()</v>
 
275
        <v>Vertices = [vertex()]</v>
 
276
      </type>
 
277
      <desc>
 
278
        <p>Returns all vertices of the digraph <c>Digraph</c>. The
 
279
          order is given by 
 
280
          a <seealso marker="#depth_first_traversal">depth-first 
 
281
          traversal</seealso> of the digraph, collecting visited
 
282
          vertices in pre-order.</p>
 
283
      </desc>
 
284
    </func>
 
285
    <func>
 
286
      <name>reachable(Vertices, Digraph) -> Vertices</name>
 
287
      <fsummary>Return the vertices reachable from some vertices of  a digraph.</fsummary>
 
288
      <type>
 
289
        <v>Digraph = digraph()</v>
 
290
        <v>Vertices = [vertex()]</v>
 
291
      </type>
 
292
      <desc>
 
293
        <p>Returns an unsorted list of digraph vertices such that for
 
294
          each vertex in the list, there is 
 
295
          a <seealso marker="#path">path</seealso> in <c>Digraph</c> from some
 
296
          vertex of <c>Vertices</c> to the vertex. In particular,
 
297
          since paths may have length zero, the vertices of
 
298
          <c>Vertices</c> are included in the returned list.
 
299
          </p>
 
300
      </desc>
 
301
    </func>
 
302
    <func>
 
303
      <name>reachable_neighbours(Vertices, Digraph) -> Vertices</name>
 
304
      <fsummary>Return the neighbours reachable from some vertices of  a digraph.</fsummary>
 
305
      <type>
 
306
        <v>Digraph = digraph()</v>
 
307
        <v>Vertices = [vertex()]</v>
 
308
      </type>
 
309
      <desc>
 
310
        <p>Returns an unsorted list of digraph vertices such that for
 
311
          each vertex in the list, there is 
 
312
          a <seealso marker="#path">path</seealso> in <c>Digraph</c> of length
 
313
          one or more from some vertex of <c>Vertices</c> to the
 
314
          vertex. As a consequence, only those vertices 
 
315
          of <c>Vertices</c> that are included in 
 
316
          some <seealso marker="#cycle">cycle</seealso> are returned.
 
317
          </p>
 
318
      </desc>
 
319
    </func>
 
320
    <func>
 
321
      <name>reaching(Vertices, Digraph) -> Vertices</name>
 
322
      <fsummary>Return the vertices that reach some vertices of  a digraph.</fsummary>
 
323
      <type>
 
324
        <v>Digraph = digraph()</v>
 
325
        <v>Vertices = [vertex()]</v>
 
326
      </type>
 
327
      <desc>
 
328
        <p>Returns an unsorted list of digraph vertices such that for
 
329
          each vertex in the list, there is 
 
330
          a <seealso marker="#path">path</seealso> from the vertex to some 
 
331
          vertex of <c>Vertices</c>. In particular, since paths may have
 
332
          length zero, the vertices of <c>Vertices</c> are included in
 
333
          the returned list.
 
334
          </p>
 
335
      </desc>
 
336
    </func>
 
337
    <func>
 
338
      <name>reaching_neighbours(Vertices, Digraph) -> Vertices</name>
 
339
      <fsummary>Return the neighbours that reach some vertices of  a digraph.</fsummary>
 
340
      <type>
 
341
        <v>Digraph = digraph()</v>
 
342
        <v>Vertices = [vertex()]</v>
 
343
      </type>
 
344
      <desc>
 
345
        <p>Returns an unsorted list of digraph vertices such that for
 
346
          each vertex in the list, there is 
 
347
          a <seealso marker="#path">path</seealso> of length one or more 
 
348
          from the vertex to some vertex of <c>Vertices</c>. As a consequence,
 
349
          only those vertices of <c>Vertices</c> that are included in
 
350
          some <seealso marker="#cycle">cycle</seealso> are returned.
 
351
          </p>
 
352
      </desc>
 
353
    </func>
 
354
    <func>
 
355
      <name>strong_components(Digraph) -> [StrongComponent]</name>
 
356
      <fsummary>Return the strong components of a digraph.</fsummary>
 
357
      <type>
 
358
        <v>Digraph = digraph()</v>
 
359
        <v>StrongComponent = [vertex()]</v>
 
360
      </type>
 
361
      <desc>
 
362
        <p>Returns a list of <seealso marker="#strong_components">strongly 
 
363
          connected components</seealso>. 
 
364
          Each strongly component is represented
 
365
          by its vertices. The order of the vertices and the order of
 
366
          the components are arbitrary. Each vertex of the digraph
 
367
          <c>Digraph</c> occurs in exactly one strong component.
 
368
          </p>
 
369
      </desc>
 
370
    </func>
 
371
    <func>
 
372
      <name>subgraph(Digraph, Vertices [, Options]) ->  Subgraph | {error, Reason}</name>
 
373
      <fsummary>Return a subgraph of a digraph.</fsummary>
 
374
      <type>
 
375
        <v>Digraph = Subgraph = digraph()</v>
 
376
        <v>Options = [{type, SubgraphType}, {keep_labels, bool()}]</v>
 
377
        <v>Reason = {invalid_option, term()} | {unknown_type, term()}</v>
 
378
        <v>SubgraphType = inherit | type()</v>
 
379
        <v>Vertices = [vertex()]</v>
 
380
      </type>
 
381
      <desc>
 
382
        <p>Creates a maximal <seealso marker="#subgraph">subgraph</seealso> of <c>Digraph</c> having
 
383
          as vertices those vertices of <c>Digraph</c> that are
 
384
          mentioned in <c>Vertices</c>.
 
385
          </p>
 
386
        <p>If the value of the option <c>type</c> is <c>inherit</c>,
 
387
          which is the default, then the type of <c>Digraph</c> is used 
 
388
          for the subgraph as well. Otherwise the option value of <c>type</c>
 
389
          is used as argument to <c>digraph:new/1</c>.
 
390
          </p>
 
391
        <p>If the value of the option <c>keep_labels</c> is <c>true</c>,
 
392
          which is the default, then 
 
393
          the <seealso marker="#label">labels</seealso> of vertices and edges
 
394
          of <c>Digraph</c> are used for the subgraph as well. If the value
 
395
          is <c>false</c>, then the default label, <c>[]</c>, is used
 
396
          for the subgraph's vertices and edges.
 
397
          </p>
 
398
        <p><c>subgraph(Digraph, Vertices)</c> is equivalent to
 
399
          <c>subgraph(Digraph, Vertices, [])</c>.
 
400
          </p>
 
401
      </desc>
 
402
    </func>
 
403
    <func>
 
404
      <name>topsort(Digraph) -> Vertices | false</name>
 
405
      <fsummary>Return a topological sorting of the vertices of  a digraph.</fsummary>
 
406
      <type>
 
407
        <v>Digraph = digraph()</v>
 
408
        <v>Vertices = [vertex()]</v>
 
409
      </type>
 
410
      <desc>
 
411
        <p>Returns a <seealso marker="#topsort">topological 
 
412
          ordering</seealso> of the vertices of the digraph
 
413
          <c>Digraph</c> if such an ordering exists, <c>false</c>
 
414
          otherwise. For each vertex in the returned list, there are
 
415
          no <seealso marker="#out_neighbour">out-neighbours</seealso>
 
416
          that occur earlier in the list.</p>
 
417
      </desc>
 
418
    </func>
 
419
  </funcs>
 
420
 
 
421
  <section>
 
422
    <title>See Also</title>
 
423
    <p><seealso marker="digraph">digraph(3)</seealso></p>
 
424
  </section>
 
425
</erlref>
 
426