annotate 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
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(audio_ui, []).
Daniel@0 20
Daniel@0 21 :- use_module(cp_application('config-enabled/dml_permission')).
Daniel@0 22
Daniel@0 23 :- use_module(library(thread_pool)).
Daniel@0 24 :- use_module(library(http/html_write)).
Daniel@0 25 :- use_module(library(http/html_head)).
Daniel@0 26 :- use_module(library(http/http_dispatch)).
Daniel@0 27 :- use_module(library(http/http_parameters)).
Daniel@0 28 :- use_module(library(dcg_core)).
Daniel@0 29 :- use_module(library(swipe)).
Daniel@0 30 :- use_module(library(decoration)).
Daniel@0 31 :- use_module(library(rdfutils)).
Daniel@0 32 :- use_module(library(httpfiles)).
Daniel@0 33 :- use_module(library(dsp)).
Daniel@0 34
Daniel@0 35 :- use_module(library(musicbrainz), [mb_id_uri/3]).
Daniel@0 36 :- use_module(library(spotify/spotify), [spotify_player//2]).
Daniel@0 37 :- use_module(library(spotify/echotools), [mb_to_spotify/2]).
Daniel@0 38 :- use_module(library(spotify/spotools)).
Daniel@0 39
Daniel@0 40 :- use_module(components(matlab)).
Daniel@0 41 :- use_module(components(audio)).
Daniel@0 42
Daniel@0 43 :- use_module(cliopatria(hooks)).
Daniel@0 44
Daniel@0 45 :- set_prolog_flag(double_quotes,string).
Daniel@0 46
Daniel@0 47 :- http_handler(api(audio/get), audio_get, [chunked,spawn(audio)]).
Daniel@0 48 :- http_handler(api(audio/spectrogram), spectrogram_handler, []).
Daniel@0 49 :- http_handler(root(dml/audio/spectrogram/window), spectrogram_window, []).
Daniel@0 50 :- http_handler(root(dml/audio/spotify), spotify_handler, []).
Daniel@0 51 % :- http_handler(api(audio/mpc), audio_mpc, []).
Daniel@0 52
Daniel@0 53 :- setting(audio_decoration,oneof([link,player]),player,"Decoration for AudioFile URIs").
Daniel@0 54 :- setting(specgram_color_map,ground,hot,"Matlab colour map for spectrograms").
Daniel@0 55 % :- setting(mpd_host,atom,m5,"Name of MPD host").
Daniel@0 56
Daniel@0 57 :- rdf_meta reply_audio_stream(r,+,+).
Daniel@0 58
Daniel@0 59 % Disabled: was causing excessive scraping of BL pages to get audio links.
Daniel@0 60 % decoration:resource_decoration(URI,Link) -->
Daniel@0 61 % { setof(URL-Fmt,audio_link(URI,URL,Fmt),URLS), !,
Daniel@0 62 % setting(audio_decoration,Decoration)
Daniel@0 63 % },
Daniel@0 64 % audio_decoration(Decoration,l(URLS),Link).
Daniel@0 65
Daniel@0 66 decoration:resource_decoration(URI,Link) -->
Daniel@0 67 { bagof(URL-Fmt,audio_link(URI,URL,Fmt),URLS), !,
Daniel@0 68 setting(audio_decoration,Decoration)
Daniel@0 69 },
Daniel@0 70 audio_decoration(Decoration,URLS,Link).
Daniel@0 71
Daniel@0 72 decoration:resource_view(URI,_) -->
Daniel@0 73 { mb_id_uri(recording,MBID,URI)
Daniel@0 74 ; rdf(URI,mo:publication_of,Recording),
Daniel@0 75 mb_id_uri(recording,MBID,Recording)
Daniel@0 76 },
Daniel@0 77 { http_link_to_id(spotify_handler,[mbid(MBID)],SpotifyURL)},
Daniel@0 78 html( [ iframe([ name=spotify, seamless=seamless, src=SpotifyURL, allowtransparency=true
Daniel@0 79 , style="border:0px solid #ccc;width:320px;height:80px"
Daniel@0 80 ], [])
Daniel@0 81 % , iframe([name=spotifyPlayer,seamless=seamless,width=320,height=80,
Daniel@0 82 % frameborder=0,allowtransparency=true],[])
Daniel@0 83 , br([])
Daniel@0 84 ]).
Daniel@0 85
Daniel@0 86 decoration:resource_view(URI,_) -->
Daniel@0 87 % !!! HACK: force scraping for BL items here..
Daniel@0 88 {rdf(URI,dml:blpage,_) -> ignore(bl_p2r:scrape_audio_link(URI,_)); true},
Daniel@0 89 if( bagof(URL-Fmt,audio_link(URI,URL,Fmt),AudioLinks), audio_player(AudioLinks)),
Daniel@0 90 if( (audio_file(URI,_,_); audio_link(URI,_,_)), html(div(\spectrogram(URI,[height(6)])))).
Daniel@0 91
Daniel@0 92 %% spectrogram_window(+Request) is det.
Daniel@0 93 % Returns an HTML page containing spectrogram of the the requested URI over the
Daniel@0 94 % requested time range, with controls for moving forwards or backwards in the
Daniel@0 95 % signal and for zooming in or out.
Daniel@0 96 spectrogram_window(Request) :-
Daniel@0 97 http_parameters(Request,
Daniel@0 98 [ uri(URI, [ optional(false), description("URI of audio file")])
Daniel@0 99 , offset(O, [ number, optional(true), default(0), description("Offset in seconds")])
Daniel@0 100 , length(L, [ number, optional(true), default(60), description("Length of extract in seconds")])
Daniel@0 101 , width(W, [ number, optional(true), default(15)])
Daniel@0 102 , height(H, [ number, optional(true), default(8)])
Daniel@0 103 ],
Daniel@0 104 [form_data(Params)]),
Daniel@0 105 setting(specgram_color_map,CM),
Daniel@0 106 seqmap(remove_option, [offset(_),length(_),format(_)], Params, Params2),
Daniel@0 107
Daniel@0 108 ( rdf_number(URI,beets:length,Dur)
Daniel@0 109 ; rdf_number(URI,mazurka:duration,Dur)
Daniel@0 110 ; rdf(Sig,mo:sampled_version_of,URI),
Daniel@0 111 rdf_number(Sig,mo:duration,Millis),
Daniel@0 112 Dur is Millis/1000.0
Daniel@0 113 ; Dur = 36000000
Daniel@0 114 ),
Daniel@0 115 OffsetPrev is max(0,O-L),
Daniel@0 116 OffsetNext is min(Dur-L,O+L),
Daniel@0 117 LZoomIn is L/2, OffsetZoomIn is O+L/4,
Daniel@0 118 LZoomOut0 is min(Dur,L*2), OffsetZoomOut is max(0,O-L/2),
Daniel@0 119 ( OffsetZoomOut + LZoomOut0 > Dur
Daniel@0 120 -> LZoomOut is Dur-OffsetZoomOut
Daniel@0 121 ; LZoomOut is LZoomOut0
Daniel@0 122 ),
Daniel@0 123
Daniel@0 124 http_link_to_id(spectrogram_window, [offset(OffsetPrev), length(L) | Params2], URLPrev),
Daniel@0 125 http_link_to_id(spectrogram_window, [offset(OffsetNext), length(L) | Params2], URLNext),
Daniel@0 126 http_link_to_id(spectrogram_window, [offset(OffsetZoomIn), length(LZoomIn) | Params2], ZoomIn),
Daniel@0 127 http_link_to_id(spectrogram_window, [offset(OffsetZoomOut), length(LZoomOut) | Params2], ZoomOut),
Daniel@0 128 http_link_to_id(spectrogram_window, [offset(0), length(60) | Params2], Home),
Daniel@0 129
Daniel@0 130 reply_html_page(cliopatria(bare),[title("Spectrogram viewer")],
Daniel@0 131 [ \html_requires(font_awesome)
Daniel@0 132 , \figure( spectrogram(URI,O,L), W, H,
Daniel@0 133 [ format(png), color_map(CM) | Params2])
Daniel@0 134 , div(style="display:inline-block;vertical_align:middle",
Daniel@0 135 [ a(href=Home, i(class='fa fa-home',[])), br([])
Daniel@0 136 , a(href=ZoomIn, i(class='fa fa-plus',[])), br([])
Daniel@0 137 , a(href=ZoomOut, i(class='fa fa-minus',[])), br([])
Daniel@0 138 , a(href=URLPrev, i(class='fa fa-chevron-left',[])), br([])
Daniel@0 139 , a(href=URLNext, i(class='fa fa-chevron-right',[]))
Daniel@0 140 ])
Daniel@0 141 ],
Daniel@0 142 [stable]).
Daniel@0 143
Daniel@0 144 remove_option(Opt,O1,O2) :- select_option(Opt,O1,O2,_).
Daniel@0 145
Daniel@0 146 %% spectrogram_handler(+Request) is det.
Daniel@0 147 % Returns an image file containing a spectrogram of the requested URI over
Daniel@0 148 % a given time window.
Daniel@0 149 spectrogram_handler(Request) :-
Daniel@0 150 http_parameters(Request,
Daniel@0 151 [ uri(URI, [ optional(false), description("URI of audio file")])
Daniel@0 152 , offset(O, [ number, optional(true), default(0), description("Offset in seconds")])
Daniel@0 153 , length(L, [ number, optional(true), default(60), description("Length of extract in seconds")])
Daniel@0 154 ],
Daniel@0 155 [form_data(Params)]),
Daniel@0 156 select(uri(_),Params,P1),
Daniel@0 157 Code=dsp:spectrogram(URI,O,L),
Daniel@0 158 term_to_atom(Code,CodeAtom),
Daniel@0 159 http_link_to_id(api_matlab:figure_render,[code(CodeAtom)|P1],URL),
Daniel@0 160 http_redirect(see_other,URL,Request).
Daniel@0 161
Daniel@0 162 %% spotify_handler(+Request) is det.
Daniel@0 163 % Looks up a Spotify track URLs for the given Musicbrainz recording ID.
Daniel@0 164 % If one is found, then returns an HTML page containing just a Spotify
Daniel@0 165 % player component for all the Spotify tracks. If no tracks are found,
Daniel@0 166 % then an HTML page containing a message is returned.
Daniel@0 167 spotify_handler(Request) :-
Daniel@0 168 http_parameters(Request,
Daniel@0 169 [ mbid(MBID, [ optional(false), description("MusicBrainz recording ID")])
Daniel@0 170 ]),
Daniel@0 171 with_output_to(string(_),findall(S,mb_to_spotify(MBID,S),SpotifyURIs)),
Daniel@0 172 Head=[title("Spotify tracks for MBZ recording ~w"-MBID)],
Daniel@0 173 ( SpotifyURIs=[]
Daniel@0 174 -> reply_html_page(cliopatria(bare),Head,html(h3('Not found on Spotify')),[stable])
Daniel@0 175 ; reply_html_page(cliopatria(bare),Head,
Daniel@0 176 \spotify_player(tracks('RecordingTracks',SpotifyURIs),[width(320),height(80)]),[stable])
Daniel@0 177 ).
Daniel@0 178
Daniel@0 179 % list of Spotify URIs and a Spotify player
Daniel@0 180 % spotify_handler(Request) :-
Daniel@0 181 % http_parameters(Request,
Daniel@0 182 % [ mbid(MBID, [ optional(false), description("MusicBrainz recording ID")])
Daniel@0 183 % ]),
Daniel@0 184 % with_output_to(string(_),findall([S],mb_to_spotify(MBID,S),SpotifyURIs)),
Daniel@0 185 % reply_html_page(cliopatria(bare), [title("Spotify tracks for recording")],
Daniel@0 186 % table([ thead(td("Spotify URIs"))
Daniel@0 187 % , \seqmap(table_row(spotify_link),SpotifyURIs)
Daniel@0 188 % ])).
Daniel@0 189
Daniel@0 190 % spotify_link(URI) -->
Daniel@0 191 % { spotify_player_url(track(URI),[],URL) },
Daniel@0 192 % html(a([href=URL,target=spotifyPlayer ],URI)).
Daniel@0 193
Daniel@0 194 % table_row(Format,Cells) --> html(tr(\seqmap(td(Format),Cells))).
Daniel@0 195 % td(Format,Cell) --> html(td(\call(Format,Cell))).
Daniel@0 196
Daniel@0 197
Daniel@0 198 % spotify_player(ID) -->
Daniel@0 199 % ( {with_output_to(string(_),catch(mb_to_spotify(ID,SPID),_,fail))}
Daniel@0 200 % -> spotify:spotify_player(SPID,[])
Daniel@0 201 % ; html(p("Not found on Spotify"))
Daniel@0 202 % ).
Daniel@0 203
Daniel@0 204
Daniel@0 205 audio_get(Request) :-
Daniel@0 206 http_parameters(Request,
Daniel@0 207 [ uri(URI, [ optional(false), description("URI of audio file")])
Daniel@0 208 , format(T, [ optional(true), default(original)
Daniel@0 209 , oneof([original,ogg,mp3]), description("Audio format") ])
Daniel@0 210 ]),
Daniel@0 211 debug(audio_ui,"Requested audio as ~w: ~s",[T,URI]),
Daniel@0 212 insist(audio_file(URI,In,just(T0))),
Daniel@0 213 insist(file_permission(In,public), access_denied),
Daniel@0 214 ( (T=original; T0=T)
Daniel@0 215 -> debug(audio_ui,"Returing original (~q) file ~q",[T0,In]),
Daniel@0 216 reply_file(In,T0)
Daniel@0 217 ; insist(command(transcode(In,URI,T0,T),Cmd)),
Daniel@0 218 insist(reply_file(pipe(Cmd),T))
Daniel@0 219 ).
Daniel@0 220
Daniel@0 221 % audio_mpc(Request) :-
Daniel@0 222 % http_parameters(Request,
Daniel@0 223 % [ uri(URI, [ optional(false), description("URI of audio file")])
Daniel@0 224 % ]),
Daniel@0 225 % atom_concat('audio:',Rel,URI),
Daniel@0 226 % setting(mpd_host,MPDHost),
Daniel@0 227 % run(mpc_insert(MPDHost,Rel) * mpc_next(MPDHost)).
Daniel@0 228
Daniel@0 229 % ----- conversion pipelines -----------
Daniel@0 230
Daniel@0 231 find_script(Name,Path) :- absolute_file_name(dml(scripts/Name),Path,[access(execute)]).
Daniel@0 232
Daniel@0 233 swipe:def(P,Q) :- def(P,Q).
Daniel@0 234
Daniel@0 235 def( mpc_insert(Host,Rel), sh(0>>0, "MPD_HOST=~w ~s ~w",[\Host,@MPC,@Rel])) :- find_script(mpc_insert,MPC).
Daniel@0 236 def( mpc_next(Host), sh(0>>0, "MPD_HOST=~w mpc next",[\Host])).
Daniel@0 237
Daniel@0 238 def( transcode(In,_,T1,T2), sox(In,T1,T2)) :-
Daniel@0 239 sox_supported(T1).
Daniel@0 240
Daniel@0 241 def( transcode(In,URI,aac,T2), faad(In,Bits) >> soxraw(af(Bits,C,SR),T2)) :-
Daniel@0 242 ( rdf_number(URI,beets:samplerate,SR),
Daniel@0 243 rdf_number(URI,beets:channels,C)
Daniel@0 244 ; rdf(URI,mazurka:pid,_),
Daniel@0 245 SR=44100, C=2
Daniel@0 246 ).
Daniel@0 247
Daniel@0 248 def( faad(In,16), sh( 0 >> $audio(raw), "faad -f 2 -w ~s", [In+read])).
Daniel@0 249 def( sox(In,F1,F2), sh( 0 >> $audio(F2), "sox -t ~w ~s -t ~w -",[\F1,In+read,\F2])).
Daniel@0 250 def( soxraw(AF,Fmt), sh( $audio(raw) >> $audio(Fmt), F,[\Rate,\Bits,\Chans,\Fmt])) :-
Daniel@0 251 F="sox -t raw -r ~d -b ~d -e signed -c ~d - -t ~w -",
Daniel@0 252 AF=af(Bits,Chans,Rate).
Daniel@0 253
Daniel@0 254 sox_supported(mp3).
Daniel@0 255 sox_supported(wav).
Daniel@0 256 sox_supported(ogg).
Daniel@0 257 sox_supported(au).
Daniel@0 258 sox_supported(aiff).
Daniel@0 259
Daniel@0 260 :- initialization
Daniel@0 261 current_thread_pool(audio), !;
Daniel@0 262 thread_pool_create(audio, 20, [local(100), global(100), trail(100), backlog(100)]).
Daniel@0 263