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(audio_ui, []). Daniel@0: Daniel@0: :- use_module(cp_application('config-enabled/dml_permission')). Daniel@0: Daniel@0: :- use_module(library(thread_pool)). Daniel@0: :- use_module(library(http/html_write)). Daniel@0: :- use_module(library(http/html_head)). Daniel@0: :- use_module(library(http/http_dispatch)). Daniel@0: :- use_module(library(http/http_parameters)). Daniel@0: :- use_module(library(dcg_core)). Daniel@0: :- use_module(library(swipe)). Daniel@0: :- use_module(library(decoration)). Daniel@0: :- use_module(library(rdfutils)). Daniel@0: :- use_module(library(httpfiles)). Daniel@0: :- use_module(library(dsp)). Daniel@0: Daniel@0: :- use_module(library(musicbrainz), [mb_id_uri/3]). Daniel@0: :- use_module(library(spotify/spotify), [spotify_player//2]). Daniel@0: :- use_module(library(spotify/echotools), [mb_to_spotify/2]). Daniel@0: :- use_module(library(spotify/spotools)). Daniel@0: Daniel@0: :- use_module(components(matlab)). Daniel@0: :- use_module(components(audio)). Daniel@0: Daniel@0: :- use_module(cliopatria(hooks)). Daniel@0: Daniel@0: :- set_prolog_flag(double_quotes,string). Daniel@0: Daniel@0: :- http_handler(api(audio/get), audio_get, [chunked,spawn(audio)]). Daniel@0: :- http_handler(api(audio/spectrogram), spectrogram_handler, []). Daniel@0: :- http_handler(root(dml/audio/spectrogram/window), spectrogram_window, []). Daniel@0: :- http_handler(root(dml/audio/spotify), spotify_handler, []). Daniel@0: % :- http_handler(api(audio/mpc), audio_mpc, []). Daniel@0: Daniel@0: :- setting(audio_decoration,oneof([link,player]),player,"Decoration for AudioFile URIs"). Daniel@0: :- setting(specgram_color_map,ground,hot,"Matlab colour map for spectrograms"). Daniel@0: % :- setting(mpd_host,atom,m5,"Name of MPD host"). Daniel@0: Daniel@0: :- rdf_meta reply_audio_stream(r,+,+). Daniel@0: Daniel@0: % Disabled: was causing excessive scraping of BL pages to get audio links. Daniel@0: % decoration:resource_decoration(URI,Link) --> Daniel@0: % { setof(URL-Fmt,audio_link(URI,URL,Fmt),URLS), !, Daniel@0: % setting(audio_decoration,Decoration) Daniel@0: % }, Daniel@0: % audio_decoration(Decoration,l(URLS),Link). Daniel@0: Daniel@0: decoration:resource_decoration(URI,Link) --> Daniel@0: { bagof(URL-Fmt,audio_link(URI,URL,Fmt),URLS), !, Daniel@0: setting(audio_decoration,Decoration) Daniel@0: }, Daniel@0: audio_decoration(Decoration,URLS,Link). Daniel@0: Daniel@0: decoration:resource_view(URI,_) --> Daniel@0: { mb_id_uri(recording,MBID,URI) Daniel@0: ; rdf(URI,mo:publication_of,Recording), Daniel@0: mb_id_uri(recording,MBID,Recording) Daniel@0: }, Daniel@0: { http_link_to_id(spotify_handler,[mbid(MBID)],SpotifyURL)}, Daniel@0: html( [ iframe([ name=spotify, seamless=seamless, src=SpotifyURL, allowtransparency=true Daniel@0: , style="border:0px solid #ccc;width:320px;height:80px" Daniel@0: ], []) Daniel@0: % , iframe([name=spotifyPlayer,seamless=seamless,width=320,height=80, Daniel@0: % frameborder=0,allowtransparency=true],[]) Daniel@0: , br([]) Daniel@0: ]). Daniel@0: Daniel@0: decoration:resource_view(URI,_) --> Daniel@0: % !!! HACK: force scraping for BL items here.. Daniel@0: {rdf(URI,dml:blpage,_) -> ignore(bl_p2r:scrape_audio_link(URI,_)); true}, Daniel@0: if( bagof(URL-Fmt,audio_link(URI,URL,Fmt),AudioLinks), audio_player(AudioLinks)), Daniel@0: if( (audio_file(URI,_,_); audio_link(URI,_,_)), html(div(\spectrogram(URI,[height(6)])))). Daniel@0: Daniel@0: %% spectrogram_window(+Request) is det. Daniel@0: % Returns an HTML page containing spectrogram of the the requested URI over the Daniel@0: % requested time range, with controls for moving forwards or backwards in the Daniel@0: % signal and for zooming in or out. Daniel@0: spectrogram_window(Request) :- Daniel@0: http_parameters(Request, Daniel@0: [ uri(URI, [ optional(false), description("URI of audio file")]) Daniel@0: , offset(O, [ number, optional(true), default(0), description("Offset in seconds")]) Daniel@0: , length(L, [ number, optional(true), default(60), description("Length of extract in seconds")]) Daniel@0: , width(W, [ number, optional(true), default(15)]) Daniel@0: , height(H, [ number, optional(true), default(8)]) Daniel@0: ], Daniel@0: [form_data(Params)]), Daniel@0: setting(specgram_color_map,CM), Daniel@0: seqmap(remove_option, [offset(_),length(_),format(_)], Params, Params2), Daniel@0: Daniel@0: ( rdf_number(URI,beets:length,Dur) Daniel@0: ; rdf_number(URI,mazurka:duration,Dur) Daniel@0: ; rdf(Sig,mo:sampled_version_of,URI), Daniel@0: rdf_number(Sig,mo:duration,Millis), Daniel@0: Dur is Millis/1000.0 Daniel@0: ; Dur = 36000000 Daniel@0: ), Daniel@0: OffsetPrev is max(0,O-L), Daniel@0: OffsetNext is min(Dur-L,O+L), Daniel@0: LZoomIn is L/2, OffsetZoomIn is O+L/4, Daniel@0: LZoomOut0 is min(Dur,L*2), OffsetZoomOut is max(0,O-L/2), Daniel@0: ( OffsetZoomOut + LZoomOut0 > Dur Daniel@0: -> LZoomOut is Dur-OffsetZoomOut Daniel@0: ; LZoomOut is LZoomOut0 Daniel@0: ), Daniel@0: Daniel@0: http_link_to_id(spectrogram_window, [offset(OffsetPrev), length(L) | Params2], URLPrev), Daniel@0: http_link_to_id(spectrogram_window, [offset(OffsetNext), length(L) | Params2], URLNext), Daniel@0: http_link_to_id(spectrogram_window, [offset(OffsetZoomIn), length(LZoomIn) | Params2], ZoomIn), Daniel@0: http_link_to_id(spectrogram_window, [offset(OffsetZoomOut), length(LZoomOut) | Params2], ZoomOut), Daniel@0: http_link_to_id(spectrogram_window, [offset(0), length(60) | Params2], Home), Daniel@0: Daniel@0: reply_html_page(cliopatria(bare),[title("Spectrogram viewer")], Daniel@0: [ \html_requires(font_awesome) Daniel@0: , \figure( spectrogram(URI,O,L), W, H, Daniel@0: [ format(png), color_map(CM) | Params2]) Daniel@0: , div(style="display:inline-block;vertical_align:middle", Daniel@0: [ a(href=Home, i(class='fa fa-home',[])), br([]) Daniel@0: , a(href=ZoomIn, i(class='fa fa-plus',[])), br([]) Daniel@0: , a(href=ZoomOut, i(class='fa fa-minus',[])), br([]) Daniel@0: , a(href=URLPrev, i(class='fa fa-chevron-left',[])), br([]) Daniel@0: , a(href=URLNext, i(class='fa fa-chevron-right',[])) Daniel@0: ]) Daniel@0: ], Daniel@0: [stable]). Daniel@0: Daniel@0: remove_option(Opt,O1,O2) :- select_option(Opt,O1,O2,_). Daniel@0: Daniel@0: %% spectrogram_handler(+Request) is det. Daniel@0: % Returns an image file containing a spectrogram of the requested URI over Daniel@0: % a given time window. Daniel@0: spectrogram_handler(Request) :- Daniel@0: http_parameters(Request, Daniel@0: [ uri(URI, [ optional(false), description("URI of audio file")]) Daniel@0: , offset(O, [ number, optional(true), default(0), description("Offset in seconds")]) Daniel@0: , length(L, [ number, optional(true), default(60), description("Length of extract in seconds")]) Daniel@0: ], Daniel@0: [form_data(Params)]), Daniel@0: select(uri(_),Params,P1), Daniel@0: Code=dsp:spectrogram(URI,O,L), Daniel@0: term_to_atom(Code,CodeAtom), Daniel@0: http_link_to_id(api_matlab:figure_render,[code(CodeAtom)|P1],URL), Daniel@0: http_redirect(see_other,URL,Request). Daniel@0: Daniel@0: %% spotify_handler(+Request) is det. Daniel@0: % Looks up a Spotify track URLs for the given Musicbrainz recording ID. Daniel@0: % If one is found, then returns an HTML page containing just a Spotify Daniel@0: % player component for all the Spotify tracks. If no tracks are found, Daniel@0: % then an HTML page containing a message is returned. Daniel@0: spotify_handler(Request) :- Daniel@0: http_parameters(Request, Daniel@0: [ mbid(MBID, [ optional(false), description("MusicBrainz recording ID")]) Daniel@0: ]), Daniel@0: with_output_to(string(_),findall(S,mb_to_spotify(MBID,S),SpotifyURIs)), Daniel@0: Head=[title("Spotify tracks for MBZ recording ~w"-MBID)], Daniel@0: ( SpotifyURIs=[] Daniel@0: -> reply_html_page(cliopatria(bare),Head,html(h3('Not found on Spotify')),[stable]) Daniel@0: ; reply_html_page(cliopatria(bare),Head, Daniel@0: \spotify_player(tracks('RecordingTracks',SpotifyURIs),[width(320),height(80)]),[stable]) Daniel@0: ). Daniel@0: Daniel@0: % list of Spotify URIs and a Spotify player Daniel@0: % spotify_handler(Request) :- Daniel@0: % http_parameters(Request, Daniel@0: % [ mbid(MBID, [ optional(false), description("MusicBrainz recording ID")]) Daniel@0: % ]), Daniel@0: % with_output_to(string(_),findall([S],mb_to_spotify(MBID,S),SpotifyURIs)), Daniel@0: % reply_html_page(cliopatria(bare), [title("Spotify tracks for recording")], Daniel@0: % table([ thead(td("Spotify URIs")) Daniel@0: % , \seqmap(table_row(spotify_link),SpotifyURIs) Daniel@0: % ])). Daniel@0: Daniel@0: % spotify_link(URI) --> Daniel@0: % { spotify_player_url(track(URI),[],URL) }, Daniel@0: % html(a([href=URL,target=spotifyPlayer ],URI)). Daniel@0: Daniel@0: % table_row(Format,Cells) --> html(tr(\seqmap(td(Format),Cells))). Daniel@0: % td(Format,Cell) --> html(td(\call(Format,Cell))). Daniel@0: Daniel@0: Daniel@0: % spotify_player(ID) --> Daniel@0: % ( {with_output_to(string(_),catch(mb_to_spotify(ID,SPID),_,fail))} Daniel@0: % -> spotify:spotify_player(SPID,[]) Daniel@0: % ; html(p("Not found on Spotify")) Daniel@0: % ). Daniel@0: Daniel@0: Daniel@0: audio_get(Request) :- Daniel@0: http_parameters(Request, Daniel@0: [ uri(URI, [ optional(false), description("URI of audio file")]) Daniel@0: , format(T, [ optional(true), default(original) Daniel@0: , oneof([original,ogg,mp3]), description("Audio format") ]) Daniel@0: ]), Daniel@0: debug(audio_ui,"Requested audio as ~w: ~s",[T,URI]), Daniel@0: insist(audio_file(URI,In,just(T0))), Daniel@0: insist(file_permission(In,public), access_denied), Daniel@0: ( (T=original; T0=T) Daniel@0: -> debug(audio_ui,"Returing original (~q) file ~q",[T0,In]), Daniel@0: reply_file(In,T0) Daniel@0: ; insist(command(transcode(In,URI,T0,T),Cmd)), Daniel@0: insist(reply_file(pipe(Cmd),T)) Daniel@0: ). Daniel@0: Daniel@0: % audio_mpc(Request) :- Daniel@0: % http_parameters(Request, Daniel@0: % [ uri(URI, [ optional(false), description("URI of audio file")]) Daniel@0: % ]), Daniel@0: % atom_concat('audio:',Rel,URI), Daniel@0: % setting(mpd_host,MPDHost), Daniel@0: % run(mpc_insert(MPDHost,Rel) * mpc_next(MPDHost)). Daniel@0: Daniel@0: % ----- conversion pipelines ----------- Daniel@0: Daniel@0: find_script(Name,Path) :- absolute_file_name(dml(scripts/Name),Path,[access(execute)]). Daniel@0: Daniel@0: swipe:def(P,Q) :- def(P,Q). Daniel@0: Daniel@0: def( mpc_insert(Host,Rel), sh(0>>0, "MPD_HOST=~w ~s ~w",[\Host,@MPC,@Rel])) :- find_script(mpc_insert,MPC). Daniel@0: def( mpc_next(Host), sh(0>>0, "MPD_HOST=~w mpc next",[\Host])). Daniel@0: Daniel@0: def( transcode(In,_,T1,T2), sox(In,T1,T2)) :- Daniel@0: sox_supported(T1). Daniel@0: Daniel@0: def( transcode(In,URI,aac,T2), faad(In,Bits) >> soxraw(af(Bits,C,SR),T2)) :- Daniel@0: ( rdf_number(URI,beets:samplerate,SR), Daniel@0: rdf_number(URI,beets:channels,C) Daniel@0: ; rdf(URI,mazurka:pid,_), Daniel@0: SR=44100, C=2 Daniel@0: ). Daniel@0: Daniel@0: def( faad(In,16), sh( 0 >> $audio(raw), "faad -f 2 -w ~s", [In+read])). Daniel@0: def( sox(In,F1,F2), sh( 0 >> $audio(F2), "sox -t ~w ~s -t ~w -",[\F1,In+read,\F2])). Daniel@0: def( soxraw(AF,Fmt), sh( $audio(raw) >> $audio(Fmt), F,[\Rate,\Bits,\Chans,\Fmt])) :- Daniel@0: F="sox -t raw -r ~d -b ~d -e signed -c ~d - -t ~w -", Daniel@0: AF=af(Bits,Chans,Rate). Daniel@0: Daniel@0: sox_supported(mp3). Daniel@0: sox_supported(wav). Daniel@0: sox_supported(ogg). Daniel@0: sox_supported(au). Daniel@0: sox_supported(aiff). Daniel@0: Daniel@0: :- initialization Daniel@0: current_thread_pool(audio), !; Daniel@0: thread_pool_create(audio, 20, [local(100), global(100), trail(100), backlog(100)]). Daniel@0: