View source with formatted 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(rdf_label,
   32	  [ rdf_label/2,		% +Resource, -Literal
   33	    rdf_display_label/2,	% +Resource, -Text
   34	    rdf_display_label/3,	% +Resource, +Lang, -Text
   35	    literal_text/2,		% +Literal, -Text
   36	    truncate_atom/3,		% +Atom, -MaxLen -Text
   37	    label_property/1		% ?Property
   38	  ]).   39:- use_module(library(error)).   40:- use_module(library(sgml_write)).   41:- use_module(library(semweb/rdf_db)).   42:- use_module(user(preferences)).   43
   44
   45/** <module> Generate labels for RDF objects
   46
   47This library deals with  a  common   problem  in  RDF applications: show
   48labels for resources and display literals.  There is no clear-cut answer
   49to this problem because there  are  too   many  options.  Think of e.g.,
   50language  preferences,  producing   summaries,    desired   rdfs/owl/...
   51reasoning. Therefore, this library provides the  required APIs a default
   52implementation and hooks that allow for dealing with the above mentioned
   53issues.
   54*/
   55
   56:- multifile
   57	label_property/1,		% ?Resource
   58	label_hook/2,			% +Resource, -Literal
   59	display_label_hook/3.		% +Resource, ?Lang, -Label
   60
   61:- rdf_meta
   62	rdf_label(r,-),
   63	rdf_display_label(r,-),
   64	rdf_display_label(r,?,-),
   65	label_property(r).   66
   67					% this dependency is not ideal ...
   68:- rdf_register_ns(foaf, 'http://xmlns.com/foaf/0.1/').   69
   70%%	label_property(?Property) is nondet.
   71%
   72%	True if Property is  used  to   represent  labels.  The  default
   73%	definition defines SKOS (prefLabel,  altLabel,   DC  (title) and
   74%	rdfs:label. This predicate is defined as =multifile=.
   75
   76label_property(skos:prefLabel).
   77label_property(foaf:name).
   78label_property(dc:title).
   79label_property(rdfs:label).
   80label_property(skos:altLabel).
   81
   82
   83%%	rdf_label(+R, -Label:literal) is nondet.
   84%
   85%	Label is a label for R.  This   predicate  first  calls the hook
   86%	label_hook/2. If this hook fails it produces all property-values
   87%	for the properties  defined  by   label_property/1  that  have a
   88%	literal value.
   89
   90rdf_label(R, Label) :-
   91	(   label_hook(R, Label)
   92	*-> true
   93	;   label_property(P),
   94	    rdf_has(R, P, Label),
   95	    rdf_is_literal(Label)
   96	).
   97
   98
   99%%	rdf_display_label(+R, -Label:atom) is det.
  100%
  101%	Provide a label for R in the   user's  default language. This is
  102%	the same as rdf_display_label(R, _, Label).
  103%
  104%	@see user_preference/2
  105
  106rdf_display_label(R, Label) :-
  107	rdf_display_label(R, _, Label).
  108
  109
  110%%	rdf_display_label(+R, ?Lang, -Label:atom) is det.
  111%
  112%	Label is the preferred label to display   the  resource R in the
  113%	language Lang. As a last resort, this predicates creates a label
  114%	from the URI R.  In that case, Lang is unified with =url=.
  115
  116rdf_display_label(R, Lang, Label) :-
  117	rdf_real_label(R, Lang, Label), !.
  118rdf_display_label(Resource, url, Label) :-
  119	(   after_char(Resource, '#', Local), Local \= ''
  120	->  Label = Local
  121	;   after_char(Resource, '/', Local), Local \= ''
  122	->  Label = Local
  123	;   Label = Resource
  124	).
  125
  126
  127rdf_real_label(R, Lang, Label) :-
  128	display_label_hook(R, Lang, Label), !.
  129rdf_real_label(R, Lang, Label) :-
  130	rdf_is_resource(R),
  131	(   nonvar(Lang), % try fast option first:
  132	    rdf_label(R, literal(lang(Lang, Literal)))
  133	->  true
  134	;   nonvar(Lang),
  135	    % warning: BT over next call is quite expensive when R has labels in many languages:
  136	    rdf_label(R, Literal),
  137	    Literal = literal(lang(L, _)),
  138	    lang_matches(L, Lang)
  139	->  true
  140	;   user_preference(user:lang, literal(Lang)), % try fast option first:
  141	    rdf_label(R, literal(lang(Lang, Literal)))
  142	->  true
  143	;   user_preference(user:lang, literal(Lang)),
  144	    % warning: BT over next call is quite expensive when R has labels in many languages:
  145	    rdf_label(R, Literal),
  146	    Literal = literal(lang(L, _)),
  147	    lang_matches(L, Lang)
  148	->  true
  149	;   rdf_label(R, Literal),
  150	    literal_lang(Literal, Lang),
  151	    var(Lang)
  152	->  true
  153	;   rdf_label(R, Literal),
  154	    literal_lang(Literal, Lang)
  155	->  true
  156	), !,
  157	literal_text(Literal, Label).
  158rdf_real_label(BNode, Lang, Label) :-
  159	rdf_has(BNode, rdf:value, Value),
  160	rdf_real_label(Value, Lang, Label0), !,
  161	format(atom(Label), '[~a..]', Label0).
  162rdf_real_label(Literal, Lang, Label) :-
  163	rdf_is_literal(Literal), !,
  164	literal_lang(Literal, Lang),
  165	literal_text(Literal, Label).
  166
  167after_char(Atom, Char, Rest) :-
  168	State = last(-),
  169	(   sub_atom(Atom, _, _, L, Char),
  170	    nb_setarg(1, State, L),
  171	    fail
  172	;   arg(1, State, L),
  173	    L \== (-)
  174	),
  175	sub_atom(Atom, _, L, 0, Rest).
  176
  177literal_lang(literal(Lang0, _), Lang) :- !,
  178	Lang = Lang0.
  179literal_lang(_, _).
  180
  181%%	literal_text(+Object, -Text:atom) is semidet.
  182%
  183%	Text is the textual content of Object. Fails if Object is not an
  184%	RDF literal (term literal(Value)). If   Object is an XMLLiteral,
  185%	Text is unified with the XML-text.
  186%
  187%	@error instantiation_error if Object is not ground
  188
  189literal_text(X, _) :-
  190	\+ ground(X), !, !,
  191	instantiation_error(X).
  192literal_text(literal(L), Text) :- !,
  193	literal_text(L, Text).
  194literal_text(type(Type, Value), Text) :- !,
  195	typed_text(Type, Value, Text).
  196literal_text(lang(_, Text), Text) :- !.
  197literal_text(Text, Text).
  198
  199:- rdf_meta
  200	typed_text(r, +, -).  201
  202typed_text(_, Value, Text) :-
  203	atom(Value), !,
  204	Text = Value.
  205typed_text(rdfs:'XMLLiteral', Value, Text) :-
  206	xml_is_dom(Value), !,
  207	with_output_to(atom(Text),
  208		       xml_write(current_output, Value,
  209				 [ header(false),
  210				   layout(false)
  211				 ])).
  212typed_text(_, Value, Text) :-
  213	format(atom(Text), '~w', [Value]).
  214
  215%%	truncate_atom(+Atom, +MaxLen, -Truncated) is det.
  216%
  217%	If Atom is longer than MaxLen, truncate  it. If MaxLen is =inf=,
  218%	Truncated is unified with Atom.
  219
  220truncate_atom(Atom, inf, All) :- !,
  221	All = Atom.
  222truncate_atom(Atom, MaxLen, Truncated) :-
  223	atom_length(Atom, Len),
  224	(   Len =< MaxLen
  225	->  Truncated = Atom
  226	;   TLen is max(3, MaxLen-4),
  227	    sub_atom(Atom, 0, TLen, _, S0),
  228	    atom_concat(S0, ' ...', Truncated)
  229	).
  230
  231		 /*******************************
  232		 *	      SANDBOX		*
  233		 *******************************/
  234
  235:- multifile
  236	sandbox:safe_primitive/1.  237
  238sandbox:safe_primitive(rdf_label:typed_text(_,_,_))