Daniel@0: /* Part of DML (Digital Music Laboratory) Daniel@0: Copyright 2014-2015 Samer Abdallah, University of London Daniel@0: Daniel@0: This program is free software; you can redistribute it and/or Daniel@0: modify it under the terms of the GNU General Public License Daniel@0: as published by the Free Software Foundation; either version 2 Daniel@0: of the License, or (at your option) any later version. Daniel@0: Daniel@0: This program is distributed in the hope that it will be useful, Daniel@0: but WITHOUT ANY WARRANTY; without even the implied warranty of Daniel@0: MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the Daniel@0: GNU General Public License for more details. Daniel@0: Daniel@0: You should have received a copy of the GNU General Public Daniel@0: License along with this library; if not, write to the Free Software Daniel@0: Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA Daniel@0: */ Daniel@0: Daniel@0: :- module(api_score, [get_link/3]). Daniel@0: Daniel@0: /** Score related services and components Daniel@0: */ Daniel@0: :- use_module(library(thread_pool)). Daniel@0: :- use_module(library(http/http_dispatch)). Daniel@0: :- use_module(library(http/http_parameters)). Daniel@0: :- use_module(library(fileutils)). Daniel@0: :- use_module(library(swipe)). Daniel@0: :- use_module(library(httpfiles)). Daniel@0: :- use_module(library(humdrum_p2r)). Daniel@0: Daniel@0: :- set_prolog_flag(double_quotes,string). Daniel@0: Daniel@0: :- initialization Daniel@0: current_thread_pool(sonify), !; Daniel@0: thread_pool_create(sonify, 20, [local(100), global(100), trail(100), backlog(100)]). Daniel@0: Daniel@0: user:term_expansion((:- file_setting(Name,Dir,Def,Desc)), (:- setting(Name,oneof(Files),Def1,Desc))) :- Daniel@0: absolute_file_name(Dir,Path,[file_type(directory),expand(true)]), Daniel@0: directory_files(Path,All), Daniel@0: exclude(dotfile,All,FilesUnsorted), Daniel@0: sort(FilesUnsorted,Files), Daniel@0: debug(score,'Found fluidsynth rc files: ~q',[All]), Daniel@0: ( member(Def,Files) -> Def1=Def Daniel@0: ; member(default,Files) -> Def1=default Daniel@0: ; member(Def1,Files) Daniel@0: ). Daniel@0: Daniel@0: dotfile(X) :- atom_concat('.',_,X). Daniel@0: Daniel@0: :- http_handler(api(score/render), score_render, []). Daniel@0: :- http_handler(api(score/get), score_get, []). Daniel@0: :- http_handler(api(score/sonify), score_sonify, [spawn(sonify),chunked]). Daniel@0: Daniel@0: :- setting(score:autobeam,boolean,true,"Use Lilypond autobeam when converting from XML"). Daniel@0: :- setting(score:default_width,number,170,"Default width of rendered score in mm"). Daniel@0: :- setting(score:reverse_spines,boolean,false,"Reverse order of spines when converting"). Daniel@0: :- setting(score:fluidsynth_sample_rate,number,44100,"Default Fluidsynth sample rate"). Daniel@0: :- setting(score:ogg_quality,between(-1,10),4,"Default oggenc quality"). Daniel@0: :- setting(score:mp3_lame_bitrate,oneof([96, 112, 128, 160, 192, 224, 256, 320]),128,"MP3 encoding bitrate"). Daniel@0: :- setting(score:hum2mid_tempo_scaling,number,1,"Tempo factor Humdrum to MIDI conversion"). Daniel@0: :- setting(score:soundfont_dir,string,"/usr/share/sounds/sf2","Soundfont directory"). Daniel@0: :- file_setting(score:fluidsynth_rc,dml(fluid),fluid_gm,"Fluidsynth initialisation file"). Daniel@0: Daniel@0: Daniel@0: %% score_get(+Request) is det. Daniel@0: % Daniel@0: % Handler for obtaining a score in one of several languages. Daniel@0: % Daniel@0: % The conversion relies on a number of executables, which must be available in the Daniel@0: % current PATH. Daniel@0: % * mvspine (humdrum) Daniel@0: % * hum2abc, hum2xml (humextra) Daniel@0: % * musicxml2ly (lilypond) Daniel@0: score_get(Request) :- Daniel@0: http_parameters(Request, Daniel@0: [ uri(URI, [ optional(false), description("URI of score to render")]) Daniel@0: , format(Fmt, [ optional(true), default(kern) Daniel@0: , oneof([kern,mxml,abc,lily]) Daniel@0: , description("Output format") ]) Daniel@0: % , transpose(Tr, [ optional(true), default('P1'), atom, description("Transposition interval") ]) Daniel@0: ]), Daniel@0: reply_converted_stream(get(Fmt),URI,[]). Daniel@0: Daniel@0: Daniel@0: %% score_sonify(+Request) is det. Daniel@0: % Daniel@0: % Handler for obtaining a score as MIDI or audio. Daniel@0: % Conversion to MIDI is affected by the following settings: Daniel@0: % Conversion is affected by the following settings: Daniel@0: % * score:hum2mid_tempo_scaling Daniel@0: % * score:fluidsynth_rc Daniel@0: % The name of fluidsynth initialisation file (in ~/etc/fluid) Daniel@0: % * score:fluidsynth_sample_rate Daniel@0: % * score:ogg_quality Daniel@0: % * score:mp3_lame_bitrate Daniel@0: % Daniel@0: % The conversion relies on a number of executables, which must be available in the Daniel@0: % current PATH. Daniel@0: % * mvspine (humdrum) Daniel@0: % * hum2mid, hum2abc, hum2xml (humextra) Daniel@0: % * oggenc (vorbis-tools) Daniel@0: % * lame Daniel@0: % * lilypond, musicxml2ly (lilypond) Daniel@0: % * pdf2svg Daniel@0: score_sonify(Request) :- Daniel@0: setting(score:hum2mid_tempo_scaling,Temp0), Daniel@0: setting(score:fluidsynth_rc,RC0), Daniel@0: ( member(range(Range),Request) Daniel@0: -> debug(score,'Got sonify request for range: ~q',[Range]) Daniel@0: ; true Daniel@0: ), Daniel@0: http_parameters(Request, Daniel@0: [ uri(URI, [ optional(false), description("URI of score")]) Daniel@0: , format(Fmt, [ optional(false), default(ogg) Daniel@0: , oneof([midi,ogg,mp3]) Daniel@0: , description("Output format") ]) Daniel@0: , tempo(Tempo,[ optional(true), default(Temp0), number, description("Tempo adjust factor") ]) Daniel@0: , fluidrc(RC, [ optional(true), default(RC0), atom, description("Fluidsynth intialisation") ]) Daniel@0: , transpose(Tr, [ optional(true), default('P1'), atom, description("Transposition interval") ]) Daniel@0: ]), Daniel@0: reply_converted_stream(sonify(Fmt,[tempo(Tempo),fluidrc(RC),transpose(Tr)]),URI,[]). Daniel@0: % ( uri_conversion_length(URI,sonify(Fmt,Tempo),Length) Daniel@0: % -> reply_converted_stream(sonify(Fmt,[tempo(Tempo),fluidrc(RC)]),URI,[length(Length),no_cache]) Daniel@0: % ; reply_converted_stream(sonify(Fmt,[tempo(Tempo),fluidrc(RC)]),URI,[length(Length),no_cache]), Daniel@0: % assert(uri_conversion_length(URI,sonify(Fmt,Tempo),Length)) Daniel@0: % ). Daniel@0: Daniel@0: Daniel@0: %% score_render(+Request) is det. Daniel@0: % Daniel@0: % Handler for score rendering web API. Takes a URI for a Humdrum score and a target Daniel@0: % graphical format, and uses Lilypond to layout and render musical notation. Daniel@0: % The layout parameter takes the following values: Daniel@0: % * page Daniel@0: % Results in a multi-page document suitable for printing. Daniel@0: % * snip Daniel@0: % Results in single, possibly very tall, image encapsulating the entire score. Daniel@0: % Daniel@0: % The rendering is affected by a number of settings (all in the score namespace): Daniel@0: % * autobeam Daniel@0: % Conversion to Lilypond goes via MusicXML and can use beaming information in the Daniel@0: % original score (autobeam=false), or Lilypond's own automatic beaming Daniel@0: % feature (autobeam=true). Daniel@0: % * default_width Daniel@0: % Default value for width parameter. This affects the number of bars per line and Daniel@0: % hence the overall scaling of the rendered score. Daniel@0: % * reverse_spines Daniel@0: % Humdrum scores maybe arranged with parts (spines) arranged by register from Daniel@0: % highest to lowest, or lowest to highest. If the latter, then it may help to Daniel@0: % reverse the spines to obtain a score with the highest parts at the top. Daniel@0: % Daniel@0: % Rendering requires serveral executable in addition to those required for conversion Daniel@0: % to a lilypond score: Daniel@0: % * lilypond Daniel@0: % * pdf2svg Daniel@0: score_render(Request) :- Daniel@0: setting(score:default_width,DefWidth), Daniel@0: http_parameters(Request, Daniel@0: [ uri(URI, [ optional(false), description("URI of score to render")]) Daniel@0: , format(F, [ optional(true), default(svg), oneof([svg,pdf,png]) Daniel@0: , description("Output format") ]) Daniel@0: , width(W, [ optional(true), default(DefWidth), nonneg Daniel@0: , description("Page width in mm") ]) Daniel@0: , layout(L, [ optional(true), default(snip), oneof([snip,page]) Daniel@0: , description("Lilypond backend") ]) Daniel@0: , transpose(Tr, [ optional(true), default('P1'), atom Daniel@0: , description("Transposition interval") ]) Daniel@0: ]), Daniel@0: reply_score(render(F,W,L,[transpose(Tr)]),URI). Daniel@0: Daniel@0: reply_score(Conversion,URI) :- Daniel@0: hum_uri_path(URI,In), Daniel@0: debug(score,"reply_score: ~q",Conversion), Daniel@0: with_temp_dir(Dir, Daniel@0: ( run(in(Dir,convert(Conversion,In,Out,Type))), Daniel@0: absolute_file_name(Dir/Out,File), Daniel@0: reply_file(File,Type))). Daniel@0: Daniel@0: reply_converted_stream(Conversion,URI,Opts) :- Daniel@0: hum_uri_path(URI,In), Daniel@0: debug(score,"~q",reply_converted_stream(Conversion,URI,Opts)), Daniel@0: with_temp_dir(Dir, Daniel@0: with_pipe_output( S, [type(binary)], Daniel@0: in(Dir,convert(Conversion,In,Type)), Daniel@0: reply_stream(S,Type,Opts))). Daniel@0: Daniel@0: % this should be in swipe... Daniel@0: :- meta_predicate with_pipe_output(-,+,+,0). Daniel@0: with_pipe_output(S, Opts, Spec, Goal) :- Daniel@0: command(Spec, 0>> $_, Cmd), Daniel@0: with_stream(S, open(pipe(Cmd), read, S, Opts), Goal). Daniel@0: Daniel@0: Daniel@0: get_link(URI,s-Fmt,URL) :- http_link_to_id(score_get,[uri(URI),format(Fmt)],URL). Daniel@0: get_link(URI,a-Fmt,URL) :- http_link_to_id(score_sonify,[uri(URI),format(Fmt)],URL). Daniel@0: get_link(URI,a(Ps)-Fmt,URL) :- http_link_to_id(score_sonify,[uri(URI),format(Fmt)|Ps],URL). Daniel@0: Daniel@0: Daniel@0: Daniel@0: % ----- conversion pipelines ----------- Daniel@0: Daniel@0: swipe:def(P,Q) :- def(P,Q). Daniel@0: Daniel@0: % get/1 conversion runs a pipeline into a file out in the Daniel@0: % current directory. Daniel@0: def( convert(get(F), In, out,F), In^kern :> humto(F,[]) >: out^F). Daniel@0: Daniel@0: % conversions with piped output (but might create files in current directory) Daniel@0: def( convert(get(F), In, F), In^kern :> humto(F,[])). Daniel@0: def( convert(sonify(F,Opts), In, F), In^kern :> humto(F,Opts)). Daniel@0: Daniel@0: % render/3 conversion produces a file out. in the current Daniel@0: % directory where F is the requested format. Daniel@0: def( convert(render(F,W,L,Opts),In,Out,F), In^kern :> humto(lily,Opts) >> adjust(W,L) >> render(F,L)):- Daniel@0: atom_concat('out.',F,Out). Daniel@0: Daniel@0: Daniel@0: % these all read from In and output to stdout Daniel@0: Daniel@0: def( tomidi(Out,O), hum2mid(TF,Out)) :- option(tempo(TF),O,1). Daniel@0: Daniel@0: def( humto(Fmt,O), transpose(Interval) >> humto(Fmt,O1)) :- select_option(transpose(Interval),O,O1), Interval\='P1', !. Daniel@0: def( humto(Fmt,O), trans(Semis) >> humto(Fmt,O1)) :- select_option(trans(Semis),O,O1), Semis\=0, !. Daniel@0: def( humto(kern,_), cat). Daniel@0: def( humto(abc,_), sh( $kern >> $abc, "~s",[dml(scripts/hum2abcp)+execute])). Daniel@0: def( humto(lily,O), humto(mxml,O) >> xml2ly(B)) :- setting(score:autobeam,B). Daniel@0: def( humto(mxml,_), Pipe) :- Daniel@0: ( setting(score:reverse_spines,true) Daniel@0: -> Pipe = sh( $kern -> $kern, "mvspine -r") >> hum2xml Daniel@0: ; Pipe = hum2xml Daniel@0: ). Daniel@0: def( humto(midi,O), tomidi(Out,O) * sh($midi >> $midi, 'cat ~s',[@Out])). Daniel@0: def( humto(ogg,O), humto(raw(B,2,R),O) >> oggenc(B,R,Quality)) :- setting(score:ogg_quality,Quality). Daniel@0: def( humto(mp3,O), humto(raw(B,2,R),O) >> lame(B,R,BR)) :- setting(score:mp3_lame_bitrate,BR). Daniel@0: def( humto(raw(16,2,Rate),O), tomidi(Out,O) * midi2raw(Out,RC,Rate,s16)) :- Daniel@0: setting(score:fluidsynth_sample_rate,Rate), Daniel@0: setting(score:fluidsynth_rc,RC0), Daniel@0: option(fluidrc(RC),O,RC0). Daniel@0: Daniel@0: def( hum2mid(TF,Out), sh( $kern >> 0, "hum2mid --mv 1 --hv 1 -t ~f -o ~s", [\TF,@Out])) :- Out="out.mid". Daniel@0: def( midi2raw(In,RC,Rate,Fmt), Daniel@0: sh( 0>> $audio(raw), Daniel@0: "~s ~w ~s ~f ~w ~s", Daniel@0: [ dml(scripts/midi2snd)+execute, @In, dml(fluid/RC)+read, \Rate, \Fmt, @AbsSFDir])) :- Daniel@0: setting(score:soundfont_dir,SFDir), Daniel@0: absolute_file_name(SFDir,AbsSFDir,[file_type(directory),expand(true)]). Daniel@0: Daniel@0: def( oggenc(Q), sh( $audio(F) >> $audio(ogg), "oggenc -Q -q ~d -", [\Q])) :- member(F,[wav,aiff,flac]). Daniel@0: 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: def( lame(B,R,BR), sh( $audio(raw) >> $audio(mp3), Fmt, [\B,\K,\BR])) :- Daniel@0: Fmt="lame -h -r --bitwidth ~d -s ~f -b ~d - -", Daniel@0: K is R/1000. Daniel@0: Daniel@0: % these all process stdin to stdout Daniel@0: def( adjust(W,L), sh( 0 >> $lily, "~s ~d\\\\mm",[dml(scripts/L)+execute,\W])*cat). Daniel@0: def( xml2ly(true), sh( $mxml >> $lily, "musicxml2ly --no-beaming -")). Daniel@0: def( xml2ly(false), sh( $mxml >> $lily, "musicxml2ly -")). Daniel@0: def( hum2xml, sh( $kern >> $mxml, "hum2xml")). Daniel@0: def( transpose(I), sh( $kern >> $kern, "transpose -t ~s",[\I])). Daniel@0: def( trans(N), sh( $kern >> $kern, "trans -d 0 -c ~d",[\N])). Daniel@0: Daniel@0: % these all read stdin and produce a file called out. Daniel@0: def( render(svg,snip), lilypond(eps,pdf) * sh(0>>0,"pdf2svg out.pdf out.svg")) :- !. Daniel@0: def( render(svg,page), lilypond(svg,svg)) :- !. Daniel@0: def( render(Fmt,Layout), lilypond(BE,Fmt)) :- Daniel@0: member(Layout/BE,[page/ps,snip/eps]). Daniel@0: Daniel@0: % lilypond produces out. where F is in {pdf,svg,png} Daniel@0: def( lilypond(B,F), sh($lily>>0, "lilypond -dsafe -dbackend=~w -f~w -o out -",[\B,\F])). Daniel@0: