34
35:- module(rdf_triple,
36 [ rdf_triples/2, 37 rdf_triples/3, 38 rdf_reset_ids/0, 39 rdf_start_file/2, 40 rdf_end_file/1, 41 anon_prefix/1 42 ]). 43:- autoload(library(gensym),[gensym/2,reset_gensym/1]). 44:- autoload(library(option),[option/3,option/2]). 45:- autoload(library(rdf_parser),[rdf_name_space/1]). 46:- autoload(library(uri),[iri_normalized/2]). 47
48
49:- predicate_options(rdf_start_file/2, 1,
50 [ base_uri(atom),
51 blank_nodes(oneof([share,noshare]))
52 ]). 53
86
99
100rdf_triples(RDF, Tripples) :-
101 rdf_triples(RDF, Tripples, []).
102
103rdf_triples([]) -->
104 !,
105 [].
106rdf_triples([H|T]) -->
107 !,
108 rdf_triples(H),
109 rdf_triples(T).
110rdf_triples(Term) -->
111 triples(Term, _).
112
117
118triples(description(Type, About, Props), Subject) -->
119 { var(About),
120 share_blank_nodes(true)
121 },
122 !,
123 ( { shared_description(description(Type, Props), Subject)
124 }
125 -> []
126 ; { make_id('_:Description', Id)
127 },
128 triples(description(Type, about(Id), Props), Subject),
129 { assert_shared_description(description(Type, Props), Subject)
130 }
131 ).
132triples(description(description, IdAbout, Props), Subject) -->
133 !,
134 { description_id(IdAbout, Subject)
135 },
136 properties(Props, Subject).
137triples(description(TypeURI, IdAbout, Props), Subject) -->
138 { description_id(IdAbout, Subject)
139 },
140 properties([ rdf:type = TypeURI
141 | Props
142 ], Subject).
143triples(unparsed(Data), Id) -->
144 { make_id('_:Error', Id),
145 print_message(error, rdf(unparsed(Data)))
146 },
147 [].
148
149
150 153
154:- thread_local
155 node_id/2, 156 unique_id/1. 157
158rdf_reset_node_ids :-
159 retractall(node_id(_,_)),
160 retractall(unique_id(_)).
161
162description_id(Id, Id) :-
163 var(Id),
164 !,
165 make_id('_:Description', Id).
166description_id(about(Id), Id).
167description_id(id(Id), Id) :-
168 ( unique_id(Id)
169 -> print_message(error, rdf(redefined_id(Id)))
170 ; assert(unique_id(Id))
171 ).
172description_id(each(Id), each(Id)).
173description_id(prefix(Id), prefix(Id)).
174description_id(node(NodeID), Id) :-
175 ( node_id(NodeID, Id)
176 -> true
177 ; make_id('_:Node', Id),
178 assert(node_id(NodeID, Id))
179 ).
180
181properties(PlRDF, Subject) -->
182 properties(PlRDF, 1, [], [], Subject).
183
184properties([], _, Bag, Bag, _) -->
185 [].
186properties([H0|T0], N, Bag0, Bag, Subject) -->
187 property(H0, N, NN, Bag0, Bag1, Subject),
188 properties(T0, NN, Bag1, Bag, Subject).
189
201
202property(Pred0 = Object, N, NN, BagH, BagT, Subject) --> 203 triples(Object, Id),
204 !,
205 { li_pred(Pred0, Pred, N, NN)
206 },
207 statement(Subject, Pred, Id, _, BagH, BagT).
208property(Pred0 = collection(Elems), N, NN, BagH, BagT, Subject) -->
209 !,
210 { li_pred(Pred0, Pred, N, NN)
211 },
212 statement(Subject, Pred, Object, _Id, BagH, BagT),
213 collection(Elems, Object).
214property(Pred0 = Object, N, NN, BagH, BagT, Subject) -->
215 !,
216 { li_pred(Pred0, Pred, N, NN)
217 },
218 statement(Subject, Pred, Object, _Id, BagH, BagT).
219property(id(Id, Pred0 = Object), N, NN, BagH, BagT, Subject) -->
220 triples(Object, ObjectId),
221 !,
222 { li_pred(Pred0, Pred, N, NN)
223 },
224 statement(Subject, Pred, ObjectId, Id, BagH, BagT).
225property(id(Id, Pred0 = collection(Elems)), N, NN, BagH, BagT, Subject) -->
226 !,
227 { li_pred(Pred0, Pred, N, NN)
228 },
229 statement(Subject, Pred, Object, Id, BagH, BagT),
230 collection(Elems, Object).
231property(id(Id, Pred0 = Object), N, NN, BagH, BagT, Subject) -->
232 { li_pred(Pred0, Pred, N, NN)
233 },
234 statement(Subject, Pred, Object, Id, BagH, BagT).
235
240
241statement(Subject, Pred, Object, Id, BagH, BagT) -->
242 rdf(Subject, Pred, Object),
243 { BagH = [Id|BagT]
244 -> statement_id(Id)
245 ; BagT = BagH
246 },
247 ( { nonvar(Id)
248 }
249 -> rdf(Id, rdf:type, rdf:'Statement'),
250 rdf(Id, rdf:subject, Subject),
251 rdf(Id, rdf:predicate, Pred),
252 rdf(Id, rdf:object, Object)
253 ; []
254 ).
255
256
257statement_id(Id) :-
258 nonvar(Id),
259 !.
260statement_id(Id) :-
261 make_id('_:Statement', Id).
262
266
267li_pred(rdf:li, rdf:Pred, N, NN) :-
268 !,
269 NN is N + 1,
270 atom_concat('_', N, Pred).
271li_pred(Pred, Pred, N, N).
272
277
278collection([], Nil) -->
279 { global_ref(rdf:nil, Nil)
280 }.
281collection([H|T], Id) -->
282 triples(H, HId),
283 { make_id('_:List', Id)
284 },
285 rdf(Id, rdf:type, rdf:'List'),
286 rdf(Id, rdf:first, HId),
287 rdf(Id, rdf:rest, TId),
288 collection(T, TId).
289
290
291rdf(S0, P0, O0) -->
292 { global_ref(S0, S),
293 global_ref(P0, P),
294 global_obj(O0, O)
295 },
296 [ rdf(S, P, O) ].
297
298
299global_ref(In, Out) :-
300 ( nonvar(In),
301 In = NS:Local
302 -> ( NS == rdf,
303 rdf_name_space(RDF)
304 -> atom_concat(RDF, Local, Out)
305 ; atom_concat(NS, Local, Out0),
306 iri_normalized(Out0, Out)
307 )
308 ; Out = In
309 ).
310
311global_obj(V, V) :-
312 var(V),
313 !.
314global_obj(literal(type(Local, X)), literal(type(Global, X))) :-
315 !,
316 global_ref(Local, Global).
317global_obj(literal(X), literal(X)) :- !.
318global_obj(Local, Global) :-
319 global_ref(Local, Global).
320
321
322 325
326:- thread_local
327 shared_description/3, 328 share_blank_nodes/1, 329 shared_nodes/1. 330
331reset_shared_descriptions :-
332 retractall(shared_description(_,_,_)),
333 retractall(shared_nodes(_)).
334
335shared_description(Term, Subject) :-
336 term_hash(Term, Hash),
337 shared_description(Hash, Term, Subject),
338 ( retract(shared_nodes(N))
339 -> N1 is N + 1
340 ; N1 = 1
341 ),
342 assert(shared_nodes(N1)).
343
344
345assert_shared_description(Term, Subject) :-
346 term_hash(Term, Hash),
347 assert(shared_description(Hash, Term, Subject)).
348
349
350 353
357
358rdf_start_file(Options, Cleanup) :-
359 rdf_reset_node_ids, 360 reset_shared_descriptions,
361 set_bnode_sharing(Options, C1),
362 set_anon_prefix(Options, C2),
363 add_cleanup(C1, C2, Cleanup).
364
368
369rdf_end_file(Cleanup) :-
370 rdf_reset_node_ids,
371 ( shared_nodes(N)
372 -> print_message(informational, rdf(shared_blank_nodes(N)))
373 ; true
374 ),
375 reset_shared_descriptions,
376 Cleanup.
377
378set_bnode_sharing(Options, erase(Ref)) :-
379 option(blank_nodes(Share), Options, noshare),
380 ( Share == share
381 -> assert(share_blank_nodes(true), Ref), !
382 ; Share == noshare
383 -> fail 384 ; throw(error(domain_error(share, Share), _))
385 ).
386set_bnode_sharing(_, true).
387
388set_anon_prefix(Options, erase(Ref)) :-
389 option(base_uri(BaseURI), Options),
390 nonvar(BaseURI),
391 !,
392 ( BaseURI == []
393 -> AnonBase = '_:'
394 ; atomic_list_concat(['_:', BaseURI, '#'], AnonBase)
395 ),
396 asserta(anon_prefix(AnonBase), Ref).
397set_anon_prefix(_, true).
398
399add_cleanup(true, X, X) :- !.
400add_cleanup(X, true, X) :- !.
401add_cleanup(X, Y, (X, Y)).
402
403
404 407
411
412:- thread_local
413 anon_prefix/1. 414
415make_id(For, ID) :-
416 anon_prefix(Prefix),
417 !,
418 atom_concat(Prefix, For, Base),
419 gensym(Base, ID).
420make_id(For, ID) :-
421 gensym(For, ID).
422
423anon_base('_:Description').
424anon_base('_:Statement').
425anon_base('_:List').
426anon_base('_:Node').
427
433
434rdf_reset_ids :-
435 anon_prefix(Prefix),
436 !,
437 ( anon_base(Base),
438 atom_concat(Prefix, Base, X),
439 reset_gensym(X),
440 fail
441 ; true
442 ).
443rdf_reset_ids :-
444 ( anon_base(Base),
445 reset_gensym(Base),
446 fail
447 ; true
448 )