diff cpack/dml/api/transcription.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/api/transcription.pl	Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,136 @@
+/* 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(api_transcription, [transcription_link/3]).
+
+/** <module> Score related services and components
+*/
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/http_parameters)).
+:- use_module(library(fileutils), [with_temp_dir/2, with_stream/3]).
+:- use_module(library(dcg_core),  [seqmap//2]).
+:- use_module(library(httpfiles), [reply_stream/3]).
+:- use_module(library(csvutils),  [uri_to_csv/2]).
+:- use_module(library(computations)).
+:- use_module(library(plsmf)).
+:- use_module(library(swipe)).
+:- use_module(api(score)). % needed for pipelines
+
+:- set_prolog_flag(double_quotes,string).
+
+:- http_handler(api(transcription/sonify), transcription_sonify, [chunked]).
+
+:- dynamic uri_conversion_length/3.
+
+%% transcription_sonify(+Request) is det.
+%
+%  Handler for obtaining a score as MIDI or audio.
+%  Conversion to MIDI is affected by the following settings:
+%  Conversion is affected by the following settings: 
+%     *  score:hum2mid_tempo_scaling
+%     *  score:fluidsynth_rc
+%        The name of fluidsynth initialisation file (in ~/etc/fluid)
+%     *  score:fluidsynth_sample_rate  
+%     *  score:ogg_quality
+%     *  score:mp3_lame_bitrate
+%
+%  The conversion relies on a number of executables, which must be available in the
+%  current PATH.
+%     *  oggenc (vorbis-tools)
+%     *  lame
+transcription_sonify(Request) :-
+   setting(score:fluidsynth_rc,RC0),
+   http_parameters(Request,
+      [ uri(URI,    [ optional(false), description("URI of transcription")])
+      , format(Fmt, [ optional(false), default(ogg)
+                    , oneof([midi,ogg,mp3])
+                    , description("Output format") ])
+      , tempo(Tempo,[ optional(true), default(1), number, description("Tempo adjust factor") ])
+      , fluidrc(RC, [ optional(true), default(RC0), atom, description("Fluidsynth intialisation") ])
+      ]),
+   debug(transcription,'Sonify transcription ~w as ~w',[URI,Fmt]),
+
+   %  uri_conversion_length(URI,sonify(Fmt,Tempo),Length)
+   reply_sonfied_transcription(URI,Fmt,Tempo,RC,[]).
+
+reply_sonfied_transcription(URI,Fmt,Tempo,RC,Opts) :-
+   insist(uri_to_csv(URI,Rows)),
+   insist(once(( transcription_class(URI,Class),
+                 seqmap(row_event(Class,Tempo),Rows,Events,[])))),
+
+   with_temp_dir(Dir,
+      (  directory_file_path(Dir,'tmp.mid',MidiFile),
+         events_to_midi_file(Events,MidiFile),
+         with_pipe_output( S, [type(binary)],
+            in(Dir,sonify_events(Fmt,MidiFile,[fluidrc(RC)])),
+            reply_stream(S,Fmt,Opts)))).
+
+% this should be in swipe...
+:- meta_predicate with_pipe_output(-,+,+,0).
+with_pipe_output(S, Opts, Spec, Goal) :-
+   command(Spec, 0>> $_, Cmd),
+   with_stream(S, open(pipe(Cmd), read, S, Opts), Goal).
+
+
+transcription_class(URI,Class) :-
+   rdf(Comp,dml:'comp/output',URI),
+   rdf(Comp,dml:'comp/function',Fn),
+   % rdf(Fn,vamp:plugin,Plugin),
+   computations:transform(Class,Fn).
+
+transcription_link(URI,a(Ps)-Fmt,URL) :- http_link_to_id(transcription_sonify,[uri(URI),format(Fmt)|Ps],URL).
+transcription_link(URI,a-Fmt,URL) :- transcription_link(URI,a([])-Fmt,URL).
+
+events_to_midi_file(Events,File) :-
+   debug(transcription,'Writing events to ~w',[File]),
+   smf_new(SMF),
+   smf_add_events(SMF,Events),
+   smf_write(SMF,File).
+
+row_event(transcription,Tempo,row(Time,Dur,Freq,Vel,'')) --> !,
+   { freq_note_number(Freq,NN), T0 is Time/Tempo, T1 is (Time+Dur)/Tempo },
+   [ smf(T0,144,NN,Vel), smf(T1,128,NN,0) ].
+
+row_event(transcription,Tempo,row(Time,Dur,_,Vel,Pitch)) -->
+   { remove_cents(Pitch,Pitch1) },
+   { pitch_name_number(Pitch1,NN), T0 is Time/Tempo, T1 is (Time+Dur)/Tempo },
+   [ smf(T0,144,NN,Vel), smf(T1,128,NN,0) ].
+
+row_event(chord_notes,Tempo,row(Time,Dur,NN)) -->
+   { T0 is Time/Tempo, T1 is (Time+Dur)/Tempo },
+   [ smf(T0,144,NN,64), smf(T1,128,NN,0) ].
+
+
+% ----- conversion pipelines -----------
+
+swipe:def(P,Q) :- def(P,Q).
+
+% these all read from In and output to stdout
+
+def( sonify_events(midi,In,_), cat(In^midi)).
+def( sonify_events(ogg,In,O),  sonify_events(raw(B,2,R),In,O) >> oggenc(B,R,Quality)) :- setting(score:ogg_quality,Quality).
+def( sonify_events(mp3,In,O),  sonify_events(raw(B,2,R),In,O) >> lame(B,R,BR)) :- setting(score:mp3_lame_bitrate,BR).
+def( sonify_events(raw(16,2,Rate),In,O), midi2raw(In,RC,Rate,s16)) :- 
+   setting(score:fluidsynth_sample_rate,Rate),
+   setting(score:fluidsynth_rc,RC0),
+   option(fluidrc(RC),O,RC0).
+
+remove_cents(P1,P2) :- sub_atom(P1,Bef,_,_,'-'), !, sub_atom(P1,0,Bef,_,P2).
+remove_cents(P1,P2) :- sub_atom(P1,Bef,_,_,'+'), !, sub_atom(P1,0,Bef,_,P2).
+remove_cents(P1,P1).
+