amalgame/commit

merged two util files into one ...

authorJacco van Ossenbruggen
Mon Jan 28 18:53:00 2013 +0100
committerJacco van Ossenbruggen
Mon Jan 28 18:53:00 2013 +0100
commit203317b234be8127960ef04f0562fca59f5d1878
treea24cdc164cce028e992652aeba257e237663f2db
parent1288ffacfd6477a08594dfeb919fa1e054eaa1ce
Diff style: patch stat
diff --git a/api/mapping.pl b/api/mapping.pl
index 4352d43..1654f54 100644
--- a/api/mapping.pl
+++ b/api/mapping.pl
@@ -19,7 +19,6 @@
 :- use_module(library(amalgame/edoal)).
 :- use_module(library(amalgame/map)).
 :- use_module(library(amalgame/expand_graph)).
-:- use_module(library(ag_util)).
 :- use_module(library(amalgame/util)).
 
 :- setting(rows_per_page, integer, 100,
diff --git a/api/mappinglist.pl b/api/mappinglist.pl
index 0178a78..df13ede 100644
--- a/api/mappinglist.pl
+++ b/api/mappinglist.pl
@@ -10,7 +10,7 @@
 :- use_module(user(preferences)).
 :- use_module(library(semweb/rdf_label)).
 
-:- use_module(library(ag_util)).
+:- use_module(library(amalgame/util)).
 :- use_module(library(amalgame/vocabulary)).
 :- use_module(library(amalgame/ag_stats)).
 :- use_module(library(amalgame/expand_graph)).
diff --git a/lib/ag_modules/arity_select.pl b/lib/ag_modules/arity_select.pl
index da0f207..7f96bf3 100644
--- a/lib/ag_modules/arity_select.pl
+++ b/lib/ag_modules/arity_select.pl
@@ -1,8 +1,6 @@
 :- module(arity_select,[]).
 
-:- use_module(library(semweb/rdf_db)).
 :- use_module(library(amalgame/map)).
-:- use_module(library(ag_util)).
 
 :- public amalgame_module/1.
 :- public selecter/5.
diff --git a/lib/ag_modules/best_numeric.pl b/lib/ag_modules/best_numeric.pl
index 161615b..98a046a 100644
--- a/lib/ag_modules/best_numeric.pl
+++ b/lib/ag_modules/best_numeric.pl
@@ -1,9 +1,6 @@
 :- module(best_numeric, []).
 
-:- use_module(library(semweb/rdf_db)).
-:- use_module(library(semweb/rdfs)).
 :- use_module(library(amalgame/map)).
-:- use_module(library(ag_util)).
 
 :- public amalgame_module/1.
 :- public selecter/5.
diff --git a/lib/ag_util.pl b/lib/ag_util.pl
deleted file mode 100644
index c896f14..0000000
--- a/lib/ag_util.pl
+++ /dev/null
@@ -1,140 +0,0 @@
-:- module(ag_util,
-	  [ find_unique/4,              % +Var, +Goal, +Max, -Results
-	    list_offset/3,
-	    list_limit/4,
-	    sort_by_arg/3,
-	    sort_by_arg/4,
-	    group_by_arg/3,
-	    remove_resource/2 % +Resource, +Graph
-	  ]).
-
-:- use_module(library(semweb/rdf_db)).
-
-:- meta_predicate
-        find_unique(-, 0, +, -).
-
-%%      find_unique(Var, :Goal, +MaxResults, -SortedSet)
-%
-%       Find at most MaxResults distinct solutions for Var in Goal.
-
-find_unique(T, G, inf, Ts) :- !,
-        findall(T, G, Raw),
-        sort(Raw, Ts).
-find_unique(T, G, Max, Ts) :-
-        empty_nb_set(Set),
-        State = count(0),
-        (       G,
-                add_nb_set(T, Set, true),
-                arg(1, State, C0),
-                C is C0 + 1,
-                nb_setarg(1, State, C),
-                C == Max
-        ->      true
-        ;       true
-        ),
-        nb_set_to_list(Set, Ts).
-
-
-%%	list_offset(+List, +N, -SmallerList)
-%
-%	SmallerList starts at the nth element of List.
-
-list_offset(L, N, []) :-
-	length(L, Length),
-	Length < N,
-	!.
-list_offset(L, N, L1) :-
-	list_offset_(L, N, L1).
-
-list_offset_(L, 0, L) :- !.
-list_offset_([_|T], N, Rest) :-
-	N1 is N-1,
-	list_offset_(T, N1, Rest).
-
-%%	list_limit(+List, +N, -SmallerList, -Rest)
-%
-%	SmallerList ends at the nth element of List.
-
-list_limit(L, N, L, []) :-
-	N < 0,
-	!.
-list_limit(L, N, L, []) :-
-	length(L, Length),
-	Length < N,
-	!.
-list_limit(L, N, L1, Rest) :-
-	list_limit_(L, N, L1, Rest).
-
-list_limit_(Rest, 0, [], Rest) :- !.
-list_limit_([H|T], N, [H|T1], Rest) :-
-	N1 is N-1,
-	list_limit_(T, N1, T1, Rest).
-
-
-%%	sort_by_arg(+ListOfTerms, +Arg, -SortedList)
-%
-%	SortedList contains the Terms from ListOfTerms sorted by their
-%	nth Arg.
-
-sort_by_arg(List, Arg, Sorted) :-
-	maplist(arg_key(Arg), List, Pairs),
-	keysort(Pairs, SortedPairs),
-	pairs_values(SortedPairs, Sorted).
-
-%%	sort_by_arg(+ListOfTerms, +Arg, +Direction, -SortedList)
-%
-%	SortedList contains the Terms from ListOfTerms sorted by their
-%	nth Arg.
-
-sort_by_arg(List, Arg, Direction, Sorted) :-
-	sort_by_arg(List, Arg, Sorted0),
-	(   Direction == desc
-	->  reverse(Sorted0, Sorted)
-	;   Sorted = Sorted0
-	).
-
-%%	group_by_arg(+ListOfTerms, +Arg, -GroupedList)
-%
-%	GroupedList contains the Terms from ListOfTerms grouped by their
-%	nth Arg.
-
-group_by_arg(List, Arg, Sorted) :-
-	maplist(arg_key(Arg), List, Pairs),
-	keysort(Pairs, SortedPairs),
-	group_pairs_by_key(SortedPairs, Sorted).
-
-arg_key(Args, Term, Keys-Term) :-
-	is_list(Args),
-	!,
-	args(Args, Term, Keys).
-arg_key(Arg, Term, Key-Term) :-
-	arg(Arg, Term, Key).
-
-args([A], Term, [Key]) :- !,
-	arg(A, Term, Key).
-args([A|As], Term, [Key|Ks]) :-
-	arg(A, Term, Key),
-	args(As, Term, Ks).
-
-%%	remove_resource(+Resource, +Graph) is det.
-%
-%	Remove all references to Resource from Graph,
-%	including (recursively) all blank nodes that
-%	Resource uniquely referred to.
-
-remove_resource(R, G) :-
-	ground(R),
-	ground(G),
-	findall(Blank,
-		(   rdf(R,_,Blank, G),
-		    rdf_is_bnode(Blank),
-		    \+ (rdf(R2, _, Blank, G), R2 \= R)
-		),
-		BlankNodes),
-	forall(member(B, BlankNodes),
-	       remove_resource(B, G)
-	      ),
-	rdf_retractall(R,_,_,G),
-	rdf_retractall(_,R,_,G),
-	rdf_retractall(_,_,R,G).
-
diff --git a/lib/amalgame/map.pl b/lib/amalgame/map.pl
index e8a8442..c0499b1 100644
--- a/lib/amalgame/map.pl
+++ b/lib/amalgame/map.pl
@@ -37,7 +37,7 @@ align(Source,Target,EvidenceList) terms.
 
 :- use_module(library(amalgame/edoal)).
 :- use_module(library(amalgame/alignment)).
-:- use_module(library(ag_util)).
+:- use_module(library(amalgame/util)).
 
 %%	correspondence_source(?C,?S) is det.
 %
diff --git a/lib/amalgame/util.pl b/lib/amalgame/util.pl
index e82abc9..eea7b83 100644
--- a/lib/amalgame/util.pl
+++ b/lib/amalgame/util.pl
@@ -8,7 +8,15 @@
 	    now_xsd/1,
 	    xsd_timestamp/2,
 	    is_edm_collection/1,
-	    has_write_permission/0
+	    has_write_permission/0,
+
+	    find_unique/4,              % +Var, +Goal, +Max, -Results
+	    list_offset/3,
+	    list_limit/4,
+	    sort_by_arg/3,
+	    sort_by_arg/4,
+	    group_by_arg/3,
+	    remove_resource/2 % +Resource, +Graph
 	  ]).
 
 
