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