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