diff 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
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/cpack/dml/applications/transcription_ui.pl	Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,101 @@
+/* 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(transcription_ui, []).
+
+/** <module> Score related pages and hooks
+
+   This module provides a web pages for displaying rendered scores and for
+   an audio player to play sonified scores.
+   It also module provides resource decorations and local view customisations
+   for Humdrum scores.
+*/
+
+:- use_module(library(http/html_write)).
+:- use_module(library(http/html_head)).
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(http/http_parameters)).
+:- use_module(library(semweb/rdf_db)).
+:- use_module(library(computations)).
+:- use_module(library(csvutils)).
+:- use_module(library(decoration)).
+:- use_module(library(httpfiles)).
+:- use_module(library(sandbox)).
+:- use_module(library(real)).
+:- use_module(api(transcription)).
+:- use_module(components(audio), [audio_player//2]).
+:- use_module(components(r_fig), [figure//4]).
+:- use_module(applications(score_ui)).
+
+:- set_prolog_flag(double_quotes,string).
+
+:- http_handler(root(dml/transcription/audio), transcription_audio, []).
+
+decoration:resource_view(URI,_) -->
+    { once(rdf(Comp,dml:'comp/output',URI)), 
+      rdf(Comp,dml:'comp/function',Transform),
+      rdf(Transform,vamp:plugin,vamp_plugins:'silvet#silvet') },
+    html([  h2("Transcription sonification")
+         ,  \sonify_ui(URI,transcription_ui:transcription_audio)
+         ,  \figure(piano_roll(URI),20,8,[])
+         ]).
+
+decoration:resource_view(URI,_) -->
+    { once(rdf(Comp,dml:'comp/output',URI)), 
+      rdf(Comp,dml:'comp/function',Transform),
+      computations:transform(chord_notes,Transform) },
+    html([  h2("Chord notes sonification")
+         ,  \sonify_ui(URI,transcription_ui:transcription_audio)
+         ]).
+
+transcription_audio(Request) :-
+   http_parameters(Request,
+      [ uri(URI, [optional(false), description("URI of transcription to sonify")])
+      , autoplay(Auto, [boolean, default(false)]) 
+      ], [form_data(Params)]),
+   maplist(transcription_audio_link(URI,Params),[ogg,mp3],Links),
+   reply_html_page(cliopatria(bare), [title("Audio element")], 
+      \audio_player(Links,[autoplay(Auto)]),
+      [stable]).
+
+transcription_audio_link(URI,Params,Fmt,URL-just(Fmt)) :-
+   transcription_link(URI,a(Params)-Fmt,URL).
+
+freq_pitch_name_number(Freq,'',NN) :- !, freq_note_number(Freq,NN).
+freq_pitch_name_number(_,Pitch,NN) :- remove_cents(Pitch,Pitch1), pitch_name_number(Pitch1,NN).
+
+piano_roll(URI) :- 
+   uri_to_csv(URI,Rows),
+   maplist(computations:column(transcription),[time,dur,freq,vel,pitch],Cols),
+   rows_cols(Cols,Rows,[Time,Dur,Freq,Vel,Pitch]),
+   maplist(freq_pitch_name_number,Freq,Pitch,NoteNum),
+   aggregate_all(min(NN)-max(NN),member(NN,NoteNum),MinNN-MaxNN),
+   % using ggplot2? ...
+   % r( ggplot()
+   %    +geom_rect('data.frame'([t=Time,d=Dur,v=Vel,nn=NoteNum]),
+   %               mapping(xmin=t,xmax=t+d,ymin=nn-0.4,ymax=nn+0.4,alpha=0.25+v/256))
+   %    +theme_minimal()),
+   r(par(ps=10,mar=[2.1,2.2,0.1,0],yaxs="i",xaxs="i")),
+   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)),
+   r(rect(Time,NoteNum-0.4,Time+Dur,NoteNum+0.4,border='NA',col=rgb(0,0,0,64+Vel,maxColorValue=255))).
+
+remove_cents(P1,P2) :- sub_atom(P1,Bef,_,_,'-'), !, sub_atom(P1,0,Bef,_,P2).
+remove_cents(P1,P2) :- sub_atom(P1,Bef,_,_,'+'), !, sub_atom(P1,0,Bef,_,P2).
+remove_cents(P1,P1).
+
+sandbox:safe_primitive(transcription_ui:piano_roll(_)).