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)  2010-2018, University of Amsterdam
    7                              VU University Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(sparql,
   37          [ sparql_query/3,             % +Query, -Result, +Options
   38            sparql_compile/3,           % +Query, -Compiled, +Options
   39            sparql_run/2                % +Compiled, -Reply
   40          ]).   41:- use_module(library(option)).   42:- use_module(library(assoc)).   43:- use_module(library(apply)).   44:- use_module(library(semweb/rdf_db), [rdf_is_bnode/1]).   45:- use_module(library(semweb/rdf_optimise)).   46:- use_module(library(settings)).   47:- use_module(sparql_grammar).   48:- use_module(sparql_runtime).   49:- use_module(rdfql_util).   50:- use_module(library(settings)).   51:- include(entailment(load)).
   52
   53:- multifile
   54    function/2.                     % user-defined functions
   55
   56:- setting(entailment, atom, rdf,
   57           '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
   88sparql_query(Query, Reply, Options) :-
   89    sparql_compile(Query, Compiled, Options),
   90    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.
  100sparql_compile(Query, sparql_query(Optimised, ReplyTemplate, Module), Options) :-
  101    sparql_parse(Query, Parsed, Options),
  102    optimise(Parsed, Optimised, Options),
  103    (   option(entailment(Entailment), Options)
  104    ->  true
  105    ;   setting(entailment, Entailment)
  106    ),
  107    option(type(Type), Options, _),
  108    option(ordered(Order), Options, _),
  109    option(distinct(Distinct), Options, _),
  110    entailment_module(Entailment, Module),
  111    prepare(Parsed, Type, Order, Distinct, ReplyTemplate).
  112
  113prepare(select(Vars, _, _, S), select(Names), O, D, Reply) :-
  114    !,
  115    select_result(Vars, Reply, Names),
  116    solutions(S, O, D).
  117prepare(construct(_,_,_,S), construct, O, D, _) :-
  118    !,
  119    solutions(S, O, D).
  120prepare(ask(_,_,S), ask, O, D, _) :-
  121    !,
  122    solutions(S, O, D).
  123prepare(describe(_,_,_,S), describe, O, D, _) :-
  124    !,
  125    solutions(S, O, D).
  126prepare(update(_), update, false, false, _) :- !.
  127prepare(Query, Type, _, _, _) :-
  128    nonvar(Type),
  129    functor(Type, Expected, _),
  130    functor(Query, Found, _),
  131    throw(error(type_error(query_type(Expected), Found), _)).
  132
  133solutions(distinct(S), O, true) :-
  134    !,
  135    solutions(S, O).
  136solutions(S, O, false) :-
  137    solutions(S, O).
  138
  139solutions(solutions(_Group, _Having, _Aggregate, unsorted, _, _), O) :-
  140    !,
  141    O = false.
  142solutions(_, 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.
  153optimise(update(Updates), update(Updates), _) :- !.
  154optimise(Parsed, Optimised, Options) :-
  155    (   option(optimise(Optimise), Options)
  156    ->  Optimise == true
  157    ;   setting(cliopatria:optimise_query, true)
  158    ),
  159    prolog_goal(Parsed, Goal0),
  160    simplify_group(Goal0, Goal1),
  161    optimise_eval(Goal1, Goal2),
  162    rdf_optimise(Goal2, Goal3),
  163    !,
  164    bind_null(Goal3, Goal, Options),
  165    set_prolog_goal(Parsed, Goal, Optimised).
  166optimise(Parsed, Optimised, Options) :-
  167    prolog_goal(Parsed, Goal0),
  168    simplify_group(Goal0, Goal1),
  169    bind_null(Goal1, Goal, Options),
  170    set_prolog_goal(Parsed, Goal, Optimised).
  171
  172% remove the outer SPARQL group. It has no meaning and reduces
  173% readability.
  174
  175simplify_group(sparql_group(G), G) :- !.
  176simplify_group(sparql_group(G, VIn, VOut), G) :-
  177    VIn = VOut,
  178    !.
  179simplify_group(Goal, Goal).
  180
  181bind_null(Goal0, Goal, Options) :-
  182    option(bind_null(true), Options),
  183    !,
  184    serql_select_bind_null(Goal0, Goal).
  185bind_null(Goal, Goal, _).
  186
  187
  188prolog_goal(select(_Proj, _DataSets, Goal, _Solutions), Goal).
  189prolog_goal(construct(_Templ, _DataSets, Goal, _Solutions), Goal).
  190prolog_goal(ask(_DataSets, Goal, _Solutions), Goal).
  191prolog_goal(describe(_Proj, _DataSets, Goal, _Solutions), Goal).
  192prolog_goal(sparql_group(Goal), Goal).
  193prolog_goal(sparql_group(Goal,_VA,_VZ), Goal).
  194
  195set_prolog_goal(select(Proj, DataSets, _Goal, Solutions), Goal,
  196                select(Proj, DataSets, Goal, Solutions)).
  197set_prolog_goal(construct(Templ, DataSets, _Goal, Solutions), Goal,
  198                construct(Templ, DataSets, Goal, Solutions)).
  199set_prolog_goal(ask(DataSets, _Goal, Solutions), Goal,
  200                ask(DataSets, Goal, Solutions)).
  201set_prolog_goal(describe(Proj, DataSets, _Goal, Solutions), Goal,
  202                describe(Proj, DataSets, Goal, Solutions)).
  203set_prolog_goal(sparql_group(_Goal), Goal, Goal).
  204set_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.
  212optimise_eval(GoalIn, GoalOut) :-
  213    annotate_variables(GoalIn, Vars),
  214    optimise_annotated(GoalIn, GoalOut),
  215    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.
  223annotate_variables(Goal, Vars) :-
  224    empty_assoc(Vars0),
  225    annotate_vars(Goal, Vars0, Vars).
  226
  227annotate_vars(Var, _, _) :-
  228    var(Var),
  229    !,
  230    instantiation_error(Var).
  231annotate_vars((A,B), Vars0, Vars) :-
  232    !,
  233    annotate_vars(A, Vars0, Vars1),
  234    annotate_vars(B, Vars1, Vars).
  235annotate_vars((A;B), Vars0, Vars) :-
  236    !,
  237    annotate_vars(A, Vars0, Vars1),
  238    annotate_vars(B, Vars1, Vars).
  239annotate_vars((A*->B), Vars0, Vars) :-
  240    !,
  241    annotate_vars(A, Vars0, Vars1),
  242    annotate_vars(B, Vars1, Vars).
  243annotate_vars(sparql_group(G), Vars0, Vars) :-
  244    !,
  245    annotate_vars(G, Vars0, Vars).
  246annotate_vars(sparql_group(G, _, _), Vars0, Vars) :-
  247    !,
  248    annotate_vars(G, Vars0, Vars).
  249annotate_vars(rdf(S,P,_), Vars0, Vars) :-
  250    !,
  251    annotate_var(S, resource, Vars0, Vars1),
  252    annotate_var(P, resource, Vars1, Vars).
  253annotate_vars(rdf(S,P,_,G), Vars0, Vars) :-
  254    !,
  255    annotate_var(S, resource, Vars0, Vars1),
  256    annotate_var(P, resource, Vars1, Vars2),
  257    annotate_var(G, resource, Vars2, Vars).
  258annotate_vars(_, Vars, Vars).
  259
  260annotate_var(V, Type, Vars0, Vars) :-
  261    var(V),
  262    (   get_attr(V, annotations, A0)
  263    ->  \+ memberchk(Type, A0)
  264    ;   A0 = []
  265    ),
  266    !,
  267    put_attr(V, annotations, [Type|A0]),
  268    put_assoc(V, Vars0, true, Vars).
  269annotate_var(_, _, Vars, Vars).
  270
  271unbind_variables(VarAssoc) :-
  272    assoc_to_keys(VarAssoc, VarList),
  273    maplist(unbind_var, VarList).
  274
  275unbind_var(V) :-
  276    del_attr(V, annotations).
 optimise_eval(+GoalIn, -GoalOut)
  280optimise_annotated((A0,B0), (A,B)) :-
  281    !,
  282    optimise_annotated(A0, A),
  283    optimise_annotated(B0, B).
  284optimise_annotated((A0;B0), (A;B)) :-
  285    !,
  286    optimise_annotated(A0, A),
  287    optimise_annotated(B0, B).
  288optimise_annotated((A0*->B0), (A*->B)) :-
  289    !,
  290    optimise_annotated(A0, A),
  291    optimise_annotated(B0, B).
  292optimise_annotated(sparql_group(G0), sparql_group(G)) :-
  293    !,
  294    optimise_annotated(G0, G).
  295optimise_annotated(sparql_group(G0, OV, IV), sparql_group(G, OV, IV)) :-
  296    !,
  297    optimise_annotated(G0, G).
  298optimise_annotated(sparql_true(E), G) :-
  299    !,
  300    sparql_simplify(sparql_true(E), G).
  301optimise_annotated(sparql_eval(E,V), G) :-
  302    !,
  303    sparql_simplify(sparql_eval(E,V), G).
  304optimise_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.
  314sparql_run(sparql_query(Parsed, Reply, Module), Reply) :-
  315    sparql_reset_bnodes,
  316    sparql_run(Parsed, Reply, Module).
  317
  318sparql_run(select(_Vars, _DataSets, Query, Solutions), Reply, Module) :-
  319    select_results(Solutions, Reply, Module:Query).
  320sparql_run(construct(Triples, _DataSets, Query, Solutions), Reply, Module) :-
  321    select_results(Solutions, Reply,
  322                   Module:( Query,
  323                            rdfql_triple_in(Reply, Triples)
  324                          )).
  325sparql_run(ask(_DataSets, Query, _Solutions), Result, Module) :-
  326    (   Module:Query
  327    ->  Result = true
  328    ;   Result = false
  329    ).
  330sparql_run(describe(IRIs, _DataSets, Query, Solutions), Reply, Module) :-
  331    select_results(Solutions, Reply,
  332                   (   Module:Query,
  333                       member(IRI, IRIs)
  334                   )),
  335    sparql_describe(IRI, Module, Reply).
  336sparql_run(update(Updates), Result, Module) :-
  337    (   Module:sparql_update(Updates)
  338    ->  Result = true
  339    ;   Result = false
  340    ).
 select_results(+Spec, -Reply, :Goal)
Apply ordering and limits on result-set.
To be done
- Handle reduced
  348:- meta_predicate select_results(+,+,0).  349:- public select_results/3.             % used on sparql_subquery/4
  350
  351select_results(distinct(solutions(Group, Having, Agg, Order, Limit, Offset)),
  352               Reply, Goal) :-
  353    !,
  354    select_results(distinct, Group, Having, Agg, Offset, Limit,
  355                   Order, Reply, Goal).
  356select_results(reduced(Solutions),
  357               Reply, Goal) :-
  358    !,
  359    select_results(Solutions, Reply, Goal).
  360select_results(solutions(Group, Having, Agg, Order, Limit, Offset),
  361               Reply, Goal) :-
  362    select_results(all, Group, Having, Agg, Offset, Limit,
  363                   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)
  377select_result(Bindings, Row, Names) :-
  378    vars_in_bindings(Bindings, Vars, VarNames),
  379    Names =.. [names|VarNames],
  380    Row =.. [row|Vars].
  381
  382vars_in_bindings([], [], []).
  383vars_in_bindings([Name=Var|T0], [Var|T], [Name|NT]) :-
  384    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.
  393sparql_describe(_Var=IRI, Module, Triple) :-
  394    !,
  395    sparql_describe(IRI, Module, Triple).
  396sparql_describe(IRI, Module, Triple) :-
  397    empty_assoc(Seen),
  398    sparql_describe(IRI, Module, Triple, Seen).
  399
  400sparql_describe(IRI, Module, Triple, Seen) :-
  401    Module:rdf(IRI, P, O),
  402    (   rdf_is_bnode(O),
  403        \+ get_assoc(O, Seen, true)
  404    ->  (   Triple = rdf(IRI, P, O)
  405        ;   put_assoc(O, Seen, true, Seen2),
  406            sparql_describe(O, Module, Triple, Seen2)
  407        )
  408    ;   Triple = rdf(IRI, P, O)
  409    )