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