diff cpack/dml/applications/audio_ui.pl @ 0:718306e29690 tip

commiting public release
author Daniel Wolff
date Tue, 09 Feb 2016 21:05:06 +0100
parents
children
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/cpack/dml/applications/audio_ui.pl	Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,263 @@
+/* Part of DML (Digital Music Laboratory)
+	Copyright 2014-2015 Samer Abdallah, University of London
+	 
+	This program is free software; you can redistribute it and/or
+	modify it under the terms of the GNU General Public License
+	as published by the Free Software Foundation; either version 2
+	of the License, or (at your option) any later version.
+
+	This program is distributed in the hope that it will be useful,
+	but WITHOUT ANY WARRANTY; without even the implied warranty of
+	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+	GNU General Public License for more details.
+
+	You should have received a copy of the GNU General Public
+	License along with this library; if not, write to the Free Software
+	Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
+*/
+
+:- module(audio_ui, []).
+
+:- use_module(cp_application('config-enabled/dml_permission')).
+
+:- use_module(library(thread_pool)).
+:- use_module(library(http/html_write)).
+:- use_module(library(http/html_head)).
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/http_parameters)).
+:- use_module(library(dcg_core)).
+:- use_module(library(swipe)).
+:- use_module(library(decoration)).
+:- use_module(library(rdfutils)).
+:- use_module(library(httpfiles)).
+:- use_module(library(dsp)).
+
+:- use_module(library(musicbrainz), [mb_id_uri/3]).
+:- use_module(library(spotify/spotify), [spotify_player//2]).
+:- use_module(library(spotify/echotools), [mb_to_spotify/2]).
+:- use_module(library(spotify/spotools)).
+
+:- use_module(components(matlab)).
+:- use_module(components(audio)).
+
+:- use_module(cliopatria(hooks)).
+
+:- set_prolog_flag(double_quotes,string).
+
+:- http_handler(api(audio/get), audio_get, [chunked,spawn(audio)]).
+:- http_handler(api(audio/spectrogram), spectrogram_handler, []).
+:- http_handler(root(dml/audio/spectrogram/window), spectrogram_window, []).
+:- http_handler(root(dml/audio/spotify), spotify_handler, []).
+% :- http_handler(api(audio/mpc), audio_mpc, []).
+
+:- setting(audio_decoration,oneof([link,player]),player,"Decoration for AudioFile URIs").
+:- setting(specgram_color_map,ground,hot,"Matlab colour map for spectrograms").
+% :- setting(mpd_host,atom,m5,"Name of MPD host").
+
+:- rdf_meta reply_audio_stream(r,+,+).
+
+% Disabled: was causing excessive scraping of BL pages to get audio links.
+% decoration:resource_decoration(URI,Link) -->
+%    {  setof(URL-Fmt,audio_link(URI,URL,Fmt),URLS), !,
+%       setting(audio_decoration,Decoration)
+%    },
+%    audio_decoration(Decoration,l(URLS),Link).
+
+decoration:resource_decoration(URI,Link) -->
+   {  bagof(URL-Fmt,audio_link(URI,URL,Fmt),URLS), !,
+      setting(audio_decoration,Decoration)
+   },
+   audio_decoration(Decoration,URLS,Link).
+
+decoration:resource_view(URI,_) -->
+   { mb_id_uri(recording,MBID,URI)
+   ; rdf(URI,mo:publication_of,Recording),
+     mb_id_uri(recording,MBID,Recording)
+   },
+   { http_link_to_id(spotify_handler,[mbid(MBID)],SpotifyURL)},
+   html( [ iframe([ name=spotify, seamless=seamless, src=SpotifyURL, allowtransparency=true
+                  , style="border:0px solid #ccc;width:320px;height:80px"
+                  ], [])
+         % , iframe([name=spotifyPlayer,seamless=seamless,width=320,height=80,
+         %           frameborder=0,allowtransparency=true],[])   
+         , br([])
+         ]).
+   
+decoration:resource_view(URI,_) -->
+   % !!! HACK: force scraping for BL items here..
+   {rdf(URI,dml:blpage,_) -> ignore(bl_p2r:scrape_audio_link(URI,_)); true},
+   if( bagof(URL-Fmt,audio_link(URI,URL,Fmt),AudioLinks), audio_player(AudioLinks)),
+   if( (audio_file(URI,_,_); audio_link(URI,_,_)), html(div(\spectrogram(URI,[height(6)])))).
+
+%% spectrogram_window(+Request) is det.
+%  Returns an HTML page containing spectrogram of the the requested URI over the
+%  requested time range, with controls for moving forwards or backwards in the
+%  signal and for zooming in or out.
+spectrogram_window(Request) :-
+   http_parameters(Request,
+      [ uri(URI,  [ optional(false), description("URI of audio file")]) 
+      , offset(O, [ number, optional(true), default(0), description("Offset in seconds")])
+      , length(L, [ number, optional(true), default(60), description("Length of extract in seconds")])
+      , width(W,  [ number, optional(true), default(15)])
+      , height(H, [ number, optional(true), default(8)])
+      ],
+      [form_data(Params)]),
+   setting(specgram_color_map,CM),
+   seqmap(remove_option, [offset(_),length(_),format(_)], Params, Params2),
+
+   (  rdf_number(URI,beets:length,Dur)
+   ;  rdf_number(URI,mazurka:duration,Dur)
+   ;  rdf(Sig,mo:sampled_version_of,URI),
+      rdf_number(Sig,mo:duration,Millis),
+      Dur is Millis/1000.0
+   ;  Dur = 36000000
+   ),
+   OffsetPrev is max(0,O-L),
+   OffsetNext is min(Dur-L,O+L), 
+   LZoomIn is L/2,            OffsetZoomIn is O+L/4,
+   LZoomOut0 is min(Dur,L*2), OffsetZoomOut is max(0,O-L/2),
+   (  OffsetZoomOut + LZoomOut0 > Dur 
+   -> LZoomOut is Dur-OffsetZoomOut
+   ;  LZoomOut is LZoomOut0
+   ),
+
+   http_link_to_id(spectrogram_window, [offset(OffsetPrev), length(L) | Params2], URLPrev),
+   http_link_to_id(spectrogram_window, [offset(OffsetNext), length(L) | Params2], URLNext),
+   http_link_to_id(spectrogram_window, [offset(OffsetZoomIn), length(LZoomIn) | Params2], ZoomIn),
+   http_link_to_id(spectrogram_window, [offset(OffsetZoomOut), length(LZoomOut) | Params2], ZoomOut),
+   http_link_to_id(spectrogram_window, [offset(0), length(60) | Params2], Home),
+
+   reply_html_page(cliopatria(bare),[title("Spectrogram viewer")],
+      [ \html_requires(font_awesome)
+      , \figure( spectrogram(URI,O,L), W, H, 
+                 [ format(png), color_map(CM) | Params2])
+      , div(style="display:inline-block;vertical_align:middle",
+         [  a(href=Home,    i(class='fa fa-home',[])), br([]) 
+         ,  a(href=ZoomIn,  i(class='fa fa-plus',[])), br([])
+         ,  a(href=ZoomOut, i(class='fa fa-minus',[])), br([])
+         ,  a(href=URLPrev, i(class='fa fa-chevron-left',[])), br([]) 
+         ,  a(href=URLNext, i(class='fa fa-chevron-right',[]))
+         ])
+      ],
+      [stable]).
+
+remove_option(Opt,O1,O2) :- select_option(Opt,O1,O2,_).
+
+%% spectrogram_handler(+Request) is det.
+%  Returns an image file containing a spectrogram of the requested URI over
+%  a given time window.
+spectrogram_handler(Request) :-
+   http_parameters(Request,
+      [ uri(URI,  [ optional(false), description("URI of audio file")]) 
+      , offset(O, [ number, optional(true), default(0), description("Offset in seconds")])
+      , length(L, [ number, optional(true), default(60), description("Length of extract in seconds")])
+      ],
+      [form_data(Params)]),
+   select(uri(_),Params,P1),
+   Code=dsp:spectrogram(URI,O,L),
+   term_to_atom(Code,CodeAtom),
+   http_link_to_id(api_matlab:figure_render,[code(CodeAtom)|P1],URL),
+   http_redirect(see_other,URL,Request).
+
+%% spotify_handler(+Request) is det.
+%  Looks up a Spotify track URLs for the given Musicbrainz recording ID. 
+%  If one is found, then returns an HTML page containing just a Spotify
+%  player component for all the Spotify tracks. If no tracks are found,
+%  then an HTML page containing a message is returned.
+spotify_handler(Request) :-
+   http_parameters(Request,
+      [ mbid(MBID,  [ optional(false), description("MusicBrainz recording ID")]) 
+      ]),
+   with_output_to(string(_),findall(S,mb_to_spotify(MBID,S),SpotifyURIs)),
+   Head=[title("Spotify tracks for MBZ recording ~w"-MBID)],
+   (  SpotifyURIs=[] 
+   -> reply_html_page(cliopatria(bare),Head,html(h3('Not found on Spotify')),[stable])
+   ;  reply_html_page(cliopatria(bare),Head, 
+         \spotify_player(tracks('RecordingTracks',SpotifyURIs),[width(320),height(80)]),[stable])
+   ).
+
+% list of Spotify URIs and a Spotify player
+% spotify_handler(Request) :-
+%    http_parameters(Request,
+%       [ mbid(MBID,  [ optional(false), description("MusicBrainz recording ID")]) 
+%       ]),
+%    with_output_to(string(_),findall([S],mb_to_spotify(MBID,S),SpotifyURIs)),
+%    reply_html_page(cliopatria(bare), [title("Spotify tracks for recording")], 
+%       table([  thead(td("Spotify URIs"))
+%             ,  \seqmap(table_row(spotify_link),SpotifyURIs)
+%             ])).
+
+% spotify_link(URI) -->
+%    { spotify_player_url(track(URI),[],URL) },
+%    html(a([href=URL,target=spotifyPlayer ],URI)).
+
+% table_row(Format,Cells) --> html(tr(\seqmap(td(Format),Cells))).
+% td(Format,Cell) --> html(td(\call(Format,Cell))).
+
+
+% spotify_player(ID) --> 
+%    (  {with_output_to(string(_),catch(mb_to_spotify(ID,SPID),_,fail))}
+%    -> spotify:spotify_player(SPID,[])
+%    ;  html(p("Not found on Spotify"))
+%    ).
+
+
+audio_get(Request) :-
+   http_parameters(Request,
+      [ uri(URI,  [ optional(false), description("URI of audio file")]) 
+      , format(T, [ optional(true), default(original)
+                  , oneof([original,ogg,mp3]), description("Audio format") ])
+      ]),
+   debug(audio_ui,"Requested audio as ~w: ~s",[T,URI]),
+   insist(audio_file(URI,In,just(T0))),
+   insist(file_permission(In,public), access_denied),
+   (  (T=original; T0=T)
+   -> debug(audio_ui,"Returing original (~q) file ~q",[T0,In]),
+      reply_file(In,T0)
+   ;  insist(command(transcode(In,URI,T0,T),Cmd)),
+      insist(reply_file(pipe(Cmd),T))
+   ).
+
+% audio_mpc(Request) :-
+%    http_parameters(Request,
+%       [ uri(URI,  [ optional(false), description("URI of audio file")]) 
+%       ]),
+%    atom_concat('audio:',Rel,URI),
+%    setting(mpd_host,MPDHost),
+%    run(mpc_insert(MPDHost,Rel) * mpc_next(MPDHost)).
+
+% ----- conversion pipelines -----------
+
+find_script(Name,Path) :- absolute_file_name(dml(scripts/Name),Path,[access(execute)]).
+
+swipe:def(P,Q) :- def(P,Q).
+
+def( mpc_insert(Host,Rel), sh(0>>0, "MPD_HOST=~w ~s ~w",[\Host,@MPC,@Rel])) :- find_script(mpc_insert,MPC).
+def( mpc_next(Host), sh(0>>0, "MPD_HOST=~w mpc next",[\Host])).
+
+def( transcode(In,_,T1,T2), sox(In,T1,T2)) :- 
+   sox_supported(T1).
+
+def( transcode(In,URI,aac,T2), faad(In,Bits) >> soxraw(af(Bits,C,SR),T2)) :- 
+   (  rdf_number(URI,beets:samplerate,SR),
+      rdf_number(URI,beets:channels,C)
+   ;  rdf(URI,mazurka:pid,_),
+      SR=44100, C=2
+   ).
+
+def( faad(In,16), sh( 0 >> $audio(raw), "faad -f 2 -w ~s", [In+read])).
+def( sox(In,F1,F2), sh( 0 >> $audio(F2), "sox -t ~w ~s -t ~w -",[\F1,In+read,\F2])).
+def( soxraw(AF,Fmt), sh( $audio(raw) >> $audio(Fmt), F,[\Rate,\Bits,\Chans,\Fmt])) :-
+   F="sox -t raw -r ~d -b ~d -e signed -c ~d - -t ~w -", 
+   AF=af(Bits,Chans,Rate).
+
+sox_supported(mp3).
+sox_supported(wav).
+sox_supported(ogg).
+sox_supported(au).
+sox_supported(aiff).
+
+:- initialization 
+      current_thread_pool(audio), !;
+      thread_pool_create(audio, 20, [local(100), global(100), trail(100), backlog(100)]).
+