Daniel@0
|
1 /* Part of DML (Digital Music Laboratory)
|
Daniel@0
|
2 Copyright 2014-2015 Samer Abdallah, University of London
|
Daniel@0
|
3
|
Daniel@0
|
4 This program is free software; you can redistribute it and/or
|
Daniel@0
|
5 modify it under the terms of the GNU General Public License
|
Daniel@0
|
6 as published by the Free Software Foundation; either version 2
|
Daniel@0
|
7 of the License, or (at your option) any later version.
|
Daniel@0
|
8
|
Daniel@0
|
9 This program is distributed in the hope that it will be useful,
|
Daniel@0
|
10 but WITHOUT ANY WARRANTY; without even the implied warranty of
|
Daniel@0
|
11 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
Daniel@0
|
12 GNU General Public License for more details.
|
Daniel@0
|
13
|
Daniel@0
|
14 You should have received a copy of the GNU General Public
|
Daniel@0
|
15 License along with this library; if not, write to the Free Software
|
Daniel@0
|
16 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
|
Daniel@0
|
17 */
|
Daniel@0
|
18
|
Daniel@0
|
19 :- module(score_ui, [ sonify_ui//2]).
|
Daniel@0
|
20
|
Daniel@0
|
21 /** <module> Score related pages and hooks
|
Daniel@0
|
22
|
Daniel@0
|
23 This module provides a web pages for displaying rendered scores and for
|
Daniel@0
|
24 an audio player to play sonified scores.
|
Daniel@0
|
25 It also module provides resource decorations and local view customisations
|
Daniel@0
|
26 for Humdrum scores.
|
Daniel@0
|
27 */
|
Daniel@0
|
28
|
Daniel@0
|
29 :- use_module(library(http/html_write)).
|
Daniel@0
|
30 :- use_module(library(http/html_head)).
|
Daniel@0
|
31 :- use_module(library(http/http_dispatch)).
|
Daniel@0
|
32 :- use_module(library(http/http_parameters)).
|
Daniel@0
|
33 :- use_module(library(semweb/rdfs)).
|
Daniel@0
|
34 :- use_module(library(semweb/rdf_label)).
|
Daniel@0
|
35 :- use_module(library(dcg_core)).
|
Daniel@0
|
36 :- use_module(library(dcg_codes)).
|
Daniel@0
|
37 :- use_module(library(decoration)).
|
Daniel@0
|
38 :- use_module(library(rdfutils)).
|
Daniel@0
|
39 :- use_module(library(httpfiles)).
|
Daniel@0
|
40 :- use_module(components(score)).
|
Daniel@0
|
41 :- use_module(components(icons)).
|
Daniel@0
|
42 :- use_module(api(score)).
|
Daniel@0
|
43
|
Daniel@0
|
44 :- set_prolog_flag(double_quotes,string).
|
Daniel@0
|
45
|
Daniel@0
|
46 :- http_handler(root(dml/score/audio), score_audio, []).
|
Daniel@0
|
47 :- http_handler(root(dml/score/view), score_view, []).
|
Daniel@0
|
48
|
Daniel@0
|
49 decoration:resource_decoration(URI,Link) -->
|
Daniel@0
|
50 {rdfs_individual_of(URI,hum:'File')}, !,
|
Daniel@0
|
51 {http_link_to_id(score_view,[uri(URI)],ScoreURL)},
|
Daniel@0
|
52 {http_link_to_id(score_sonify,[uri(URI),format(ogg)],AudioURL)},
|
Daniel@0
|
53 html_requires(font_awesome),
|
Daniel@0
|
54 html_requires(js('add_dummy_iframe.js')),
|
Daniel@0
|
55 html( span( [ a(href(ScoreURL),\icon(music))
|
Daniel@0
|
56 , &(nbsp), a([href(AudioURL),target(dummy)],\icon(play))
|
Daniel@0
|
57 , &(nbsp), a([href('about:blank'),target(dummy)],\icon(stop))
|
Daniel@0
|
58 , &(ensp), \Link
|
Daniel@0
|
59 ])).
|
Daniel@0
|
60
|
Daniel@0
|
61 rdf_label:label_hook(URI,literal(Lit)) :-
|
Daniel@0
|
62 rdf(URI,rdf:type,hum:'File'),
|
Daniel@0
|
63 (var(Lit) -> Lit=Label; Lit=lang(_,Label)),
|
Daniel@0
|
64 phrase_string(uri_label(URI),Label).
|
Daniel@0
|
65
|
Daniel@0
|
66 uri_label(URI) -->
|
Daniel@0
|
67 {atom_concat('kern:',File,URI)},
|
Daniel@0
|
68 file_label(URI,File).
|
Daniel@0
|
69
|
Daniel@0
|
70 file_label(URI,File) -->
|
Daniel@0
|
71 { suffix(30,File,ShortFile) },
|
Daniel@0
|
72 at(ShortFile),
|
Daniel@0
|
73 if(rdf_text(URI,hum:'refcode/OTL',Title), (" - ",at(Title)," ")),
|
Daniel@0
|
74 if((rdf_text(URI,hum:'refcode/COM',Composer),short_name(Composer,Comp)),
|
Daniel@0
|
75 paren(at(Comp))).
|
Daniel@0
|
76
|
Daniel@0
|
77 suffix(MaxLen,String,Shorter) :-
|
Daniel@0
|
78 string_length(String,N),
|
Daniel@0
|
79 ( N=<MaxLen, Shorter=String
|
Daniel@0
|
80 ; sub_string(String,_,MaxLen,0,S1),
|
Daniel@0
|
81 string_concat("...",S1,Shorter)
|
Daniel@0
|
82 ).
|
Daniel@0
|
83 surname(Full,Surname) :-
|
Daniel@0
|
84 split_string(Full,","," ",[Surname|_]).
|
Daniel@0
|
85 short_name(Full,Short) :-
|
Daniel@0
|
86 split_string(Full,","," ",[Surname|Rest]),
|
Daniel@0
|
87 maplist(split(" "," "),Rest,ForeNested),
|
Daniel@0
|
88 flatten(ForeNested,Forenames),
|
Daniel@0
|
89 maplist(initial,Forenames,Initials),
|
Daniel@0
|
90 atomics_to_string(Initials,".",Inits),
|
Daniel@0
|
91 atomics_to_string([Inits,Surname],".",Short).
|
Daniel@0
|
92
|
Daniel@0
|
93
|
Daniel@0
|
94 split(Sep,Pad,String,Parts) :- split_string(String,Sep,Pad,Parts).
|
Daniel@0
|
95 initial(String,Init) :- string_chars(String,[Init|_]).
|
Daniel@0
|
96
|
Daniel@0
|
97 decoration:resource_view(URI,_) -->
|
Daniel@0
|
98 {rdfs_individual_of(URI,hum:'File')},
|
Daniel@0
|
99 {http_link_to_id(score_view,[uri(URI)],ViewURL)},
|
Daniel@0
|
100 html([ a(href=ViewURL, [\icon(music), " View score"]), &('MediumSpace')
|
Daniel@0
|
101 , br([]), "Download as:"
|
Daniel@0
|
102 , \seqmap(link(URI),[s-kern,s-mxml,s-lily,s-abc,a-midi])
|
Daniel@0
|
103 , \seqmap(render_link(URI),[pdf])
|
Daniel@0
|
104 , h2("Score sonification")
|
Daniel@0
|
105 % , br([]), "Download audio as:"
|
Daniel@0
|
106 % , \seqmap(link(URI),[a-ogg,a-mp3])
|
Daniel@0
|
107 % , br([])
|
Daniel@0
|
108 % , \score_audio_player(URI)
|
Daniel@0
|
109 , \sonify_ui(URI,score_ui:score_audio)
|
Daniel@0
|
110 , \pitch_class_histogram(URI)
|
Daniel@0
|
111 ]).
|
Daniel@0
|
112
|
Daniel@0
|
113
|
Daniel@0
|
114 score_audio(Request) :-
|
Daniel@0
|
115 http_parameters(Request,
|
Daniel@0
|
116 [ uri(URI, [optional(false), description("URI of score to render")])
|
Daniel@0
|
117 , autoplay(Auto, [boolean, default(false)])
|
Daniel@0
|
118 ], [form_data(Params)]),
|
Daniel@0
|
119 reply_html_page(cliopatria(bare), [title("Audio element")],
|
Daniel@0
|
120 \score_audio_player(URI,[autoplay(Auto)],Params),
|
Daniel@0
|
121 [stable]).
|
Daniel@0
|
122
|
Daniel@0
|
123 score_view(Request) :-
|
Daniel@0
|
124 http_parameters(Request,
|
Daniel@0
|
125 [ uri(URI, [optional(false), description("URI of score to render")])
|
Daniel@0
|
126 , width(W, [ optional(true), default(170), nonneg
|
Daniel@0
|
127 , description("Page width in mm") ])
|
Daniel@0
|
128 ]),
|
Daniel@0
|
129 ( (rdf_text(URI,hum:'refcode/OPT',Parent);rdf_text(URI,hum:'refcode/OPR',Parent))
|
Daniel@0
|
130 -> (rdf_text(URI,hum:'refcode/OTL',Title); Title="<Untitled part>"),
|
Daniel@0
|
131 format(string(FullTitle),"~w, ~w",[Parent,Title])
|
Daniel@0
|
132 ; (rdf_text(URI,hum:'refcode/OTL',FullTitle); FullTitle="<Untitled>")
|
Daniel@0
|
133 ),
|
Daniel@0
|
134 (rdf(URI,hum:'refcode/COM',Composer); Composer="<Unknown composer>"),
|
Daniel@0
|
135 reply_html_page(cliopatria(demo), [title(FullTitle)],
|
Daniel@0
|
136 [ h1(FullTitle)
|
Daniel@0
|
137 , h2(['By ',Composer])
|
Daniel@0
|
138 , p([ "Resource view: ", \(cp_label:rdf_link(URI,[decoration(false), resource_format(nslabel)]))
|
Daniel@0
|
139 % , br([])
|
Daniel@0
|
140 % , "Download as:"
|
Daniel@0
|
141 % , \seqmap(link(URI),[s-kern,s-mxml,s-lily,s-abc,a-midi])
|
Daniel@0
|
142 % , \seqmap(render_link(URI),[pdf])
|
Daniel@0
|
143 , \sonify_ui(URI,score_ui:score_audio)
|
Daniel@0
|
144 % , br([]), "Download audio as:"
|
Daniel@0
|
145 % , \seqmap(link(URI),[a-ogg,a-mp3])
|
Daniel@0
|
146 % , br([])
|
Daniel@0
|
147 % , \score_audio_player(URI)
|
Daniel@0
|
148 , br([])
|
Daniel@0
|
149 ])
|
Daniel@0
|
150 , \score(URI,W)
|
Daniel@0
|
151 ],
|
Daniel@0
|
152 [stable]).
|
Daniel@0
|
153
|
Daniel@0
|
154 render_link(URI,Fmt) -->
|
Daniel@0
|
155 {http_link_to_id(score_render,[uri(URI),layout(page),format(Fmt)],URL),
|
Daniel@0
|
156 string_concat("score.",Fmt,Filename)},
|
Daniel@0
|
157 html([" ",a([href=URL,download=Filename],Fmt)]).
|
Daniel@0
|
158
|
Daniel@0
|
159 link(URI,R-Fmt) -->
|
Daniel@0
|
160 { variant_sha1(URI,Hash),
|
Daniel@0
|
161 atomics_to_string([score,Hash,'.',Fmt],Filename),
|
Daniel@0
|
162 get_link(URI,R-Fmt,URL)
|
Daniel@0
|
163 },
|
Daniel@0
|
164 html([" ",a([href=URL,download=Filename],Fmt)]).
|
Daniel@0
|
165
|