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