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): 1985-2012, University of Amsterdam
    7			      VU University Amsterdam
    8
    9    This program is free software; you can redistribute it and/or
   10    modify it under the terms of the GNU General Public License
   11    as published by the Free Software Foundation; either version 2
   12    of the License, or (at your option) any later version.
   13
   14    This program is distributed in the hope that it will be useful,
   15    but WITHOUT ANY WARRANTY; without even the implied warranty of
   16    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   17    GNU General Public License for more details.
   18
   19    You should have received a copy of the GNU Lesser General Public
   20    License along with this library; if not, write to the Free Software
   21    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   22
   23    As a special exception, if you link this library with other files,
   24    compiled with a Free Software compiler, to produce an executable, this
   25    library does not by itself cause the resulting executable to be covered
   26    by the GNU General Public License. This exception does not however
   27    invalidate any other reasons why the executable file might be covered by
   28    the GNU General Public License.
   29*/
   30
   31:- module(rdfql_runtime,
   32	  [ rdfql_carthesian/1,		% +Bags
   33
   34	    rdfql_bind_null/1,		% +List
   35	    rdfql_cond_bind_null/1,	% +List
   36	    rdfql_triple_in/2,		% -Triple, +Triples
   37
   38					% SeRQL support
   39	    serql_compare/3,		% +Comparison, +Left, +Right
   40	    serql_eval/2,		% +Term, -Evaluated
   41	    serql_member_statement/2,	% -Triple, +List
   42
   43					% SPAQRL support
   44	    sparql_true/1,		% +Term
   45	    sparql_eval/2,		% +Expression, -Result
   46	    sparql_find/5,		% ?From, ?To, ?F, ?T, :Q
   47	    sparql_minus/2,		% :Q1, :Q2
   48	    sparql_group/1,		% :Query
   49	    sparql_group/3,		% :Query, +OuterVars, +InnerVars
   50	    sparql_subquery/3,		% +Proj, +Query, +Solutions
   51	    sparql_service/5,		% +Silent, +URL, +Prefixes, +Vars, +QText
   52	    sparql_update/1		% +Updates
   53	  ]).   54:- use_module(library(nb_set)).   55:- use_module(library(debug)).   56:- use_module(serql_runtime).   57:- use_module(sparql_runtime).   58
   59:- meta_predicate
   60	rdfql_carthesian(:).

SPARQL/SeRQL runtime support predicates

This module provides runtime support for running compiled queries. I.e. it defines special constructs that may be emitted by the compiler and optmizer that are common to all query languages. Language specific runtime support is in serql_runtime.pl and sparql_runtime.pl

See also
- serql_runtime.pl for the implementation of the SeRQL routines.
- sparql_runtime.pl for the implementation of the SPARQL routines. */
   73		 /*******************************
   74		 *      CARTHESIAN PRODUCT	*
   75		 *******************************/
 rdfql_carthesian(:Bags) is nondet
Bags is a list of independent goals. This predicate provides the variable bindings for the carthesian product of all solutions of each goal in Bags. For example:
?- rdfql_carthesian([ bag([X], between(1,2,X)),
                      bag([Y], between(1,2,Y))]).
X = 1, Y = 1 ;
X = 1, Y = 2 ;
X = 2, Y = 1 ;
X = 2, Y = 2 ;
false.
   93rdfql_carthesian(M:Bags) :-
   94	solve_bags(Bags, M, 1, Sets),
   95	(   debugging(carthesian_size)
   96	->  solution_set_size(Sets, Size),
   97	    debug(carthesian_size, 'Total size = ~D; NO select', [Size])
   98	;   true
   99	),
  100	(   debugging(carthesian_no_select)
  101	->  true
  102	;   carthesian_select(Sets)
  103	).
  104
  105solve_bags([], _, _, []).
  106solve_bags([bag(Templ, Goal, _Branch, _Cost)|T0], M, N, [set(Templ,Set,Size)|T]) :-
  107	empty_nb_set(Set),
  108	(   M:Goal,
  109	    add_nb_set(Templ, Set),
  110	    fail
  111	;   true
  112	),
  113	size_nb_set(Set, Size),
  114	debug(carthesian_bags, 'Bag ~d: solution size = ~D', [N, Size]),
  115	Size > 0,
  116	N2 is N + 1,
  117	solve_bags(T0, M, N2, T).
  118
  119
  120carthesian_select([]).
  121carthesian_select([call(Goal)|T]) :-
  122	call(Goal),
  123	carthesian_select(T).
  124carthesian_select([set(Templ,Set,_)|T]) :-
  125	gen_nb_set(Set, Templ),
  126	carthesian_select(T).
  127
  128solution_set_size([], 0).
  129solution_set_size([set(_,_,Len)|T], Size) :-
  130	(   T == []
  131	->  Size = Len
  132	;   solution_set_size(T, Size0),
  133	    Size is Len * Size0
  134	).
  135
  136
  137		 /*******************************
  138		 *	    NULL HANDLING	*
  139		 *******************************/
 rdfql_cond_bind_null(+List) is det
Bind variables in List to our NULL-representation, which is $null$.
  146rdfql_cond_bind_null([]).
  147rdfql_cond_bind_null([H|T]) :-
  148	(   var(H)
  149	->  H = '$null$'
  150	;   true
  151	),
  152	rdfql_cond_bind_null(T).
 rdfql_bind_null(+List) is semidet
True if all elements in List unify with $null$.
  158rdfql_bind_null([]).
  159rdfql_bind_null(['$null$'|T]) :-
  160	rdfql_bind_null(T).
 rdfql_triple_in(-Triple, +Triples) is nondet
True when Triple is an rdf(S,P,O) element in Triples that does not contain NULL. Used for CONSTRUCT and DESCRIBE.
  168rdfql_triple_in(Triple, Triples) :-
  169	Triple = rdf(S,P,O),
  170	member(Triple, Triples),
  171	S \== '$null$',
  172	P \== '$null$',
  173	O \== '$null$'