View source with raw comments or as raw
   1/*  Part of ClioPatria SeRQL and SPARQL server
   2
   3    Author:        Jan Wielemaker
   4    E-mail:        J.Wielemaker@cs.vu.nl
   5    WWW:           http://www.swi-prolog.org
   6    Copyright (C): 2010, University of Amsterdam,
   7		   VU University Amsterdam
   8
   9    This program is free software; you can redistribute it and/or
  10    modify it under the terms of the GNU General Public License
  11    as published by the Free Software Foundation; either version 2
  12    of the License, or (at your option) any later version.
  13
  14    This program is distributed in the hope that it will be useful,
  15    but WITHOUT ANY WARRANTY; without even the implied warranty of
  16    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
  17    GNU General Public License for more details.
  18
  19    You should have received a copy of the GNU General Public
  20    License along with this library; if not, write to the Free Software
  21    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
  22
  23    As a special exception, if you link this library with other files,
  24    compiled with a Free Software compiler, to produce an executable, this
  25    library does not by itself cause the resulting executable to be covered
  26    by the GNU General Public License. This exception does not however
  27    invalidate any other reasons why the executable file might be covered by
  28    the GNU General Public License.
  29*/
  30
  31:- module(cp_label,
  32	  [ turtle_label//1,		% +Literal
  33	    rdf_link//1,		% +RDFTerm
  34	    rdf_link//2,		% +RDFTerm, +Options
  35	    resource_link/2		% +URI, -URL
  36	  ]).
  37:- use_module(library(error)).
  38:- use_module(library(option)).
  39:- use_module(library(sgml)).
  40:- use_module(library(sgml_write)).
  41:- use_module(library(aggregate)).
  42:- use_module(library(semweb/rdf_db)).
  43:- use_module(library(semweb/rdf_label)).
  44:- use_module(library(http/html_write)).
  45:- use_module(library(http/http_dispatch)).
  46:- if(exists_source(library(semweb/rdf11))).
  47:- use_module(library(semweb/rdf11), [rdf_lexical_form/2]).
  48:- endif.
  49
  50:- use_module(cliopatria(hooks)).
  51
  52/** <module> Support for showing labels
  53
  54This module provides HTML components to display labels for resources.
  55
  56@see	library(semweb/rdf_label) returns textual labels.
  57*/
  58
  59
  60%%	turtle_label(+RDFTerm)// is det.
  61%
  62%	HTML  rule  to  emit  an  RDF   term  (resource  or  object)  in
  63%	turtle-like notation with CSS classes.
  64%
  65%	@tbd	Implement possibility for a summary.
  66
  67turtle_label(R) -->
  68	turtle_label(R, []).
  69
  70turtle_label(R, _) -->
  71	{ atom(R),
  72	  rdf_global_id(NS:Local, R), !
  73	},
  74	html([span(class(prefix), NS), ':', span(class(local), Local)]).
  75turtle_label(R, Options) -->
  76	{ atom(R),
  77	  rdf_display_label(R, Lang, LabelText),
  78	  Lang \== url,
  79	  LabelText \== '',
  80	  truncate_text(LabelText, Show, Options)
  81	},
  82	html(Show).
  83turtle_label(R, Options) -->
  84	{ rdf_is_bnode(R) },
  85	bnode_label(R, Options), !.
  86turtle_label(R, _) -->
  87	{ atom(R) }, !,
  88	html(['<',R,'>']).
  89turtle_label(literal(Lit), Options) --> !,
  90	literal_label(Lit, Options).
  91turtle_label(@(String,Lang), Options) --> !,
  92	literal_label(lang(Lang, String), Options).
  93:- if(current_predicate(rdf_lexical_form/2)).
  94turtle_label(^^(Value,Type), Options) --> !,
  95	(   {rdf_equal(Type, xsd:string)}
  96	->  literal_label(type(Type, Value), Options)
  97	;   {rdf_lexical_form(^^(Value,Type), ^^(String,_))},
  98	    literal_label(type(Type, String), Options)
  99	).
 100:- endif.
 101
 102literal_label(type(Type, Value), Options) --> !,
 103	{ truncate_text(Value, Show, Options) },
 104	html(span(class(literal),
 105		  [span(class(oquote), '"'), span(class(l_text), Show), span(class(cquote), '"'),
 106		   span(class(l_type), '^^'), \turtle_label(Type)])).
 107literal_label(lang(Lang, Value), Options) --> !,
 108	{ truncate_text(Value, Show, Options) },
 109	html(span(class(literal),
 110		  [span(class(oquote), '"'), span(class(l_text), Show), span(class(cquote), '"'),
 111		   span(class(l_lang), '@'), span(class(lang), Lang)])).
 112literal_label(Value, Options) -->
 113	{ truncate_text(Value, Show, Options) },
 114	html(span(class(literal),
 115		  [span(class(oquote), '"'), span(class(l_text), Show), span(class(cquote), '"')])).
 116
 117truncate_text(Text, Text, []) :- !.
 118truncate_text(Text, Truncated, Options) :-
 119	option(max_length(Len), Options), !,
 120	truncate_atom(Text, Len, Truncated).
 121truncate_text(Text, Text, _).
 122
 123
 124%%	bnode_label(+Resource, +Options)// is semidet.
 125%
 126%	Display an HTML label for an  RDF   blank  node.  This DCG rules
 127%	first  calls  the  hook  cliopatria:bnode_label//1.  On  failure
 128%	performs its default task:
 129%
 130%	    * If the bnode has an rdf:value, display the label thereof
 131%	    with [<label>...]
 132%
 133%	    * If the bnode is an RDF collection, display its first 5
 134%	    members as (<member-1>, <member-2, ...)
 135
 136bnode_label(R, _) -->
 137	cliopatria:bnode_label(R), !.
 138bnode_label(R, Options) -->
 139	{ rdf_has(R, rdf:value, Value),
 140	  (   Value = literal(_)
 141	  ;   \+ rdf_is_bnode(Value)
 142	  )
 143	}, !,
 144	html(span([ class(rdf_bnode),
 145		    title('RDF bnode using rdf:value')
 146		  ],
 147		  ['[', \turtle_label(Value, Options), '...]'])).
 148bnode_label(R, Options) -->
 149	{ rdf_collection_list(R, List), !,
 150	  length(List, Len),
 151	  format(string(Title), 'RDF collection with ~D members', Len)
 152	},
 153	html(span([ class(rdf_list),
 154		    title(Title)
 155		  ],
 156		  ['(', \collection_members(List, 0, Len, 5, Options), ')'])).
 157
 158collection_members([], _, _, _, _) --> [].
 159collection_members(_, Max, Total, Max, _) --> !,
 160	{ Left is Total - Max },
 161	html('... ~D more'-[Left]).
 162collection_members([H|T], I, Total, Max, Options) -->
 163	turtle_label(H, Options),
 164	(   { T == [] }
 165	->  []
 166	;   html(','),
 167	    { I2 is I + 1 },
 168	    collection_members(T, I2, Total, Max, Options)
 169	).
 170
 171
 172rdf_collection_list(R, []) :-
 173	rdf_equal(rdf:nil, R), !.
 174rdf_collection_list(R, [H|T]) :-
 175	rdf_has(R, rdf:first, H),
 176	rdf_has(R, rdf:rest, RT),
 177	rdf_collection_list(RT, T).
 178
 179
 180%%	rdf_link(+URI)// is det.
 181%%	rdf_link(+URI, +Options)// is det.
 182%
 183%	Make a hyper-link to an arbitrary   RDF resource or object using
 184%	the label.  Options processed:
 185%
 186%	    * resource_format(+Format)
 187%	    Determines peference for displaying resources.  Values are:
 188%
 189%	        * plain
 190%	        Display full resource a plain text
 191%	        * label
 192%	        Try to display a resource using its label
 193%	        * nslabel
 194%	        Try to display a resource as <prefix>:<Label>
 195%	    * max_length(+Len)
 196%	    Truncate long texts to Len characters, using ellipses to
 197%	    indicate that the text is truncated.
 198%	    * target(+Target)
 199%	    Passed to the HTML <a> element as `target` attribute.
 200%
 201%	This predicate creates two types of  links. Resources are linked
 202%	to the handler implementing   =list_resource= using r=<resource>
 203%	and  literals  that  appear  multiple    times   are  linked  to
 204%	=list_triples_with_object= using a Prolog  representation of the
 205%	literal.
 206%
 207%	This predicate can be hooked using cliopatria:display_link//2.
 208%
 209%	@tbd	Make it easier to determine the format of the label
 210%	@tbd	Allow linking to different handlers.
 211
 212rdf_link(R) -->
 213	rdf_link(R, []).
 214
 215rdf_link(R, Options) -->
 216	cliopatria:display_link(R, Options), !.
 217rdf_link(R, Options) -->
 218	{ atom(R), !,
 219	  resource_link(R, HREF),
 220	  (   rdf(R, _, _)
 221	  ->  Class = r_def
 222	  ;   rdf_graph(R)
 223	  ->  Class = r_graph
 224	  ;   Class = r_undef
 225	  ),
 226	  link_options(Extra, Options)
 227	},
 228	html(a([class(['rdf-r',Class]), href(HREF)|Extra],
 229	       \resource_label(R, Options))).
 230rdf_link(Literal, Options) -->
 231	{ aggregate_all(count, literal_occurrence(Literal, Options), Count),
 232	  Count > 1, !,
 233	  format(string(Title), 'Used ~D times', [Count]),
 234	  term_to_atom(Literal, Atom),
 235	  http_link_to_id(list_triples_with_object, [l=Atom], HREF),
 236	  link_options(Extra, Options)
 237	},
 238	html(a([ class(l_count),
 239		 href(HREF),
 240		 title(Title)
 241	       | Extra
 242	       ],
 243	       \turtle_label(Literal))).
 244rdf_link(Literal, _) -->
 245	turtle_label(Literal).
 246
 247literal_occurrence(Literal, Options) :-
 248	Literal = literal(_), !,
 249	(   option(graph(Graph), Options)
 250	->  rdf_db:rdf(_,_,Literal,Graph)
 251	;   rdf_db:rdf(_,_,Literal)
 252	).
 253:- if(current_predicate(rdf11:rdf/4)).
 254literal_occurrence(Literal, Options) :-
 255	(   option(graph(Graph), Options)
 256	->  rdf11:rdf(_,_,Literal,Graph)
 257	;   rdf11:rdf(_,_,Literal)
 258	).
 259:- endif.
 260
 261link_options(LinkOptions, Options) :-
 262	option(target(Target), Options), !,
 263	LinkOptions = [target(Target)].
 264link_options([], _).
 265
 266
 267%%	resource_link(+URI, -URL) is det.
 268%
 269%	Generate a link to display more   information  about a resource.
 270%	The  default  is  to  link  to  the  HTTP  handler  implementing
 271%	=list_resource=     using     the     parameter     =r=.     See
 272%	cpa_browse:list_resource/1.  This  predicate  calls    the  hook
 273%	cliopatria:resource_link/2,  which  allows  for  overruling  the
 274%	default.
 275
 276resource_link(R, HREF) :-
 277	cliopatria:resource_link(R, HREF), !.
 278resource_link(R, HREF) :-
 279	http_link_to_id(list_resource, [r=R], HREF).
 280
 281resource_label(R, Options) -->
 282	{ option(resource_format(Format), Options) }, !,
 283	resource_flabel(Format, R, Options).
 284resource_label(R, Options) -->
 285	turtle_label(R, Options).
 286
 287resource_flabel(plain, R, _) --> !,
 288	html(R).
 289resource_flabel(label, R, Options) --> !,
 290	(   { rdf_display_label(R, Label),
 291	      truncate_text(Label, Show, Options)
 292	    }
 293	->  html([span(class(r_label), Show)])
 294	;   turtle_label(R)
 295	).
 296resource_flabel(nslabel, R, _Options) -->
 297	{ (   rdf_is_bnode(R)
 298	  ->  NS = '_'
 299	  ;   rdf_global_id(NS:_Local, R)
 300	  ->  true
 301	  ;   NS = '?'
 302	  ), !,
 303	  rdf_display_label(R, Label)
 304	},
 305	html([span(class(prefix),NS),':',span(class(r_label),Label)]).
 306resource_flabel(_, R, Options) -->
 307	turtle_label(R, Options).