Daniel@0: /* Part of DML (Digital Music Laboratory) Daniel@0: Copyright 2014-2015 Samer Abdallah, University of London Daniel@0: Daniel@0: This program is free software; you can redistribute it and/or Daniel@0: modify it under the terms of the GNU General Public License Daniel@0: as published by the Free Software Foundation; either version 2 Daniel@0: of the License, or (at your option) any later version. Daniel@0: Daniel@0: This program is distributed in the hope that it will be useful, Daniel@0: but WITHOUT ANY WARRANTY; without even the implied warranty of Daniel@0: MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the Daniel@0: GNU General Public License for more details. Daniel@0: Daniel@0: You should have received a copy of the GNU General Public Daniel@0: License along with this library; if not, write to the Free Software Daniel@0: Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA Daniel@0: */ Daniel@0: Daniel@0: :- module(transcription_ui, []). Daniel@0: Daniel@0: /** Score related pages and hooks Daniel@0: Daniel@0: This module provides a web pages for displaying rendered scores and for Daniel@0: an audio player to play sonified scores. Daniel@0: It also module provides resource decorations and local view customisations Daniel@0: for Humdrum scores. Daniel@0: */ Daniel@0: Daniel@0: :- use_module(library(http/html_write)). Daniel@0: :- use_module(library(http/html_head)). Daniel@0: :- use_module(library(http/http_dispatch)). Daniel@0: :- use_module(library(http/http_parameters)). Daniel@0: :- use_module(library(semweb/rdf_db)). Daniel@0: :- use_module(library(computations)). Daniel@0: :- use_module(library(csvutils)). Daniel@0: :- use_module(library(decoration)). Daniel@0: :- use_module(library(httpfiles)). Daniel@0: :- use_module(library(sandbox)). Daniel@0: :- use_module(library(real)). Daniel@0: :- use_module(api(transcription)). Daniel@0: :- use_module(components(audio), [audio_player//2]). Daniel@0: :- use_module(components(r_fig), [figure//4]). Daniel@0: :- use_module(applications(score_ui)). Daniel@0: Daniel@0: :- set_prolog_flag(double_quotes,string). Daniel@0: Daniel@0: :- http_handler(root(dml/transcription/audio), transcription_audio, []). Daniel@0: Daniel@0: decoration:resource_view(URI,_) --> Daniel@0: { once(rdf(Comp,dml:'comp/output',URI)), Daniel@0: rdf(Comp,dml:'comp/function',Transform), Daniel@0: rdf(Transform,vamp:plugin,vamp_plugins:'silvet#silvet') }, Daniel@0: html([ h2("Transcription sonification") Daniel@0: , \sonify_ui(URI,transcription_ui:transcription_audio) Daniel@0: , \figure(piano_roll(URI),20,8,[]) Daniel@0: ]). Daniel@0: Daniel@0: decoration:resource_view(URI,_) --> Daniel@0: { once(rdf(Comp,dml:'comp/output',URI)), Daniel@0: rdf(Comp,dml:'comp/function',Transform), Daniel@0: computations:transform(chord_notes,Transform) }, Daniel@0: html([ h2("Chord notes sonification") Daniel@0: , \sonify_ui(URI,transcription_ui:transcription_audio) Daniel@0: ]). Daniel@0: Daniel@0: transcription_audio(Request) :- Daniel@0: http_parameters(Request, Daniel@0: [ uri(URI, [optional(false), description("URI of transcription to sonify")]) Daniel@0: , autoplay(Auto, [boolean, default(false)]) Daniel@0: ], [form_data(Params)]), Daniel@0: maplist(transcription_audio_link(URI,Params),[ogg,mp3],Links), Daniel@0: reply_html_page(cliopatria(bare), [title("Audio element")], Daniel@0: \audio_player(Links,[autoplay(Auto)]), Daniel@0: [stable]). Daniel@0: Daniel@0: transcription_audio_link(URI,Params,Fmt,URL-just(Fmt)) :- Daniel@0: transcription_link(URI,a(Params)-Fmt,URL). Daniel@0: Daniel@0: freq_pitch_name_number(Freq,'',NN) :- !, freq_note_number(Freq,NN). Daniel@0: freq_pitch_name_number(_,Pitch,NN) :- remove_cents(Pitch,Pitch1), pitch_name_number(Pitch1,NN). Daniel@0: Daniel@0: piano_roll(URI) :- Daniel@0: uri_to_csv(URI,Rows), Daniel@0: maplist(computations:column(transcription),[time,dur,freq,vel,pitch],Cols), Daniel@0: rows_cols(Cols,Rows,[Time,Dur,Freq,Vel,Pitch]), Daniel@0: maplist(freq_pitch_name_number,Freq,Pitch,NoteNum), Daniel@0: aggregate_all(min(NN)-max(NN),member(NN,NoteNum),MinNN-MaxNN), Daniel@0: % using ggplot2? ... Daniel@0: % r( ggplot() Daniel@0: % +geom_rect('data.frame'([t=Time,d=Dur,v=Vel,nn=NoteNum]), Daniel@0: % mapping(xmin=t,xmax=t+d,ymin=nn-0.4,ymax=nn+0.4,alpha=0.25+v/256)) Daniel@0: % +theme_minimal()), Daniel@0: r(par(ps=10,mar=[2.1,2.2,0.1,0],yaxs="i",xaxs="i")), Daniel@0: 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: r(rect(Time,NoteNum-0.4,Time+Dur,NoteNum+0.4,border='NA',col=rgb(0,0,0,64+Vel,maxColorValue=255))). Daniel@0: Daniel@0: remove_cents(P1,P2) :- sub_atom(P1,Bef,_,_,'-'), !, sub_atom(P1,0,Bef,_,P2). Daniel@0: remove_cents(P1,P2) :- sub_atom(P1,Bef,_,_,'+'), !, sub_atom(P1,0,Bef,_,P2). Daniel@0: remove_cents(P1,P1). Daniel@0: Daniel@0: sandbox:safe_primitive(transcription_ui:piano_roll(_)).