comparison 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
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(decoration, []).
20 /** <module> Hook for customised RDF links with extra HTML
21 */
22
23
24 :- use_module(cliopatria(hooks)).
25 :- use_module(library(http/html_write)).
26 :- use_module(library(http/html_head)).
27 :- use_module(library(semweb/rdfs)).
28 :- use_module(library(dcg_core)).
29 :- use_module(library(rdfutils)).
30 :- use_module(components(label)).
31 :- use_module(components(icons)).
32
33
34 :- multifile resource_decoration//2, resource_view//2.
35
36 %% resource_decoration(URI)// is nondet.
37 % This DCG rule succeeds when the resource specified by URI should be
38 % preceeded by arbitrary HTML elements. It should produce a list of HTML
39 % tokens as produced by html//1.
40
41 cliopatria:display_link(R,_) -->
42 { rdf_equal(R,rdf:nil) }, !, html(span(title('rdf:nil'),b('[]'))).
43
44 cliopatria:display_link(R,Opts) -->
45 { rdf_has(R,rdf:first,_), !,
46 option(max_length(Max),Opts,5),
47 cp_label:resource_link(R,ListLink),
48 rdf_list_take(Max,R,Items,Tail),
49 rdf_list_length(Tail,Rem),
50 ( Rem=0 -> length(Items,ListLength)
51 ; ListLength is Max+Rem
52 ),
53 format(string(ListTitle), 'RDF collection with ~D members', ListLength)
54 },
55 html([ a([href(ListLink),title(ListTitle)],b('['))
56 , \seqmap_with_sep(comma, display_item(Opts), Items)
57 , \display_tail(Rem,Tail)
58 , a([href(ListLink),title(ListTitle)],b(']'))
59 ]).
60
61 cliopatria:display_link(R,Opts) -->
62 { rdf(R,rdf:type,owl:'Restriction'),
63 rdf(R,owl:onProperty,Prop),
64 restriction_condition(R,Cond)
65 }, !,
66 html(span(title(R),['(', \html(Cond),')',&(nbsp),\rdf_link(Prop,Opts)])).
67
68 restriction_condition(R,['=',Num]) :- rdf_number(R,owl:cardinality,Num), !.
69 restriction_condition(R,[&(ge),Num]) :- rdf_number(R,owl:minCardinality,Num), !.
70 restriction_condition(R,[&(le),Num]) :- rdf_number(R,owl:maxCardinality,Num), !.
71
72 cliopatria:display_link(URI,Opts) -->
73 { atom(URI), \+rdf_graph(URI), !,
74 cp_label:resource_link(URI, Target),
75 (rdf(URI,_,_) -> Class=r_def; Class=r_undef),
76 Link = a( [class(Class), href(Target), title(URI)],
77 \(cp_label:resource_label(URI, Opts)))
78 },
79 ( {option(decoration(true),Opts,true)},
80 resource_decoration(URI,decoration:html(Link)) -> []
81 ; html(Link)
82 ).
83
84 decoration:resource_decoration(URI,Link) -->
85 { rdf_has(_,foaf:page,URI)
86 ; rdf_has(_,foaf:isPrimaryTopicOf,URI)
87 % ; rdfs_individual_of(URI,foaf:'Document')
88 }, !,
89 html_requires(font_awesome),
90 html( span( [ \Link, &(nbsp), a([href(URI),target('_blank')],\icon('external-link')) ])).
91
92
93 display_item(Opts,Item) --> rdf_link(Item,Opts).
94 display_tail(0,_) --> !.
95 display_tail(N,Tail) -->
96 { cp_label:resource_link(Tail,Link),
97 format(string(Title),'Remaining ~D items',[N])
98 },
99 html([' | ',a([href(Link),title(Title)],&(hellip))]).
100
101 comma --> html(', ').
102
103 cliopatria:list_resource(URI,Opts) -->
104 {debug(decoration,'Checking for views for ~q...',[URI])},
105 {findall(Head-Tail,resource_view(URI,Opts,Head,Tail),Views), Views\=[]}, !,
106 {length(Views,N), debug(decoration,'Found ~d views.',[N])},
107 seqmap(dlist,Views),
108 cpa_browse:list_resource(URI,[raw(true)|Opts]).
109
110 dlist(Head-Tail,Head,Tail).