Mercurial > hg > dml-open-cliopatria
view 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 |
line wrap: on
line source
/* 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(score_ui, [ sonify_ui//2]). /** <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/rdfs)). :- use_module(library(semweb/rdf_label)). :- use_module(library(dcg_core)). :- use_module(library(dcg_codes)). :- use_module(library(decoration)). :- use_module(library(rdfutils)). :- use_module(library(httpfiles)). :- use_module(components(score)). :- use_module(components(icons)). :- use_module(api(score)). :- set_prolog_flag(double_quotes,string). :- http_handler(root(dml/score/audio), score_audio, []). :- http_handler(root(dml/score/view), score_view, []). decoration:resource_decoration(URI,Link) --> {rdfs_individual_of(URI,hum:'File')}, !, {http_link_to_id(score_view,[uri(URI)],ScoreURL)}, {http_link_to_id(score_sonify,[uri(URI),format(ogg)],AudioURL)}, html_requires(font_awesome), html_requires(js('add_dummy_iframe.js')), html( span( [ a(href(ScoreURL),\icon(music)) , &(nbsp), a([href(AudioURL),target(dummy)],\icon(play)) , &(nbsp), a([href('about:blank'),target(dummy)],\icon(stop)) , &(ensp), \Link ])). rdf_label:label_hook(URI,literal(Lit)) :- rdf(URI,rdf:type,hum:'File'), (var(Lit) -> Lit=Label; Lit=lang(_,Label)), phrase_string(uri_label(URI),Label). uri_label(URI) --> {atom_concat('kern:',File,URI)}, file_label(URI,File). file_label(URI,File) --> { suffix(30,File,ShortFile) }, at(ShortFile), if(rdf_text(URI,hum:'refcode/OTL',Title), (" - ",at(Title)," ")), if((rdf_text(URI,hum:'refcode/COM',Composer),short_name(Composer,Comp)), paren(at(Comp))). suffix(MaxLen,String,Shorter) :- string_length(String,N), ( N=<MaxLen, Shorter=String ; sub_string(String,_,MaxLen,0,S1), string_concat("...",S1,Shorter) ). surname(Full,Surname) :- split_string(Full,","," ",[Surname|_]). short_name(Full,Short) :- split_string(Full,","," ",[Surname|Rest]), maplist(split(" "," "),Rest,ForeNested), flatten(ForeNested,Forenames), maplist(initial,Forenames,Initials), atomics_to_string(Initials,".",Inits), atomics_to_string([Inits,Surname],".",Short). split(Sep,Pad,String,Parts) :- split_string(String,Sep,Pad,Parts). initial(String,Init) :- string_chars(String,[Init|_]). decoration:resource_view(URI,_) --> {rdfs_individual_of(URI,hum:'File')}, {http_link_to_id(score_view,[uri(URI)],ViewURL)}, html([ a(href=ViewURL, [\icon(music), " View score"]), &('MediumSpace') , br([]), "Download as:" , \seqmap(link(URI),[s-kern,s-mxml,s-lily,s-abc,a-midi]) , \seqmap(render_link(URI),[pdf]) , h2("Score sonification") % , br([]), "Download audio as:" % , \seqmap(link(URI),[a-ogg,a-mp3]) % , br([]) % , \score_audio_player(URI) , \sonify_ui(URI,score_ui:score_audio) , \pitch_class_histogram(URI) ]). score_audio(Request) :- http_parameters(Request, [ uri(URI, [optional(false), description("URI of score to render")]) , autoplay(Auto, [boolean, default(false)]) ], [form_data(Params)]), reply_html_page(cliopatria(bare), [title("Audio element")], \score_audio_player(URI,[autoplay(Auto)],Params), [stable]). score_view(Request) :- http_parameters(Request, [ uri(URI, [optional(false), description("URI of score to render")]) , width(W, [ optional(true), default(170), nonneg , description("Page width in mm") ]) ]), ( (rdf_text(URI,hum:'refcode/OPT',Parent);rdf_text(URI,hum:'refcode/OPR',Parent)) -> (rdf_text(URI,hum:'refcode/OTL',Title); Title="<Untitled part>"), format(string(FullTitle),"~w, ~w",[Parent,Title]) ; (rdf_text(URI,hum:'refcode/OTL',FullTitle); FullTitle="<Untitled>") ), (rdf(URI,hum:'refcode/COM',Composer); Composer="<Unknown composer>"), reply_html_page(cliopatria(demo), [title(FullTitle)], [ h1(FullTitle) , h2(['By ',Composer]) , p([ "Resource view: ", \(cp_label:rdf_link(URI,[decoration(false), resource_format(nslabel)])) % , br([]) % , "Download as:" % , \seqmap(link(URI),[s-kern,s-mxml,s-lily,s-abc,a-midi]) % , \seqmap(render_link(URI),[pdf]) , \sonify_ui(URI,score_ui:score_audio) % , br([]), "Download audio as:" % , \seqmap(link(URI),[a-ogg,a-mp3]) % , br([]) % , \score_audio_player(URI) , br([]) ]) , \score(URI,W) ], [stable]). render_link(URI,Fmt) --> {http_link_to_id(score_render,[uri(URI),layout(page),format(Fmt)],URL), string_concat("score.",Fmt,Filename)}, html([" ",a([href=URL,download=Filename],Fmt)]). link(URI,R-Fmt) --> { variant_sha1(URI,Hash), atomics_to_string([score,Hash,'.',Fmt],Filename), get_link(URI,R-Fmt,URL) }, html([" ",a([href=URL,download=Filename],Fmt)]).