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