annotate cpack/dml/components/audio.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(cp_audio,
Daniel@0 20 [ audio_player//1
Daniel@0 21 , audio_player//2
Daniel@0 22 , audio_decoration//3
Daniel@0 23 , spectrogram//2
Daniel@0 24 , audio_link/3
Daniel@0 25 , audio_file/3
Daniel@0 26 , audio_playlist//2
Daniel@0 27 , finder_player/2
Daniel@0 28 , finder_player/3
Daniel@0 29 ]).
Daniel@0 30
Daniel@0 31 :- use_module(library(http/http_dispatch)).
Daniel@0 32 :- use_module(library(http/http_path)).
Daniel@0 33 :- use_module(library(http/html_write)).
Daniel@0 34 :- use_module(library(http/html_head)).
Daniel@0 35 :- use_module(library(http/js_write)).
Daniel@0 36 :- use_module(library(semweb/rdf_db)).
Daniel@0 37 :- use_module(library(semweb/rdf_label),[rdf_label/2]).
Daniel@0 38 :- use_module(library(dcg_core)).
Daniel@0 39 :- use_module(library(httpfiles)).
Daniel@0 40 :- use_module(library(optutils)).
Daniel@0 41 :- use_module(components(icons)).
Daniel@0 42
Daniel@0 43 :- multifile audio_link/3, audio_file/3.
Daniel@0 44 :- rdf_meta audio_link(r,-,-).
Daniel@0 45
Daniel@0 46 :- html_resource(js('add_dummy_iframe.js'), [requires(jquery)]).
Daniel@0 47
Daniel@0 48
Daniel@0 49 %% audio_decoration(+Type:oneof([none,link,player]), +Links:list(pair(url,maybe(filetype))), +Content:phrase) is det.
Daniel@0 50 %
Daniel@0 51 % Emits the HTML content specified by Content, but optionally decorated with controls
Daniel@0 52 % that allow any associated audio to be played. Links is a list of pairs of links to audio
Daniel@0 53 % content with an optional filetype, where a filetype is a standard audiofile extension like
Daniel@0 54 % mp3, ogg, wav etc.
Daniel@0 55 audio_decoration(none,_,Link) --> phrase(Link).
Daniel@0 56
Daniel@0 57 audio_decoration(link,[URL|_],Link) -->
Daniel@0 58 html_requires(font_awesome),
Daniel@0 59 html_requires(js('add_dummy_iframe.js')),
Daniel@0 60 html(span( [ a([href(URL),target(dummy)],\icon(play))
Daniel@0 61 , &(nbsp), a([href('about:blank'),target(dummy)],\icon(stop))
Daniel@0 62 , &(ensp), \Link
Daniel@0 63 ])).
Daniel@0 64
Daniel@0 65 audio_decoration(player,URLS,Link) -->
Daniel@0 66 html(span(style="display:inline-block;width=auto",
Daniel@0 67 [ div(\audio_player(URLS)), div(\Link) ])).
Daniel@0 68
Daniel@0 69 audio_player(Links) --> audio_player(Links,[]).
Daniel@0 70 audio_player(Links,Attribs) -->
Daniel@0 71 html(audio([ controls, preload=none | Attribs ],
Daniel@0 72 [ \seqmap(audio_source,Links),
Daniel@0 73 "Your browser does not support HTML5 audio." ])).
Daniel@0 74
Daniel@0 75 audio_playlist(ID,Links) -->
Daniel@0 76 % html_requires(js('playlist.js')),
Daniel@0 77 {http_absolute_location(js('playlist.js'),PlaylistJS,[])},
Daniel@0 78 {Links=[item(Src1,_,_)|_]},
Daniel@0 79 html( div(class(playlist),
Daniel@0 80 [ style([ 'div.playlist ul {list-style-type:none; margin:0px;padding:0px;height:10em;overflow:auto }'
Daniel@0 81 , 'div.playlist li div {display:block}'
Daniel@0 82 , 'div.playlist li div a {color:#ccc;text-decoration:none;overflow-x:hidden}'
Daniel@0 83 , 'div.playlist li div a:hover {color:white}'
Daniel@0 84 , 'div.playlist li.active {color:black;background-color:#eee}'
Daniel@0 85 , 'div.playlist li.active div a {color:black}'
Daniel@0 86 , 'div.playlist {padding:1ex;background-color:#222;width:400px;border-radius:1ex}'
Daniel@0 87 ])
Daniel@0 88 , audio([ id('~w-audio'-[ID]), controls, preload=none ],
Daniel@0 89 [ source([src=Src1],[]), "Your browser does not support HTML5 audio." ])
Daniel@0 90 , ul(id('~w-list'-[ID]), \alinks(1,Links))
Daniel@0 91 , \js_script({|javascript(PlaylistJS,ID)||
Daniel@0 92 $.getScript(PlaylistJS, function(x,y,z){init_playlist(ID)})|})
Daniel@0 93 % , script(type('text/javascript'),'init_playlist(~w)'-ID)
Daniel@0 94 ])).
Daniel@0 95
Daniel@0 96 alinks(NSelected,Links) --> alinks(NSelected,1,Links).
Daniel@0 97 alinks(_,_,[]) --> !.
Daniel@0 98 alinks(N,N,[Item|Links]) --> !, {succ(N,M)}, html(li(class(active),\alink(Item))), alinks(N,M,Links).
Daniel@0 99 alinks(S,N,[Item|Links]) --> !, {succ(N,M)}, html(li(\alink(Item))), alinks(S,M,Links).
Daniel@0 100 alink(item(URL,Label,Page)) -->
Daniel@0 101 html(div([ a([href(Page),target('_blank')],\icon('external-link')),' '
Daniel@0 102 , a([class(audio),href(URL)],Label)])).
Daniel@0 103
Daniel@0 104
Daniel@0 105 audio_source(URL-Fmt) -->
Daniel@0 106 ( {Fmt=just(Type), mime_type(Type,MimeType)}
Daniel@0 107 -> html(source([src=URL,type=MimeType],[]))
Daniel@0 108 ; html(source([src=URL],[]))
Daniel@0 109 ).
Daniel@0 110
Daniel@0 111
Daniel@0 112 %% spectrogram(+URI, +Options) is det.
Daniel@0 113 %
Daniel@0 114 % Emits HTML for a spectrogram viewer for a given recording URI. The viewer
Daniel@0 115 % includes controls for controlling the time window extracted from the full signal.
Daniel@0 116 spectrogram(URI,Opts) -->
Daniel@0 117 { seqmap( option_default_select,
Daniel@0 118 [offset(Off), length(Len), width(W), height(H)],
Daniel@0 119 [0, 60, 15, 7],
Daniel@0 120 Opts,Opts1),
Daniel@0 121 http_link_to_id(spectrogram_window,
Daniel@0 122 [ uri(URI), offset(Off), length(Len), width(W), height(H) | Opts1 ],
Daniel@0 123 SpectroURL )
Daniel@0 124 },
Daniel@0 125 html_requires(font_awesome),
Daniel@0 126 html(iframe([ frameborder=0, seamless=seamless, src=SpectroURL,
Daniel@0 127 scrolling=no, style="width:100%;height:~dcm"-[H] ],[])).
Daniel@0 128
Daniel@0 129 :- meta_predicate finder_player(1,-).
Daniel@0 130 %% finder_player(+Finder:pred(-uri), -Player:html_term) is det.
Daniel@0 131 finder_player(Finder,html(\audio_playlist(ID,Items))) :-
Daniel@0 132 gensym(pl,ID),
Daniel@0 133 findall(item(H,L,P),( call(Finder,X),
Daniel@0 134 http_link_to_id(list_resource,[r(X)],P),
Daniel@0 135 audio_link(X,H,_),
Daniel@0 136 rdf_label(X,L)
Daniel@0 137 ), Items).
Daniel@0 138
Daniel@0 139 %% finder_player(@URI:uri, +Finder:goal, -Player:html_term) is det.
Daniel@0 140 :- meta_predicate finder_player(-,0,-).
Daniel@0 141 finder_player(R,Goal,Player) :- finder_player(call1(R,Goal),Player).
Daniel@0 142 call1(R,Goal,R) :- call(Goal).
Daniel@0 143