Mercurial > hg > dml-open-cliopatria
comparison cpack/dml/applications/score_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(score_ui, [ sonify_ui//2]). | |
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/rdfs)). | |
34 :- use_module(library(semweb/rdf_label)). | |
35 :- use_module(library(dcg_core)). | |
36 :- use_module(library(dcg_codes)). | |
37 :- use_module(library(decoration)). | |
38 :- use_module(library(rdfutils)). | |
39 :- use_module(library(httpfiles)). | |
40 :- use_module(components(score)). | |
41 :- use_module(components(icons)). | |
42 :- use_module(api(score)). | |
43 | |
44 :- set_prolog_flag(double_quotes,string). | |
45 | |
46 :- http_handler(root(dml/score/audio), score_audio, []). | |
47 :- http_handler(root(dml/score/view), score_view, []). | |
48 | |
49 decoration:resource_decoration(URI,Link) --> | |
50 {rdfs_individual_of(URI,hum:'File')}, !, | |
51 {http_link_to_id(score_view,[uri(URI)],ScoreURL)}, | |
52 {http_link_to_id(score_sonify,[uri(URI),format(ogg)],AudioURL)}, | |
53 html_requires(font_awesome), | |
54 html_requires(js('add_dummy_iframe.js')), | |
55 html( span( [ a(href(ScoreURL),\icon(music)) | |
56 , &(nbsp), a([href(AudioURL),target(dummy)],\icon(play)) | |
57 , &(nbsp), a([href('about:blank'),target(dummy)],\icon(stop)) | |
58 , &(ensp), \Link | |
59 ])). | |
60 | |
61 rdf_label:label_hook(URI,literal(Lit)) :- | |
62 rdf(URI,rdf:type,hum:'File'), | |
63 (var(Lit) -> Lit=Label; Lit=lang(_,Label)), | |
64 phrase_string(uri_label(URI),Label). | |
65 | |
66 uri_label(URI) --> | |
67 {atom_concat('kern:',File,URI)}, | |
68 file_label(URI,File). | |
69 | |
70 file_label(URI,File) --> | |
71 { suffix(30,File,ShortFile) }, | |
72 at(ShortFile), | |
73 if(rdf_text(URI,hum:'refcode/OTL',Title), (" - ",at(Title)," ")), | |
74 if((rdf_text(URI,hum:'refcode/COM',Composer),short_name(Composer,Comp)), | |
75 paren(at(Comp))). | |
76 | |
77 suffix(MaxLen,String,Shorter) :- | |
78 string_length(String,N), | |
79 ( N=<MaxLen, Shorter=String | |
80 ; sub_string(String,_,MaxLen,0,S1), | |
81 string_concat("...",S1,Shorter) | |
82 ). | |
83 surname(Full,Surname) :- | |
84 split_string(Full,","," ",[Surname|_]). | |
85 short_name(Full,Short) :- | |
86 split_string(Full,","," ",[Surname|Rest]), | |
87 maplist(split(" "," "),Rest,ForeNested), | |
88 flatten(ForeNested,Forenames), | |
89 maplist(initial,Forenames,Initials), | |
90 atomics_to_string(Initials,".",Inits), | |
91 atomics_to_string([Inits,Surname],".",Short). | |
92 | |
93 | |
94 split(Sep,Pad,String,Parts) :- split_string(String,Sep,Pad,Parts). | |
95 initial(String,Init) :- string_chars(String,[Init|_]). | |
96 | |
97 decoration:resource_view(URI,_) --> | |
98 {rdfs_individual_of(URI,hum:'File')}, | |
99 {http_link_to_id(score_view,[uri(URI)],ViewURL)}, | |
100 html([ a(href=ViewURL, [\icon(music), " View score"]), &('MediumSpace') | |
101 , br([]), "Download as:" | |
102 , \seqmap(link(URI),[s-kern,s-mxml,s-lily,s-abc,a-midi]) | |
103 , \seqmap(render_link(URI),[pdf]) | |
104 , h2("Score sonification") | |
105 % , br([]), "Download audio as:" | |
106 % , \seqmap(link(URI),[a-ogg,a-mp3]) | |
107 % , br([]) | |
108 % , \score_audio_player(URI) | |
109 , \sonify_ui(URI,score_ui:score_audio) | |
110 , \pitch_class_histogram(URI) | |
111 ]). | |
112 | |
113 | |
114 score_audio(Request) :- | |
115 http_parameters(Request, | |
116 [ uri(URI, [optional(false), description("URI of score to render")]) | |
117 , autoplay(Auto, [boolean, default(false)]) | |
118 ], [form_data(Params)]), | |
119 reply_html_page(cliopatria(bare), [title("Audio element")], | |
120 \score_audio_player(URI,[autoplay(Auto)],Params), | |
121 [stable]). | |
122 | |
123 score_view(Request) :- | |
124 http_parameters(Request, | |
125 [ uri(URI, [optional(false), description("URI of score to render")]) | |
126 , width(W, [ optional(true), default(170), nonneg | |
127 , description("Page width in mm") ]) | |
128 ]), | |
129 ( (rdf_text(URI,hum:'refcode/OPT',Parent);rdf_text(URI,hum:'refcode/OPR',Parent)) | |
130 -> (rdf_text(URI,hum:'refcode/OTL',Title); Title="<Untitled part>"), | |
131 format(string(FullTitle),"~w, ~w",[Parent,Title]) | |
132 ; (rdf_text(URI,hum:'refcode/OTL',FullTitle); FullTitle="<Untitled>") | |
133 ), | |
134 (rdf(URI,hum:'refcode/COM',Composer); Composer="<Unknown composer>"), | |
135 reply_html_page(cliopatria(demo), [title(FullTitle)], | |
136 [ h1(FullTitle) | |
137 , h2(['By ',Composer]) | |
138 , p([ "Resource view: ", \(cp_label:rdf_link(URI,[decoration(false), resource_format(nslabel)])) | |
139 % , br([]) | |
140 % , "Download as:" | |
141 % , \seqmap(link(URI),[s-kern,s-mxml,s-lily,s-abc,a-midi]) | |
142 % , \seqmap(render_link(URI),[pdf]) | |
143 , \sonify_ui(URI,score_ui:score_audio) | |
144 % , br([]), "Download audio as:" | |
145 % , \seqmap(link(URI),[a-ogg,a-mp3]) | |
146 % , br([]) | |
147 % , \score_audio_player(URI) | |
148 , br([]) | |
149 ]) | |
150 , \score(URI,W) | |
151 ], | |
152 [stable]). | |
153 | |
154 render_link(URI,Fmt) --> | |
155 {http_link_to_id(score_render,[uri(URI),layout(page),format(Fmt)],URL), | |
156 string_concat("score.",Fmt,Filename)}, | |
157 html([" ",a([href=URL,download=Filename],Fmt)]). | |
158 | |
159 link(URI,R-Fmt) --> | |
160 { variant_sha1(URI,Hash), | |
161 atomics_to_string([score,Hash,'.',Fmt],Filename), | |
162 get_link(URI,R-Fmt,URL) | |
163 }, | |
164 html([" ",a([href=URL,download=Filename],Fmt)]). | |
165 |