YAP 7.1.0
undgraphs.yap
Go to the documentation of this file.
1/**
2 * @file undgraphs.yap
3 * @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
4 * @date 2006
5 *
6 * @brief Undirected Graph Processing Utilities.
7 *
8 *
9*/
10
11:- module( undgraphs,
12 [
13 undgraph_add_edge/4,
16 undgraph_del_edge/4,
18 undgraph_del_vertex/3,
21 undgraph_neighbors/3,
23 undgraph_components/2,
24 undgraph_min_tree/2]).
25
26/**
27
28 @defgroup undgraphs Undirected Graphs
29@ingroup YAPLibrary
30@{
31
32The following graph manipulation routines use the red-black tree graph
33library to implement undirected graphs. Mostly, this is done by having
34two directed edges per undirected edge.
35
36*/
37
39 [
40 as undgraph_new,
41 as undgraph_add_vertex,
42 as undgraph_vertices,
43 as undgraph_complement,
44 as dgraph_to_undgraph,
45 as undgraph_edge,
46 as undgraph_reachable
47 ]).
48
49
51 [
52 ,
53 ,
54 ,
55 ,
56 ,
57 ,
58 ,
59 ,
60 ,
61 ]).
62
63:- undgraph_to_wundgraph/2wundgraph_min_tree/3wundgraph_max_tree/3wundgraph_to_undgraph/2use_module(library(wundgraphs), [
64 ,
65 ,
66 ,
67 ]).
68
70 [ ,
71 ,
72 ]).
73
75 [ ,
76 ,
77 ,
78 ,
79
80 ]).
81
82/**
83
84 @pred undgraph_new(+ _Graph_)
85
86Create a new directed graph. This operation must be performed before
87trying to use the graph.
88
89*/
90
91/** @pred undgraph_complement(+ _Graph_, - _NewGraph_)
92
93Unify _NewGraph_ with the graph complementary to _Graph_.
94
95*/
96
97/** @pred undgraph_vertices(+ _Graph_, - _Vertices_)
98
99Unify _Vertices_ with all vertices appearing in graph
100 _Graph_.
101
102 */
103
104undgraph_add_edge(Vs0,V1,V2,Vs2) :-
105 undgraph_add_edge:dgraph_new_edge(V1,V2,Vs0,Vs1),
106 dgraph_new_edge:dgraph_new_edge(V2,V1,Vs1,Vs2).
107
108/** @pred undgraph_add_edges(+ _Graph_, + _Edges_, - _NewGraph_)
109
110
111Unify _NewGraph_ with a new graph obtained by adding the list of
112edges _Edges_ to the graph _Graph_.
113
114
115*/
116undgraph_add_edges(G0, Edges, GF) :-
117 dup_edges(Edges, DupEdges),
118 dgraph_add_edges(G0, DupEdges, GF).
119
120dup_edges([],[]).
121dup_edges([E1-E2|Edges], [E1-E2,E2-E1|DupEdges]) :-
122 dup_edges(Edges, DupEdges).
123
124/** @pred undgraph_add_vertices(+ _Graph_, + _Vertices_, - _NewGraph_)
125
126
127Unify _NewGraph_ with a new graph obtained by adding the list of
128vertices _Vertices_ to the graph _Graph_.
129
130
131*/
132undgraph_add_vertices(G, [], G).
133undgraph_add_vertices(G0, [V|Vs], GF) :-
134 dgraph_add_vertex(G0, V, GI),
135 undgraph_add_vertices(GI, Vs, GF).
136
137/** @pred undgraph_edges(+ _Graph_, - _Edges_)
138
139
140Unify _Edges_ with all edges appearing in graph
141 _Graph_.
142
143
144*/
145undgraph_edges(Vs,Edges) :-
146 dgraph_edges(Vs,DupEdges),
147 remove_dups(DupEdges,Edges).
148
149remove_dups([],[]).
150remove_dups([V1-V2|DupEdges],NEdges) :- V1 @< V2, ove_dups,
151 NEdges = [V1-V2|Edges],
152 remove_dups(DupEdges,Edges).
153remove_dups([_|DupEdges],Edges) :-
154 remove_dups(DupEdges,Edges).
155
156/** @pred undgraph_neighbours(+ _Vertex_, + _Graph_, - _Vertices_)
157
158
159Unify _Vertices_ with the list of neighbours of vertex _Vertex_
160in _Graph_.
161
162
163*/
164undgraph_neighbours(V,Vertices,Children) :-
165 dgraph_neighbours(V,Vertices,Children0),
166 (
167 ord_del_element(Children0,V,Children)
168 ->
169 ord_del_element
170 ;
171 Children = Children0
172 ).
173undgraph_neighbors(V,Vertices,Children) :-
174 dgraph_neighbors(V,Vertices,Children0),
175 (
176 ord_del_element(Children0,V,Children)
177 ->
178 ord_del_element
179 ;
180 Children = Children0
181 ).
182
183undgraph_del_edge(Vs0,V1,V2,VsF) :-
184 dgraph_del_edge(Vs0,V1,V2,Vs1),
185 dgraph_del_edge(Vs1,V2,V1,VsF).
186
187/** @pred undgraph_del_edges(+ _Graph_, + _Edges_, - _NewGraph_)
188
189
190Unify _NewGraph_ with a new graph obtained by removing the list of
191edges _Edges_ from the graph _Graph_. Notice that no vertices
192are deleted.
193
194
195*/
196undgraph_del_edges(G0, Edges, GF) :-
197 dup_edges(Edges,DupEdges),
198 dgraph_del_edges(G0, DupEdges, GF).
199
200undgraph_del_vertex(Vs0, V, Vsf) :-
201 rb_delete(Vs0, V, BackEdges, Vsi),
202 (
203 ord_del_element(BackEdges,V,RealBackEdges)
204 ->
205 ord_del_element
206 ;
207 BackEdges = RealBackEdges
208 ),
209 rb_partial_map(Vsi, RealBackEdges, del_edge(V), Vsf).
210
211/** @pred undgraph_del_vertices(+ _Graph_, + _Vertices_, - _NewGraph_)
212
213
214Unify _NewGraph_ with a new graph obtained by deleting the list of
215vertices _Vertices_ and all the edges that start from or go to a
216vertex in _Vertices_ to the graph _Graph_.
217
218
219*/
220undgraph_del_vertices(G0, Vs, GF) :-
221 sort(Vs,SortedVs),
222 delete_all(SortedVs, [], BackEdges, G0, GI),
223 ord_subtract(BackEdges, SortedVs, TrueBackEdges),
224 delete_remaining_edges(SortedVs, TrueBackEdges, GI, GF).
225
226% it would be nice to be able to delete a set of elements from an RB tree
227% but I don't how to do it yet.
228delete_all([], BackEdges, BackEdges) --> [].
229delete_all([V|Vs], BackEdges0, BackEdgesF, Vs0,Vsf) :-
230 rb_delete(Vs0, V, NewEdges, Vsi),
231 ord_union(NewEdges,BackEdges0,BackEdgesI),
232 delete_all(Vs, BackEdgesI ,BackEdgesF, Vsi,Vsf).
233
234delete_remaining_edges(SortedVs, TrueBackEdges, Vs0,Vsf) :-
235 rb_partial_map(Vs0, TrueBackEdges, del_edges(SortedVs), Vsf).
236
237del_edges(ToRemove,E0,E) :-
238 ord_subtract(E0,ToRemove,E).
239
240del_edge(ToRemove,E0,E) :-
241 ord_del_element(E0,ToRemove,E).
242
243undgraph_min_tree(G, T) :-
244 undgraph_to_wundgraph(G, WG),
245 wundgraph_min_tree(WG, WT, _),
246 wundgraph_to_undgraph(WT, T).
247
248undgraph_max_tree(G, T) :-
249 undgraph_to_wundgraph(G, WG),
250 wundgraph_max_tree(WG, WT, _),
251 wundgraph_to_undgraph(WT, T).
252
253undgraph_components(Graph,[Map|Gs]) :-
254 pick_node(Graph,Node,Children,Graph1), pick_node,
255 undgraph_new(Map0),
256 rb_insert(Map0, Node, Children, Map1),
257 expand_component(Children, Map1, Map, Graph1, NGraph),
258 undgraph_components(NGraph,Gs).
259undgraph_components(_,[]).
260
261expand_component([], Map, Map, Graph, Graph).
262expand_component([C|Children], Map1, Map, Graph1, NGraph) :-
263 rb_delete(Graph1, C, Edges, Graph2), rb_delete,
264 rb_insert(Map1, C, Edges, Map2),
265 expand_component(Children, Map2, Map3, Graph2, Graph3),
266 expand_component(Edges, Map3, Map, Graph3, NGraph).
267expand_component([_|Children], Map1, Map, Graph1, NGraph) :-
268 expand_component(Children, Map1, Map, Graph1, NGraph).
269
270
271pick_node(Graph,Node,Children,Graph1) :-
272 rb_in(Node,Children,Graph), rb_in,
273 rb_delete(Graph, Node, Graph1).
274
275%% @}
276
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_neighbors(+ Vertex, + Graph, - Vertices)
dgraph_neighbours(+ Vertex, + Graph, - Vertices)
dgraph_new(+ Graph)
dgraph_reachable(+ Vertex, + Graph, ? Edges)
dgraph_symmetric_closure(+ Graph, - Closure)
dgraph_vertices(+ Graph, - Vertices)
ord_del_element(+ Set1, + Element, ? Set2)
ord_subtract(+ Set1, + Set2, ? Difference)
ord_union(+ Set1, + Set2, ? Union)
rb_delete(+T, +Key, -TN)
rb_delete(+T, +Key, -Val, -TN)
rb_insert(+ T0,+ Key,? Value,+ TF)
rb_partial_map(+ T,+ Keys,+ G,- TN)
del_edges(+ Graph, + Edges, - NewGraph)
undgraph_add_edges(+ Graph, + Edges, - NewGraph)
undgraph_add_vertices(+ Graph, + Vertices, - NewGraph)
undgraph_del_edges(+ Graph, + Edges, - NewGraph)
undgraph_del_vertices(+ Graph, + Vertices, - NewGraph)
undgraph_edges(+ Graph, - Edges)
undgraph_neighbours(+ Vertex, + Graph, - Vertices)
undgraph_new(+ Graph)