diff 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
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/cpack/dml/lib/dovamp.pl	Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,96 @@
+/* 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(dovamp, []).
+
+
+:- use_module(library(persistency)).
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(semweb/rdf_turtle_write)).
+:- use_module(library(fileutils)).
+:- use_module(library(computations)).
+:- use_module(library(swipe)).
+:- use_module(library(async)).
+:- use_module(components(audio)).
+:- use_module(api(archive)).
+
+computations:do_computation(Transform,Input,Output) :-
+   rdf(Transform,rdf:type,vamp:'Transform'), !,
+   debug(dovamp,'Doing on demand Vamp ~q on ~q',[Transform,Input]),
+   with_temp_dir(Dir, with_progress_stack(sonic_annotator(Dir,Transform,Input,Output))).
+
+sonic_annotator(Dir,Transform,Input,CSVFile) :-
+   directory_file_path(Dir,'transform.n3',TFile),
+   directory_file_path(Dir,'*.csv',CSVPattern),
+   (  cp_audio:audio_file(Input,AudioFile,_) -> true
+   ;  % !!! HACK
+      (rdf(Input,dml:blpage,_) -> ignore(bl_p2r:scrape_audio_link(Input,_)); true),
+      cp_audio:audio_link(Input,AudioLink,_),
+      directory_file_path(Dir,audio,AudioFile),
+      format(string(Desc),"Downloading audio for ~w to ~w",[Input,AudioFile]),
+      simple_task(Desc,run(curl(AudioLink)>:AudioFile^_))
+   ), 
+   write_transform(Transform,TFile),
+   run_with_progress(sonic_annotator(csv(Dir),TFile,AudioFile)),
+   expand_file_name(CSVPattern,[LocalCSV]),
+   archive_file('.csv',LocalCSV,CSVFile).
+
+run_with_progress(Pipeline) :-
+   command(Pipeline,Cmd),
+   debug(dovamp,'Running shell: ~s',[Cmd]),
+   setup_call_cleanup(
+      process_create(path(bash),['-c',Cmd],[stdin(null),stdout(null),stderr(pipe(Msgs)),process(PID)]),
+      % !!! not sure why I need once(_) here, but it doesn't work without it
+      call_cleanup( once(updatable_status_task('Initialising...',Update,read_messages(Msgs,Update))),
+                    exception(_), process_kill(PID)),
+      (close(Msgs), process_wait(PID,Status))
+   ),
+   check_status(Cmd,Status).
+
+read_messages(Stream,Update) :-
+   set_stream(Stream,buffer(false)),
+   repeat, % argh.. it's a failure driven loop
+   read_string(Stream, "\n\r", "",End, String),
+   (  string_concat(_,"%",String) -> call(Update,String)
+   ;  string_concat("ERROR: ",Err,String) -> throw(sonic_annotator(Err))
+   ;  String\="" -> debug(sonic_annotator,'SA: >~w<',[String])
+   ;  true
+   ),
+   End = -1, !.
+
+prolog:message(sonic_annotator(Err)) --> ['Sonic annotator error: ~s'-[Err]].
+prolog:message(shell_error(Cmd,RC)) --> ['Shell command exit code ~w: ~s'-[RC,Cmd]].
+
+check_status(_,exit(0)) :- !.
+check_status(Cmd,exit(RC)) :- RC\=0, throw(shell_error(Cmd,RC)).
+check_status(Cmd,killed(S)) :- throw(shell_killed(Cmd,S)).
+
+write_transform(Transform,File) :- rdf_save_turtle(File,[expand(transform_triple(Transform))]).
+
+:- rdf_meta transform_triple(r,r,r,o,-).
+transform_triple(T, T, P, O, _) :- rdf(T, P, O).
+transform_triple(T, S, P, O, _) :- rdf(T, vamp:parameter_binding, Param), describe(Param,rdf(S,P,O)).
+
+describe(S,rdf(S,P,O)) :- rdf(S,P,O).
+describe(S,Triple) :- rdf(S,_,O), atom(O), describe(O,Triple).
+
+
+swipe:def( curl(URL), sh(0>>_, "curl -L ~s 2>/dev/null", [@URL])).
+swipe:def( sonic_annotator(csv(Dir),T,In), 
+           sh(0>>0, "sonic-annotator -t ~s -w csv --csv-basedir ~s ~s",
+           [T+read,@Dir,In+read])). % Dir+write fails for directories