View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2005-2012, University of Amsterdam
    7			      VU University Amsterdam
    8
    9    This program is free software; you can redistribute it and/or
   10    modify it under the terms of the GNU General Public License
   11    as published by the Free Software Foundation; either version 2
   12    of the License, or (at your option) any later version.
   13
   14    This program is distributed in the hope that it will be useful,
   15    but WITHOUT ANY WARRANTY; without even the implied warranty of
   16    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   17    GNU General Public License for more details.
   18
   19    You should have received a copy of the GNU Lesser General Public
   20    License along with this library; if not, write to the Free Software
   21    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   22
   23    As a special exception, if you link this library with other files,
   24    compiled with a Free Software compiler, to produce an executable, this
   25    library does not by itself cause the resulting executable to be covered
   26    by the GNU General Public License. This exception does not however
   27    invalidate any other reasons why the executable file might be covered by
   28    the GNU General Public License.
   29*/
   30
   31
   32:- module(sparql,
   33	  [ sparql_query/3,		% +Query, -Result, +Options
   34	    sparql_compile/3,		% +Query, -Compiled, +Options
   35	    sparql_run/2		% +Compiled, -Reply
   36	  ]).   37:- use_module(library(option)).   38:- use_module(library(assoc)).   39:- use_module(library(apply)).   40:- use_module(library(semweb/rdf_db), [rdf_is_bnode/1]).   41:- use_module(library(semweb/rdf_optimise)).   42:- use_module(library(settings)).   43:- use_module(sparql_grammar).   44:- use_module(sparql_runtime).   45:- use_module(rdfql_util).   46:- use_module(library(settings)).   47:- include(entailment(load)).
   48
   49:- multifile
   50	function/2.			% user-defined functions
   51
   52:- setting(entailment, atom, rdf,
   53	   'Default entailment used for SPARQL queries').
 sparql_query(+Query, -Reply, +Options)
Where Query is either a SPARQL query text or a parsed query. Reply depends on the type of query:
SELECTrow(Col1, Col2, ....)
CONSTRUCTrdf(S,P,O)
DESCRIBErdf(S,P,O)
ASKReply == true or failure of pred

Options are:

entailment(Entailment)
Specify the entailment module used. The default is controlled by the setting sparql:entailment.
base_uri(Base)
Specify the base IRI to use for parsing the query
type(-Type)
Returns one of select(-VarNames), construct, describe or ask.
ordered(-Bool)
True if query contains an ORDER BY clause
distinct(-Bool)
True if query contains a DISTINCT clause
   84sparql_query(Query, Reply, Options) :-
   85	sparql_compile(Query, Compiled, Options),
   86	sparql_run(Compiled, Reply).
 sparql_compile(+Query, -Compiled, +Options)
Performs the compilation pass of solving a SPARQL query. Splitting serves two purposes. The result of the compilation can be cached if desired and through Options we can get information about the parsed query.
   96sparql_compile(Query, sparql_query(Optimised, ReplyTemplate, Module), Options) :-
   97	sparql_parse(Query, Parsed, Options),
   98	optimise(Parsed, Optimised, Options),
   99	(   option(entailment(Entailment), Options)
  100	->  true
  101	;   setting(entailment, Entailment)
  102	),
  103	option(type(Type), Options, _),
  104	option(ordered(Order), Options, _),
  105	option(distinct(Distinct), Options, _),
  106	entailment_module(Entailment, Module),
  107	prepare(Parsed, Type, Order, Distinct, ReplyTemplate).
  108
  109prepare(select(Vars, _, _, S), select(Names), O, D, Reply) :- !,
  110	select_result(Vars, Reply, Names),
  111	solutions(S, O, D).
  112prepare(construct(_,_,_,S), construct, O, D, _) :- !,
  113	solutions(S, O, D).
  114prepare(ask(_,_,S), ask, O, D, _) :- !,
  115	solutions(S, O, D).
  116prepare(describe(_,_,_,S), describe, O, D, _) :- !,
  117	solutions(S, O, D).
  118prepare(update(_), update, false, false, _) :- !.
  119prepare(Query, Type, _, _, _) :-
  120	nonvar(Type),
  121	functor(Type, Expected, _),
  122	functor(Query, Found, _),
  123	throw(error(type_error(query_type(Expected), Found), _)).
  124
  125solutions(distinct(S), O, true) :- !,
  126	solutions(S, O).
  127solutions(S, O, false) :-
  128	solutions(S, O).
  129
  130solutions(solutions(_Group, _Having, _Aggregate, unsorted, _, _), O) :- !,
  131	O = false.
  132solutions(_, true).
 optimise(+Parsed, -Optimised, +Options) is det
