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(transcription_ui, []).
|
Daniel@0
|
20
|
Daniel@0
|
21 /** <module> Score related pages and hooks
|
Daniel@0
|
22
|
Daniel@0
|
23 This module provides a web pages for displaying rendered scores and for
|
Daniel@0
|
24 an audio player to play sonified scores.
|
Daniel@0
|
25 It also module provides resource decorations and local view customisations
|
Daniel@0
|
26 for Humdrum scores.
|
Daniel@0
|
27 */
|
Daniel@0
|
28
|
Daniel@0
|
29 :- use_module(library(http/html_write)).
|
Daniel@0
|
30 :- use_module(library(http/html_head)).
|
Daniel@0
|
31 :- use_module(library(http/http_dispatch)).
|
Daniel@0
|
32 :- use_module(library(http/http_parameters)).
|
Daniel@0
|
33 :- use_module(library(semweb/rdf_db)).
|
Daniel@0
|
34 :- use_module(library(computations)).
|
Daniel@0
|
35 :- use_module(library(csvutils)).
|
Daniel@0
|
36 :- use_module(library(decoration)).
|
Daniel@0
|
37 :- use_module(library(httpfiles)).
|
Daniel@0
|
38 :- use_module(library(sandbox)).
|
Daniel@0
|
39 :- use_module(library(real)).
|
Daniel@0
|
40 :- use_module(api(transcription)).
|
Daniel@0
|
41 :- use_module(components(audio), [audio_player//2]).
|
Daniel@0
|
42 :- use_module(components(r_fig), [figure//4]).
|
Daniel@0
|
43 :- use_module(applications(score_ui)).
|
Daniel@0
|
44
|
Daniel@0
|
45 :- set_prolog_flag(double_quotes,string).
|
Daniel@0
|
46
|
Daniel@0
|
47 :- http_handler(root(dml/transcription/audio), transcription_audio, []).
|
Daniel@0
|
48
|
Daniel@0
|
49 decoration:resource_view(URI,_) -->
|
Daniel@0
|
50 { once(rdf(Comp,dml:'comp/output',URI)),
|
Daniel@0
|
51 rdf(Comp,dml:'comp/function',Transform),
|
Daniel@0
|
52 rdf(Transform,vamp:plugin,vamp_plugins:'silvet#silvet') },
|
Daniel@0
|
53 html([ h2("Transcription sonification")
|
Daniel@0
|
54 , \sonify_ui(URI,transcription_ui:transcription_audio)
|
Daniel@0
|
55 , \figure(piano_roll(URI),20,8,[])
|
Daniel@0
|
56 ]).
|
Daniel@0
|
57
|
Daniel@0
|
58 decoration:resource_view(URI,_) -->
|
Daniel@0
|
59 { once(rdf(Comp,dml:'comp/output',URI)),
|
Daniel@0
|
60 rdf(Comp,dml:'comp/function',Transform),
|
Daniel@0
|
61 computations:transform(chord_notes,Transform) },
|
Daniel@0
|
62 html([ h2("Chord notes sonification")
|
Daniel@0
|
63 , \sonify_ui(URI,transcription_ui:transcription_audio)
|
Daniel@0
|
64 ]).
|
Daniel@0
|
65
|
Daniel@0
|
66 transcription_audio(Request) :-
|
Daniel@0
|
67 http_parameters(Request,
|
Daniel@0
|
68 [ uri(URI, [optional(false), description("URI of transcription to sonify")])
|
Daniel@0
|
69 , autoplay(Auto, [boolean, default(false)])
|
Daniel@0
|
70 ], [form_data(Params)]),
|
Daniel@0
|
71 maplist(transcription_audio_link(URI,Params),[ogg,mp3],Links),
|
Daniel@0
|
72 reply_html_page(cliopatria(bare), [title("Audio element")],
|
Daniel@0
|
73 \audio_player(Links,[autoplay(Auto)]),
|
Daniel@0
|
74 [stable]).
|
Daniel@0
|
75
|
Daniel@0
|
76 transcription_audio_link(URI,Params,Fmt,URL-just(Fmt)) :-
|
Daniel@0
|
77 transcription_link(URI,a(Params)-Fmt,URL).
|
Daniel@0
|
78
|
Daniel@0
|
79 freq_pitch_name_number(Freq,'',NN) :- !, freq_note_number(Freq,NN).
|
Daniel@0
|
80 freq_pitch_name_number(_,Pitch,NN) :- remove_cents(Pitch,Pitch1), pitch_name_number(Pitch1,NN).
|
Daniel@0
|
81
|
Daniel@0
|
82 piano_roll(URI) :-
|
Daniel@0
|
83 uri_to_csv(URI,Rows),
|
Daniel@0
|
84 maplist(computations:column(transcription),[time,dur,freq,vel,pitch],Cols),
|
Daniel@0
|
85 rows_cols(Cols,Rows,[Time,Dur,Freq,Vel,Pitch]),
|
Daniel@0
|
86 maplist(freq_pitch_name_number,Freq,Pitch,NoteNum),
|
Daniel@0
|
87 aggregate_all(min(NN)-max(NN),member(NN,NoteNum),MinNN-MaxNN),
|
Daniel@0
|
88 % using ggplot2? ...
|
Daniel@0
|
89 % r( ggplot()
|
Daniel@0
|
90 % +geom_rect('data.frame'([t=Time,d=Dur,v=Vel,nn=NoteNum]),
|
Daniel@0
|
91 % mapping(xmin=t,xmax=t+d,ymin=nn-0.4,ymax=nn+0.4,alpha=0.25+v/256))
|
Daniel@0
|
92 % +theme_minimal()),
|
Daniel@0
|
93 r(par(ps=10,mar=[2.1,2.2,0.1,0],yaxs="i",xaxs="i")),
|
Daniel@0
|
94 r(plot(x='NULL',y='NULL',xlim=c(0,max(Time+Dur)),ylim=c(MinNN-0.5,MaxNN+0.5),type="n",xlab="time/s",ylab="notenum",tcl=0.2)),
|
Daniel@0
|
95 r(rect(Time,NoteNum-0.4,Time+Dur,NoteNum+0.4,border='NA',col=rgb(0,0,0,64+Vel,maxColorValue=255))).
|
Daniel@0
|
96
|
Daniel@0
|
97 remove_cents(P1,P2) :- sub_atom(P1,Bef,_,_,'-'), !, sub_atom(P1,0,Bef,_,P2).
|
Daniel@0
|
98 remove_cents(P1,P2) :- sub_atom(P1,Bef,_,_,'+'), !, sub_atom(P1,0,Bef,_,P2).
|
Daniel@0
|
99 remove_cents(P1,P1).
|
Daniel@0
|
100
|
Daniel@0
|
101 sandbox:safe_primitive(transcription_ui:piano_roll(_)).
|