View source with raw comments or as raw
    1/*  Part of ClioPatria SPARQL server
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2012-2018, VU University Amsterdam
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(jena_properties, []).   36:- use_module(library(semweb/rdfs)).   37:- use_module(library(semweb/rdf_db)).   38:- use_module(library(aggregate)).   39:- use_module(sparql_runtime).   40
   41:- multifile
   42    sparql:functional_property/2,
   43    sparql:current_functional_property/3.   44
   45ns(apf,   'http://jena.hpl.hp.com/ARQ/property#').
   46ns(lists, 'http://jena.hpl.hp.com/ARQ/list#').
   47ns(Prefix, URI) :-
   48    rdf_current_ns(Prefix, URI).
   49
   50alias('java:com.hp.hpl.jena.sparql.pfunction.library.',
   51      'http://jena.hpl.hp.com/ARQ/property#').
   52alias('java:com.hp.hpl.jena.query.pfunction.library.',
   53      'http://jena.hpl.hp.com/ARQ/property#').
   54
   55property_alias(Prefix:Local, Global) :-
   56    ns(Prefix, URI),
   57    alias(AliasBase, URI),
   58    atom_concat(AliasBase, Local, Global).
   59
   60absolute_uri(Prefix:Local, Global) :-
   61    ns(Prefix, URI),
   62    atom_concat(URI, Local, Global).
   63
   64term_expansion((sparql:functional_property(S, NS:Term0) :- Body),
   65               [ (sparql:functional_property(S, Term) :- Body),
   66                 sparql:current_functional_property(P, P, Argc)
   67               | Aliases
   68               ]) :-
   69    Term0 =.. [Name|Args],
   70    length(Args, Argc),
   71    absolute_uri(NS:Name, P),
   72    Term =.. [P|Args],
   73    findall(sparql:current_functional_property(P1, P, Argc),
   74            property_alias(NS:Name, P1),
   75            Aliases).
   76
   77
   78                 /*******************************
   79                 *    JENA PROPERTY FUNCTIONS   *
   80                 *******************************/
   81
   82% See http://jena.sourceforge.net/ARQ/library-propfunc.html
   83
   84% (S apf:assign, O) is basically unification.
   85
   86sparql:functional_property(S, apf:assign(O)) :-
   87    (   S = O
   88    ->  true
   89    ;   sparql_true(S=O)
   90    ).
   91
   92
   93                 /*******************************
   94                 *             LISTS            *
   95                 *******************************/
   96
   97rdf_list(S) :-
   98    rdf_equal(S, rdf:nil).
   99rdf_list(S) :-
  100    rdf(S, rdf:first, _).
  101
  102rdf_container(Container) :-
  103    container_class(Class),
  104    rdfs_individual_of(Container, Class).
  105
  106:- rdf_meta container_class(r).  107
  108container_class(rdf:'Bag').
  109container_class(rdf:'Seq').
  110container_class(rdf:'Alt').
  111
  112% (S, lists:member, O) means that O is a member of the collection S. In
  113% Jena, S may be unbound, finding all lists on the database.
  114
  115sparql:functional_property(S, lists:member(O)) :-
  116    rdf_list(S),
  117    rdfs_member(O, S).
  118
  119sparql:functional_property(S, rdfs:member(O)) :-
  120    rdf_container(S),
  121    rdfs_member(O, S).
  122
  123sparql:functional_property(S, apf:bag(O)) :-
  124    nonvar(S),
  125    rdfs_individual_of(S, rdfs:'Bag'),
  126    rdfs_member(O, S).
  127sparql:functional_property(S, apf:seq(O)) :-
  128    nonvar(S),
  129    rdfs_individual_of(S, rdfs:'Seq'),
  130    rdfs_member(O, S).
  131sparql:functional_property(S, apf:alt(O)) :-
  132    nonvar(S),
  133    rdfs_individual_of(S, rdfs:'Alt'),
  134    rdfs_member(O, S).
  135
  136
  137% (S, lists:length, O) is true when O is the length of the collection S.
  138% Again, S may be unbound.
  139
  140sparql:functional_property(S, lists:length(O)) :-
  141    rdf_list(S),
  142    aggregate_all(count, rdfs_member(_, S), Len),
  143    rdf_equal(xsd:integer, IntType),
  144    atom_number(String, Len),
  145    O = literal(type(IntType, String)).
  146
  147sparql:functional_property(S, lists:index(literal(type(IntType, Index)),
  148                                          Element)) :-
  149    rdf_list(S),
  150    rdf_equal(xsd:integer, IntType),
  151    (   var(Index)
  152    ->  rdfs_nth1(I, S, Element),
  153        atom_number(Index, I)
  154    ;   atom_number(Index, I),
  155        rdfs_nth1(I, S, Element)
  156    ->  true
  157    ).
  158
  159
  160rdfs_nth1(0, Set, Element) :-
  161    rdf_has(Set, rdf:first, Element).
  162rdfs_nth1(I, Set, Element) :-
  163    var(I),
  164    !,
  165    rdf_has(Set, rdf:rest, Tail),
  166    rdfs_nth1(I0, Tail, Element),
  167    I is I0 + 1.
  168rdfs_nth1(I, Set, Element) :-
  169    I2 is I - 1,
  170    rdf_has(Set, rdf:rest, Tail),
  171    rdfs_nth1(I2, Tail, Element)