diff cpack/dml/lib/decoration.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/lib/decoration.pl	Tue Feb 09 21:05:06 2016 +0100
@@ -0,0 +1,110 @@
+/* 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(decoration, []).
+/** <module> Hook for customised RDF links with extra HTML
+*/
+
+
+:- use_module(cliopatria(hooks)).
+:- use_module(library(http/html_write)).
+:- use_module(library(http/html_head)).
+:- use_module(library(semweb/rdfs)).
+:- use_module(library(dcg_core)).
+:- use_module(library(rdfutils)).
+:- use_module(components(label)).
+:- use_module(components(icons)).
+
+
+:- multifile resource_decoration//2, resource_view//2.
+
+%% resource_decoration(URI)// is nondet.
+%  This DCG rule succeeds when the resource specified by URI should be
+%  preceeded by arbitrary HTML elements. It should produce a list of HTML
+%  tokens as produced by html//1.
+
+cliopatria:display_link(R,_) -->
+   { rdf_equal(R,rdf:nil) }, !, html(span(title('rdf:nil'),b('[]'))).
+
+cliopatria:display_link(R,Opts) -->
+   { rdf_has(R,rdf:first,_), !, 
+     option(max_length(Max),Opts,5),
+     cp_label:resource_link(R,ListLink),
+     rdf_list_take(Max,R,Items,Tail),
+     rdf_list_length(Tail,Rem),
+     (   Rem=0 -> length(Items,ListLength)
+     ;   ListLength is Max+Rem
+     ),
+     format(string(ListTitle), 'RDF collection with ~D members', ListLength) 
+   },
+   html([ a([href(ListLink),title(ListTitle)],b('['))
+        , \seqmap_with_sep(comma, display_item(Opts), Items)
+        , \display_tail(Rem,Tail)
+        , a([href(ListLink),title(ListTitle)],b(']'))
+        ]).
+
+cliopatria:display_link(R,Opts) -->
+   { rdf(R,rdf:type,owl:'Restriction'), 
+     rdf(R,owl:onProperty,Prop),
+     restriction_condition(R,Cond)
+   }, !,
+   html(span(title(R),['(', \html(Cond),')',&(nbsp),\rdf_link(Prop,Opts)])).
+
+restriction_condition(R,['=',Num])   :- rdf_number(R,owl:cardinality,Num), !.
+restriction_condition(R,[&(ge),Num]) :- rdf_number(R,owl:minCardinality,Num), !.
+restriction_condition(R,[&(le),Num]) :- rdf_number(R,owl:maxCardinality,Num), !.
+
+cliopatria:display_link(URI,Opts) --> 
+   {  atom(URI), \+rdf_graph(URI), !,
+      cp_label:resource_link(URI, Target),
+      (rdf(URI,_,_) ->  Class=r_def; Class=r_undef),
+      Link = a( [class(Class), href(Target), title(URI)], 
+                \(cp_label:resource_label(URI, Opts)))
+   },
+   (  {option(decoration(true),Opts,true)},
+      resource_decoration(URI,decoration:html(Link)) -> []
+   ;  html(Link)
+   ).
+
+decoration:resource_decoration(URI,Link) -->
+   {  rdf_has(_,foaf:page,URI)
+   ;  rdf_has(_,foaf:isPrimaryTopicOf,URI)
+   % ;  rdfs_individual_of(URI,foaf:'Document') 
+   }, !,
+   html_requires(font_awesome),
+   html( span( [ \Link, &(nbsp), a([href(URI),target('_blank')],\icon('external-link')) ])).
+
+
+display_item(Opts,Item) --> rdf_link(Item,Opts).
+display_tail(0,_) --> !.
+display_tail(N,Tail) --> 
+   {  cp_label:resource_link(Tail,Link),
+      format(string(Title),'Remaining ~D items',[N])
+   },
+   html([' | ',a([href(Link),title(Title)],&(hellip))]).
+
+comma --> html(', ').
+
+cliopatria:list_resource(URI,Opts) -->
+   {debug(decoration,'Checking for views for ~q...',[URI])},
+   {findall(Head-Tail,resource_view(URI,Opts,Head,Tail),Views), Views\=[]}, !,
+   {length(Views,N), debug(decoration,'Found ~d views.',[N])},
+   seqmap(dlist,Views),
+   cpa_browse:list_resource(URI,[raw(true)|Opts]).
+
+dlist(Head-Tail,Head,Tail).