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