diff 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
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/cpack/dml/lib/rdfutils.pl	Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,140 @@
+/* Part of DML (Digital Music Laboratory)
+	Copyright 2014-2015 Samer Abdallah, University of London
+	 
+	This program is free software; you can redistribute it and/or
+	modify it under the terms of the GNU General Public License
+	as published by the Free Software Foundation; either version 2
+	of the License, or (at your option) any later version.
+
+	This program is distributed in the hope that it will be useful,
+	but WITHOUT ANY WARRANTY; without even the implied warranty of
+	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+	GNU General Public License for more details.
+
+	You should have received a copy of the GNU General Public
+	License along with this library; if not, write to the Free Software
+	Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
+*/
+
+:- module(rdfutils, 
+      [ rdf_number/3 , rdf_number/4
+      , rdf_text/4   , rdf_text/3
+      , rdf_search/5, rdf_search/4
+      , literal_number/2
+      , literal_text/2
+      , (a)/2
+      , op(700,xfx,a)
+      , parse_duration_millis/2
+      , as_typed_literal/2
+      , rdf_list_take/4
+      , rdf_list_length/2
+      , rdfx/3
+      , op(700,xfx,~=)
+      , (~=)/2
+      ]).
+
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdf_label)).
+:- use_module(library(semweb/rdfs)).
+
+:- rdf_meta rdf_text(r,r,-),
+            rdf_text(r,r,-,+),
+            rdf_number(r,r,-),
+            rdf_number(r,r,-,+),
+            rdf_search(+,r,r,+,-),
+            rdf_search(+,r,r,+),
+            a(r,r).
+
+X a Y :- rdfs_individual_of(Y,X).
+
+rdf_text(S,P,Text) :- rdf(S,P,L), literal_text(L,Text).
+rdf_text(S,P,Text,G) :- rdf(S,P,L,G), literal_text(L,Text).
+
+rdf_number(S,P,Num) :-
+   (  var(Num)
+   -> rdf(S,P,literal(Lit)), literal_number(Lit,Num)
+   ;  literal_number(Lit,Num), rdf(S,P,literal(Lit))
+   ).
+
+rdf_number(S,P,Num,G) :-
+   (  var(Num)
+   -> rdf(S,P,literal(Lit),G), literal_number(Lit,Num)
+   ;  literal_number(Lit,Num), rdf(S,P,literal(Lit),G)
+   ).
+
+literal_number(type(_Type,A),N) :- number(A) -> N=A; atom_number(A,N).
+literal_number(Atom,Num) :- atomic(Atom), atom_number(Atom,Num).
+
+%% rdf_search(+T:match_type,?Subj:uri,?Pred:uri, +Needle:atom, -Val:atom) is nondet.
+%% rdf_search(+T:match_type,?Subj:uri,?Pred:uri, +Needle:atom) is nondet.
+%  Convenience predicate for using rdf/3 with a literal search specifier - this
+%  version is more amenable for use with maplist and other metapredicates.
+%  Match types (see rdf/3) are:
+%  ==
+%  match_type ---> substring; case; prefix; exact; plain; word; like.
+%  ==
+rdf_search(T,S,P,X,Y) :- Q=..[T,X], rdf(S,P,literal(Q,Y)).
+rdf_search(T,S,P,X) :- rdf_search(T,S,P,X,_).
+
+% :- rdf_meta type_text_val(r,+,-).
+% lit_decode(literal(type(Type,Val)),X) :- type_text_val(Type,Val,X).
+% type_text_val(xsd:decimal,V,X) :- atom_number(V,X).
+% type_text_val(xsd:integer,V,X) :- atom_number(V,X), must_be(integer,X).
+
+parse_duration_millis(Atom,Dur) :-
+   split_string(Atom,':','',Parts),
+   (  Parts=[HS,MS,SS]
+   -> number_string(H,HS),
+      number_string(M,MS),
+      number_string(S,SS)
+   ;  Parts=[MS,SS]
+   -> number_string(M,MS),
+      number_string(S,SS),
+      H=0
+   ),
+   Dur is 1000*(60*(60*H + M) + S).
+   
+:- rdf_meta xsd_type(+,r).
+xsd_type(X,xsd:integer) :- integer(X), !.
+xsd_type(X,xsd:double) :- float(X), !.
+
+as_typed_literal(X,X) :- atom(X), !.
+as_typed_literal(X,Y) :- string(X), !, atom_string(Y,X).
+as_typed_literal(X,type(Type,X)) :- xsd_type(X,Type).
+
+:- rdf_meta rdf_list_take(+,r,-,r), 
+            rdf_list_length(r,-).
+
+rdf_list_take(0,List,[],List) :- !.
+rdf_list_take(_,rdf:nil,[],rdf:nil) :- !.
+rdf_list_take(N,List,[H|T],Tail) :-
+   succ(M,N),
+   rdf(List,rdf:first,H),
+   rdf(List,rdf:rest,More),
+   rdf_list_take(M,More,T,Tail).
+
+rdf_list_length(rdf:nil,0) :- !.
+rdf_list_length(List,N) :-
+   rdf(List,rdf:rest,More),
+   rdf_list_length(More,M),
+   succ(M,N).
+
+X ~= Match :- match(Match,X).
+match(Match,literal(O)) :-
+   must_be(var,O),
+   (  get_attr(O,rdfutils,match(Matches)) -> true; Matches=[]),
+   put_attr(O,rdfutils,match([Match|Matches])).
+
+:- rdf_meta rdfx(r,t,o).
+rdfx(S,Q,literal(O)) :-
+   (  get_attr(O,rdfutils,match(Matches))
+   -> maplist(rdf_matches(Q,S,O),Matches)
+   ;  Q=exact(P), rdf(S,P,literal(O))
+   ;  Q=sub(P), rdf_has(S,P,literal(O))
+   ).
+
+rdf_matches(exact(P),S,O,M) :- rdf(S,P,literal(M,O)).
+rdf_matches(sub(P),S,O,M) :- rdf_has(S,P,literal(M,O)).
+
+attr_unify_hook(_,_).
+attr_portray_hook(match(Matches),Var) :- writeq(Var:Matches).