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): 2004-2006, 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: :- module(serql_runtime, Chris@0: [ serql_compare/3, % +Comparison, +Left, +Right Chris@0: serql_eval/2, % +Term, -Evaluated Chris@0: serql_member_statement/2 % -Triple, +List Chris@0: ]). Chris@0: :- use_module(library(xsdp_types)). Chris@0: :- use_module(library(debug)). Chris@0: :- use_module(library('semweb/rdf_db')). Chris@0: Chris@0: Chris@0: /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - Chris@0: This module provides runtime support for running compiled SeRQL queries. Chris@0: I.e. it defines special constructs that may be emitted by the SeRQL Chris@0: compiler and optimizer. Predicates common to all query languages have Chris@0: been moved to rdfql_runtime.pl Chris@0: - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */ Chris@0: Chris@0: Chris@0: /******************************* Chris@0: * RUNTIME TESTS * Chris@0: *******************************/ Chris@0: Chris@0: %% serql_compare(+Op, +Left, +Right) Chris@0: % Chris@0: % Handle numerical and textual comparison of literals. Some work Chris@0: % must be done at compiletime. Chris@0: Chris@0: serql_compare(Op, L, R) :- Chris@0: serql_eval(L, VL), Chris@0: serql_eval(R, VR), !, Chris@0: do_compare(Op, VL, VR). Chris@0: Chris@0: do_compare(like, literal(Value), Pattern) :- !, Chris@0: to_string(Value, String), Chris@0: rdf_match_label(like, Pattern, String). Chris@0: do_compare(like, Resource, Pattern) :- !, Chris@0: atom(Resource), Chris@0: rdf_match_label(like, Pattern, Resource). Chris@0: do_compare(=, X, X) :- !. Chris@0: do_compare(=, literal(X), query(X)) :- !. Chris@0: do_compare(=, X, query(X)) :- !. Chris@0: do_compare(\=, X, Y) :- !, Chris@0: \+ do_compare(=, X, Y). Chris@0: do_compare(Op, literal(Data), query(Query)) :- Chris@0: catch(to_number(Query, Right, TypeQ), _, fail), !, Chris@0: ( nonvar(TypeQ), atom(Data) Chris@0: -> catch(xsdp_convert(TypeQ, [Data], Left), _, fail) Chris@0: ; catch(to_number(Data, Left, TypeD), _, fail), Chris@0: serql_subsumes(TypeQ, TypeD) Chris@0: ), Chris@0: cmp_nums(Op, Left, Right). Chris@0: do_compare(Op, literal(Data), query(Query)) :- !, Chris@0: ( atom(Query) % plain text Chris@0: -> atom(Data), % TBD: Lang and Type Chris@0: cmp_strings(Op, Data, Query) Chris@0: ). Chris@0: do_compare(Op, query(Query), literal(Data)) :- !, Chris@0: inverse_op(Op, Inverse), Chris@0: do_compare(Inverse, literal(Data), query(Query)). Chris@0: do_compare(Op, literal(Value), literal(Number)) :- Chris@0: catch(to_number(Value, Left, TypeL), _, fail), Chris@0: catch(to_number(Number, Right, TypeR), _, fail), Chris@0: TypeL == TypeR, Chris@0: cmp_nums(Op, Left, Right). Chris@0: Chris@0: serql_eval(Var, X) :- Chris@0: var(Var), !, Chris@0: X = '$null$'. Chris@0: serql_eval(lang(X), Lang) :- !, Chris@0: lang(X, Lang). Chris@0: serql_eval(datatype(X), Type) :- !, Chris@0: datatype(X, Type). Chris@0: serql_eval(label(X), Lang) :- !, Chris@0: label(X, Lang). Chris@0: serql_eval(X, X). Chris@0: Chris@0: %% lang(+Literal, -Lang) is det. Chris@0: %% datatype(+Literal, -DataType) is det. Chris@0: %% label(+Literal, -Label) is det. Chris@0: % Chris@0: % Defined functions on literals. Chris@0: Chris@0: lang(literal(lang(Lang0, _)), Lang) :- Chris@0: nonvar(Lang0), !, Chris@0: Lang = literal(Lang0). Chris@0: lang(_, '$null$'). Chris@0: Chris@0: datatype(literal(type(Type0, _)), Type) :- Chris@0: nonvar(Type0), !, Chris@0: Type = Type0. Chris@0: datatype(_, '$null$'). Chris@0: Chris@0: label(literal(lang(_, Label0)), Label) :- Chris@0: nonvar(Label0), !, Chris@0: Label = literal(Label0). Chris@0: label(literal(Label0), Label) :- Chris@0: nonvar(Label0), !, Chris@0: Label = literal(Label0). Chris@0: label(_, '$null$'). Chris@0: Chris@0: Chris@0: cmp_nums(=, L, R) :- L =:= R. Chris@0: cmp_nums(=<, L, R) :- L =< R. Chris@0: cmp_nums(<, L, R) :- L < R. Chris@0: cmp_nums(>, L, R) :- L > R. Chris@0: cmp_nums(>=, L, R) :- L >= R. Chris@0: Chris@0: cmp_strings(Op, S1, S2) :- Chris@0: atom(S1), atom(S2), Chris@0: compare(Op, S1, S2). Chris@0: Chris@0: inverse_op(=, =). Chris@0: inverse_op(=<, >). Chris@0: inverse_op(<, >=). Chris@0: inverse_op(>, =<). Chris@0: inverse_op(>=, <). Chris@0: Chris@0: to_number(type(Type, String), Num, Type) :- !, % TBD: Check type Chris@0: atom_number(String, Num). Chris@0: to_number(lang(_Lang, String), Num, _) :- !, Chris@0: atom_number(String, Num). Chris@0: to_number(String, Num, _) :- Chris@0: assertion(atom(String)), Chris@0: atom_number(String, Num). Chris@0: Chris@0: %% serql_subsumes(QueryType, DataType) Chris@0: Chris@0: serql_subsumes(Q, Var) :- % odd rule! Chris@0: nonvar(Q), Chris@0: var(Var), !. Chris@0: serql_subsumes(_, Var) :- % odd rule! Chris@0: var(Var), !, fail. Chris@0: serql_subsumes(Var, _) :- % type is not specified in query Chris@0: var(Var), !. Chris@0: serql_subsumes(Query, Data) :- Chris@0: xsdp_subtype_of(Data, Query). Chris@0: Chris@0: to_string(lang(_, String), String) :- !. Chris@0: to_string(type(_, String), String) :- !. Chris@0: to_string(String, String) :- Chris@0: atom(String). Chris@0: Chris@0: %% serql_member_statement(-Triple, +List) Chris@0: % Chris@0: % Get the individual triples from the original reply. Used for Chris@0: % CONSTRUCT queries. As handling optional matches is different int Chris@0: % SeRQL compared to SPARQL, the selection is in the SeRQL runtime Chris@0: % module. Chris@0: Chris@0: serql_member_statement(RDF, [H|_]) :- Chris@0: member_statement2(RDF, H). Chris@0: serql_member_statement(RDF, [_|T]) :- Chris@0: serql_member_statement(RDF, T). Chris@0: Chris@0: member_statement2(RDF, optional(True, Statements)) :- !, Chris@0: True = true, Chris@0: serql_member_statement(RDF, Statements). Chris@0: member_statement2(RDF, RDF).