diff cpack/dml/components/score.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/components/score.pl	Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,132 @@
+/* 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_score, 
+      [  score//2, score//3
+      ,  sonify_ui//2
+      ,  score_audio_player//1
+      ,  score_audio_player//3
+      ,  pitch_class_histogram//1
+      ]).
+
+:- use_module(library(http/html_write)).
+:- use_module(library(http/http_dispatch)).
+:- use_module(library(dcg_core)).
+:- use_module(library(musiclab)).
+:- use_module(library(humdrum_p2r)).
+:- use_module(library(mlserver)).
+:- use_module(library(real)).
+:- use_module(library(sandbox)).
+:- use_module(components(matlab),[]).
+:- use_module(components(r_fig),[]).
+:- use_module(components(audio),[audio_player//2]).
+:- use_module(api(score)).
+
+:- set_prolog_flag(double_quotes,string).
+
+%% score(+R:uri,+Width:number)// is det.
+%
+%  Generates an HTML DIV element containing a rendered score. URI is assumed
+%  to refer to a Humdrum file. Width is in mm and is passed to Lilypond as 
+%  the desired staff width.
+score(URI,Width) --> score(URI,Width,[]).
+score(URI,Width,Opts) -->
+   {option(transpose(T),Opts,'P1')},
+   {http_link_to_id(score_render,[uri(URI),width(Width),layout(snip),format(svg),transpose(T)],URL)},
+   html(div([id=score,width='100%',height=auto],[img([src=URL],[])])).
+
+
+%% sonify_ui(+R:uri,+ID:hander_id)// is det
+%
+%  Generates an interface for setting parameters and sonifying a Humdrum score.
+sonify_ui(URI,HandlerID) -->                       
+   { http_link_to_id(HandlerID,[],AudioPlayerURL),
+     setting_property(score:fluidsynth_rc,type(oneof(RCs))),
+     setting(score:fluidsynth_rc,RC0),
+     Intervals=['-P5','-d5','-P4','-M3','-m3','-M2','-m2','P1','m2','M2','m3','M3','P4','d5','P5']
+   }, 
+   html([ form([class=forms,target=player,method=get,action=AudioPlayerURL],
+            [ input([type=hidden,name=uri,value=URI])
+            , input([type=hidden,name=autoplay,value=true])
+            %, input([type=hidden,name=format,value=ogg])
+            , table([class=form], 
+               [ tr([ th(class=label,"Tempo scaling factor"), 
+                      td(input([type=number,min=0,max=4,step=0.1,name=tempo,value=1],[]))])
+               % , tr([ th(class=label,"Transposition in semitones"),
+               %        td(input([type=text,name=transpose,value='P1'],[]))])
+               , tr([ th(class=label,"Transposition interval"),
+                      td(\html_select(transpose,Intervals,'P1'))])
+               , tr([ th(class=label,"Fluidsynth initialisation"), 
+                      td(\html_select(fluidrc,RCs,RC0))])
+               ])
+            , input([type=submit,class=btn,value="Sonify"],[])
+            , iframe([name=player,seamless=seamless,style="display:inline-block;height:3.2em"],[])
+            ])
+        ]).
+
+html_select(Name,Values,Initial) -->
+   html(select([name=Name], \seqmap(html_option(Initial),Values))).
+
+html_option(X,X) --> !, html(option(selected=selected,X)).
+html_option(_,X) --> html(option(X)).
+
+
+%% score_audio_player(+R:uri,+As:list(html_attrib),+Ps:list(http_param))// is det.
+%% score_audio_player(+R:uri)// is det.
+%
+%  Generates an HTML 5 audio player to play a sonified score. Ps is a list
+%  of HTTP parameters to be passed ultimately to score_sonify/1. As is a list
+%  of HTML element attributes to be added to the HTML AUDIO element.
+score_audio_player(URI) --> score_audio_player(URI,[],[]).
+score_audio_player(URI,Attr,Params) -->
+   {maplist(score_audio_link(URI,Params),[ogg],Links)},
+   audio_player(Links, Attr).
+
+score_audio_link(URI,Params,Fmt,URL-just(Fmt)) :- get_link(URI,a(Params)-Fmt,URL).
+
+
+%% pitch_class_histogram(+Lang:oneof([ml,r]),+R:uri)// is det.
+%
+%  Generates a graphical rendering of the pitch class histogram computed
+%  from the given URI, assumed to refer to a Humdrum file. Figure is 
+%  generated using Matlab.
+pitch_class_histogram(URI) -->
+   cp_r_fig:figure( cp_score:pitch_class_histogram(r,URI), 12, 6, []).
+   % cp_matlab:figure( cp_score:pitch_class_histogram(ml,URI), 12, 6, []).
+
+pitch_class_histogram(Lang,URI) :-
+   hum_uri_path(URI,Path),
+   kern_pc_hist(Path,Hist1),
+   findall(PCN-X, (member(PC-X,Hist1), pitch_class_number(PC,PCN)), Hist2),
+   numlist(0,11,PCNs),
+   maplist(pc_number_name,PCNs,PCNames),
+   maplist(pcn_count(Hist2),PCNs,Counts),
+   (  Lang=r
+   -> r(par(ps=10,mar=[2.1,2.2,1.1,0])),
+      r(barplot(Counts,'names.arg'=PCNames,main="Pitch class histogram"))
+   ;  Lang=ml
+   -> ?? (  bar(PCNs,Counts);
+            xticks(PCNs,cell(PCNames));
+            title("Pitch class histogram");
+            caxis([0,3]))
+   ).
+
+pcn_count(Hist,PCN,Count) :- member(PCN-Count,Hist) -> true; Count=0.
+
+
+sandbox:safe_primitive(cp_score:pitch_class_histogram(_,_)).