Perform sparql query optimization using rdf_optimise/2. Currently, UPDATE requests are not optimized.
To be done
- The UPDATE modify requests involve a query and must be optimized.
  143optimise(update(Updates), update(Updates), _) :- !.
  144optimise(Parsed, Optimised, Options) :-
  145	(   option(optimise(Optimise), Options)
  146	->  Optimise == true
  147	;   setting(cliopatria:optimise_query, true)
  148	),
  149	prolog_goal(Parsed, Goal0),
  150	simplify_group(Goal0, Goal1),
  151	optimise_eval(Goal1, Goal2),
  152	rdf_optimise(Goal2, Goal3), !,
  153	bind_null(Goal3, Goal, Options),
  154	set_prolog_goal(Parsed, Goal, Optimised).
  155optimise(Parsed, Optimised, Options) :-
  156	prolog_goal(Parsed, Goal0),
  157	simplify_group(Goal0, Goal1),
  158	bind_null(Goal1, Goal, Options),
  159	set_prolog_goal(Parsed, Goal, Optimised).
  160
  161% remove the outer SPARQL group. It has no meaning and reduces
  162% readability.
  163
  164simplify_group(sparql_group(G), G) :- !.
  165simplify_group(sparql_group(G, VIn, VOut), G) :-
  166	VIn = VOut, !.
  167simplify_group(Goal, Goal).
  168
  169bind_null(Goal0, Goal, Options) :-
  170	option(bind_null(true), Options), !,
  171	serql_select_bind_null(Goal0, Goal).
  172bind_null(Goal, Goal, _).
  173
  174
  175prolog_goal(select(_Proj, _DataSets, Goal, _Solutions), Goal).
  176prolog_goal(construct(_Templ, _DataSets, Goal, _Solutions), Goal).
  177prolog_goal(ask(_DataSets, Goal, _Solutions), Goal).
  178prolog_goal(describe(_Proj, _DataSets, Goal, _Solutions), Goal).
  179prolog_goal(sparql_group(Goal), Goal).
  180prolog_goal(sparql_group(Goal,_VA,_VZ), Goal).
  181
  182set_prolog_goal(select(Proj, DataSets, _Goal, Solutions), Goal,
  183		select(Proj, DataSets, Goal, Solutions)).
  184set_prolog_goal(construct(Templ, DataSets, _Goal, Solutions), Goal,
  185		construct(Templ, DataSets, Goal, Solutions)).
  186set_prolog_goal(ask(DataSets, _Goal, Solutions), Goal,
  187		ask(DataSets, Goal, Solutions)).
  188set_prolog_goal(describe(Proj, DataSets, _Goal, Solutions), Goal,
  189		describe(Proj, DataSets, Goal, Solutions)).
  190set_prolog_goal(sparql_group(_Goal), Goal, Goal).
  191set_prolog_goal(sparql_group(_Goal,VA,VZ), Goal, (Goal,VA=VZ)).
 optimise_eval(+Goal0, -Goal) is det
Perform partial evaluation on sparql_true/1 and sparql_eval/2 goals.
  199optimise_eval(GoalIn, GoalOut) :-
  200	annotate_variables(GoalIn, Vars),
  201	optimise_annotated(GoalIn, GoalOut),
  202	unbind_variables(Vars).
 annotate_variables(+Goal, -Vars) is det
Annotate variables that appear in Goal. The annotation is a variable attribute named annotations and the value of this attribute is a list of annotations.
  210annotate_variables(Goal, Vars) :-
  211	empty_assoc(Vars0),
  212	annotate_vars(Goal, Vars0, Vars).
  213
  214annotate_vars(Var, _, _) :-
  215	var(Var), !,
  216	instantiation_error(Var).
  217annotate_vars((A,B), Vars0, Vars) :- !,
  218	annotate_vars(A, Vars0, Vars1),
  219	annotate_vars(B, Vars1, Vars).
  220annotate_vars((A;B), Vars0, Vars) :- !,
  221	annotate_vars(A, Vars0, Vars1),
  222	annotate_vars(B, Vars1, Vars).
  223annotate_vars((A*->B), Vars0, Vars) :- !,
  224	annotate_vars(A, Vars0, Vars1),
  225	annotate_vars(B, Vars1, Vars).
  226annotate_vars(sparql_group(G), Vars0, Vars) :- !,
  227	annotate_vars(G, Vars0, Vars).
  228annotate_vars(sparql_group(G, _, _), Vars0, Vars) :- !,
  229	annotate_vars(G, Vars0, Vars).
  230annotate_vars(rdf(S,P,_), Vars0, Vars) :- !,
  231	annotate_var(S, resource, Vars0, Vars1),
  232	annotate_var(P, resource, Vars1, Vars).
  233annotate_vars(rdf(S,P,_,G), Vars0, Vars) :- !,
  234	annotate_var(S, resource, Vars0, Vars1),
  235	annotate_var(P, resource, Vars1, Vars2),
  236	annotate_var(G, resource, Vars2, Vars).
  237annotate_vars(_, Vars, Vars).
  238
  239annotate_var(V, Type, Vars0, Vars) :-
  240	var(V),
  241	(   get_attr(V, annotations, A0)
  242	->  \+ memberchk(Type, A0)
  243	;   A0 = []
  244	), !,
  245	put_attr(V, annotations, [Type|A0]),
  246	put_assoc(V, Vars0, true, Vars).
  247annotate_var(_, _, Vars, Vars).
  248
  249unbind_variables(VarAssoc) :-
  250	assoc_to_keys(VarAssoc, VarList),
  251	maplist(unbind_var, VarList).
  252
  253unbind_var(V) :-
  254	del_attr(V, annotations).
 optimise_eval(+GoalIn, -GoalOut)
  258optimise_annotated((A0,B0), (A,B)) :- !,
  259	optimise_annotated(A0, A),
  260	optimise_annotated(B0, B).
  261optimise_annotated((A0;B0), (A;B)) :- !,
  262	optimise_annotated(A0, A),
  263	optimise_annotated(B0, B).
  264optimise_annotated((A0*->B0), (A*->B)) :- !,
  265	optimise_annotated(A0, A),
  266	optimise_annotated(B0, B).
  267optimise_annotated(sparql_group(G0), sparql_group(G)) :- !,
  268	optimise_annotated(G0, G).
  269optimise_annotated(sparql_group(G0, OV, IV), sparql_group(G, OV, IV)) :- !,
  270	optimise_annotated(G0, G).
  271optimise_annotated(sparql_true(E), G) :- !,
  272	sparql_simplify(sparql_true(E), G).
  273optimise_annotated(sparql_eval(E,V), G) :- !,
  274	sparql_simplify(sparql_eval(E,V), G).
  275optimise_annotated(G, G).
 sparql_run(+Compiled, -Reply) is nondet
