Mercurial > hg > dml-open-cliopatria
comparison 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 |
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(api_transcription, [transcription_link/3]). | |
20 | |
21 /** <module> Score related services and components | |
22 */ | |
23 :- use_module(library(http/http_dispatch)). | |
24 :- use_module(library(http/http_parameters)). | |
25 :- use_module(library(fileutils), [with_temp_dir/2, with_stream/3]). | |
26 :- use_module(library(dcg_core), [seqmap//2]). | |
27 :- use_module(library(httpfiles), [reply_stream/3]). | |
28 :- use_module(library(csvutils), [uri_to_csv/2]). | |
29 :- use_module(library(computations)). | |
30 :- use_module(library(plsmf)). | |
31 :- use_module(library(swipe)). | |
32 :- use_module(api(score)). % needed for pipelines | |
33 | |
34 :- set_prolog_flag(double_quotes,string). | |
35 | |
36 :- http_handler(api(transcription/sonify), transcription_sonify, [chunked]). | |
37 | |
38 :- dynamic uri_conversion_length/3. | |
39 | |
40 %% transcription_sonify(+Request) is det. | |
41 % | |
42 % Handler for obtaining a score as MIDI or audio. | |
43 % Conversion to MIDI is affected by the following settings: | |
44 % Conversion is affected by the following settings: | |
45 % * score:hum2mid_tempo_scaling | |
46 % * score:fluidsynth_rc | |
47 % The name of fluidsynth initialisation file (in ~/etc/fluid) | |
48 % * score:fluidsynth_sample_rate | |
49 % * score:ogg_quality | |
50 % * score:mp3_lame_bitrate | |
51 % | |
52 % The conversion relies on a number of executables, which must be available in the | |
53 % current PATH. | |
54 % * oggenc (vorbis-tools) | |
55 % * lame | |
56 transcription_sonify(Request) :- | |
57 setting(score:fluidsynth_rc,RC0), | |
58 http_parameters(Request, | |
59 [ uri(URI, [ optional(false), description("URI of transcription")]) | |
60 , format(Fmt, [ optional(false), default(ogg) | |
61 , oneof([midi,ogg,mp3]) | |
62 , description("Output format") ]) | |
63 , tempo(Tempo,[ optional(true), default(1), number, description("Tempo adjust factor") ]) | |
64 , fluidrc(RC, [ optional(true), default(RC0), atom, description("Fluidsynth intialisation") ]) | |
65 ]), | |
66 debug(transcription,'Sonify transcription ~w as ~w',[URI,Fmt]), | |
67 | |
68 % uri_conversion_length(URI,sonify(Fmt,Tempo),Length) | |
69 reply_sonfied_transcription(URI,Fmt,Tempo,RC,[]). | |
70 | |
71 reply_sonfied_transcription(URI,Fmt,Tempo,RC,Opts) :- | |
72 insist(uri_to_csv(URI,Rows)), | |
73 insist(once(( transcription_class(URI,Class), | |
74 seqmap(row_event(Class,Tempo),Rows,Events,[])))), | |
75 | |
76 with_temp_dir(Dir, | |
77 ( directory_file_path(Dir,'tmp.mid',MidiFile), | |
78 events_to_midi_file(Events,MidiFile), | |
79 with_pipe_output( S, [type(binary)], | |
80 in(Dir,sonify_events(Fmt,MidiFile,[fluidrc(RC)])), | |
81 reply_stream(S,Fmt,Opts)))). | |
82 | |
83 % this should be in swipe... | |
84 :- meta_predicate with_pipe_output(-,+,+,0). | |
85 with_pipe_output(S, Opts, Spec, Goal) :- | |
86 command(Spec, 0>> $_, Cmd), | |
87 with_stream(S, open(pipe(Cmd), read, S, Opts), Goal). | |
88 | |
89 | |
90 transcription_class(URI,Class) :- | |
91 rdf(Comp,dml:'comp/output',URI), | |
92 rdf(Comp,dml:'comp/function',Fn), | |
93 % rdf(Fn,vamp:plugin,Plugin), | |
94 computations:transform(Class,Fn). | |
95 | |
96 transcription_link(URI,a(Ps)-Fmt,URL) :- http_link_to_id(transcription_sonify,[uri(URI),format(Fmt)|Ps],URL). | |
97 transcription_link(URI,a-Fmt,URL) :- transcription_link(URI,a([])-Fmt,URL). | |
98 | |
99 events_to_midi_file(Events,File) :- | |
100 debug(transcription,'Writing events to ~w',[File]), | |
101 smf_new(SMF), | |
102 smf_add_events(SMF,Events), | |
103 smf_write(SMF,File). | |
104 | |
105 row_event(transcription,Tempo,row(Time,Dur,Freq,Vel,'')) --> !, | |
106 { freq_note_number(Freq,NN), T0 is Time/Tempo, T1 is (Time+Dur)/Tempo }, | |
107 [ smf(T0,144,NN,Vel), smf(T1,128,NN,0) ]. | |
108 | |
109 row_event(transcription,Tempo,row(Time,Dur,_,Vel,Pitch)) --> | |
110 { remove_cents(Pitch,Pitch1) }, | |
111 { pitch_name_number(Pitch1,NN), T0 is Time/Tempo, T1 is (Time+Dur)/Tempo }, | |
112 [ smf(T0,144,NN,Vel), smf(T1,128,NN,0) ]. | |
113 | |
114 row_event(chord_notes,Tempo,row(Time,Dur,NN)) --> | |
115 { T0 is Time/Tempo, T1 is (Time+Dur)/Tempo }, | |
116 [ smf(T0,144,NN,64), smf(T1,128,NN,0) ]. | |
117 | |
118 | |
119 % ----- conversion pipelines ----------- | |
120 | |
121 swipe:def(P,Q) :- def(P,Q). | |
122 | |
123 % these all read from In and output to stdout | |
124 | |
125 def( sonify_events(midi,In,_), cat(In^midi)). | |
126 def( sonify_events(ogg,In,O), sonify_events(raw(B,2,R),In,O) >> oggenc(B,R,Quality)) :- setting(score:ogg_quality,Quality). | |
127 def( sonify_events(mp3,In,O), sonify_events(raw(B,2,R),In,O) >> lame(B,R,BR)) :- setting(score:mp3_lame_bitrate,BR). | |
128 def( sonify_events(raw(16,2,Rate),In,O), midi2raw(In,RC,Rate,s16)) :- | |
129 setting(score:fluidsynth_sample_rate,Rate), | |
130 setting(score:fluidsynth_rc,RC0), | |
131 option(fluidrc(RC),O,RC0). | |
132 | |
133 remove_cents(P1,P2) :- sub_atom(P1,Bef,_,_,'-'), !, sub_atom(P1,0,Bef,_,P2). | |
134 remove_cents(P1,P2) :- sub_atom(P1,Bef,_,_,'+'), !, sub_atom(P1,0,Bef,_,P2). | |
135 remove_cents(P1,P1). | |
136 |