Chris@0
|
1 /* $Id$
|
Chris@0
|
2
|
Chris@0
|
3 Part of SWI-Prolog
|
Chris@0
|
4
|
Chris@0
|
5 Author: Jan Wielemaker
|
Chris@0
|
6 E-mail: wielemak@science.uva.nl
|
Chris@0
|
7 WWW: http://www.swi-prolog.org
|
Chris@0
|
8 Copyright (C): 1985-2005, University of Amsterdam
|
Chris@0
|
9
|
Chris@0
|
10 This program is free software; you can redistribute it and/or
|
Chris@0
|
11 modify it under the terms of the GNU General Public License
|
Chris@0
|
12 as published by the Free Software Foundation; either version 2
|
Chris@0
|
13 of the License, or (at your option) any later version.
|
Chris@0
|
14
|
Chris@0
|
15 This program is distributed in the hope that it will be useful,
|
Chris@0
|
16 but WITHOUT ANY WARRANTY; without even the implied warranty of
|
Chris@0
|
17 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
Chris@0
|
18 GNU General Public License for more details.
|
Chris@0
|
19
|
Chris@0
|
20 You should have received a copy of the GNU Lesser General Public
|
Chris@0
|
21 License along with this library; if not, write to the Free Software
|
Chris@0
|
22 Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
Chris@0
|
23
|
Chris@0
|
24 As a special exception, if you link this library with other files,
|
Chris@0
|
25 compiled with a Free Software compiler, to produce an executable, this
|
Chris@0
|
26 library does not by itself cause the resulting executable to be covered
|
Chris@0
|
27 by the GNU General Public License. This exception does not however
|
Chris@0
|
28 invalidate any other reasons why the executable file might be covered by
|
Chris@0
|
29 the GNU General Public License.
|
Chris@0
|
30 */
|
Chris@0
|
31
|
Chris@0
|
32
|
Chris@0
|
33 :- module(sparql,
|
Chris@0
|
34 [ sparql_query/3, % +Query, -Result, +Options
|
Chris@0
|
35 sparql_compile/3, % +Query, -Compiled, +Options
|
Chris@0
|
36 sparql_run/2 % +Compiled, -Reply
|
Chris@0
|
37 ]).
|
Chris@0
|
38 :- use_module(library(option)).
|
Chris@0
|
39 :- use_module(sparql_grammar).
|
Chris@0
|
40 :- use_module(sparql_runtime).
|
Chris@0
|
41 :- use_module(rdfql_util).
|
Chris@0
|
42
|
Chris@0
|
43 :- multifile
|
Chris@0
|
44 function/2. % user-defined functions
|
Chris@0
|
45
|
Chris@0
|
46 %% sparql_query(+Query, -Reply, +Options)
|
Chris@0
|
47 %
|
Chris@0
|
48 % Where Query is either a SPARQL query text or a parsed
|
Chris@0
|
49 % query. Reply depends on the type of query:
|
Chris@0
|
50 %
|
Chris@0
|
51 % |SELECT | row(Col1, Col2, ....) |
|
Chris@0
|
52 % |CONSTRUCT | rdf(S,P,O) |
|
Chris@0
|
53 % |DESCRIBE | rdf(S,P,O) |
|
Chris@0
|
54 % |ASK | Reply == true or failure of pred |
|
Chris@0
|
55 %
|
Chris@0
|
56 % Options are:
|
Chris@0
|
57 %
|
Chris@0
|
58 % * entailment(Entailment)
|
Chris@0
|
59 % Specify the entailment module used (default: rdf)
|
Chris@0
|
60 %
|
Chris@0
|
61 % * base_uri(Base)
|
Chris@0
|
62 % Specify the base IRI to use for parsing the query
|
Chris@0
|
63 %
|
Chris@0
|
64 % * type(-Type)
|
Chris@0
|
65 % Returns one of select(-VarNames), construct, describe or
|
Chris@0
|
66 % ask.
|
Chris@0
|
67 %
|
Chris@0
|
68 % * ordered(-Bool)
|
Chris@0
|
69 % True if query contains an ORDER BY clause
|
Chris@0
|
70 %
|
Chris@0
|
71 % * distinct(-Bool)
|
Chris@0
|
72 % True if query contains a DISTINCT clause
|
Chris@0
|
73
|
Chris@0
|
74 sparql_query(Query, Reply, Options) :-
|
Chris@0
|
75 sparql_compile(Query, Compiled, Options),
|
Chris@0
|
76 sparql_run(Compiled, Reply).
|
Chris@0
|
77
|
Chris@0
|
78
|
Chris@0
|
79 %% sparql_compile(+Query, -Compiled, +Options)
|
Chris@0
|
80 %
|
Chris@0
|
81 % Performs the compilation pass of solving a SPARQL query.
|
Chris@0
|
82 % Splitting serves two purposes. The result of the compilation can
|
Chris@0
|
83 % be cached if desired and through Options we can get information
|
Chris@0
|
84 % about the parsed query.
|
Chris@0
|
85
|
Chris@0
|
86 sparql_compile(Query, sparql_query(Parsed, ReplyTemplate, Module), Options) :-
|
Chris@0
|
87 sparql_parse(Query, Parsed, Options),
|
Chris@0
|
88 option(entailment(Entailment), Options, rdf),
|
Chris@0
|
89 option(type(Type), Options, _),
|
Chris@0
|
90 option(ordered(Order), Options, _),
|
Chris@0
|
91 option(distinct(Distinct), Options, _),
|
Chris@0
|
92 entailment_module(Entailment, Module),
|
Chris@0
|
93 prepare(Parsed, Type, Order, Distinct, ReplyTemplate).
|
Chris@0
|
94
|
Chris@0
|
95 prepare(select(Vars, _, _, S), select(Names), O, D, Reply) :- !,
|
Chris@0
|
96 select_result(Vars, Reply, Names),
|
Chris@0
|
97 solutions(S, O, D).
|
Chris@0
|
98 prepare(construct(_,_,_,S), construct, O, D, _) :- !,
|
Chris@0
|
99 solutions(S, O, D).
|
Chris@0
|
100 prepare(ask(_,_), ask, false, false, _) :- !.
|
Chris@0
|
101 prepare(describe(_,_,_,S), describe, O, D, _) :- !,
|
Chris@0
|
102 solutions(S, O, D).
|
Chris@0
|
103 prepare(Query, Type, _, _, _) :-
|
Chris@0
|
104 nonvar(Type),
|
Chris@0
|
105 functor(Type, Expected, _),
|
Chris@0
|
106 functor(Query, Found, _),
|
Chris@0
|
107 throw(error(type_error(query_type(Expected), Found), _)).
|
Chris@0
|
108
|
Chris@0
|
109 solutions(distinct(S), O, true) :- !,
|
Chris@0
|
110 solutions(S, O).
|
Chris@0
|
111 solutions(S, O, false) :-
|
Chris@0
|
112 solutions(S, O).
|
Chris@0
|
113
|
Chris@0
|
114 solutions(solutions(unsorted, _, _), O) :- !,
|
Chris@0
|
115 O = false.
|
Chris@0
|
116 solutions(_, true).
|
Chris@0
|
117
|
Chris@0
|
118 %% sparql_run(+Compiled, -Reply) is nondet.
|
Chris@0
|
119 %
|
Chris@0
|
120 % Runs a compiled SPARQL query, returning the result incrementally
|
Chris@0
|
121 % on backtracking. Provided there are no errors in the SPARQL
|
Chris@0
|
122 % implementation the only errors this can produce are
|
Chris@0
|
123 % resource-related errors.
|
Chris@0
|
124
|
Chris@0
|
125 sparql_run(sparql_query(Parsed, Reply, Module), Reply) :-
|
Chris@0
|
126 sparql_run(Parsed, Reply, Module).
|
Chris@0
|
127
|
Chris@0
|
128 sparql_run(select(_Vars, _DataSets, Query, Solutions), Reply, Module) :-
|
Chris@0
|
129 select_results(Solutions, Reply, Module:Query).
|
Chris@0
|
130 sparql_run(construct(Triples, _DataSets, Query, Solutions), Reply, Module) :-
|
Chris@0
|
131 select_results(Solutions, Reply,
|
Chris@0
|
132 ( Module:Query,
|
Chris@0
|
133 member(Reply, Triples)
|
Chris@0
|
134 )).
|
Chris@0
|
135 sparql_run(ask(_DataSets, Query), Result, Module) :-
|
Chris@0
|
136 ( Module:Query
|
Chris@0
|
137 -> Result = true
|
Chris@0
|
138 ; Result = false
|
Chris@0
|
139 ).
|
Chris@0
|
140 sparql_run(describe(IRIs, _DataSets, Query, Solutions), Reply, Module) :-
|
Chris@0
|
141 select_results(Solutions, Reply,
|
Chris@0
|
142 ( Module:Query,
|
Chris@0
|
143 member(IRI, IRIs)
|
Chris@0
|
144 )),
|
Chris@0
|
145 sparql_describe(IRI, Module, Reply).
|
Chris@0
|
146
|
Chris@0
|
147
|
Chris@0
|
148 %% select_results(+Spec, -Reply, :Goal)
|
Chris@0
|
149 %
|
Chris@0
|
150 % Apply ordering and limits on result-set.
|
Chris@0
|
151
|
Chris@0
|
152 select_results(distinct(solutions(Order, Limit, Offset)), Reply, Goal) :- !,
|
Chris@0
|
153 select_results(distinct, Offset, Limit, Order, Reply, Goal).
|
Chris@0
|
154 select_results(solutions(Order, Limit, Offset), Reply, Goal) :-
|
Chris@0
|
155 select_results(all, Offset, Limit, Order, Reply, Goal).
|
Chris@0
|
156
|
Chris@0
|
157
|
Chris@0
|
158 %% select_result(+Bindings, -Row, -Names) is det.
|
Chris@0
|
159 %
|
Chris@0
|
160 % Transform the list Bindings of the form Name=Var into a Row term
|
Chris@0
|
161 % of the form row(Col1, Col2, ...) and a list of column-names. For
|
Chris@0
|
162 % example:
|
Chris@0
|
163 %
|
Chris@0
|
164 % ==
|
Chris@0
|
165 % ?- select_result([x=1,y=2], Row, Names).
|
Chris@0
|
166 % Row = row(1,2), Names = [x,y]
|
Chris@0
|
167 % ==
|
Chris@0
|
168
|
Chris@0
|
169 select_result(Bindings, Row, Names) :-
|
Chris@0
|
170 vars_in_bindings(Bindings, Vars, Names),
|
Chris@0
|
171 Row =.. [row|Vars].
|
Chris@0
|
172
|
Chris@0
|
173 vars_in_bindings([], [], []).
|
Chris@0
|
174 vars_in_bindings([Name=Var|T0], [Var|T], [Name|NT]) :-
|
Chris@0
|
175 vars_in_bindings(T0, T, NT).
|
Chris@0
|
176
|
Chris@0
|
177 %% sparql_describe(+IRI, -Triple)
|
Chris@0
|
178 %
|
Chris@0
|
179 % Return -on backtracking- triples that describe IRI. The
|
Chris@0
|
180 % documentation does not specify which triples must be returned
|
Chris@0
|
181 % for a description. As a way to get started we simply return all
|
Chris@0
|
182 % direct properties.
|
Chris@0
|
183
|
Chris@0
|
184 sparql_describe(IRI, Module, rdf(IRI, P, O)) :-
|
Chris@0
|
185 Module:rdf(IRI, P, O).
|
Chris@0
|
186 sparql_describe(IRI,Module,rdf(S,P,IRI)) :-
|
Chris@0
|
187 Module:rdf(S,P,IRI).
|