autocompletion/commit

move instance_search to lib to allow reuse by vumix and others

authorJacco van Ossenbruggen
Mon Apr 9 18:05:06 2012 +0200
committerJacco van Ossenbruggen
Mon Apr 9 18:05:06 2012 +0200
commit11883eac38409a1a960bae7e18b676fbded94e39
treef4660e5a70f35365a7c7d6e81a2a5c68ddce019b
parent3436b8f6d13871b4549782e6c0e3e78a6b68317d
Diff style: patch stat
diff --git a/api/autocomplete_api.pl b/api/autocomplete_api.pl
index e7d3d76..1ebe907 100644
--- a/api/autocomplete_api.pl
+++ b/api/autocomplete_api.pl
@@ -1,7 +1,4 @@
-:- module(autocomplete_api,
-	[ instance_search/3		% +Query, -Hits, +Options
-
-	]).
+:- module(autocomplete_api, []).
 
 :- use_module(library(http/http_dispatch)).
 :- use_module(library(http/http_parameters)).
@@ -16,6 +13,7 @@
 :- use_module(library(find_resource)).
 :- use_module(library(ac_filter)).
 :- use_module(library(ac_list_util)).
+:- use_module(library(instance_search)).
 
 :- rdf_meta
 	all_literal_propvalues(r, r, -).
@@ -55,81 +53,6 @@ http_autocomplete(Request) :-
 	hit(uri:uri, property:atom, label:atom, info:_).
 
 
-/***************************************************
-* term search
-***************************************************/
-
-%%	instance_search(+Query, -Hits:hit(uri,property,label,info), +Options)
-%
-%	Hits contains all resources matching Query.
-%	Options are
-%		match = prefix;stem;exact
-%		filter =
-%		compound = boolean
-%		property = [property-score]
-%		shortQueriesOptimized = integer
-%		treeRemove = false;relation
-
-
-instance_search(Query, Hits, Options) :-
-	option(property(Property), Options, []),
-	label_list(Property, LabelList),
-	find_resources(Query, LabelList, Hits, Options).
-
-
-/***************************************************
-* literal matching
-***************************************************/
-
-%%	label_list(+Property, -LabelList)
-%
-%	LabelList is a list of Pairs with an rdf property
-%	score. Lower score gets preference.
-
-label_list([], LabelList) :- !,
-	rdf_equal(rdfs:label, Label),
-	rdf_equal(skos:prefLabel, PrefLabel),
-	LabelList = [
-		PrefLabel-0,
-		Label-1
-	].
-label_list(Property, LabelList) :-
-	atom(Property), !,
-	LabelList = [Property-0].
-label_list(List, LabelList) :-
-    is_list(List),
-    format_label_list(List, 0, LabelList),
-    !.
-label_list(List,_) :-
-	 type_error(labellist,  List).
-
-format_label_list([], _, []).
-format_label_list([H|T], N0, [P-N|Rest]) :-
-	N1 is N0+0.1,
-	(   atom(H)
-	->  N = N0,
-	    P = H
-	;   H = P-N,
-	    number(N)
-	->  true
-	;   H = pair(P,N)
-	->  true
-	),
-	format_label_list(T, N1, Rest).
-
-
-%%	find_resources(+Query, +LabelList, -Hits, Options)
-%
-%	Hits contains uris with prefix matching label.
-
-find_resources(Query, LabelList, Hits, Options0) :-
-	Options = [distance(false),attributes(LabelList)|Options0],
-	find_resource_by_name(Query, Hits0, Options),
-	maplist(ac_hit, Hits0, Hits1),
-	filter(Hits1, Hits, Options0).
-
-ac_hit(hit(_D,U,P,L), hit(U,P,L,[])).
-
 /***************************************************
 * expand with extra display info
 ***************************************************/
@@ -165,30 +88,3 @@ all_labels(R,Labels) :-
 			  ),
 		Labels0),
 	sort(Labels0,Labels).
