Mercurial > hg > dml-open-cliopatria
comparison cpack/dml/api/score.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_score, [get_link/3]). | |
20 | |
21 /** <module> Score related services and components | |
22 */ | |
23 :- use_module(library(thread_pool)). | |
24 :- use_module(library(http/http_dispatch)). | |
25 :- use_module(library(http/http_parameters)). | |
26 :- use_module(library(fileutils)). | |
27 :- use_module(library(swipe)). | |
28 :- use_module(library(httpfiles)). | |
29 :- use_module(library(humdrum_p2r)). | |
30 | |
31 :- set_prolog_flag(double_quotes,string). | |
32 | |
33 :- initialization | |
34 current_thread_pool(sonify), !; | |
35 thread_pool_create(sonify, 20, [local(100), global(100), trail(100), backlog(100)]). | |
36 | |
37 user:term_expansion((:- file_setting(Name,Dir,Def,Desc)), (:- setting(Name,oneof(Files),Def1,Desc))) :- | |
38 absolute_file_name(Dir,Path,[file_type(directory),expand(true)]), | |
39 directory_files(Path,All), | |
40 exclude(dotfile,All,FilesUnsorted), | |
41 sort(FilesUnsorted,Files), | |
42 debug(score,'Found fluidsynth rc files: ~q',[All]), | |
43 ( member(Def,Files) -> Def1=Def | |
44 ; member(default,Files) -> Def1=default | |
45 ; member(Def1,Files) | |
46 ). | |
47 | |
48 dotfile(X) :- atom_concat('.',_,X). | |
49 | |
50 :- http_handler(api(score/render), score_render, []). | |
51 :- http_handler(api(score/get), score_get, []). | |
52 :- http_handler(api(score/sonify), score_sonify, [spawn(sonify),chunked]). | |
53 | |
54 :- setting(score:autobeam,boolean,true,"Use Lilypond autobeam when converting from XML"). | |
55 :- setting(score:default_width,number,170,"Default width of rendered score in mm"). | |
56 :- setting(score:reverse_spines,boolean,false,"Reverse order of spines when converting"). | |
57 :- setting(score:fluidsynth_sample_rate,number,44100,"Default Fluidsynth sample rate"). | |
58 :- setting(score:ogg_quality,between(-1,10),4,"Default oggenc quality"). | |
59 :- setting(score:mp3_lame_bitrate,oneof([96, 112, 128, 160, 192, 224, 256, 320]),128,"MP3 encoding bitrate"). | |
60 :- setting(score:hum2mid_tempo_scaling,number,1,"Tempo factor Humdrum to MIDI conversion"). | |
61 :- setting(score:soundfont_dir,string,"/usr/share/sounds/sf2","Soundfont directory"). | |
62 :- file_setting(score:fluidsynth_rc,dml(fluid),fluid_gm,"Fluidsynth initialisation file"). | |
63 | |
64 | |
65 %% score_get(+Request) is det. | |
66 % | |
67 % Handler for obtaining a score in one of several languages. | |
68 % | |
69 % The conversion relies on a number of executables, which must be available in the | |
70 % current PATH. | |
71 % * mvspine (humdrum) | |
72 % * hum2abc, hum2xml (humextra) | |
73 % * musicxml2ly (lilypond) | |
74 score_get(Request) :- | |
75 http_parameters(Request, | |
76 [ uri(URI, [ optional(false), description("URI of score to render")]) | |
77 , format(Fmt, [ optional(true), default(kern) | |
78 , oneof([kern,mxml,abc,lily]) | |
79 , description("Output format") ]) | |
80 % , transpose(Tr, [ optional(true), default('P1'), atom, description("Transposition interval") ]) | |
81 ]), | |
82 reply_converted_stream(get(Fmt),URI,[]). | |
83 | |
84 | |
85 %% score_sonify(+Request) is det. | |
86 % | |
87 % Handler for obtaining a score as MIDI or audio. | |
88 % Conversion to MIDI is affected by the following settings: | |
89 % Conversion is affected by the following settings: | |
90 % * score:hum2mid_tempo_scaling | |
91 % * score:fluidsynth_rc | |
92 % The name of fluidsynth initialisation file (in ~/etc/fluid) | |
93 % * score:fluidsynth_sample_rate | |
94 % * score:ogg_quality | |
95 % * score:mp3_lame_bitrate | |
96 % | |
97 % The conversion relies on a number of executables, which must be available in the | |
98 % current PATH. | |
99 % * mvspine (humdrum) | |
100 % * hum2mid, hum2abc, hum2xml (humextra) | |
101 % * oggenc (vorbis-tools) | |
102 % * lame | |
103 % * lilypond, musicxml2ly (lilypond) | |
104 % * pdf2svg | |
105 score_sonify(Request) :- | |
106 setting(score:hum2mid_tempo_scaling,Temp0), | |
107 setting(score:fluidsynth_rc,RC0), | |
108 ( member(range(Range),Request) | |
109 -> debug(score,'Got sonify request for range: ~q',[Range]) | |
110 ; true | |
111 ), | |
112 http_parameters(Request, | |
113 [ uri(URI, [ optional(false), description("URI of score")]) | |
114 , format(Fmt, [ optional(false), default(ogg) | |
115 , oneof([midi,ogg,mp3]) | |
116 , description("Output format") ]) | |
117 , tempo(Tempo,[ optional(true), default(Temp0), number, description("Tempo adjust factor") ]) | |
118 , fluidrc(RC, [ optional(true), default(RC0), atom, description("Fluidsynth intialisation") ]) | |
119 , transpose(Tr, [ optional(true), default('P1'), atom, description("Transposition interval") ]) | |
120 ]), | |
121 reply_converted_stream(sonify(Fmt,[tempo(Tempo),fluidrc(RC),transpose(Tr)]),URI,[]). | |
122 % ( uri_conversion_length(URI,sonify(Fmt,Tempo),Length) | |
123 % -> reply_converted_stream(sonify(Fmt,[tempo(Tempo),fluidrc(RC)]),URI,[length(Length),no_cache]) | |
124 % ; reply_converted_stream(sonify(Fmt,[tempo(Tempo),fluidrc(RC)]),URI,[length(Length),no_cache]), | |
125 % assert(uri_conversion_length(URI,sonify(Fmt,Tempo),Length)) | |
126 % ). | |
127 | |
128 | |
129 %% score_render(+Request) is det. | |
130 % | |
131 % Handler for score rendering web API. Takes a URI for a Humdrum score and a target | |
132 % graphical format, and uses Lilypond to layout and render musical notation. | |
133 % The layout parameter takes the following values: | |
134 % * page | |
135 % Results in a multi-page document suitable for printing. | |
136 % * snip | |
137 % Results in single, possibly very tall, image encapsulating the entire score. | |
138 % | |
139 % The rendering is affected by a number of settings (all in the score namespace): | |
140 % * autobeam | |
141 % Conversion to Lilypond goes via MusicXML and can use beaming information in the | |
142 % original score (autobeam=false), or Lilypond's own automatic beaming | |
143 % feature (autobeam=true). | |
144 % * default_width | |
145 % Default value for width parameter. This affects the number of bars per line and | |
146 % hence the overall scaling of the rendered score. | |
147 % * reverse_spines | |
148 % Humdrum scores maybe arranged with parts (spines) arranged by register from | |
149 % highest to lowest, or lowest to highest. If the latter, then it may help to | |
150 % reverse the spines to obtain a score with the highest parts at the top. | |
151 % | |
152 % Rendering requires serveral executable in addition to those required for conversion | |
153 % to a lilypond score: | |
154 % * lilypond | |
155 % * pdf2svg | |
156 score_render(Request) :- | |
157 setting(score:default_width,DefWidth), | |
158 http_parameters(Request, | |
159 [ uri(URI, [ optional(false), description("URI of score to render")]) | |
160 , format(F, [ optional(true), default(svg), oneof([svg,pdf,png]) | |
161 , description("Output format") ]) | |
162 , width(W, [ optional(true), default(DefWidth), nonneg | |
163 , description("Page width in mm") ]) | |
164 , layout(L, [ optional(true), default(snip), oneof([snip,page]) | |
165 , description("Lilypond backend") ]) | |
166 , transpose(Tr, [ optional(true), default('P1'), atom | |
167 , description("Transposition interval") ]) | |
168 ]), | |
169 reply_score(render(F,W,L,[transpose(Tr)]),URI). | |
170 | |
171 reply_score(Conversion,URI) :- | |
172 hum_uri_path(URI,In), | |
173 debug(score,"reply_score: ~q",Conversion), | |
174 with_temp_dir(Dir, | |
175 ( run(in(Dir,convert(Conversion,In,Out,Type))), | |
176 absolute_file_name(Dir/Out,File), | |
177 reply_file(File,Type))). | |
178 | |
179 reply_converted_stream(Conversion,URI,Opts) :- | |
180 hum_uri_path(URI,In), | |
181 debug(score,"~q",reply_converted_stream(Conversion,URI,Opts)), | |
182 with_temp_dir(Dir, | |
183 with_pipe_output( S, [type(binary)], | |
184 in(Dir,convert(Conversion,In,Type)), | |
185 reply_stream(S,Type,Opts))). | |
186 | |
187 % this should be in swipe... | |
188 :- meta_predicate with_pipe_output(-,+,+,0). | |
189 with_pipe_output(S, Opts, Spec, Goal) :- | |
190 command(Spec, 0>> $_, Cmd), | |
191 with_stream(S, open(pipe(Cmd), read, S, Opts), Goal). | |
192 | |
193 | |
194 get_link(URI,s-Fmt,URL) :- http_link_to_id(score_get,[uri(URI),format(Fmt)],URL). | |
195 get_link(URI,a-Fmt,URL) :- http_link_to_id(score_sonify,[uri(URI),format(Fmt)],URL). | |
196 get_link(URI,a(Ps)-Fmt,URL) :- http_link_to_id(score_sonify,[uri(URI),format(Fmt)|Ps],URL). | |
197 | |
198 | |
199 | |
200 % ----- conversion pipelines ----------- | |
201 | |
202 swipe:def(P,Q) :- def(P,Q). | |
203 | |
204 % get/1 conversion runs a pipeline into a file out in the | |
205 % current directory. | |
206 def( convert(get(F), In, out,F), In^kern :> humto(F,[]) >: out^F). | |
207 | |
208 % conversions with piped output (but might create files in current directory) | |
209 def( convert(get(F), In, F), In^kern :> humto(F,[])). | |
210 def( convert(sonify(F,Opts), In, F), In^kern :> humto(F,Opts)). | |
211 | |
212 % render/3 conversion produces a file out.<F> in the current | |
213 % directory where F is the requested format. | |
214 def( convert(render(F,W,L,Opts),In,Out,F), In^kern :> humto(lily,Opts) >> adjust(W,L) >> render(F,L)):- | |
215 atom_concat('out.',F,Out). | |
216 | |
217 | |
218 % these all read from In and output to stdout | |
219 | |
220 def( tomidi(Out,O), hum2mid(TF,Out)) :- option(tempo(TF),O,1). | |
221 | |
222 def( humto(Fmt,O), transpose(Interval) >> humto(Fmt,O1)) :- select_option(transpose(Interval),O,O1), Interval\='P1', !. | |
223 def( humto(Fmt,O), trans(Semis) >> humto(Fmt,O1)) :- select_option(trans(Semis),O,O1), Semis\=0, !. | |
224 def( humto(kern,_), cat). | |
225 def( humto(abc,_), sh( $kern >> $abc, "~s",[dml(scripts/hum2abcp)+execute])). | |
226 def( humto(lily,O), humto(mxml,O) >> xml2ly(B)) :- setting(score:autobeam,B). | |
227 def( humto(mxml,_), Pipe) :- | |
228 ( setting(score:reverse_spines,true) | |
229 -> Pipe = sh( $kern -> $kern, "mvspine -r") >> hum2xml | |
230 ; Pipe = hum2xml | |
231 ). | |
232 def( humto(midi,O), tomidi(Out,O) * sh($midi >> $midi, 'cat ~s',[@Out])). | |
233 def( humto(ogg,O), humto(raw(B,2,R),O) >> oggenc(B,R,Quality)) :- setting(score:ogg_quality,Quality). | |
234 def( humto(mp3,O), humto(raw(B,2,R),O) >> lame(B,R,BR)) :- setting(score:mp3_lame_bitrate,BR). | |
235 def( humto(raw(16,2,Rate),O), tomidi(Out,O) * midi2raw(Out,RC,Rate,s16)) :- | |
236 setting(score:fluidsynth_sample_rate,Rate), | |
237 setting(score:fluidsynth_rc,RC0), | |
238 option(fluidrc(RC),O,RC0). | |
239 | |
240 def( hum2mid(TF,Out), sh( $kern >> 0, "hum2mid --mv 1 --hv 1 -t ~f -o ~s", [\TF,@Out])) :- Out="out.mid". | |
241 def( midi2raw(In,RC,Rate,Fmt), | |
242 sh( 0>> $audio(raw), | |
243 "~s ~w ~s ~f ~w ~s", | |
244 [ dml(scripts/midi2snd)+execute, @In, dml(fluid/RC)+read, \Rate, \Fmt, @AbsSFDir])) :- | |
245 setting(score:soundfont_dir,SFDir), | |
246 absolute_file_name(SFDir,AbsSFDir,[file_type(directory),expand(true)]). | |
247 | |
248 def( oggenc(Q), sh( $audio(F) >> $audio(ogg), "oggenc -Q -q ~d -", [\Q])) :- member(F,[wav,aiff,flac]). | |
249 def( oggenc(B,R,Q),sh( $audio(raw) >> $audio(mp3), "oggenc -Q -r -B~d -C2 -R~d -q~d -", [\B,\R,\Q])). | |
250 def( lame(B,R,BR), sh( $audio(raw) >> $audio(mp3), Fmt, [\B,\K,\BR])) :- | |
251 Fmt="lame -h -r --bitwidth ~d -s ~f -b ~d - -", | |
252 K is R/1000. | |
253 | |
254 % these all process stdin to stdout | |
255 def( adjust(W,L), sh( 0 >> $lily, "~s ~d\\\\mm",[dml(scripts/L)+execute,\W])*cat). | |
256 def( xml2ly(true), sh( $mxml >> $lily, "musicxml2ly --no-beaming -")). | |
257 def( xml2ly(false), sh( $mxml >> $lily, "musicxml2ly -")). | |
258 def( hum2xml, sh( $kern >> $mxml, "hum2xml")). | |
259 def( transpose(I), sh( $kern >> $kern, "transpose -t ~s",[\I])). | |
260 def( trans(N), sh( $kern >> $kern, "trans -d 0 -c ~d",[\N])). | |
261 | |
262 % these all read stdin and produce a file called out.<Fmt> | |
263 def( render(svg,snip), lilypond(eps,pdf) * sh(0>>0,"pdf2svg out.pdf out.svg")) :- !. | |
264 def( render(svg,page), lilypond(svg,svg)) :- !. | |
265 def( render(Fmt,Layout), lilypond(BE,Fmt)) :- | |
266 member(Layout/BE,[page/ps,snip/eps]). | |
267 | |
268 % lilypond produces out.<F> where F is in {pdf,svg,png} | |
269 def( lilypond(B,F), sh($lily>>0, "lilypond -dsafe -dbackend=~w -f~w -o out -",[\B,\F])). | |
270 |