View source with formatted comments or as raw
    1/*  Part of ClioPatria SeRQL and SPARQL server
    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(rdf_describe,
   37          [ rdf_bounded_description/4,  % :Expand, +Type, +URI, -Graph
   38            rdf_bounded_description/5,  % :Expand, +Type, +Pattern, +URI, -Graph
   39            resource_CBD/3,             % :Expand, +URI, -Graph
   40            graph_CBD/3,                % :Expand, +Graph0, -Graph
   41            rdf_include_reifications/3, % :Expand, +Graph0, -Graph
   42            rdf_include_labels/3,       % :Expand, +Graph0, -Graph
   43            lcbd_label/3                % +Subject, -Pred, -Label
   44          ]).   45:- use_module(library(semweb/rdf_db)).   46:- use_module(library(assoc)).   47:- use_module(library(lists)).   48
   49
   50/** <module> RDF Bounded descriptions
   51
   52The predicates in this module deal   with  `RDF bounded descriptions'. A
   53bounded description is a  subgraph  that   describes  a  single resource
   54(URI). Unfortunately, such  an  isolated   description  is  not possible
   55without the possibility of loosing semantics. We provide some meaningful
   56approximations described in the literature.
   57
   58Scanning the definitions given in  the   link  below, we distinguish two
   59ortogonal expansions: one expanding the graph  and another adding either
   60reifications    or    labels.    Expansion      is     implemented    by
   61rdf_bounded_description/4, while the  returned  graph   can  be  further
   62expanded using rdf_include_reifications/3 and/or rdf_include_labels/3.
   63
   64
   65@tbd    Also implement the variations on CBD
   66@see    http://n2.talis.com/wiki/Bounded_Descriptions_in_RDF
   67*/
   68
   69:- meta_predicate
   70    rdf_bounded_description(3, +, +, -),
   71    rdf_bounded_description(3, +, +, +, -),
   72    rdf_include_labels(3, +, -),
   73    resource_CBD(3, +, -),
   74    graph_CBD(3, +, -),
   75    rdf_include_reifications(3, +, -).   76
   77
   78                 /*******************************
   79                 *     RESOURCE OPERATIONS      *
   80                 *******************************/
   81
   82%!  rdf_bounded_description(:Expand, +Type, +URI, -Graph) is det.
   83%!  rdf_bounded_description(:Expand, +Type, +Filter, +URI, -Graph)  is det.
   84%
   85%   Graph is a Bounded Description of   URI.  The literature defines
   86%   various types of  bounding   descriptions.  Currently  supported
   87%   types are:
   88%
   89%       * cbd
   90%       Concise Bounded Description of URI. This notion is also
   91%       known as "the bnode-closure of a resource"
   92%       * scbd
   93%       Symmetric Concise Bounded Description is similar to
   94%       =cbd=, but includes triples with both URI as subject and
   95%       object.
   96
   97rdf_bounded_description(Expand, Type, S, Graph) :-
   98    rdf_bounded_description(Expand, Type, [], S, Graph).
   99
  100rdf_bounded_description(Expand, Type, Filter, S, Graph) :-
  101    empty_assoc(Map0),
  102    compile_pattern(Filter, Triple, Expand, Filter1),
  103    expansion(Type, Expand, S, Triple, Filter1, Graph, BNG),
  104    phrase(new_bnodes(Graph, Map0), BN),
  105    phrase(r_bnodes(BN, Type, Expand, Map0, _Map), BNG).
  106
  107compile_pattern([], _, _, true).
  108compile_pattern([rdf(S,P,O)], rdf(S,P,O), Expand,
  109                call(Expand, S,P,O)) :- !.
  110compile_pattern([rdf(S,P,O)|T], rdf(S,P,O), Expand,
  111                ( call(Expand, S,P,O) ; More )) :-
  112    compile_pattern(T, rdf(S,P,O), Expand, More).
  113
  114
  115
  116:- meta_predicate
  117    expansion(+, 3, +, +, +, -, ?),
  118    r_bnodes(+, +, 3, +, -, ?, ?).  119
  120expansion(cbd, Expand, S, rdf(S,P,O), Filter, RDF, Tail) :-
  121    findall(rdf(S,P,O), (call(Expand, S,P,O),Filter), RDF, Tail).
  122expansion(scbd, Expand, S, rdf(S,P,O), Filter, RDF, Tail) :-
  123    findall(rdf(S,P,O), (call(Expand, S,P,O),Filter), RDF, T0),
  124    findall(rdf(O,P,S), (call(Expand, O,P,S),Filter), T0, Tail).
  125
  126r_bnodes([], _, _, Map, Map) -->
  127    [].
  128r_bnodes([H|T], Type, Expand, Map0, Map, Graph, Tail) :-
  129    rdf_is_bnode(H),
  130    !,
  131    put_assoc(H, Map0, true, Map1),
  132    expansion(Type, Expand, H, _, true, Graph, Tail0),
  133    phrase(new_bnodes(Graph, Map1), BN, T),
  134    r_bnodes(BN, Type, Expand, Map1, Map, Tail0, Tail).
  135r_bnodes([_|T], Type, Expand, Map0, Map) -->
  136    r_bnodes(T, Type, Expand, Map0, Map).
  137
  138new_bnodes(Var, _) -->
  139    { var(Var) },
  140    !.
  141new_bnodes([rdf(S,_,O)|RDF], Map) -->
  142    new_bnode(S, Map),
  143    new_bnode(O, Map),
  144    new_bnodes(RDF, Map).
  145
  146new_bnode(S, Map) --> { rdf_is_bnode(S), \+ get_assoc(S, Map, _) }, !, [S].
  147new_bnode(_, _) --> [].
  148
  149
  150%!  resource_CBD(:Expand, +URI, -Graph) is det.
  151%
  152%   Graph is the Concise Bounded Description  of URI. This notion is
  153%   also known as "the bnode-closure  of   a  resource".  Note that,
  154%   according to the definition on the  Talis wiki, the CBD includes
  155%   reified  statements.  This  predicate  does  not  do  this.  Use
  156%   rdf_include_reifications/3 to add reifications to the graph.
  157%
  158%   @param  Expand is called to enumerate the PO pairs for a subject.
  159%           This will often be =rdf= to use rdf/3.
  160%   @see    http://n2.talis.com/wiki/Bounded_Descriptions_in_RDF
  161
  162resource_CBD(Expand, S, Graph) :-
  163    rdf_bounded_description(Expand, cbd, S, Graph).
  164
  165
  166                 /*******************************
  167                 *      GRAPH OPERATIONS        *
  168                 *******************************/
  169
  170%!  graph_CBD(:Expand, +Graph0, -Graph) is det.
  171%
  172%   Add concise bounded descriptions for bnodes in a graph, creating
  173%   an expanded graph.
  174
  175graph_CBD(Expand, Graph0, Graph) :-
  176    empty_assoc(Map0),
  177    must_be(list, Graph0),
  178    phrase(gr_cbd(Graph0, Expand, Map0, _Map), Graph).
  179
  180:- meta_predicate
  181    gr_cbd(+, 3, +, -, ?, ?).  182
  183gr_cbd([], _, Map, Map) -->
  184    [].
  185gr_cbd([rdf(S,P,O)|T], Expand, Map0, Map) -->
  186    {   rdf_is_bnode(S)
  187    ;   rdf_is_bnode(O)
  188    },
  189    !,
  190    [ rdf(S,P,O) ],
  191    r_bnodes([S,O], cbd, Expand, Map0, Map1),
  192    gr_cbd(T, Expand, Map1, Map).
  193gr_cbd([Triple|T], Expand, Map0, Map) -->
  194    [Triple],
  195    gr_cbd(T, Expand, Map0, Map).
  196
  197%!  rdf_include_reifications(:Expand, +Graph0, -Graph) is det.
  198%
  199%   Include the reification of any reified statements in Graph0.
  200
  201rdf_include_reifications(Expand, Graph0, Graph) :-
  202    phrase(reified_triples(Graph0, Expand), Statements),
  203    (   Statements == []
  204    ->  Graph = Graph0
  205    ;   graph_CBD(Expand, Statements, Statements1),
  206        rdf_include_reifications(Expand, Statements1, Graph1),
  207        append(Graph0, Graph1, Graph)
  208    ).
  209
  210:- meta_predicate
  211    reified_triples(+, 3, ?, ?),
  212    reification(?,?,?,3,-).  213
  214reified_triples([], _) --> [].
  215reified_triples([rdf(S,P,O)|T], Expand) -->
  216    findall(T, reification(S,P,O,Expand,T)),
  217    reified_triples(T, Expand).
  218
  219reification(S,P,O, Expand, Triple) :-
  220    rdf_equal(SP, rdf:subject),
  221    rdf_equal(PP, rdf:predicate),
  222    rdf_equal(OP, rdf:object),
  223    call(Expand, Stmt, SP, S),
  224    call(Expand, Stmt, OP, O),
  225    call(Expand, Stmt, PP, P),
  226    (   Triple = rdf(Stmt, SP, S)
  227    ;   Triple = rdf(Stmt, PP, P)
  228    ;   Triple = rdf(Stmt, OP, O)
  229    ).
  230
  231%!  rdf_include_labels(:Expand, +Graph0, -Graph) is det.
  232%
  233%   Include missing `label' statements in   Graph0.  Expand must
  234%   provide label triples on
  235%
  236%       call(Expand, S, P, O)
  237%
  238%   The  predicate  lcbd_label/3  does   this    for   the  standard
  239%   definition, considering the properties  rdfs:label, rdfs:comment
  240%   and rdfs:seeAlso.
  241
  242rdf_include_labels(Expand, Graph0, Graph) :-
  243    phrase(label_triples(Graph0, Expand), LabelRDF),
  244    (   LabelRDF == []
  245    ->  Graph = Graph0
  246    ;   append(Graph0, LabelRDF, Graph)
  247    ).
  248
  249:- meta_predicate
  250    label_triples(+, 3, ?, ?),
  251    label_triple(+, 3, -).  252
  253label_triples([], _) --> [].
  254label_triples([rdf(_,_,O)|T], Expand) -->
  255    findall(T, label_triple(O,Expand,T)),
  256    label_triples(T, Expand).
  257
  258label_triple(O, Expand, Triple) :-
  259    call(Expand, O, LP, Label),
  260    Triple = rdf(O, LP, Label).
  261
  262:- rdf_meta
  263    lcbd_property(r).  264
  265%!  lcbd_label(+S, -P, -Label) is nondet.
  266%
  267%   Standard conforming `Expand' for rdf_include_labels/3.
  268
  269lcbd_label(S, P, Label) :-
  270    lcbd_property(P),
  271    rdf_has(S, P, Label).
  272
  273lcbd_property(rdfs:label).
  274lcbd_property(rdfs:comment).
  275lcbd_property(rdfs:seeAlso)