-
-
-/***************************************************
-* filtering
-***************************************************/
-
-%%	filter(+Hits, -Filtered, +Options)
-%
-%	Fitered contains only those hits that
-%	satisfy the Filter from Options.
-
-filter(Hits0, Hits1, Options) :-
-	(	option(filter(Filter), Options),
-		Filter \== []
-	->	filter_hits(Hits0, Filter, Hits1)
-	;	Hits1 = Hits0
-	).
-filter(Hits, Hits, _Options).
-
-
-filter_hits([], _, []) :- !.
-filter_hits(HitsIn, Filter, HitsOut) :-
-	filter_to_goal(Filter, R, Goal),
-	findall(Hit, (member(Hit, HitsIn),
-		      Hit = hit(R,_,_,_),
-		      once(Goal)),
-		HitsOut).
diff --git a/lib/instance_search.pl b/lib/instance_search.pl
new file mode 100644
index 0000000..cc0a408
--- /dev/null
+++ b/lib/instance_search.pl
@@ -0,0 +1,114 @@
+:- module(ac_instance_search,
+	[ instance_search/3		% +Query, -Hits, +Options
+
+	]).
+
+:- use_module(library('semweb/rdf_db')).
+:- use_module(library('semweb/rdfs')).
+:- use_module(library('semweb/rdf_label')).
+:- use_module(library('semweb/rdf_litindex.pl')).
+
+:- use_module(library(find_resource)).
+:- use_module(library(ac_filter)).
+:- use_module(library(ac_list_util)).
+
+/***************************************************
+* term search
+***************************************************/
+
+%%	instance_search(+Query, -Hits:hit(uri,property,label,info), +Options)
+%
+%	Hits contains all resources matching Query.
+%	Options are
+%		match = prefix;stem;exact
+%		filter =
+%		compound = boolean
+%		property = [property-score]
+%		shortQueriesOptimized = integer
+%		treeRemove = false;relation
+
+
+instance_search(Query, Hits, Options) :-
+	option(property(Property), Options, []),
+	label_list(Property, LabelList),
+	find_resources(Query, LabelList, Hits, Options).
+
+
+/***************************************************
+* literal matching
+***************************************************/
+
+%%	label_list(+Property, -LabelList)
+%
+%	LabelList is a list of Pairs with an rdf property
+%	score. Lower score gets preference.
+
+label_list([], LabelList) :- !,
+	rdf_equal(rdfs:label, Label),
+	rdf_equal(skos:prefLabel, PrefLabel),
+	LabelList = [
+		PrefLabel-0,
+		Label-1
+	].
+label_list(Property, LabelList) :-
+	atom(Property), !,
+	LabelList = [Property-0].
+label_list(List, LabelList) :-
+    is_list(List),
+    format_label_list(List, 0, LabelList),
+    !.
+label_list(List,_) :-
+	 type_error(labellist,  List).
+
+format_label_list([], _, []).
+format_label_list([H|T], N0, [P-N|Rest]) :-
+	N1 is N0+0.1,
+	(   atom(H)
+	->  N = N0,
+	    P = H
+	;   H = P-N,
+	    number(N)
+	->  true
+	;   H = pair(P,N)
+	->  true
+	),
+	format_label_list(T, N1, Rest).
+
+
+%%	find_resources(+Query, +LabelList, -Hits, Options)
+%
+%	Hits contains uris with prefix matching label.
+
+find_resources(Query, LabelList, Hits, Options0) :-
+	Options = [distance(false),attributes(LabelList)|Options0],
+	find_resource_by_name(Query, Hits0, Options),
+	maplist(ac_hit, Hits0, Hits1),
+	filter(Hits1, Hits, Options0).
+
+ac_hit(hit(_D,U,P,L), hit(U,P,L,[])).
+
+/***************************************************
+* filtering
+***************************************************/
+
+%%	filter(+Hits, -Filtered, +Options)
+%
+%	Fitered contains only those hits that
+%	satisfy the Filter from Options.
+
+filter(Hits0, Hits1, Options) :-
+	(	option(filter(Filter), Options),
+		Filter \== []
+	->	filter_hits(Hits0, Filter, Hits1)
+	;	Hits1 = Hits0
+	).
+filter(Hits, Hits, _Options).
+
+
+filter_hits([], _, []) :- !.
+filter_hits(HitsIn, Filter, HitsOut) :-
+	filter_to_goal(Filter, R, Goal),
+	findall(Hit, (member(Hit, HitsIn),
+		      Hit = hit(R,_,_,_),
+		      once(Goal)),
+		HitsOut).