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@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2010-2018, University of Amsterdam,
    7                              VU University Amsterdam,
    8                              CWI, Amsterdam
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(rdf_label,
   38          [ rdf_label/2,                % +Resource, -Literal
   39            rdf_display_label/2,        % +Resource, -Text
   40            rdf_display_label/3,        % +Resource, +Lang, -Text
   41            literal_text/2,             % +Literal, -Text
   42            truncate_atom/3,            % +Atom, -MaxLen -Text
   43            label_property/1            % ?Property
   44          ]).   45:- use_module(library(semweb/rdf_db)).   46:- use_module(library(semweb/rdf11), [rdf_lexical_form/2]).   47:- use_module(user(preferences)).

Generate labels for RDF objects

This library deals with a common problem in RDF applications: show labels for resources and display literals. There is no clear-cut answer to this problem because there are too many options. Think of e.g., language preferences, producing summaries, desired rdfs/owl/... reasoning. Therefore, this library provides the required APIs a default implementation and hooks that allow for dealing with the above mentioned issues. */

   61:- multifile
   62    label_property/1,               % ?Resource
   63    label_hook/2,                   % +Resource, -Literal
   64    display_label_hook/3.           % +Resource, ?Lang, -Label
   65
   66:- rdf_meta
   67    rdf_label(r,-),
   68    rdf_display_label(r,-),
   69    rdf_display_label(r,?,-),
   70    label_property(r).   71
   72                                        % this dependency is not ideal ...
   73:- rdf_register_ns(foaf, 'http://xmlns.com/foaf/0.1/').
 label_property(?Property) is nondet
True if Property is used to represent labels. The default definition defines SKOS (prefLabel, altLabel, DC (title) and rdfs:label. This predicate is defined as multifile.
   81label_property(skos:prefLabel).
   82label_property(foaf:name).
   83label_property(dc:title).
   84label_property(rdfs:label).
   85label_property(skos:altLabel).
 rdf_label(+R, -Label:literal) is nondet
Label is a label for R. This predicate first calls the hook label_hook/2. If this hook fails it produces all property-values for the properties defined by label_property/1 that have a literal value.
   95rdf_label(R, Label) :-
   96    (   label_hook(R, Label)
   97    *-> true
   98    ;   label_property(P),
   99        rdf_has(R, P, Label),
  100        rdf_is_literal(Label)
  101    ).
 rdf_display_label(+R, -Text:text) is det
Provide a label for R in the user's default language. This is the same as rdf_display_label(R, _, Label).
See also
- user_preference/2
  112rdf_display_label(R, Label) :-
  113    rdf_display_label(R, _, Label).
 rdf_display_label(+R, ?Lang, -Text:text) is det
Label is the preferred label to display the resource R in the language Lang. As a last resort, this predicates creates a label from the URI R. In that case, Lang is unified with url.
  121rdf_display_label(R, Lang, Label) :-
  122    rdf_real_label(R, Lang, Label),
  123    !.
  124rdf_display_label(Resource, url, String) :-
  125    (   after_char(Resource, '#', Local), Local \= ''
  126    ->  Label = Local
  127    ;   after_char(Resource, '/', Local), Local \= ''
  128    ->  Label = Local
  129    ;   Label = Resource
  130    ),
  131    atom_string(Label, String).
  132
  133
  134rdf_real_label(R, Lang, Label) :-
  135    % first compute label based on user-defined hook
  136    display_label_hook(R, Lang, Label),
  137    !.
  138rdf_real_label(R, Lang, Label) :-
  139    % compute label in given language Lang
  140    nonvar(Lang),
  141    rdf_is_resource(R),
  142    (   rdf_label(R, literal(lang(Lang, Label))) % Try fast option first
  143    ->  true
  144    ;   rdf_label(R, Literal),    % warning: BT over next call is expensive when R has labels in many languages:
  145        Literal = literal(lang(Lang0, Label)),
  146        lang_matches(Lang0, Lang)
  147    ),
  148    !.
  149    % literal_text(Literal, Label). % redundant? fails on string/atom mismatch in old and new Labels
  150
  151rdf_real_label(R, Lang, Label) :-
  152    % compute label in user prefered language if Lang not given
  153    var(Lang),
  154    rdf_is_resource(R),
  155    user_preference(user:lang, literal(Lang)),
  156    rdf_real_label(R, Lang, Label).
  157
  158
  159rdf_real_label(R, Lang, Label) :-
  160    % compute label in any language, unify this language with Lang
  161    var(Lang),
  162    rdf_is_resource(R),
  163    rdf_label(R, Literal),
  164    literal_lang(Literal, Lang),
  165    literal_text(Literal, Label).
  166
  167rdf_real_label(BNode, Lang, Label) :-
  168    rdf_has(BNode, rdf:value, Value),
  169    rdf_real_label(Value, Lang, Label0),
  170    !,
  171    format(atom(Label), '[~a..]', Label0).
  172rdf_real_label(Literal, Lang, Label) :-
  173    rdf_is_literal(Literal),
  174    !,
  175    literal_lang(Literal, Lang),
  176    literal_text(Literal, Label).
  177
  178after_char(Atom, Char, Rest) :-
  179    State = last(-),
  180    (   sub_atom(Atom, _, _, L, Char),
  181        nb_setarg(1, State, L),
  182        fail
  183    ;   arg(1, State, L),
  184        L \== (-)
  185    ),
  186    sub_atom(Atom, _, L, 0, Rest).
  187
  188literal_lang(literal(Lang0, _), Lang) :-
  189    !,
  190    Lang = Lang0.
  191
  192literal_lang(literal(lang(Lang0, _)), Lang) :-
  193    !,
  194    Lang = Lang0.
  195
  196literal_lang(_, _).
 literal_text(++Object, -Text:text) is semidet
Text is the textual content of Object. Fails if Object is not an RDF literal (term literal(Value)). If Object is an XMLLiteral, Text is unified with the XML-text.
Errors
- instantiation_error if Object is not ground
  206literal_text(Literal, Text) :-
  207    ground(Literal),
  208    (   atom(Literal)
  209    ->  Text = Literal
  210    ;   string(Literal)
  211    ->  Text = Literal
  212    ;   rdf_lexical_form(Literal, Lexical),
  213        (   Lexical = @(Text, _Lang)
  214        ->  true
  215        ;   Lexical = ^^(Text, _Type)
  216        )
  217    ).
 truncate_atom(+Atom, +MaxLen, -Truncated) is det
If Atom is longer than MaxLen, truncate it. If MaxLen is inf, Truncated is unified with Atom.
  224truncate_atom(Atom, inf, All) :-
  225    !,
  226    All = Atom.
  227truncate_atom(Atom, MaxLen, Truncated) :-
  228    atom_length(Atom, Len),
  229    (   Len =< MaxLen
  230    ->  Truncated = Atom
  231    ;   TLen is max(3, MaxLen-4),
  232        sub_atom(Atom, 0, TLen, _, S0),
  233        atom_concat(S0, ' ...', Truncated)
  234    ).
  235
  236                 /*******************************
  237                 *            SANDBOX           *
  238                 *******************************/
  239
  240:- multifile
  241    sandbox:safe_primitive/1.  242
  243sandbox:safe_primitive(rdf_label:literal_text(_,_))