YAP 7.1.0
dgraphs.yap
Go to the documentation of this file.
1/**
2 * @file dgraphs.yap
3 * @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
4 * @date Tue Nov 17 01:23:20 2015
5 *
6 * @brief Directed Graph Processing Utilities.
7 *
8 *
9*/
10
11:- module( dgraphs,
12 [
30 dgraph_compose/3,
43 ]).
44
45/** @defgroup dgraphs Directed Graphs
46@ingroup YAPLibrary
47@{
48
49The following graph manipulation routines use the red-black tree library
50to try to avoid linear-time scans of the graph for all graph
51operations. Graphs are represented as a red-black tree, where the key is
52the vertex, and the associated value is a list of vertices reachable
53from that vertex through an edge (ie, a list of edges).
54
55*/
56
57
58/** @pred dgraph_new(+ _Graph_)
59
60
61Create a new directed graph. This operation must be performed before
62trying to use the graph.
63
64
65*/
66:- rb_new/1reexport(library(rbtrees),
67 [ as dgraph_new]).
68
70 [,
71 ,
72 ,
73 ,
74 ,
75 ,
76 ,
77 ,
78 ,
79 ,
80 ]).
81
83 [,
84 ,
85 ,
86 ,
87 ]).
88
89:- dgraph_to_wdgraph/2wdgraph_min_path/5wdgraph_max_path/5wdgraph_min_paths/3use_module(library(wdgraphs),
90 [,
91 ,
92 ,
93 ]).
94
95
96/** @pred dgraph_add_edge(+ _Graph_, + _N1_, + _N2_, - _NewGraph_)
97
98
99Unify _NewGraph_ with a new graph obtained by adding the edge
100 _N1_- _N2_ to the graph _Graph_.
101
102
103*/
104dgraph_add_edge(Vs0,V1,V2,Vs2) :-
105 dgraph_new_edge(V1,V2,Vs0,Vs1),
106 dgraph_add_vertex(Vs1,V2,Vs2).
107
108
109/** @pred dgraph_add_edges(+ _Graph_, + _Edges_, - _NewGraph_)
110
111
112Unify _NewGraph_ with a new graph obtained by adding the list of
113edges _Edges_ to the graph _Graph_.
114
115
116*/
117dgraph_add_edges(V0, Edges, VF) :-
118 rb_empty(V0), rb_empty,
119 sort(Edges,SortedEdges),
120 all_vertices_in_edges(SortedEdges,Vertices),
121 sort(Vertices,SortedVertices),
122 edges2graphl(SortedVertices, SortedEdges, GraphL),
123 ord_list_to_rbtree(GraphL, VF).
124dgraph_add_edges(G0, Edges, GF) :-
125 sort(Edges,SortedEdges),
126 all_vertices_in_edges(SortedEdges,Vertices),
127 sort(Vertices,SortedVertices),
128 dgraph_add_edges(SortedVertices,SortedEdges, G0, GF).
129
130all_vertices_in_edges([],[]).
131all_vertices_in_edges([V1-V2|Edges],[V1,V2|Vertices]) :-
132 all_vertices_in_edges(Edges,Vertices).
133
134edges2graphl([], [], []).
135edges2graphl([V|Vertices], [VV-V1|SortedEdges], [V-[V1|Children]|GraphL]) :-
136 V == VV, edges2graphl,
137 get_extra_children(SortedEdges,VV,Children,RemEdges),
138 edges2graphl(Vertices, RemEdges, GraphL).
139edges2graphl([V|Vertices], SortedEdges, [V-[]|GraphL]) :-
140 edges2graphl(Vertices, SortedEdges, GraphL).
141
142
143dgraph_add_edges([],[]) --> [].
144dgraph_add_edges([V|Vs],[V0-V1|Es]) --> { V == V0 }, ,
145 { get_extra_children(Es,V,Children,REs) },
146 dgraph_update_vertex(V,[V1|Children]),
147 dgraph_add_edges(Vs,REs).
148dgraph_add_edges([V|Vs],Es) --> dgraph_add_edges,
149 dgraph_update_vertex(V,[]),
150 dgraph_add_edges(Vs,Es).
151
152get_extra_children([V-C|Es],VV,[C|Children],REs) :- V == VV, get_extra_children,
153 get_extra_children(Es,VV,Children,REs).
154get_extra_children(Es,_,[],Es).
155
156dgraph_update_vertex(V,Children, Vs0, Vs) :-
157 rb_apply(Vs0, V, add_edges(Children), Vs), rb_apply.
158dgraph_update_vertex(V,Children, Vs0, Vs) :-
159 rb_insert(Vs0,V,Children,Vs).
160
161add_edges(E0,E1,E) :-
162 ord_union(E0,E1,E).
163
164dgraph_new_edge(V1,V2,Vs0,Vs) :-
165 rb_apply(Vs0, V1, insert_edge(V2), Vs), rb_apply.
166dgraph_new_edge(V1,V2,Vs0,Vs) :-
167 rb_insert(Vs0,V1,[V2],Vs).
168
169insert_edge(V2, Children0, Children) :-
170 ord_insert(Children0,V2,Children).
171
172/** @pred dgraph_add_vertices(+ _Graph_, + _Vertices_, - _NewGraph_)
173
174
175Unify _NewGraph_ with a new graph obtained by adding the list of
176vertices _Vertices_ to the graph _Graph_.
177
178
179*/
180dgraph_add_vertices(G, [], G).
181dgraph_add_vertices(G0, [V|Vs], GF) :-
182 dgraph_add_vertex(G0, V, G1),
183 dgraph_add_vertices(G1, Vs, GF).
184
185
186/** @pred dgraph_add_vertex(+ _Graph_, + _Vertex_, - _NewGraph_)
187
188Unify _NewGraph_ with a new graph obtained by adding
189vertex _Vertex_ to the graph _Graph_.
190
191
192*/
193dgraph_add_vertex(Vs0, V, Vs0) :-
194 rb_lookup(V,_,Vs0), rb_lookup.
195dgraph_add_vertex(Vs0, V, Vs) :-
196 rb_insert(Vs0, V, [], Vs).
197
198
199/** @pred dgraph_edges(+ _Graph_, - _Edges_)
200
201
202Unify _Edges_ with all edges appearing in graph
203 _Graph_.
204
205
206*/
207dgraph_edges(Vs,Edges) :-
208 rb_visit(Vs,L0),
209 cvt2edges(L0,Edges).
210
211/** @pred dgraph_vertices(+ _Graph_, - _Vertices_)
212
213
214Unify _Vertices_ with all vertices appearing in graph
215 _Graph_.
216
217*/
218dgraph_vertices(Vs,Vertices) :-
219 rb_keys(Vs,Vertices).
220
221cvt2edges([],[]).
222cvt2edges([V-Children|L0],Edges) :-
223 children2edges(Children,V,Edges,Edges0),
224 cvt2edges(L0,Edges0).
225
226children2edges([],_,Edges,Edges).
227children2edges([Child|L0],V,[V-Child|EdgesF],Edges0) :-
228 children2edges(L0,V,EdgesF,Edges0).
229
230/** @pred dgraph_neighbours(+ _Vertex_, + _Graph_, - _Vertices_)
231
232
233Unify _Vertices_ with the list of neighbours of vertex _Vertex_
234in _Graph_.
235
236
237*/
238dgraph_neighbours(V,Vertices,Children) :-
239 rb_lookup(V,Children,Vertices).
240
241/** @pred dgraph_neighbors(+ _Vertex_, + _Graph_, - _Vertices_)
242
243
244Unify _Vertices_ with the list of neighbors of vertex _Vertex_
245in _Graph_. If the vertice is not in the graph fail.
246
247
248*/
249dgraph_neighbors(V,Vertices,Children) :-
250 rb_lookup(V,Children,Vertices).
251
252add_vertices(Graph, [], Graph).
253add_vertices(Graph, [V|Vertices], NewGraph) :-
254 rb_insert(Graph, V, [], IntGraph),
255 add_vertices(IntGraph, Vertices, NewGraph).
256
257/** @pred dgraph_complement(+ _Graph_, - _NewGraph_)
258
259
260Unify _NewGraph_ with the graph complementary to _Graph_.
261
262
263*/
264dgraph_complement(Vs0,VsF) :-
265 dgraph_vertices(Vs0,Vertices),
266 rb_map(Vs0,complement(Vertices),VsF).
267
268complement(Vs,Children,NewChildren) :-
269 ord_subtract(Vs,Children,NewChildren).
270
271/** @pred dgraph_del_edge(+ _Graph_, + _N1_, + _N2_, - _NewGraph_)
272
273
274Succeeds if _NewGraph_ unifies with a new graph obtained by
275removing the edge _N1_- _N2_ from the graph _Graph_. Notice
276that no vertices are deleted.
277
278
279*/
280dgraph_del_edge(Vs0,V1,V2,Vs1) :-
281 rb_apply(Vs0, V1, delete_edge(V2), Vs1).
282
283/** @pred dgraph_del_edges(+ _Graph_, + _Edges_, - _NewGraph_)
284
285
286Unify _NewGraph_ with a new graph obtained by removing the list of
287edges _Edges_ from the graph _Graph_. Notice that no vertices
288are deleted.
289
290
291*/
292dgraph_del_edges(G0, Edges, Gf) :-
293 sort(Edges,SortedEdges),
294 continue_del_edges(SortedEdges, G0, Gf).
295
296continue_del_edges([]) --> [].
297continue_del_edges([V-V1|Es]) --> continue_del_edges,
298 { get_extra_children(Es,V,Children,REs) },
299 contract_vertex(V,[V1|Children]),
300 continue_del_edges(REs).
301
302contract_vertex(V,Children, Vs0, Vs) :-
303 rb_apply(Vs0, V, del_edges(Children), Vs).
304
305del_edges(ToRemove,E0,E) :-
306 ord_subtract(E0,ToRemove,E).
307
308/** @pred dgraph_del_vertex(+ _Graph_, + _Vertex_, - _NewGraph_)
309
310
311Unify _NewGraph_ with a new graph obtained by deleting vertex
312 _Vertex_ and all the edges that start from or go to _Vertex_ to
313the graph _Graph_.
314
315
316*/
317dgraph_del_vertex(Vs0, V, Vsf) :-
318 rb_delete(Vs0, V, Vs1),
319 rb_map(Vs1, delete_edge(V), Vsf).
320
321delete_edge(Edges0, V, Edges) :-
322 ord_del_element(Edges0, V, Edges).
323
324/** @pred dgraph_del_vertices(+ _Graph_, + _Vertices_, - _NewGraph_)
325
326
327Unify _NewGraph_ with a new graph obtained by deleting the list of
328vertices _Vertices_ and all the edges that start from or go to a
329vertex in _Vertices_ to the graph _Graph_.
330
331
332*/
333dgraph_del_vertices(G0, Vs, GF) :-
334 sort(Vs,SortedVs),
335 delete_all(SortedVs, G0, G1),
336 delete_remaining_edges(SortedVs, G1, GF).
337
338% it would be nice to be able to delete a set of elements from an RB tree
339% but I don't how to do it yet.
340delete_all([]) --> [].
341delete_all([V|Vs],Vs0,Vsf) :-
342 rb_delete(Vs0, V, Vsi),
343 delete_all(Vs,Vsi,Vsf).
344
345delete_remaining_edges(SortedVs,Vs0,Vsf) :-
346 rb_map(Vs0, del_edges(SortedVs), Vsf).
347
348/** @pred dgraph_transpose(+ _Graph_, - _Transpose_)
349
350
351Unify _NewGraph_ with a new graph obtained from _Graph_ by
352replacing all edges of the form _V1-V2_ by edges of the form
353 _V2-V1_.
354
355
356*/
357dgraph_transpose(Graph, TGraph) :-
358 rb_visit(Graph, Edges),
359 transpose(Edges, Nodes, TEdges, []),
360 dgraph_new(G0),
361 % make sure we have all vertices, even if they are unconnected.
362 dgraph_add_vertices(G0, Nodes, G1),
363 dgraph_add_edges(G1, TEdges, TGraph).
364
365transpose([], []) --> [].
366transpose([V-Edges|MoreVs], [V|Vs]) -->
367 transpose_edges(Edges, V),
368 transpose(MoreVs, Vs).
369
370transpose_edges([], _V) --> [].
371transpose_edges(E.Edges, V) -->
372 [E-V],
373 transpose_edges(Edges, V).
374
375dgraph_compose(T1,T2,CT) :-
376 rb_visit(T1,Nodes),
377 compose(Nodes,T2,NewNodes),
378 dgraph_new(CT0),
379 dgraph_add_edges(CT0,NewNodes,CT).
380
381compose([],_,[]).
382compose([V-Children|Nodes],T2,NewNodes) :-
383 compose2(Children,V,T2,NewNodes,NewNodes0),
384 compose(Nodes,T2,NewNodes0).
385
386compose2([],_,_,NewNodes,NewNodes).
387compose2([C|Children],V,T2,NewNodes,NewNodes0) :-
388 rb_lookup(C, GrandChildren, T2),
389 compose3(GrandChildren, V, NewNodes,NewNodesI),
390 compose2(Children,V,T2,NewNodesI,NewNodes0).
391
392compose3([], _, NewNodes, NewNodes).
393compose3([GC|GrandChildren], V, [V-GC|NewNodes], NewNodes0) :-
394 compose3(GrandChildren, V, NewNodes, NewNodes0).
395
396/** @pred dgraph_transitive_closure(+ _Graph_, - _Closure_)
397
398
399Unify _Closure_ with the transitive closure of graph _Graph_.
400
401
402*/
403dgraph_transitive_closure(G,Closure) :-
404 dgraph_edges(G,Edges),
405 continue_closure(Edges,G,Closure).
406
407continue_closure([], Closure, Closure) :- continue_closure.
408continue_closure(Edges, G, Closure) :-
409 transit_graph(Edges,G,NewEdges),
410 dgraph_add_edges(G, NewEdges, GN),
411 continue_closure(NewEdges, GN, Closure).
412
413transit_graph([],_,[]).
414transit_graph([V-V1|Edges],G,NewEdges) :-
415 rb_lookup(V1, GrandChildren, G),
416 transit_graph2(GrandChildren, V, G, NewEdges, MoreEdges),
417 transit_graph(Edges, G, MoreEdges).
418
419transit_graph2([], _, _, NewEdges, NewEdges).
420transit_graph2([GC|GrandChildren], V, G, NewEdges, MoreEdges) :-
421 is_edge(V,GC,G), is_edge,
422 transit_graph2(GrandChildren, V, G, NewEdges, MoreEdges).
423transit_graph2([GC|GrandChildren], V, G, [V-GC|NewEdges], MoreEdges) :-
424 transit_graph2(GrandChildren, V, G, NewEdges, MoreEdges).
425
426is_edge(V1,V2,G) :-
427 rb_lookup(V1,Children,G),
428 ord_memberchk(V2, Children).
429
430/** @pred dgraph_symmetric_closure(+ _Graph_, - _Closure_)
431
432
433Unify _Closure_ with the symmetric closure of graph _Graph_,
434that is, if _Closure_ contains an edge _U-V_ it must also
435contain the edge _V-U_.
436
437
438*/
440 dgraph_edges(G, Edges),
441 invert_edges(Edges, InvertedEdges),
442 dgraph_add_edges(G, InvertedEdges, S).
443
444invert_edges([], []).
445invert_edges([V1-V2|Edges], [V2-V1|InvertedEdges]) :-
446 invert_edges(Edges, InvertedEdges).
447
448/** @pred dgraph_top_sort(+ _Graph_, - _Vertices_)
449
450
451Unify _Vertices_ with the topological sort of graph _Graph_.
452
453
454*/
455dgraph_top_sort(G, Q) :-
456 dgraph_top_sort(G, Q, []).
457
458/** @pred dgraph_top_sort(+ _Graph_, - _Vertices_, ? _Vertices0_)
459
460Unify the difference list _Vertices_- _Vertices0_ with the
461topological sort of graph _Graph_.
462
463
464*/
465dgraph_top_sort(G, Q, RQ0) :-
466 % O(E)
467 rb_visit(G, Vs),
468 % O(E)
469 invert_and_link(Vs, Links, UnsortedInvertedEdges, AllVs, Q),
470 % O(V)
471 rb_clone(G, LinkedG, Links),
472 % O(Elog(E))
473 sort(UnsortedInvertedEdges, InvertedEdges),
474 % O(E)
475 dgraph_vertices(G, AllVs),
476 start_queue(AllVs, InvertedEdges, Q, RQ),
477 continue_queue(Q, LinkedG, RQ, RQ0).
478
479invert_and_link([], [], [], [], []).
480invert_and_link([V-Vs|Edges], [V-NVs|ExtraEdges], UnsortedInvertedEdges, [V|AllVs],[_|Q]) :-
481 inv_links(Vs, NVs, V, UnsortedInvertedEdges, UnsortedInvertedEdges0),
482 invert_and_link(Edges, ExtraEdges, UnsortedInvertedEdges0, AllVs, Q).
483
484inv_links([],[],_,UnsortedInvertedEdges,UnsortedInvertedEdges).
485inv_links([V2|Vs],[l(V2,A,B,S,E)|VLnks],V1,[V2-e(A,B,S,E)|UnsortedInvertedEdges],UnsortedInvertedEdges0) :-
486 inv_links(Vs,VLnks,V1,UnsortedInvertedEdges,UnsortedInvertedEdges0).
487
488dup([], []).
489dup([_|AllVs], [_|Q]) :-
490 dup(AllVs, Q).
491
492start_queue([], [], RQ, RQ).
493start_queue([V|AllVs], [VV-e(S,B,S,E)|InvertedEdges], Q, RQ) :- V == VV, start_queue,
494 link_edges(InvertedEdges, VV, B, S, E, RemainingEdges),
495 start_queue(AllVs, RemainingEdges, Q, RQ).
496start_queue([V|AllVs], InvertedEdges, [V|Q], RQ) :-
497 start_queue(AllVs, InvertedEdges, Q, RQ).
498
499link_edges([V-e(A,B,S,E)|InvertedEdges], VV, A, S, E, RemEdges) :- V == VV, link_edges,
500 link_edges(InvertedEdges, VV, B, S, E, RemEdges).
501link_edges(RemEdges, _, A, _, A, RemEdges).
502
503continue_queue([], _, RQ0, RQ0).
504continue_queue([V|Q], LinkedG, RQ, RQ0) :-
505 rb_lookup(V, Links, LinkedG),
506 close_links(Links, RQ, RQI),
507 % not clear whether I should deleted V from LinkedG
508 continue_queue(Q, LinkedG, RQI, RQ0).
509
510close_links([], RQ, RQ).
511close_links([l(V,A,A,S,E)|Links], RQ, RQ0) :-
512 ( S == E -> RQ = [V| RQ1] ; RQ = RQ1),
513 close_links(Links, RQ1, RQ0).
514
515/** @pred ugraph_to_dgraph( +_UGraph_, -_Graph_)
516
517
518Unify _Graph_ with the directed graph obtain from _UGraph_,
519represented in the form used in the _ugraphs_ unweighted graphs
520library.
521
522*/
523ugraph_to_dgraph(UG, DG) :-
524 ord_list_to_rbtree(UG, DG).
525
526/** @pred dgraph_to_ugraph(+ _Graph_, - _UGraph_)
527
528
529Unify _UGraph_ with the representation used by the _ugraphs_
530unweighted graphs library, that is, a list of the form
531 _V-Neighbors_, where _V_ is a node and _Neighbors_ the nodes
532children.
533
534*/
535dgraph_to_ugraph(DG, UG) :-
536 rb_visit(DG, UG).
537
538/** @pred dgraph_edge(+ _N1_, + _N2_, + _Graph_)
539
540
541Edge _N1_- _N2_ is an edge in directed graph _Graph_.
542
543
544*/
545dgraph_edge(N1, N2, G) :-
546 rb_lookup(N1, Ns, G),
547 ord_memberchk(N2, Ns).
548
549/** @pred dgraph_min_path(+ _V1_, + _V1_, + _Graph_, - _Path_, ? _Costt_)
550
551
552Unify the list _Path_ with the minimal cost path between nodes
553 _N1_ and _N2_ in graph _Graph_. Path _Path_ has cost
554 _Cost_.
555
556
557*/
558dgraph_min_path(V1, V2, Graph, Path, Cost) :-
559 dgraph_to_wdgraph(Graph, WGraph),
560 wdgraph_min_path(V1, V2, WGraph, Path, Cost).
561
562/** @pred dgraph_max_path(+ _V1_, + _V1_, + _Graph_, - _Path_, ? _Costt_)
563
564
565Unify the list _Path_ with the maximal cost path between nodes
566 _N1_ and _N2_ in graph _Graph_. Path _Path_ has cost
567 _Cost_.
568
569
570*/
571dgraph_max_path(V1, V2, Graph, Path, Cost) :-
572 dgraph_to_wdgraph(Graph, WGraph),
573 wdgraph_max_path(V1, V2, WGraph, Path, Cost).
574
575/** @pred dgraph_min_paths(+ _V1_, + _Graph_, - _Paths_)
576
577
578Unify the list _Paths_ with the minimal cost paths from node
579 _N1_ to the nodes in graph _Graph_.
580
581
582*/
583dgraph_min_paths(V1, Graph, Paths) :-
584 dgraph_to_wdgraph(Graph, WGraph),
585 wdgraph_min_paths(V1, WGraph, Paths).
586
587/** @pred dgraph_path(+ _Vertex_, + _Vertex1_, + _Graph_, ? _Path_)
588
589The path _Path_ is a path starting at vertex _Vertex_ in graph
590 _Graph_ and ending at path _Vertex2_.
591
592
593*/
594dgraph_path(V1, V2, Graph, Path) :-
595 rb_new(E0),
596 rb_lookup(V1, Children, Graph),
597 dgraph_path_children(Children, V2, E0, Graph, Path).
598
599dgraph_path_children([V1|_], V2, _E1, _Graph, []) :- V1 == V2.
600dgraph_path_children([V1|_], V2, E1, Graph, [V1|Path]) :-
601 V2 \== V1,
602 \+ rb_lookup(V1, _, E0),
603 rb_insert(E0, V2, [], E1),
604 rb_lookup(V1, Children, Graph),
605 dgraph_path_children(Children, V2, E1, Graph, Path).
606dgraph_path_children([_|Children], V2, E1, Graph, Path) :-
607 dgraph_path_children(Children, V2, E1, Graph, Path).
608
609
610do_path([], _, _, []).
611do_path([C|Children], G, SoFar, Path) :-
612 do_children([C|Children], G, SoFar, Path).
613
614do_children([V|_], G, SoFar, [V|Path]) :-
615 rb_lookup(V, Children, G),
616 ord_subtract(Children, SoFar, Ch),
617 ord_insert(SoFar, V, NextSoFar),
618 do_path(Ch, G, NextSoFar, Path).
619do_children([_|Children], G, SoFar, Path) :-
620 do_children(Children, G, SoFar, Path).
621
622/** @pred dgraph_path(+ _Vertex_, + _Graph_, ? _Path_)
623
624
625The path _Path_ is a path starting at vertex _Vertex_ in graph
626 _Graph_.
627
628
629*/
630dgraph_path(V, G, [V|P]) :-
631 rb_lookup(V, Children, G),
632 ord_del_element(Children, V, Ch),
633 do_path(Ch, G, [V], P).
634
635
636/** @pred dgraph_isomorphic(+ _Vs_, + _NewVs_, + _G0_, - _GF_)
637
638
639Unify the list _GF_ with the graph isomorphic to _G0_ where
640vertices in _Vs_ map to vertices in _NewVs_.
641
642
643*/
644dgraph_isomorphic(Vs, Vs2, G1, G2) :-
645 rb_new(Map0),
646 mapping(Vs,Vs2,Map0,Map),
647 dgraph_edges(G1,Edges),
648 translate_edges(Edges,Map,TEdges),
649 dgraph_new(G20),
650 dgraph_add_vertices(Vs2,G20,G21),
651 dgraph_add_edges(G21,TEdges,G2).
652
653mapping([],[],Map,Map).
654mapping([V1|Vs],[V2|Vs2],Map0,Map) :-
655 rb_insert(Map0,V1,V2,MapI),
656 mapping(Vs,Vs2,MapI,Map).
657
658
659
660translate_edges([],_,[]).
661translate_edges([V1-V2|Edges],Map,[NV1-NV2|TEdges]) :-
662 rb_lookup(V1,NV1,Map),
663 rb_lookup(V2,NV2,Map),
664 translate_edges(Edges,Map,TEdges).
665
666/** @pred dgraph_reachable(+ _Vertex_, + _Graph_, ? _Edges_)
667
668
669The path _Path_ is a path starting at vertex _Vertex_ in graph
670 _Graph_.
671
672
673*/
674dgraph_reachable(V, G, Edges) :-
675 rb_lookup(V, Children, G),
676 ord_list_to_rbtree([V-[]],Done0),
677 reachable(Children, Done0, _, G, Edges, []).
678
679reachable([], Done, Done, _, Edges, Edges).
680reachable([V|Vertices], Done0, DoneF, G, EdgesF, Edges0) :-
681 rb_lookup(V,_, Done0), rb_lookup,
682 reachable(Vertices, Done0, DoneF, G, EdgesF, Edges0).
683reachable([V|Vertices], Done0, DoneF, G, [V|EdgesF], Edges0) :-
684 rb_lookup(V, Kids, G),
685 rb_insert(Done0, V, [], Done1),
686 reachable(Kids, Done1, DoneI, G, EdgesF, EdgesI),
687 reachable(Vertices, DoneI, DoneF, G, EdgesI, Edges0).
688
689/** @pred dgraph_leaves(+ _Graph_, ? _Vertices_)
690
691
692The vertices _Vertices_ have no outgoing edge in graph
693 _Graph_.
694
695
696 */
697dgraph_leaves(Graph, Vertices) :-
698 rb_visit(Graph, Pairs),
699 vertices_without_children(Pairs, Vertices).
700
701vertices_without_children([], []).
702vertices_without_children((V-[]).Pairs, V.Vertices) :-
703 vertices_without_children(Pairs, Vertices).
704vertices_without_children(_V-[_|_].Pairs, Vertices) :-
705 vertices_without_children(Pairs, Vertices).
706
707/** @} */
708
709
sort(+ L,- S)
reexport(+F)
use_module( +Files )
dgraph_add_edge(+ Graph, + N1, + N2, - NewGraph)
dgraph_add_edges(+ Graph, + Edges, - NewGraph)
dgraph_add_vertex(+ Graph, + Vertex, - NewGraph)
dgraph_add_vertices(+ Graph, + Vertices, - NewGraph)
dgraph_complement(+ Graph, - NewGraph)
dgraph_del_edge(+ Graph, + N1, + N2, - NewGraph)
dgraph_del_edges(+ Graph, + Edges, - NewGraph)
dgraph_del_vertex(+ Graph, + Vertex, - NewGraph)
dgraph_del_vertices(+ Graph, + Vertices, - NewGraph)
dgraph_edge(+ N1, + N2, + Graph)
dgraph_edges(+ Graph, - Edges)
dgraph_isomorphic(+ Vs, + NewVs, + G0, - GF)
dgraph_leaves(+ Graph, ? Vertices)
dgraph_max_path(+ V1, + V1, + Graph, - Path, ? Costt)
dgraph_min_path(+ V1, + V1, + Graph, - Path, ? Costt)
dgraph_min_paths(+ V1, + Graph, - Paths)
dgraph_neighbors(+ Vertex, + Graph, - Vertices)
dgraph_neighbours(+ Vertex, + Graph, - Vertices)
dgraph_new(+ Graph)
dgraph_path(+ Vertex, + Graph, ? Path)
dgraph_path(+ Vertex, + Vertex1, + Graph, ? Path)
dgraph_reachable(+ Vertex, + Graph, ? Edges)
dgraph_symmetric_closure(+ Graph, - Closure)
dgraph_to_ugraph(+ Graph, - UGraph)
dgraph_top_sort(+ Graph, - Vertices)
dgraph_top_sort(+ Graph, - Vertices, ? Vertices0)
dgraph_transitive_closure(+ Graph, - Closure)
dgraph_transpose(+ Graph, - Transpose)
dgraph_vertices(+ Graph, - Vertices)
ugraph_to_dgraph( +_UGraph_, -_Graph_)
ord_del_element(+ Set1, + Element, ? Set2)
ord_insert(+ Set1, + Element, ? Set2)
ord_subtract(+ Set1, + Set2, ? Difference)
ord_union(+ Set1, + Set2, ? Union)
rb_apply(+T, +Key, :G, -TN)
rb_clone(+ T,+ NT,+ Nodes)
rb_delete(+T, +Key, -TN)
rb_empty(?T)
rb_insert(+ T0,+ Key,? Value,+ TF)
rb_keys(+ T,+ Keys)
rb_lookup(+Key, -Value, +T)
rb_map(+ T,+ G,- TN)
rb_new(-T)
rb_visit(+ T,- Pairs)
add_edges(+ Graph, + Edges, - NewGraph)
add_vertices(+ Graph, + Vertices, - NewGraph)
compose(+ LeftGraph, + RightGraph, - NewGraph)
del_edges(+ Graph, + Edges, - NewGraph)
transpose(+ Graph, - NewGraph)