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): 2004-2006, 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 :- module(serql_runtime,
|
Chris@0
|
33 [ serql_compare/3, % +Comparison, +Left, +Right
|
Chris@0
|
34 serql_eval/2, % +Term, -Evaluated
|
Chris@0
|
35 serql_member_statement/2 % -Triple, +List
|
Chris@0
|
36 ]).
|
Chris@0
|
37 :- use_module(library(xsdp_types)).
|
Chris@0
|
38 :- use_module(library(debug)).
|
Chris@0
|
39 :- use_module(library('semweb/rdf_db')).
|
Chris@0
|
40
|
Chris@0
|
41
|
Chris@0
|
42 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
|
Chris@0
|
43 This module provides runtime support for running compiled SeRQL queries.
|
Chris@0
|
44 I.e. it defines special constructs that may be emitted by the SeRQL
|
Chris@0
|
45 compiler and optimizer. Predicates common to all query languages have
|
Chris@0
|
46 been moved to rdfql_runtime.pl
|
Chris@0
|
47 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
|
Chris@0
|
48
|
Chris@0
|
49
|
Chris@0
|
50 /*******************************
|
Chris@0
|
51 * RUNTIME TESTS *
|
Chris@0
|
52 *******************************/
|
Chris@0
|
53
|
Chris@0
|
54 %% serql_compare(+Op, +Left, +Right)
|
Chris@0
|
55 %
|
Chris@0
|
56 % Handle numerical and textual comparison of literals. Some work
|
Chris@0
|
57 % must be done at compiletime.
|
Chris@0
|
58
|
Chris@0
|
59 serql_compare(Op, L, R) :-
|
Chris@0
|
60 serql_eval(L, VL),
|
Chris@0
|
61 serql_eval(R, VR), !,
|
Chris@0
|
62 do_compare(Op, VL, VR).
|
Chris@0
|
63
|
Chris@0
|
64 do_compare(like, literal(Value), Pattern) :- !,
|
Chris@0
|
65 to_string(Value, String),
|
Chris@0
|
66 rdf_match_label(like, Pattern, String).
|
Chris@0
|
67 do_compare(like, Resource, Pattern) :- !,
|
Chris@0
|
68 atom(Resource),
|
Chris@0
|
69 rdf_match_label(like, Pattern, Resource).
|
Chris@0
|
70 do_compare(=, X, X) :- !.
|
Chris@0
|
71 do_compare(=, literal(X), query(X)) :- !.
|
Chris@0
|
72 do_compare(=, X, query(X)) :- !.
|
Chris@0
|
73 do_compare(\=, X, Y) :- !,
|
Chris@0
|
74 \+ do_compare(=, X, Y).
|
Chris@0
|
75 do_compare(Op, literal(Data), query(Query)) :-
|
Chris@0
|
76 catch(to_number(Query, Right, TypeQ), _, fail), !,
|
Chris@0
|
77 ( nonvar(TypeQ), atom(Data)
|
Chris@0
|
78 -> catch(xsdp_convert(TypeQ, [Data], Left), _, fail)
|
Chris@0
|
79 ; catch(to_number(Data, Left, TypeD), _, fail),
|
Chris@0
|
80 serql_subsumes(TypeQ, TypeD)
|
Chris@0
|
81 ),
|
Chris@0
|
82 cmp_nums(Op, Left, Right).
|
Chris@0
|
83 do_compare(Op, literal(Data), query(Query)) :- !,
|
Chris@0
|
84 ( atom(Query) % plain text
|
Chris@0
|
85 -> atom(Data), % TBD: Lang and Type
|
Chris@0
|
86 cmp_strings(Op, Data, Query)
|
Chris@0
|
87 ).
|
Chris@0
|
88 do_compare(Op, query(Query), literal(Data)) :- !,
|
Chris@0
|
89 inverse_op(Op, Inverse),
|
Chris@0
|
90 do_compare(Inverse, literal(Data), query(Query)).
|
Chris@0
|
91 do_compare(Op, literal(Value), literal(Number)) :-
|
Chris@0
|
92 catch(to_number(Value, Left, TypeL), _, fail),
|
Chris@0
|
93 catch(to_number(Number, Right, TypeR), _, fail),
|
Chris@0
|
94 TypeL == TypeR,
|
Chris@0
|
95 cmp_nums(Op, Left, Right).
|
Chris@0
|
96
|
Chris@0
|
97 serql_eval(Var, X) :-
|
Chris@0
|
98 var(Var), !,
|
Chris@0
|
99 X = '$null$'.
|
Chris@0
|
100 serql_eval(lang(X), Lang) :- !,
|
Chris@0
|
101 lang(X, Lang).
|
Chris@0
|
102 serql_eval(datatype(X), Type) :- !,
|
Chris@0
|
103 datatype(X, Type).
|
Chris@0
|
104 serql_eval(label(X), Lang) :- !,
|
Chris@0
|
105 label(X, Lang).
|
Chris@0
|
106 serql_eval(X, X).
|
Chris@0
|
107
|
Chris@0
|
108 %% lang(+Literal, -Lang) is det.
|
Chris@0
|
109 %% datatype(+Literal, -DataType) is det.
|
Chris@0
|
110 %% label(+Literal, -Label) is det.
|
Chris@0
|
111 %
|
Chris@0
|
112 % Defined functions on literals.
|
Chris@0
|
113
|
Chris@0
|
114 lang(literal(lang(Lang0, _)), Lang) :-
|
Chris@0
|
115 nonvar(Lang0), !,
|
Chris@0
|
116 Lang = literal(Lang0).
|
Chris@0
|
117 lang(_, '$null$').
|
Chris@0
|
118
|
Chris@0
|
119 datatype(literal(type(Type0, _)), Type) :-
|
Chris@0
|
120 nonvar(Type0), !,
|
Chris@0
|
121 Type = Type0.
|
Chris@0
|
122 datatype(_, '$null$').
|
Chris@0
|
123
|
Chris@0
|
124 label(literal(lang(_, Label0)), Label) :-
|
Chris@0
|
125 nonvar(Label0), !,
|
Chris@0
|
126 Label = literal(Label0).
|
Chris@0
|
127 label(literal(Label0), Label) :-
|
Chris@0
|
128 nonvar(Label0), !,
|
Chris@0
|
129 Label = literal(Label0).
|
Chris@0
|
130 label(_, '$null$').
|
Chris@0
|
131
|
Chris@0
|
132
|
Chris@0
|
133 cmp_nums(=, L, R) :- L =:= R.
|
Chris@0
|
134 cmp_nums(=<, L, R) :- L =< R.
|
Chris@0
|
135 cmp_nums(<, L, R) :- L < R.
|
Chris@0
|
136 cmp_nums(>, L, R) :- L > R.
|
Chris@0
|
137 cmp_nums(>=, L, R) :- L >= R.
|
Chris@0
|
138
|
Chris@0
|
139 cmp_strings(Op, S1, S2) :-
|
Chris@0
|
140 atom(S1), atom(S2),
|
Chris@0
|
141 compare(Op, S1, S2).
|
Chris@0
|
142
|
Chris@0
|
143 inverse_op(=, =).
|
Chris@0
|
144 inverse_op(=<, >).
|
Chris@0
|
145 inverse_op(<, >=).
|
Chris@0
|
146 inverse_op(>, =<).
|
Chris@0
|
147 inverse_op(>=, <).
|
Chris@0
|
148
|
Chris@0
|
149 to_number(type(Type, String), Num, Type) :- !, % TBD: Check type
|
Chris@0
|
150 atom_number(String, Num).
|
Chris@0
|
151 to_number(lang(_Lang, String), Num, _) :- !,
|
Chris@0
|
152 atom_number(String, Num).
|
Chris@0
|
153 to_number(String, Num, _) :-
|
Chris@0
|
154 assertion(atom(String)),
|
Chris@0
|
155 atom_number(String, Num).
|
Chris@0
|
156
|
Chris@0
|
157 %% serql_subsumes(QueryType, DataType)
|
Chris@0
|
158
|
Chris@0
|
159 serql_subsumes(Q, Var) :- % odd rule!
|
Chris@0
|
160 nonvar(Q),
|
Chris@0
|
161 var(Var), !.
|
Chris@0
|
162 serql_subsumes(_, Var) :- % odd rule!
|
Chris@0
|
163 var(Var), !, fail.
|
Chris@0
|
164 serql_subsumes(Var, _) :- % type is not specified in query
|
Chris@0
|
165 var(Var), !.
|
Chris@0
|
166 serql_subsumes(Query, Data) :-
|
Chris@0
|
167 xsdp_subtype_of(Data, Query).
|
Chris@0
|
168
|
Chris@0
|
169 to_string(lang(_, String), String) :- !.
|
Chris@0
|
170 to_string(type(_, String), String) :- !.
|
Chris@0
|
171 to_string(String, String) :-
|
Chris@0
|
172 atom(String).
|
Chris@0
|
173
|
Chris@0
|
174 %% serql_member_statement(-Triple, +List)
|
Chris@0
|
175 %
|
Chris@0
|
176 % Get the individual triples from the original reply. Used for
|
Chris@0
|
177 % CONSTRUCT queries. As handling optional matches is different int
|
Chris@0
|
178 % SeRQL compared to SPARQL, the selection is in the SeRQL runtime
|
Chris@0
|
179 % module.
|
Chris@0
|
180
|
Chris@0
|
181 serql_member_statement(RDF, [H|_]) :-
|
Chris@0
|
182 member_statement2(RDF, H).
|
Chris@0
|
183 serql_member_statement(RDF, [_|T]) :-
|
Chris@0
|
184 serql_member_statement(RDF, T).
|
Chris@0
|
185
|
Chris@0
|
186 member_statement2(RDF, optional(True, Statements)) :- !,
|
Chris@0
|
187 True = true,
|
Chris@0
|
188 serql_member_statement(RDF, Statements).
|
Chris@0
|
189 member_statement2(RDF, RDF).
|