@@ -26,6 +34,9 @@
 :- multifile
 	eq:menu_item/2.
 
+:- meta_predicate
+        find_unique(-, 0, +, -).
+
 eq:menu_item(900=Handler, Label) :-
 	(   (logged_on(User, X), X \== User)
 	->  fail
@@ -254,3 +265,129 @@ is_edm_collection_(EDM, Graph, Class) :-
 
 
 
+
+%%      find_unique(Var, :Goal, +MaxResults, -SortedSet)
+%
+%       Find at most MaxResults distinct solutions for Var in Goal.
+
+find_unique(T, G, inf, Ts) :- !,
+        findall(T, G, Raw),
+        sort(Raw, Ts).
+find_unique(T, G, Max, Ts) :-
+        empty_nb_set(Set),
+        State = count(0),
+        (       G,
+                add_nb_set(T, Set, true),
+                arg(1, State, C0),
+                C is C0 + 1,
+                nb_setarg(1, State, C),
+                C == Max
+        ->      true
+        ;       true
+        ),
+        nb_set_to_list(Set, Ts).
+
+
+%%	list_offset(+List, +N, -SmallerList)
+%
+%	SmallerList starts at the nth element of List.
+
+list_offset(L, N, []) :-
+	length(L, Length),
+	Length < N,
+	!.
+list_offset(L, N, L1) :-
+	list_offset_(L, N, L1).
+
+list_offset_(L, 0, L) :- !.
+list_offset_([_|T], N, Rest) :-
+	N1 is N-1,
+	list_offset_(T, N1, Rest).
+
+%%	list_limit(+List, +N, -SmallerList, -Rest)
+%
+%	SmallerList ends at the nth element of List.
+
+list_limit(L, N, L, []) :-
+	N < 0,
+	!.
+list_limit(L, N, L, []) :-
+	length(L, Length),
+	Length < N,
+	!.
+list_limit(L, N, L1, Rest) :-
+	list_limit_(L, N, L1, Rest).
+
+list_limit_(Rest, 0, [], Rest) :- !.
+list_limit_([H|T], N, [H|T1], Rest) :-
+	N1 is N-1,
+	list_limit_(T, N1, T1, Rest).
+
+
+%%	sort_by_arg(+ListOfTerms, +Arg, -SortedList)
+%
+%	SortedList contains the Terms from ListOfTerms sorted by their
+%	nth Arg.
+
+sort_by_arg(List, Arg, Sorted) :-
+	maplist(arg_key(Arg), List, Pairs),
+	keysort(Pairs, SortedPairs),
+	pairs_values(SortedPairs, Sorted).
+
+%%	sort_by_arg(+ListOfTerms, +Arg, +Direction, -SortedList)
+%
+%	SortedList contains the Terms from ListOfTerms sorted by their
+%	nth Arg.
+
+sort_by_arg(List, Arg, Direction, Sorted) :-
+	sort_by_arg(List, Arg, Sorted0),
+	(   Direction == desc
+	->  reverse(Sorted0, Sorted)
+	;   Sorted = Sorted0
+	).
+
+%%	group_by_arg(+ListOfTerms, +Arg, -GroupedList)
+%
+%	GroupedList contains the Terms from ListOfTerms grouped by their
+%	nth Arg.
+
+group_by_arg(List, Arg, Sorted) :-
+	maplist(arg_key(Arg), List, Pairs),
+	keysort(Pairs, SortedPairs),
+	group_pairs_by_key(SortedPairs, Sorted).
+
+arg_key(Args, Term, Keys-Term) :-
+	is_list(Args),
+	!,
+	args(Args, Term, Keys).
+arg_key(Arg, Term, Key-Term) :-
+	arg(Arg, Term, Key).
+
+args([A], Term, [Key]) :- !,
+	arg(A, Term, Key).
+args([A|As], Term, [Key|Ks]) :-
+	arg(A, Term, Key),
+	args(As, Term, Ks).
+
+%%	remove_resource(+Resource, +Graph) is det.
+%
+%	Remove all references to Resource from Graph,
+%	including (recursively) all blank nodes that
+%	Resource uniquely referred to.
+
+remove_resource(R, G) :-
+	ground(R),
+	ground(G),
+	findall(Blank,
+		(   rdf(R,_,Blank, G),
+		    rdf_is_bnode(Blank),
+		    \+ (rdf(R2, _, Blank, G), R2 \= R)
+		),
+		BlankNodes),
+	forall(member(B, BlankNodes),
+	       remove_resource(B, G)
+	      ),
+	rdf_retractall(R,_,_,G),
+	rdf_retractall(_,R,_,G),
+	rdf_retractall(_,_,R,G).
+