1 % (c) 2009-2022 Lehrstuhl fuer Softwaretechnik und Programmiersprachen,
2 % Heinrich Heine Universitaet Duesseldorf
3 % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html)
4
5 :- module(avl_ugraphs,[avl_set_to_ugraph/2,
6 ugraph_to_avl_set/2,
7 avl_transitive_closure/2,
8 avl_scc_sets/2]).
9
10 %
11
12 :- use_module(probsrc(module_information)).
13 :- module_info(group,external_functions).
14 :- module_info(description,'A module to interface ProB\'s avl_set relations with the SICStus ugraph library (unweighted graphs).').
15
16
17 :- use_module(library(avl)).
18 :- use_module(library(lists)).
19 :- use_module(library(ugraphs),[vertices_edges_to_ugraph/3,
20 transitive_closure/2, edges/2,
21 reduce/2, vertices/2]).
22
23 pair_to_minus((A,B),A-B).
24 %pair_to_minus((A,B),CA-CB) :- convert_val(A,CA), convert_val(B,CB).
25 minus_to_pair(A-B,(A,B)-true).
26 %minus_to_pair(A-B,(CA,CB)-true) :- reconvert_val(A,CA), reconvert_val(B,CB).
27
28 %convert_val(int(X),R) :- !, R=X.
29 %convert_val(R,R).
30 %reconvert_val(X,R) :- number(X),!, R=int(X).
31 %reconvert_val(R,R).
32
33 % closure1(%x.(x:1..2000|x*x)) is much slower with this than with the version in custom-explicit sets (1 secs vs 10ms)
34 % closure1(%x.(x:1..1000|x*x) \/ %x.(x:1..2000|x+x) \/ %x.(x:1..1000|x/2)): 9.3 seconds vs 2 seconds
35 % others like closure1(nxt \/ nxt~) for TrackUp.mch are faster (110ms vs 380ms)
36
37 avl_set_to_ugraph(A,UGraph) :-
38 avl_domain(A,AList),
39 maplist(pair_to_minus,AList,InEdges),
40 vertices_edges_to_ugraph([],InEdges,UGraph).
41
42 ugraph_to_avl_set(UGraph,Res) :-
43 edges(UGraph,Edges),
44 maplist(minus_to_pair,Edges,Res).
45
46
47 avl_transitive_closure(A,Res) :- % print(start1),debug:nl_time,
48 avl_set_to_ugraph(A,UGraph),
49 transitive_closure(UGraph,TUG), %print(tc(TUG)),debug:nl_time,
50 edges(TUG,Edges), %print(edg(Edges)),debug:nl_time,
51 maplist(minus_to_pair,Edges,ListRes),
52 sort(ListRes,SListRes), %print(sl(SListRes)),debug:nl_time,
53 ord_list_to_avl(SListRes,Res). % could be empty
54 %print(stop1),debug:nl_time,fail.
55
56 %Note: result could be empty, use: construct_avl_set on Res
57
58 :- use_module(probsrc(custom_explicit_sets),[convert_to_avl/2]).
59
60 % compute strongly connected components, returning a set of sets of vertices
61 avl_scc_sets(A,Res) :- %print(start_scc),debug:nl_time,
62 avl_set_to_ugraph(A,UGraph),
63 reduce(UGraph,SCCGraph),
64 vertices(SCCGraph,VList), %print(vl(VList)),nl,
65 %print(stop_scc),debug:nl_time,
66 %maplist(convert_to_avl,V,SCCList),
67 convert_to_avl(VList,avl_set(Res)). % could be empty
68
69 /* TO DO:
70
71 reduce(+Graph, -Reduced)
72 is true if Reduced is the reduced graph for Graph. The vertices of the reduced
73 graph are the strongly connected components of Graph. There is an edge in
74 Reduced from u to v iff there is an edge in Graph from one of the vertices in u
75 to one of the vertices in v. A strongly connected component is a maximal set
76 of vertices where each vertex has a path to every other vertex. Algorithm from
77 "Algorithms" by Sedgewick, page 482, Tarjan’s algorithm.
78
79 | ?- vertices_edges_to_ugraph([a,b,c],[a-b,b-c,c-b,b-d],G), reduce(G,G2), edges(G2,Edges).
80 G = [a-[b],b-[c,d],c-[b],d-[]],
81 G2 = [[a]-[[b,c]],[b,c]-[[d]],[d]-[]],
82 Edges = [[a]-[b,c],[b,c]-[d]] ?
83
84 reachable(+Vertex, +Graph, -Reachable)
85 is given a Graph and a Vertex of that Graph, and returns the set of vertices
86 that are Reachable from that Vertex. Takes O(N^2) time.
87
88 random_ugraph(+P, +N, -Graph)
89 where P is a probability, unifies Graph with a random graph of N vertices where
90 each possible edge is included with probability P.
91
92 */