Chris@0: /* $Id$ Chris@0: Chris@0: Part of SWI-Prolog Chris@0: Chris@0: Author: Jan Wielemaker Chris@0: E-mail: wielemak@science.uva.nl Chris@0: WWW: http://www.swi-prolog.org Chris@0: Copyright (C): 1985-2005, University of Amsterdam Chris@0: Chris@0: This program is free software; you can redistribute it and/or Chris@0: modify it under the terms of the GNU General Public License Chris@0: as published by the Free Software Foundation; either version 2 Chris@0: of the License, or (at your option) any later version. Chris@0: Chris@0: This program is distributed in the hope that it will be useful, Chris@0: but WITHOUT ANY WARRANTY; without even the implied warranty of Chris@0: MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the Chris@0: GNU General Public License for more details. Chris@0: Chris@0: You should have received a copy of the GNU Lesser General Public Chris@0: License along with this library; if not, write to the Free Software Chris@0: Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Chris@0: Chris@0: As a special exception, if you link this library with other files, Chris@0: compiled with a Free Software compiler, to produce an executable, this Chris@0: library does not by itself cause the resulting executable to be covered Chris@0: by the GNU General Public License. This exception does not however Chris@0: invalidate any other reasons why the executable file might be covered by Chris@0: the GNU General Public License. Chris@0: */ Chris@0: Chris@0: Chris@0: :- module(sparql, Chris@0: [ sparql_query/3, % +Query, -Result, +Options Chris@0: sparql_compile/3, % +Query, -Compiled, +Options Chris@0: sparql_run/2 % +Compiled, -Reply Chris@0: ]). Chris@0: :- use_module(library(option)). Chris@0: :- use_module(sparql_grammar). Chris@0: :- use_module(sparql_runtime). Chris@0: :- use_module(rdfql_util). Chris@0: Chris@0: :- multifile Chris@0: function/2. % user-defined functions Chris@0: Chris@0: %% sparql_query(+Query, -Reply, +Options) Chris@0: % Chris@0: % Where Query is either a SPARQL query text or a parsed Chris@0: % query. Reply depends on the type of query: Chris@0: % Chris@0: % |SELECT | row(Col1, Col2, ....) | Chris@0: % |CONSTRUCT | rdf(S,P,O) | Chris@0: % |DESCRIBE | rdf(S,P,O) | Chris@0: % |ASK | Reply == true or failure of pred | Chris@0: % Chris@0: % Options are: Chris@0: % Chris@0: % * entailment(Entailment) Chris@0: % Specify the entailment module used (default: rdf) Chris@0: % Chris@0: % * base_uri(Base) Chris@0: % Specify the base IRI to use for parsing the query Chris@0: % Chris@0: % * type(-Type) Chris@0: % Returns one of select(-VarNames), construct, describe or Chris@0: % ask. Chris@0: % Chris@0: % * ordered(-Bool) Chris@0: % True if query contains an ORDER BY clause Chris@0: % Chris@0: % * distinct(-Bool) Chris@0: % True if query contains a DISTINCT clause Chris@0: Chris@0: sparql_query(Query, Reply, Options) :- Chris@0: sparql_compile(Query, Compiled, Options), Chris@0: sparql_run(Compiled, Reply). Chris@0: Chris@0: Chris@0: %% sparql_compile(+Query, -Compiled, +Options) Chris@0: % Chris@0: % Performs the compilation pass of solving a SPARQL query. Chris@0: % Splitting serves two purposes. The result of the compilation can Chris@0: % be cached if desired and through Options we can get information Chris@0: % about the parsed query. Chris@0: Chris@0: sparql_compile(Query, sparql_query(Parsed, ReplyTemplate, Module), Options) :- Chris@0: sparql_parse(Query, Parsed, Options), Chris@0: option(entailment(Entailment), Options, rdf), Chris@0: option(type(Type), Options, _), Chris@0: option(ordered(Order), Options, _), Chris@0: option(distinct(Distinct), Options, _), Chris@0: entailment_module(Entailment, Module), Chris@0: prepare(Parsed, Type, Order, Distinct, ReplyTemplate). Chris@0: Chris@0: prepare(select(Vars, _, _, S), select(Names), O, D, Reply) :- !, Chris@0: select_result(Vars, Reply, Names), Chris@0: solutions(S, O, D). Chris@0: prepare(construct(_,_,_,S), construct, O, D, _) :- !, Chris@0: solutions(S, O, D). Chris@0: prepare(ask(_,_), ask, false, false, _) :- !. Chris@0: prepare(describe(_,_,_,S), describe, O, D, _) :- !, Chris@0: solutions(S, O, D). Chris@0: prepare(Query, Type, _, _, _) :- Chris@0: nonvar(Type), Chris@0: functor(Type, Expected, _), Chris@0: functor(Query, Found, _), Chris@0: throw(error(type_error(query_type(Expected), Found), _)). Chris@0: Chris@0: solutions(distinct(S), O, true) :- !, Chris@0: solutions(S, O). Chris@0: solutions(S, O, false) :- Chris@0: solutions(S, O). Chris@0: Chris@0: solutions(solutions(unsorted, _, _), O) :- !, Chris@0: O = false. Chris@0: solutions(_, true). Chris@0: Chris@0: %% sparql_run(+Compiled, -Reply) is nondet. Chris@0: % Chris@0: % Runs a compiled SPARQL query, returning the result incrementally Chris@0: % on backtracking. Provided there are no errors in the SPARQL Chris@0: % implementation the only errors this can produce are Chris@0: % resource-related errors. Chris@0: Chris@0: sparql_run(sparql_query(Parsed, Reply, Module), Reply) :- Chris@0: sparql_run(Parsed, Reply, Module). Chris@0: Chris@0: sparql_run(select(_Vars, _DataSets, Query, Solutions), Reply, Module) :- Chris@0: select_results(Solutions, Reply, Module:Query). Chris@0: sparql_run(construct(Triples, _DataSets, Query, Solutions), Reply, Module) :- Chris@0: select_results(Solutions, Reply, Chris@0: ( Module:Query, Chris@0: member(Reply, Triples) Chris@0: )). Chris@0: sparql_run(ask(_DataSets, Query), Result, Module) :- Chris@0: ( Module:Query Chris@0: -> Result = true Chris@0: ; Result = false Chris@0: ). Chris@0: sparql_run(describe(IRIs, _DataSets, Query, Solutions), Reply, Module) :- Chris@0: select_results(Solutions, Reply, Chris@0: ( Module:Query, Chris@0: member(IRI, IRIs) Chris@0: )), Chris@0: sparql_describe(IRI, Module, Reply). Chris@0: Chris@0: Chris@0: %% select_results(+Spec, -Reply, :Goal) Chris@0: % Chris@0: % Apply ordering and limits on result-set. Chris@0: Chris@0: select_results(distinct(solutions(Order, Limit, Offset)), Reply, Goal) :- !, Chris@0: select_results(distinct, Offset, Limit, Order, Reply, Goal). Chris@0: select_results(solutions(Order, Limit, Offset), Reply, Goal) :- Chris@0: select_results(all, Offset, Limit, Order, Reply, Goal). Chris@0: Chris@0: Chris@0: %% select_result(+Bindings, -Row, -Names) is det. Chris@0: % Chris@0: % Transform the list Bindings of the form Name=Var into a Row term Chris@0: % of the form row(Col1, Col2, ...) and a list of column-names. For Chris@0: % example: Chris@0: % Chris@0: % == Chris@0: % ?- select_result([x=1,y=2], Row, Names). Chris@0: % Row = row(1,2), Names = [x,y] Chris@0: % == Chris@0: Chris@0: select_result(Bindings, Row, Names) :- Chris@0: vars_in_bindings(Bindings, Vars, Names), Chris@0: Row =.. [row|Vars]. Chris@0: Chris@0: vars_in_bindings([], [], []). Chris@0: vars_in_bindings([Name=Var|T0], [Var|T], [Name|NT]) :- Chris@0: vars_in_bindings(T0, T, NT). Chris@0: Chris@0: %% sparql_describe(+IRI, -Triple) Chris@0: % Chris@0: % Return -on backtracking- triples that describe IRI. The Chris@0: % documentation does not specify which triples must be returned Chris@0: % for a description. As a way to get started we simply return all Chris@0: % direct properties. Chris@0: Chris@0: sparql_describe(IRI, Module, rdf(IRI, P, O)) :- Chris@0: Module:rdf(IRI, P, O). Chris@0: sparql_describe(IRI,Module,rdf(S,P,IRI)) :- Chris@0: Module:rdf(S,P,IRI).