View source with formatted 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)  2010-2018, University of Amsterdam
    7                              VU University Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(rdfql_runtime,
   37          [ rdfql_carthesian/1,         % +Bags
   38
   39            rdfql_bind_null/1,          % +List
   40            rdfql_cond_bind_null/1,     % +List
   41            rdfql_triple_in/2,          % -Triple, +Triples
   42
   43                                        % SeRQL support
   44            serql_compare/3,            % +Comparison, +Left, +Right
   45            serql_eval/2,               % +Term, -Evaluated
   46            serql_member_statement/2,   % -Triple, +List
   47
   48                                        % SPAQRL support
   49            sparql_true/1,              % +Term
   50            sparql_eval/2,              % +Expression, -Result
   51            sparql_find/5,              % ?From, ?To, ?F, ?T, :Q
   52            sparql_minus/2,             % :Q1, :Q2
   53            sparql_group/1,             % :Query
   54            sparql_group/3,             % :Query, +OuterVars, +InnerVars
   55            sparql_subquery/3,          % +Proj, +Query, +Solutions
   56            sparql_service/5,           % +Silent, +URL, +Prefixes, +Vars, +QText
   57            sparql_update/1             % +Updates
   58          ]).   59:- use_module(library(nb_set)).   60:- use_module(library(debug)).   61:- use_module(serql_runtime).   62:- use_module(sparql_runtime).   63
   64:- meta_predicate
   65    rdfql_carthesian(:).   66
   67/** <module> SPARQL/SeRQL runtime support predicates
   68
   69This module provides runtime support for  running compiled queries. I.e.
   70it defines special constructs that may be   emitted  by the compiler and
   71optmizer that are common  to  all   query  languages.  Language specific
   72runtime support is in serql_runtime.pl and sparql_runtime.pl
   73
   74@see    serql_runtime.pl for the implementation of the SeRQL routines.
   75@see    sparql_runtime.pl for the implementation of the SPARQL routines.
   76*/
   77
   78                 /*******************************
   79                 *      CARTHESIAN PRODUCT      *
   80                 *******************************/
   81
   82%!  rdfql_carthesian(:Bags) is nondet.
   83%
   84%   Bags is a list of independent goals. This predicate provides the
   85%   variable bindings for the carthesian product of all solutions of
   86%   each goal in Bags.  For example:
   87%
   88%       ==
   89%       ?- rdfql_carthesian([ bag([X], between(1,2,X)),
   90%                             bag([Y], between(1,2,Y))]).
   91%       X = 1, Y = 1 ;
   92%       X = 1, Y = 2 ;
   93%       X = 2, Y = 1 ;
   94%       X = 2, Y = 2 ;
   95%       false.
   96%       ==
   97
   98rdfql_carthesian(M:Bags) :-
   99    solve_bags(Bags, M, 1, Sets),
  100    (   debugging(carthesian_size)
  101    ->  solution_set_size(Sets, Size),
  102        debug(carthesian_size, 'Total size = ~D; NO select', [Size])
  103    ;   true
  104    ),
  105    (   debugging(carthesian_no_select)
  106    ->  true
  107    ;   carthesian_select(Sets)
  108    ).
  109
  110solve_bags([], _, _, []).
  111solve_bags([bag(Templ, Goal, _Branch, _Cost)|T0], M, N, [set(Templ,Set,Size)|T]) :-
  112    empty_nb_set(Set),
  113    (   M:Goal,
  114        add_nb_set(Templ, Set),
  115        fail
  116    ;   true
  117    ),
  118    size_nb_set(Set, Size),
  119    debug(carthesian_bags, 'Bag ~d: solution size = ~D', [N, Size]),
  120    Size > 0,
  121    N2 is N + 1,
  122    solve_bags(T0, M, N2, T).
  123
  124
  125carthesian_select([]).
  126carthesian_select([call(Goal)|T]) :-
  127    call(Goal),
  128    carthesian_select(T).
  129carthesian_select([set(Templ,Set,_)|T]) :-
  130    gen_nb_set(Set, Templ),
  131    carthesian_select(T).
  132
  133solution_set_size([], 0).
  134solution_set_size([set(_,_,Len)|T], Size) :-
  135    (   T == []
  136    ->  Size = Len
  137    ;   solution_set_size(T, Size0),
  138        Size is Len * Size0
  139    ).
  140
  141
  142                 /*******************************
  143                 *          NULL HANDLING       *
  144                 *******************************/
  145
  146%!  rdfql_cond_bind_null(+List) is det.
  147%
  148%   Bind variables in List  to   our  NULL-representation,  which is
  149%   =|$null$|=.
  150
  151rdfql_cond_bind_null([]).
  152rdfql_cond_bind_null([H|T]) :-
  153    (   var(H)
  154    ->  H = '$null$'
  155    ;   true
  156    ),
  157    rdfql_cond_bind_null(T).
  158
  159%!  rdfql_bind_null(+List) is semidet.
  160%
  161%   True if all elements in List unify with =|$null$|=.
  162
  163rdfql_bind_null([]).
  164rdfql_bind_null(['$null$'|T]) :-
  165    rdfql_bind_null(T).
  166
  167
  168%!  rdfql_triple_in(-Triple, +Triples) is nondet.
  169%
  170%   True when Triple is an rdf(S,P,O) element in Triples that does
  171%   not contain NULL.  Used for CONSTRUCT and DESCRIBE.
  172
  173rdfql_triple_in(Triple, Triples) :-
  174    Triple = rdf(S,P,O),
  175    member(Triple, Triples),
  176    S \== '$null$',
  177    P \== '$null$',
  178    O \== '$null$'