Runs a compiled SPARQL query, returning the result incrementally on backtracking. Provided there are no errors in the SPARQL implementation the only errors this can produce are resource-related errors.
  285sparql_run(sparql_query(Parsed, Reply, Module), Reply) :-
  286	sparql_reset_bnodes,
  287	sparql_run(Parsed, Reply, Module).
  288
  289sparql_run(select(_Vars, _DataSets, Query, Solutions), Reply, Module) :-
  290	select_results(Solutions, Reply, Module:Query).
  291sparql_run(construct(Triples, _DataSets, Query, Solutions), Reply, Module) :-
  292	select_results(Solutions, Reply,
  293		       Module:( Query,
  294				rdfql_triple_in(Reply, Triples)
  295			      )).
  296sparql_run(ask(_DataSets, Query, _Solutions), Result, Module) :-
  297	(   Module:Query
  298	->  Result = true
  299	;   Result = false
  300	).
  301sparql_run(describe(IRIs, _DataSets, Query, Solutions), Reply, Module) :-
  302	select_results(Solutions, Reply,
  303		       (   Module:Query,
  304			   member(IRI, IRIs)
  305		       )),
  306	sparql_describe(IRI, Module, Reply).
  307sparql_run(update(Updates), Result, Module) :-
  308	(   Module:sparql_update(Updates)
  309	->  Result = true
  310	;   Result = false
  311	).
 select_results(+Spec, -Reply, :Goal)
Apply ordering and limits on result-set.
To be done
- Handle reduced
  319:- meta_predicate select_results(+,+,0).  320:- public select_results/3.		% used on sparql_subquery/4
  321
  322select_results(distinct(solutions(Group, Having, Agg, Order, Limit, Offset)),
  323	       Reply, Goal) :- !,
  324	select_results(distinct, Group, Having, Agg, Offset, Limit,
  325		       Order, Reply, Goal).
  326select_results(reduced(Solutions),
  327	       Reply, Goal) :- !,
  328	select_results(Solutions, Reply, Goal).
  329select_results(solutions(Group, Having, Agg, Order, Limit, Offset),
  330	       Reply, Goal) :-
  331	select_results(all, Group, Having, Agg, Offset, Limit,
  332		       Order, Reply, Goal).
 select_result(+Bindings, -Row, -Names) is det
Transform the list Bindings of the form Name=Var into a Row term of the form row(Col1, Col2, ...) and a term names(Name1, ...). For example:
?- select_result([x=1,y=2], Row, Names).
Row = row(1,2), Names = names(x,y)
  346select_result(Bindings, Row, Names) :-
  347	vars_in_bindings(Bindings, Vars, VarNames),
  348	Names =.. [names|VarNames],
  349	Row =.. [row|Vars].
  350
  351vars_in_bindings([], [], []).
  352vars_in_bindings([Name=Var|T0], [Var|T], [Name|NT]) :-
  353	vars_in_bindings(T0, T, NT).
 sparql_describe(+IRI, -Triple)
Return -on backtracking- triples that describe IRI. The documentation does not specify which triples must be returned for a description. As a way to get started we simply return all direct properties.
  362sparql_describe(_Var=IRI, Module, Triple) :- !,
  363	sparql_describe(IRI, Module, Triple).
  364sparql_describe(IRI, Module, Triple) :-
  365	empty_assoc(Seen),
  366	sparql_describe(IRI, Module, Triple, Seen).
  367
  368sparql_describe(IRI, Module, Triple, Seen) :-
  369	Module:rdf(IRI, P, O),
  370	(   rdf_is_bnode(O),
  371	    \+ get_assoc(O, Seen, true)
  372	->  (   Triple = rdf(IRI, P, O)
  373	    ;	put_assoc(O, Seen, true, Seen2),
  374	        sparql_describe(O, Module, Triple, Seen2)
  375	    )
  376	;   Triple = rdf(IRI, P, O)
  377	)