comparison cpack/dml/lib/rdfutils.pl @ 0:718306e29690 tip

commiting public release
author Daniel Wolff
date Tue, 09 Feb 2016 21:05:06 +0100
parents
children
comparison
equal deleted inserted replaced
-1:000000000000 0:718306e29690
1 /* Part of DML (Digital Music Laboratory)
2 Copyright 2014-2015 Samer Abdallah, University of London
3
4 This program is free software; you can redistribute it and/or
5 modify it under the terms of the GNU General Public License
6 as published by the Free Software Foundation; either version 2
7 of the License, or (at your option) any later version.
8
9 This program is distributed in the hope that it will be useful,
10 but WITHOUT ANY WARRANTY; without even the implied warranty of
11 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12 GNU General Public License for more details.
13
14 You should have received a copy of the GNU General Public
15 License along with this library; if not, write to the Free Software
16 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
17 */
18
19 :- module(rdfutils,
20 [ rdf_number/3 , rdf_number/4
21 , rdf_text/4 , rdf_text/3
22 , rdf_search/5, rdf_search/4
23 , literal_number/2
24 , literal_text/2
25 , (a)/2
26 , op(700,xfx,a)
27 , parse_duration_millis/2
28 , as_typed_literal/2
29 , rdf_list_take/4
30 , rdf_list_length/2
31 , rdfx/3
32 , op(700,xfx,~=)
33 , (~=)/2
34 ]).
35
36 :- use_module(library(semweb/rdf_db)).
37 :- use_module(library(semweb/rdf_label)).
38 :- use_module(library(semweb/rdfs)).
39
40 :- rdf_meta rdf_text(r,r,-),
41 rdf_text(r,r,-,+),
42 rdf_number(r,r,-),
43 rdf_number(r,r,-,+),
44 rdf_search(+,r,r,+,-),
45 rdf_search(+,r,r,+),
46 a(r,r).
47
48 X a Y :- rdfs_individual_of(Y,X).
49
50 rdf_text(S,P,Text) :- rdf(S,P,L), literal_text(L,Text).
51 rdf_text(S,P,Text,G) :- rdf(S,P,L,G), literal_text(L,Text).
52
53 rdf_number(S,P,Num) :-
54 ( var(Num)
55 -> rdf(S,P,literal(Lit)), literal_number(Lit,Num)
56 ; literal_number(Lit,Num), rdf(S,P,literal(Lit))
57 ).
58
59 rdf_number(S,P,Num,G) :-
60 ( var(Num)
61 -> rdf(S,P,literal(Lit),G), literal_number(Lit,Num)
62 ; literal_number(Lit,Num), rdf(S,P,literal(Lit),G)
63 ).
64
65 literal_number(type(_Type,A),N) :- number(A) -> N=A; atom_number(A,N).
66 literal_number(Atom,Num) :- atomic(Atom), atom_number(Atom,Num).
67
68 %% rdf_search(+T:match_type,?Subj:uri,?Pred:uri, +Needle:atom, -Val:atom) is nondet.
69 %% rdf_search(+T:match_type,?Subj:uri,?Pred:uri, +Needle:atom) is nondet.
70 % Convenience predicate for using rdf/3 with a literal search specifier - this
71 % version is more amenable for use with maplist and other metapredicates.
72 % Match types (see rdf/3) are:
73 % ==
74 % match_type ---> substring; case; prefix; exact; plain; word; like.
75 % ==
76 rdf_search(T,S,P,X,Y) :- Q=..[T,X], rdf(S,P,literal(Q,Y)).
77 rdf_search(T,S,P,X) :- rdf_search(T,S,P,X,_).
78
79 % :- rdf_meta type_text_val(r,+,-).
80 % lit_decode(literal(type(Type,Val)),X) :- type_text_val(Type,Val,X).
81 % type_text_val(xsd:decimal,V,X) :- atom_number(V,X).
82 % type_text_val(xsd:integer,V,X) :- atom_number(V,X), must_be(integer,X).
83
84 parse_duration_millis(Atom,Dur) :-
85 split_string(Atom,':','',Parts),
86 ( Parts=[HS,MS,SS]
87 -> number_string(H,HS),
88 number_string(M,MS),
89 number_string(S,SS)
90 ; Parts=[MS,SS]
91 -> number_string(M,MS),
92 number_string(S,SS),
93 H=0
94 ),
95 Dur is 1000*(60*(60*H + M) + S).
96
97 :- rdf_meta xsd_type(+,r).
98 xsd_type(X,xsd:integer) :- integer(X), !.
99 xsd_type(X,xsd:double) :- float(X), !.
100
101 as_typed_literal(X,X) :- atom(X), !.
102 as_typed_literal(X,Y) :- string(X), !, atom_string(Y,X).
103 as_typed_literal(X,type(Type,X)) :- xsd_type(X,Type).
104
105 :- rdf_meta rdf_list_take(+,r,-,r),
106 rdf_list_length(r,-).
107
108 rdf_list_take(0,List,[],List) :- !.
109 rdf_list_take(_,rdf:nil,[],rdf:nil) :- !.
110 rdf_list_take(N,List,[H|T],Tail) :-
111 succ(M,N),
112 rdf(List,rdf:first,H),
113 rdf(List,rdf:rest,More),
114 rdf_list_take(M,More,T,Tail).
115
116 rdf_list_length(rdf:nil,0) :- !.
117 rdf_list_length(List,N) :-
118 rdf(List,rdf:rest,More),
119 rdf_list_length(More,M),
120 succ(M,N).
121
122 X ~= Match :- match(Match,X).
123 match(Match,literal(O)) :-
124 must_be(var,O),
125 ( get_attr(O,rdfutils,match(Matches)) -> true; Matches=[]),
126 put_attr(O,rdfutils,match([Match|Matches])).
127
128 :- rdf_meta rdfx(r,t,o).
129 rdfx(S,Q,literal(O)) :-
130 ( get_attr(O,rdfutils,match(Matches))
131 -> maplist(rdf_matches(Q,S,O),Matches)
132 ; Q=exact(P), rdf(S,P,literal(O))
133 ; Q=sub(P), rdf_has(S,P,literal(O))
134 ).
135
136 rdf_matches(exact(P),S,O,M) :- rdf(S,P,literal(M,O)).
137 rdf_matches(sub(P),S,O,M) :- rdf_has(S,P,literal(M,O)).
138
139 attr_unify_hook(_,_).
140 attr_portray_hook(match(Matches),Var) :- writeq(Var:Matches).