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