diff cpack/dml/lib/backend_rdf.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/backend_rdf.pl	Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,82 @@
+/* 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(backend_rdf, 
+      [  rdf//3 
+      ,  in/5
+      ]).
+
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/turtle)).
+:- use_module(library(semweb/rdf_turtle_write)).
+:- use_module(library(dcg_core)).
+
+:- rdf_meta rdf(r,r,o,?,?).
+rdf(S,P,O) --> [rdf(S,P,O)].
+
+:- rdf_meta to_literal(+,o).
+to_literal(integer(X), literal(type(xsd:integer,Y))) :- atom_number(Y,X).
+to_literal(float(X),   literal(type(xsd:float,Y))) :- atom_number(Y,X).
+to_literal(double(X),  literal(type(xsd:double,Y))) :- atom_number(Y,X).
+to_literal(string(X),  literal(type(xsd:string,Y))) :- atom_string(Y,X).
+to_literal(atom(X),literal(X)).
+
+comp(Comp,Function,Input) -->
+   {once(to_literal(Input,InputLit))},
+   rdf(Comp,dmlcla:function,literal(Function)),
+   rdf(Comp,dmlcla:input,InputLit).
+
+
+inx(Triples,SS,PP,OO,_) :- 
+   in(Triples,S,P,O,_),
+   rdf_global_id(S,SS),
+   rdf_global_id(P,PP),
+   rdf_global_object(O,OO).
+
+in(Triples,S,P,O,_) :- 
+   number_vars_as_uris(Triples),
+   member(rdf(S,P,O),Triples).
+
+phrase_triple(Phrase,S,P,O,_) :-
+   phrase(Phrase,Triples),
+   number_vars_as_uris(Triples),
+   member(rdf(S,P,O),Triples).
+
+
+:- meta_predicate python_rdf(//,-).
+python_rdf(Input,Output) :-
+   phrase(Input,Triples),
+   number_vars_as_uris(Triples),
+   setup_call_cleanup(
+      process_create( dml('python/rdf_wrapper.py'),[],
+                      [ cwd(dml(python)), process(PID),
+                        stdin(pipe(ToScript)), stdout(pipe(FromScript))]),
+      (  call_cleanup(rdf_save_turtle(stream(ToScript),[expand(in(Triples)), silent(true)]), close(ToScript)),
+         rdf_read_turtle(stream(FromScript),Output,[base_uri('_:tmp#')])
+      ),
+      (close(FromScript), process_wait(PID,Status))
+   ),
+   debug(backend,'Process exit status was: ~q',[Status]).
+
+number_vars_as_uris(Term) :-
+   term_variables(Term,Vars),
+   seqmap(number_var_as_uri,Vars,1,_).
+number_var_as_uri(Var,N,M) :-
+   atom_number(NN,N),
+   rdf_global_id(dmlcla:NN,Var),
+   succ(N,M).