comparison 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
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(backend_rdf,
20 [ rdf//3
21 , in/5
22 ]).
23
24 :- use_module(library(semweb/rdf_db)).
25 :- use_module(library(semweb/turtle)).
26 :- use_module(library(semweb/rdf_turtle_write)).
27 :- use_module(library(dcg_core)).
28
29 :- rdf_meta rdf(r,r,o,?,?).
30 rdf(S,P,O) --> [rdf(S,P,O)].
31
32 :- rdf_meta to_literal(+,o).
33 to_literal(integer(X), literal(type(xsd:integer,Y))) :- atom_number(Y,X).
34 to_literal(float(X), literal(type(xsd:float,Y))) :- atom_number(Y,X).
35 to_literal(double(X), literal(type(xsd:double,Y))) :- atom_number(Y,X).
36 to_literal(string(X), literal(type(xsd:string,Y))) :- atom_string(Y,X).
37 to_literal(atom(X),literal(X)).
38
39 comp(Comp,Function,Input) -->
40 {once(to_literal(Input,InputLit))},
41 rdf(Comp,dmlcla:function,literal(Function)),
42 rdf(Comp,dmlcla:input,InputLit).
43
44
45 inx(Triples,SS,PP,OO,_) :-
46 in(Triples,S,P,O,_),
47 rdf_global_id(S,SS),
48 rdf_global_id(P,PP),
49 rdf_global_object(O,OO).
50
51 in(Triples,S,P,O,_) :-
52 number_vars_as_uris(Triples),
53 member(rdf(S,P,O),Triples).
54
55 phrase_triple(Phrase,S,P,O,_) :-
56 phrase(Phrase,Triples),
57 number_vars_as_uris(Triples),
58 member(rdf(S,P,O),Triples).
59
60
61 :- meta_predicate python_rdf(//,-).
62 python_rdf(Input,Output) :-
63 phrase(Input,Triples),
64 number_vars_as_uris(Triples),
65 setup_call_cleanup(
66 process_create( dml('python/rdf_wrapper.py'),[],
67 [ cwd(dml(python)), process(PID),
68 stdin(pipe(ToScript)), stdout(pipe(FromScript))]),
69 ( call_cleanup(rdf_save_turtle(stream(ToScript),[expand(in(Triples)), silent(true)]), close(ToScript)),
70 rdf_read_turtle(stream(FromScript),Output,[base_uri('_:tmp#')])
71 ),
72 (close(FromScript), process_wait(PID,Status))
73 ),
74 debug(backend,'Process exit status was: ~q',[Status]).
75
76 number_vars_as_uris(Term) :-
77 term_variables(Term,Vars),
78 seqmap(number_var_as_uri,Vars,1,_).
79 number_var_as_uri(Var,N,M) :-
80 atom_number(NN,N),
81 rdf_global_id(dmlcla:NN,Var),
82 succ(N,M).