35
36:- module(rdf_describe,
37 [ rdf_bounded_description/4, 38 rdf_bounded_description/5, 39 resource_CBD/3, 40 graph_CBD/3, 41 rdf_include_reifications/3, 42 rdf_include_labels/3, 43 lcbd_label/3 44 ]). 45:- use_module(library(semweb/rdf_db)). 46:- use_module(library(assoc)). 47:- use_module(library(lists)). 48
49
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 81
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
161
162resource_CBD(Expand, S, Graph) :-
163 rdf_bounded_description(Expand, cbd, S, Graph).
164
165
166 169
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
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
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
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)