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)).

Support for showing labels

This module provides HTML components to display labels for resources.

See also
- library(semweb/rdf_label) returns textual labels. */
 turtle_label(+RDFTerm)// is det
HTML rule to emit an RDF term (resource or object) in turtle-like notation with CSS classes.
To be done
- Implement possibility for a summary.
   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, _).
 bnode_label(+Resource, +Options)// is semidet
Display an HTML label for an RDF blank node. This DCG rules first calls the hook cliopatria:bnode_label//1. On failure performs its default task:
  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).
 rdf_link(+URI)// is det
 rdf_link(+URI, +Options)// is det
Make a hyper-link to an arbitrary RDF resource or object using the label. Options processed:
resource_format(+Format)
Determines peference for displaying resources. Values are:
plain
Display full resource a plain text
label
Try to display a resource using its label
nslabel
Try to display a resource as <prefix>:<Label>
turtle
Try to display as Turtle <prefix>:<local>
max_length(+Len)
Truncate long texts to Len characters, using ellipses to indicate that the text is truncated.
target(+Target)
Passed to the HTML <a> element as target attribute.
role(+Role)
Passed to display_link/2 hook as option. Can be used to differentiate display of URI depending on role as subject, predicate, object, bnode, domain, or range.

This predicate creates two types of links. Resources are linked to the handler implementing list_resource using r=<resource> and literals that appear multiple times are linked to list_triples_with_object using a Prolog representation of the literal.

This predicate can be hooked using display_link//2.

To be done
- Make it easier to determine the format of the label
- Allow linking to different handlers.
  218rdf_link(R) -->
  219	rdf_link(R, []).
  220
  221rdf_link(R, Options) -->
  222	cliopatria:display_link(R, Options), !.
  223rdf_link(R, Options) -->
  224	{ atom(R), !,
  225	  resource_link(R, HREF),
  226	  (   rdf(R, _, _)
  227	  ->  Class = r_def
  228	  ;   rdf_graph(R)
  229	  ->  Class = r_graph
  230	  ;   Class = r_undef
  231	  ),
  232	  link_options(Extra, Options)
  233	},
  234	html(a([class(['rdf-r',Class]), href(HREF)|Extra],
  235	       \resource_label(R, Options))).
  236rdf_link(Literal, Options) -->
  237	{ aggregate_all(count, literal_occurrence(Literal, Options), Count),
  238	  Count > 1, !,
  239	  format(string(Title), 'Used ~D times', [Count]),
  240	  term_to_atom(Literal, Atom),
  241	  http_link_to_id(list_triples_with_object, [l=Atom], HREF),
  242	  link_options(Extra, Options)
  243	},
  244	html(a([ class(l_count),
  245		 href(HREF),
  246		 title(Title)
  247	       | Extra
  248	       ],
  249	       \turtle_label(Literal))).
  250rdf_link(Literal, _) -->
  251	turtle_label(Literal).
  252
  253literal_occurrence(Literal, Options) :-
  254	Literal = literal(_), !,
  255	(   option(graph(Graph), Options)
  256	->  rdf_db:rdf(_,_,Literal,Graph)
  257	;   rdf_db:rdf(_,_,Literal)
  258	).
  259:- if(current_predicate(rdf11:rdf/4)).  260literal_occurrence(Literal, Options) :-
  261	(   option(graph(Graph), Options)
  262	->  rdf11:rdf(_,_,Literal,Graph)
  263	;   rdf11:rdf(_,_,Literal)
  264	).
  265:- endif.  266
  267link_options(LinkOptions, Options) :-
  268	option(target(Target), Options), !,
  269	LinkOptions = [target(Target)].
  270link_options([], _).
 resource_link(+URI, -URL) is det
Generate a link to display more information about a resource. The default is to link to the HTTP handler implementing list_resource using the parameter r. See cpa_browse:list_resource/1. This predicate calls the hook resource_link/2, which allows for overruling the default.
  282resource_link(R, HREF) :-
  283	cliopatria:resource_link(R, HREF), !.
  284resource_link(R, HREF) :-
  285	http_link_to_id(list_resource, [r=R], HREF).
  286
  287resource_label(R, Options) -->
  288	{ option(resource_format(Format), Options) }, !,
  289	resource_flabel(Format, R, Options).
  290resource_label(R, Options) -->
  291	turtle_label(R, Options).
  292
  293resource_flabel(plain, R, _) --> !,
  294	html(R).
  295resource_flabel(label, R, Options) --> !,
  296	(   { rdf_display_label(R, Label),
  297	      truncate_text(Label, Show, Options)
  298	    }
  299	->  html([span(class(r_label), Show)])
  300	;   turtle_label(R)
  301	).
  302resource_flabel(nslabel, R, _Options) -->
  303	{ (   rdf_is_bnode(R)
  304	  ->  NS = '_'
  305	  ;   rdf_global_id(NS:_Local, R)
  306	  ->  true
  307	  ;   NS = '?'
  308	  ), !,
  309	  rdf_display_label(R, Label)
  310	},
  311	html([span(class(prefix),NS),':',span(class(r_label),Label)]).
  312resource_flabel(_, R, Options) -->
  313	turtle_label(R, Options)