annotate cpack/dml/applications/dml_overview.pl @ 0:718306e29690 tip

commiting public release
author Daniel Wolff
date Tue, 09 Feb 2016 21:05:06 +0100
parents
children
rev   line source
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(dml_overview, []).
Daniel@0 20
Daniel@0 21 /** <module> DML Overview pages
Daniel@0 22 */
Daniel@0 23
Daniel@0 24 :- use_module(library(http/html_write)).
Daniel@0 25 :- use_module(library(http/html_head)).
Daniel@0 26 :- use_module(library(http/http_dispatch)).
Daniel@0 27 :- use_module(library(semweb/rdf_db)).
Daniel@0 28 :- use_module(library(dcg_core)).
Daniel@0 29 :- use_module(library(rdfutils)).
Daniel@0 30 :- use_module(library(httpfiles),[reply_html_page/4]).
Daniel@0 31 % :- use_module(components(score)).
Daniel@0 32 % :- use_module(api(score)).
Daniel@0 33
Daniel@0 34 :- set_prolog_flag(double_quotes,string).
Daniel@0 35
Daniel@0 36 :- http_handler(root(dml/overview/top), dml_overview, []).
Daniel@0 37
Daniel@0 38 dml_overview(_Request) :-
Daniel@0 39 rdf(Rec,beets:title,literal(substring('I want to talk about you'),_)),
Daniel@0 40 reply_html_page(cliopatria(demo), [title("DML Overview")],
Daniel@0 41 [ html_post(head,style( ["h2 { margin-top:1em }"]))
Daniel@0 42 , h1("Digital Music Lab Overview")
Daniel@0 43 , h2("Knowledge representation: relational models and RDF")
Daniel@0 44 , h2("Exploring the collections")
Daniel@0 45 , p([ "The music libraries are organised in to 'graphs' (RDF sub-databases) on the basis of their origin. "
Daniel@0 46 , "One way to explore them is to start from the page for each graph, and examine the predicates and classes "
Daniel@0 47 , "the use to describe their content. For example, one can browse a list of values of the 'charm:composer' "
Daniel@0 48 , "predicate and from their find recordings that have particular values of that property."])
Daniel@0 49 , p(\ll(list_predicates,[graph(bl_p2r)],"Predicates in the British Library recordings graph"))
Daniel@0 50 , \ll(list_predicates,[graph(charm_p2r)],"Predicates CHARM collection graph")
Daniel@0 51 % , p("The CHARM collection contains works by many composers. This pie chart shows the top 25 composer by number of recordings.")
Daniel@0 52 % , \charm_composers_plot
Daniel@0 53 , h2("The semantic web")
Daniel@0 54 , p([ "DML can follow Musicbrainz URIs to retrieve information from the Linkedbrainz SPARQL endpoint and "
Daniel@0 55 , "the Musicbrainz XML web service. Information from Linkedbrainz is already in Music Ontology format, "
Daniel@0 56 , "but information from Musicbrainz is reorganised on import to conform to the Music Ontology's schema "
Daniel@0 57 , "of events to describe composition, recordinging, and other music related data." ])
Daniel@0 58 , p(\ll(list_resource,[r(Rec)],"A recording with Musicbrainz links."))
Daniel@0 59 , h2("Symbolic scores")
Daniel@0 60 , p("The database includes symbolic scores in Humdrum/Kern format obtained from the KernScores website.")
Daniel@0 61 , p(\ll(list_predicate_resources,[side=object,graph=humdrum_p2r,predicate='http://dml.org/humdrum/schema/refcode/COM'],"Humdrum scores by Bach"))
Daniel@0 62 , h2("Computation and memoisation")
Daniel@0 63 , \ll(list_instances,[graph=memo_p2r,class='http://dml.org/memo/Function'],"Memoised functions")
Daniel@0 64 , h2("SWISH: collaborative web-based Prolog")
Daniel@0 65 , p([ "DML embeds a SWISH server to provide a web-based Prolog programming environment with access to the "
Daniel@0 66 , "DML database and analsis functions, as well as facilities for visualising results and collaborative development." ])
Daniel@0 67 , p(html(a(href('/cp/swish/p/c3examples.swinb#'),"Music library statistics visualised using C3 graphics")))
Daniel@0 68 ],
Daniel@0 69 [stable]).
Daniel@0 70
Daniel@0 71 ll(ID,Params,HTML) --> line(\link(ID,Params,HTML)).
Daniel@0 72 link(ID,Params,HTML) -->
Daniel@0 73 {http_link_to_id(ID,Params,Link)},
Daniel@0 74 html(a(href(Link),HTML)).
Daniel@0 75
Daniel@0 76 line(HTML) --> html(HTML), html(br([])).
Daniel@0 77
Daniel@0 78 :- rdf_meta collection_property_hist(+,r,+,-).
Daniel@0 79 collection_property_hist(Coll,P,Min,c3{data:_{columns:Pairs, type:pie}}) :-
Daniel@0 80 setof([C,N], (collection_property_value_count(Coll,P,literal(C),N),N>Min), Pairs).
Daniel@0 81
Daniel@0 82 collection_property_value_count(Collection,Property,Value,Count) :-
Daniel@0 83 aggregate(count, R^(collection(Collection,R), rdf_has(R,Property,Value)), Count).
Daniel@0 84
Daniel@0 85 collection(charm,X) :- rdf(X,charm:file_name,_).
Daniel@0 86 collection(bl,X) :- rdf(X,rdf:type,mo:'Signal',bl_p2r).
Daniel@0 87
Daniel@0 88 charm_composers_plot -->
Daniel@0 89 {swish_render:renderer(c3,C3Mod,_)},
Daniel@0 90 {collection_property_hist(charm,dml:composer,25,Pairs)},
Daniel@0 91 % !!! This is not working.
Daniel@0 92 C3Mod:term_rendering(Pairs,_,[]).
Daniel@0 93