view 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
line wrap: on
line source
/* 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(cp_audio,
		[  audio_player//1
		,  audio_player//2
      ,  audio_decoration//3
      ,  spectrogram//2
      ,  audio_link/3
      ,  audio_file/3
      ,  audio_playlist//2
      ,  finder_player/2
      ,  finder_player/3
		]).

:- use_module(library(http/http_dispatch)).
:- use_module(library(http/http_path)).
:- use_module(library(http/html_write)).
:- use_module(library(http/html_head)).
:- use_module(library(http/js_write)).
:- use_module(library(semweb/rdf_db)).
:- use_module(library(semweb/rdf_label),[rdf_label/2]).
:- use_module(library(dcg_core)).
:- use_module(library(httpfiles)).
:- use_module(library(optutils)).
:- use_module(components(icons)).

:- multifile audio_link/3, audio_file/3.
:- rdf_meta audio_link(r,-,-).

:- html_resource(js('add_dummy_iframe.js'), [requires(jquery)]).


%% audio_decoration(+Type:oneof([none,link,player]), +Links:list(pair(url,maybe(filetype))), +Content:phrase) is det.
%
%  Emits the HTML content specified by Content, but optionally decorated with controls
%  that allow any associated audio to be played. Links is a list of pairs of links to audio
%  content with an optional filetype, where a filetype is a standard audiofile extension like
%  mp3, ogg, wav etc.
audio_decoration(none,_,Link) --> phrase(Link).

audio_decoration(link,[URL|_],Link) -->
   html_requires(font_awesome),
   html_requires(js('add_dummy_iframe.js')),
   html(span( [ a([href(URL),target(dummy)],\icon(play))
              , &(nbsp), a([href('about:blank'),target(dummy)],\icon(stop))
              , &(ensp), \Link
              ])).

audio_decoration(player,URLS,Link) -->
   html(span(style="display:inline-block;width=auto",
             [ div(\audio_player(URLS)), div(\Link) ])).

audio_player(Links) --> audio_player(Links,[]).
audio_player(Links,Attribs) -->
   html(audio([ controls, preload=none | Attribs ], 
              [ \seqmap(audio_source,Links),
                "Your browser does not support HTML5 audio." ])).

audio_playlist(ID,Links) -->
   % html_requires(js('playlist.js')),
   {http_absolute_location(js('playlist.js'),PlaylistJS,[])},
   {Links=[item(Src1,_,_)|_]},
   html( div(class(playlist), 
         [ style([ 'div.playlist ul {list-style-type:none; margin:0px;padding:0px;height:10em;overflow:auto }'
                 , 'div.playlist li div {display:block}'
                 , 'div.playlist li div a {color:#ccc;text-decoration:none;overflow-x:hidden}'
                 , 'div.playlist li div a:hover {color:white}'
                 , 'div.playlist li.active {color:black;background-color:#eee}'
                 , 'div.playlist li.active div a {color:black}'
                 , 'div.playlist {padding:1ex;background-color:#222;width:400px;border-radius:1ex}'
                 ])
         , audio([ id('~w-audio'-[ID]), controls, preload=none ], 
                 [ source([src=Src1],[]), "Your browser does not support HTML5 audio." ])
         , ul(id('~w-list'-[ID]), \alinks(1,Links))
         , \js_script({|javascript(PlaylistJS,ID)||
                        $.getScript(PlaylistJS, function(x,y,z){init_playlist(ID)})|})
         % , script(type('text/javascript'),'init_playlist(~w)'-ID)
         ])).

alinks(NSelected,Links) --> alinks(NSelected,1,Links).
alinks(_,_,[]) --> !.
alinks(N,N,[Item|Links]) --> !, {succ(N,M)}, html(li(class(active),\alink(Item))), alinks(N,M,Links).
alinks(S,N,[Item|Links]) --> !, {succ(N,M)}, html(li(\alink(Item))), alinks(S,M,Links).
alink(item(URL,Label,Page)) --> 
   html(div([ a([href(Page),target('_blank')],\icon('external-link')),' '
            , a([class(audio),href(URL)],Label)])).


audio_source(URL-Fmt) --> 
   (  {Fmt=just(Type), mime_type(Type,MimeType)} 
   -> html(source([src=URL,type=MimeType],[]))
   ;  html(source([src=URL],[]))
   ).


%% spectrogram(+URI, +Options) is det.
%
%  Emits HTML for a spectrogram viewer for a given recording URI. The viewer
%  includes controls for controlling the time window extracted from the full signal.
spectrogram(URI,Opts) -->
   { seqmap( option_default_select, 
             [offset(Off), length(Len), width(W), height(H)],
             [0, 60, 15, 7],
             Opts,Opts1),
     http_link_to_id(spectrogram_window, 
                     [ uri(URI), offset(Off), length(Len), width(W), height(H) | Opts1 ],
                     SpectroURL )
   },
   html_requires(font_awesome),
   html(iframe([ frameborder=0, seamless=seamless, src=SpectroURL, 
                 scrolling=no, style="width:100%;height:~dcm"-[H] ],[])).

:- meta_predicate finder_player(1,-).
%% finder_player(+Finder:pred(-uri), -Player:html_term) is det.
finder_player(Finder,html(\audio_playlist(ID,Items))) :-
    gensym(pl,ID),
    findall(item(H,L,P),( call(Finder,X),
                          http_link_to_id(list_resource,[r(X)],P),
                          audio_link(X,H,_),
                          rdf_label(X,L)
                        ), Items).

%% finder_player(@URI:uri, +Finder:goal, -Player:html_term) is det.
:- meta_predicate finder_player(-,0,-).
finder_player(R,Goal,Player) :- finder_player(call1(R,Goal),Player).
call1(R,Goal,R) :- call(Goal).