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