35
   36:- module(cp_label,
   37          [ turtle_label//1,               38            rdf_link//1,                   39            rdf_link//2,                   40            resource_link/2                41          ]).   42:- use_module(library(error)).   43:- use_module(library(option)).   44:- use_module(library(sgml)).   45:- use_module(library(sgml_write)).   46:- use_module(library(aggregate)).   47:- use_module(library(semweb/rdf_db)).   48:- use_module(library(semweb/rdf_label)).   49:- use_module(library(http/html_write)).   50:- use_module(library(http/http_dispatch)).   51:- if(exists_source(library(semweb/rdf11))).   52:- use_module(library(semweb/rdf11), [rdf_lexical_form/2]).   53:- endif.   54
   55:- use_module(cliopatria(hooks)).   56
   63
   64
   71
   72turtle_label(R) -->
   73    turtle_label(R, []).
   74
   75turtle_label(R, _) -->
   76    { atom(R),
   77      rdf_global_id(NS:Local, R), !
   78    },
   79    html([span(class(prefix), NS), ':', span(class(local), Local)]).
   80turtle_label(R, Options) -->
   81    { atom(R),
   82      rdf_display_label(R, Lang, LabelText),
   83      Lang \== url,
   84      LabelText \== '',
   85      truncate_text(LabelText, Show, Options)
   86    },
   87    html(Show).
   88turtle_label(R, Options) -->
   89    { rdf_is_bnode(R) },
   90    bnode_label(R, Options),
   91    !.
   92turtle_label(R, _) -->
   93    { atom(R) },
   94    !,
   95    html(['<',R,'>']).
   96turtle_label(literal(Lit), Options) -->
   97    !,
   98    literal_label(Lit, Options).
   99turtle_label(@(String,Lang), Options) -->
  100    !,
  101    literal_label(lang(Lang, String), Options).
  102:- if(current_predicate(rdf_lexical_form/2)).  103turtle_label(^^(Value,Type), Options) -->
  104    !,
  105    (   {rdf_equal(Type, xsd:string)}
  106    ->  literal_label(type(Type, Value), Options)
  107    ;   {rdf_lexical_form(^^(Value,Type), ^^(String,_))},
  108        literal_label(type(Type, String), Options)
  109    ).
  110:- endif.  111
  112literal_label(type(Type, Value), Options) -->
  113    !,
  114    { truncate_text(Value, Show, Options) },
  115    html(span(class(literal),
  116              [span(class(oquote), '"'), span(class(l_text), Show), span(class(cquote), '"'),
  117               span(class(l_type), '^^'), \turtle_label(Type)])).
  118literal_label(lang(Lang, Value), Options) -->
  119    !,
  120    { truncate_text(Value, Show, Options) },
  121    html(span(class(literal),
  122              [span(class(oquote), '"'), span(class(l_text), Show), span(class(cquote), '"'),
  123               span(class(l_lang), '@'), span(class(lang), Lang)])).
  124literal_label(Value, Options) -->
  125    { truncate_text(Value, Show, Options) },
  126    html(span(class(literal),
  127              [span(class(oquote), '"'), span(class(l_text), Show), span(class(cquote), '"')])).
  128
  129truncate_text(Text, Text, []) :- !.
  130truncate_text(Text, Truncated, Options) :-
  131    option(max_length(Len), Options),
  132    !,
  133    truncate_atom(Text, Len, Truncated).
  134truncate_text(Text, Text, _).
  135
  136
  148
  149bnode_label(R, _) -->
  150    cliopatria:bnode_label(R),
  151    !.
  152bnode_label(R, Options) -->
  153    { rdf_has(R, rdf:value, Value),
  154      (   Value = literal(_)
  155      ;   \+ rdf_is_bnode(Value)
  156      )
  157    },
  158    !,
  159    html(span([ class(rdf_bnode),
  160                title('RDF bnode using rdf:value')
  161              ],
  162              ['[', \turtle_label(Value, Options), '...]'])).
  163bnode_label(R, Options) -->
  164    { rdf_collection_list(R, List),
  165      !,
  166      length(List, Len),
  167      format(string(Title), 'RDF collection with ~D members', Len)
  168    },
  169    html(span([ class(rdf_list),
  170                title(Title)
  171              ],
  172              ['(', \collection_members(List, 0, Len, 5, Options), ')'])).
  173
  174collection_members([], _, _, _, _) --> [].
  175collection_members(_, Max, Total, Max, _) -->
  176    !,
  177    { Left is Total - Max },
  178    html('... ~D more'-[Left]).
  179collection_members([H|T], I, Total, Max, Options) -->
  180    turtle_label(H, Options),
  181    (   { T == [] }
  182    ->  []
  183    ;   html(','),
  184        { I2 is I + 1 },
  185        collection_members(T, I2, Total, Max, Options)
  186    ).
  187
  188
  189rdf_collection_list(R, []) :-
  190    rdf_equal(rdf:nil, R),
  191    !.
  192rdf_collection_list(R, [H|T]) :-
  193    rdf_has(R, rdf:first, H),
  194    rdf_has(R, rdf:rest, RT),
  195    rdf_collection_list(RT, T).
  196
  197
  235
  236rdf_link(R) -->
  237    rdf_link(R, []).
  238
  239rdf_link(R, Options) -->
  240    cliopatria:display_link(R, Options),
  241    !.
  242rdf_link(R, Options) -->
  243    { atom(R),
  244      !,
  245      resource_link(R, HREF),
  246      (   rdf(R, _, _)
  247      ->  Class = r_def
  248      ;   rdf_graph(R)
  249      ->  Class = r_graph
  250      ;   Class = r_undef
  251      ),
  252      link_options(Extra, Options)
  253    },
  254    html(a([class(['rdf-r',Class]), href(HREF)|Extra],
  255           \resource_label(R, Options))).
  256rdf_link(Literal, Options) -->
  257    { aggregate_all(count, literal_occurrence(Literal, Options), Count),
  258      Count > 1,
  259      !,
  260      format(string(Title), 'Used ~D times', [Count]),
  261      term_to_atom(Literal, Atom),
  262      http_link_to_id(list_triples_with_object, [l=Atom], HREF),
  263      link_options(Extra, Options)
  264    },
  265    html(a([ class(l_count),
  266             href(HREF),
  267             title(Title)
  268           | Extra
  269           ],
  270           \turtle_label(Literal))).
  271rdf_link(Literal, _) -->
  272    turtle_label(Literal).
  273
  274literal_occurrence(Literal, Options) :-
  275    Literal = literal(_),
  276    !,
  277    (   option(graph(Graph), Options)
  278    ->  rdf_db:rdf(_,_,Literal,Graph)
  279    ;   rdf_db:rdf(_,_,Literal)
  280    ).
  281:- if(current_predicate(rdf11:rdf/4)).  282literal_occurrence(Literal, Options) :-
  283    (   option(graph(Graph), Options)
  284    ->  rdf11:rdf(_,_,Literal,Graph)
  285    ;   rdf11:rdf(_,_,Literal)
  286    ).
  287:- endif.  288
  289link_options(LinkOptions, Options) :-
  290    option(target(Target), Options),
  291    !,
  292    LinkOptions = [target(Target)].
  293link_options([], _).
  294
  295
  304
  305resource_link(R, HREF) :-
  306    cliopatria:resource_link(R, HREF),
  307    !.
  308resource_link(R, HREF) :-
  309    http_link_to_id(list_resource, [r=R], HREF).
  310
  311resource_label(R, Options) -->
  312    { debug(rdf(label), 'resource_label(~p,~p)',
  313            [R, Options]),
  314      option(resource_format(Format), Options)
  315    },
  316    !,
  317    resource_flabel(Format, R, Options).
  318resource_label(R, Options) -->
  319    turtle_label(R, Options).
  320
  321resource_flabel(plain, R, _) -->
  322    !,
  323    html(R).
  324resource_flabel(label, R, Options) -->
  325    !,
  326    (   { rdf_display_label(R, Label),
  327          truncate_text(Label, Show, Options)
  328        }
  329    ->  html([span(class(r_label), Show)])
  330    ;   turtle_label(R)
  331    ).
  332resource_flabel(nslabel, R, _Options) -->
  333    { (   rdf_is_bnode(R)
  334      ->  NS = '_'
  335      ;   rdf_global_id(NS:_Local, R)
  336      ->  true
  337      ;   NS = '?'
  338      ),
  339      !,
  340      rdf_display_label(R, Label)
  341    },
  342    html([span(class(prefix),NS),':',span(class(r_label),Label)]).
  343resource_flabel(_, R, Options) -->
  344    turtle_label(R, Options)