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(dovamp, []).
|
Daniel@0
|
20
|
Daniel@0
|
21
|
Daniel@0
|
22 :- use_module(library(persistency)).
|
Daniel@0
|
23 :- use_module(library(semweb/rdf_db)).
|
Daniel@0
|
24 :- use_module(library(semweb/rdf_turtle_write)).
|
Daniel@0
|
25 :- use_module(library(fileutils)).
|
Daniel@0
|
26 :- use_module(library(computations)).
|
Daniel@0
|
27 :- use_module(library(swipe)).
|
Daniel@0
|
28 :- use_module(library(async)).
|
Daniel@0
|
29 :- use_module(components(audio)).
|
Daniel@0
|
30 :- use_module(api(archive)).
|
Daniel@0
|
31
|
Daniel@0
|
32 computations:do_computation(Transform,Input,Output) :-
|
Daniel@0
|
33 rdf(Transform,rdf:type,vamp:'Transform'), !,
|
Daniel@0
|
34 debug(dovamp,'Doing on demand Vamp ~q on ~q',[Transform,Input]),
|
Daniel@0
|
35 with_temp_dir(Dir, with_progress_stack(sonic_annotator(Dir,Transform,Input,Output))).
|
Daniel@0
|
36
|
Daniel@0
|
37 sonic_annotator(Dir,Transform,Input,CSVFile) :-
|
Daniel@0
|
38 directory_file_path(Dir,'transform.n3',TFile),
|
Daniel@0
|
39 directory_file_path(Dir,'*.csv',CSVPattern),
|
Daniel@0
|
40 ( cp_audio:audio_file(Input,AudioFile,_) -> true
|
Daniel@0
|
41 ; % !!! HACK
|
Daniel@0
|
42 (rdf(Input,dml:blpage,_) -> ignore(bl_p2r:scrape_audio_link(Input,_)); true),
|
Daniel@0
|
43 cp_audio:audio_link(Input,AudioLink,_),
|
Daniel@0
|
44 directory_file_path(Dir,audio,AudioFile),
|
Daniel@0
|
45 format(string(Desc),"Downloading audio for ~w to ~w",[Input,AudioFile]),
|
Daniel@0
|
46 simple_task(Desc,run(curl(AudioLink)>:AudioFile^_))
|
Daniel@0
|
47 ),
|
Daniel@0
|
48 write_transform(Transform,TFile),
|
Daniel@0
|
49 run_with_progress(sonic_annotator(csv(Dir),TFile,AudioFile)),
|
Daniel@0
|
50 expand_file_name(CSVPattern,[LocalCSV]),
|
Daniel@0
|
51 archive_file('.csv',LocalCSV,CSVFile).
|
Daniel@0
|
52
|
Daniel@0
|
53 run_with_progress(Pipeline) :-
|
Daniel@0
|
54 command(Pipeline,Cmd),
|
Daniel@0
|
55 debug(dovamp,'Running shell: ~s',[Cmd]),
|
Daniel@0
|
56 setup_call_cleanup(
|
Daniel@0
|
57 process_create(path(bash),['-c',Cmd],[stdin(null),stdout(null),stderr(pipe(Msgs)),process(PID)]),
|
Daniel@0
|
58 % !!! not sure why I need once(_) here, but it doesn't work without it
|
Daniel@0
|
59 call_cleanup( once(updatable_status_task('Initialising...',Update,read_messages(Msgs,Update))),
|
Daniel@0
|
60 exception(_), process_kill(PID)),
|
Daniel@0
|
61 (close(Msgs), process_wait(PID,Status))
|
Daniel@0
|
62 ),
|
Daniel@0
|
63 check_status(Cmd,Status).
|
Daniel@0
|
64
|
Daniel@0
|
65 read_messages(Stream,Update) :-
|
Daniel@0
|
66 set_stream(Stream,buffer(false)),
|
Daniel@0
|
67 repeat, % argh.. it's a failure driven loop
|
Daniel@0
|
68 read_string(Stream, "\n\r", "",End, String),
|
Daniel@0
|
69 ( string_concat(_,"%",String) -> call(Update,String)
|
Daniel@0
|
70 ; string_concat("ERROR: ",Err,String) -> throw(sonic_annotator(Err))
|
Daniel@0
|
71 ; String\="" -> debug(sonic_annotator,'SA: >~w<',[String])
|
Daniel@0
|
72 ; true
|
Daniel@0
|
73 ),
|
Daniel@0
|
74 End = -1, !.
|
Daniel@0
|
75
|
Daniel@0
|
76 prolog:message(sonic_annotator(Err)) --> ['Sonic annotator error: ~s'-[Err]].
|
Daniel@0
|
77 prolog:message(shell_error(Cmd,RC)) --> ['Shell command exit code ~w: ~s'-[RC,Cmd]].
|
Daniel@0
|
78
|
Daniel@0
|
79 check_status(_,exit(0)) :- !.
|
Daniel@0
|
80 check_status(Cmd,exit(RC)) :- RC\=0, throw(shell_error(Cmd,RC)).
|
Daniel@0
|
81 check_status(Cmd,killed(S)) :- throw(shell_killed(Cmd,S)).
|
Daniel@0
|
82
|
Daniel@0
|
83 write_transform(Transform,File) :- rdf_save_turtle(File,[expand(transform_triple(Transform))]).
|
Daniel@0
|
84
|
Daniel@0
|
85 :- rdf_meta transform_triple(r,r,r,o,-).
|
Daniel@0
|
86 transform_triple(T, T, P, O, _) :- rdf(T, P, O).
|
Daniel@0
|
87 transform_triple(T, S, P, O, _) :- rdf(T, vamp:parameter_binding, Param), describe(Param,rdf(S,P,O)).
|
Daniel@0
|
88
|
Daniel@0
|
89 describe(S,rdf(S,P,O)) :- rdf(S,P,O).
|
Daniel@0
|
90 describe(S,Triple) :- rdf(S,_,O), atom(O), describe(O,Triple).
|
Daniel@0
|
91
|
Daniel@0
|
92
|
Daniel@0
|
93 swipe:def( curl(URL), sh(0>>_, "curl -L ~s 2>/dev/null", [@URL])).
|
Daniel@0
|
94 swipe:def( sonic_annotator(csv(Dir),T,In),
|
Daniel@0
|
95 sh(0>>0, "sonic-annotator -t ~s -w csv --csv-basedir ~s ~s",
|
Daniel@0
|
96 [T+read,@Dir,In+read])). % Dir+write fails for directories
|