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, VU University Amsterdam
    7                              CWI, Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(cpa_browse,
   37          [ graph_info//1,              % +Graph
   38            graph_as_resource//2,       % +Graph, +Options
   39            graph_actions//1,           % +Graph
   40            list_resource//2,           % +URI, +Options
   41            context_graph//2            % +URI, +Options
   42          ]).   43:- use_module(library(http/http_dispatch)).   44:- use_module(library(http/http_parameters)).   45:- use_module(library(http/html_write)).   46:- use_module(library(http/js_write)).   47:- use_module(library(http/html_head)).   48:- use_module(library(http/http_wrapper)).   49:- use_module(library(http/yui_resources)).   50:- use_module(library(http/http_path)).   51:- use_module(library(http/cp_jquery)).   52
   53:- use_module(library(semweb/rdf_db)).   54:- use_module(library(semweb/rdfs)).   55:- use_module(library(semweb/rdf_litindex)).   56:- use_module(library(semweb/rdf_persistency)).   57
   58:- use_module(library(aggregate)).   59:- use_module(library(lists)).   60:- use_module(library(pairs)).   61:- use_module(library(debug)).   62:- use_module(library(option)).   63:- use_module(library(apply)).   64:- use_module(library(settings)).   65
   66:- use_module(components(label)).   67:- use_module(components(simple_search)).   68:- use_module(components(graphviz)).   69:- use_module(components(basics)).   70:- use_module(api(lod_crawler)).   71:- use_module(api(sesame)).   72:- use_module(library(semweb/rdf_abstract)).   73:- use_module(library(semweb/rdf_label)).   74
   75:- use_module(user(user_db)).

ClioPatria RDF data browser

This module implements basic browsing of an RDF repository. This is not intended to be used as an end-user application, but for the developer to gain insight in the data in the RDF store. That said, the distinction between end-user and developer can be rather vague if we consider `back-office' applications. To a certain extend, back-office applications are considered within the scope of this module and therefore it provides several hooks and defines several `components' that allow back-office applications to reuse this infrastructure.

See also
- cliopatria(hooks) for available hooks. */
   92                 /*******************************
   93                 *            PATHS             *
   94                 *******************************/
   95
   96:- http_handler(rdf_browser(.),
   97                http_404([index(list_graphs)]),
   98                [spawn(cliopatria), prefix]).   99:- http_handler(rdf_browser(list_graphs),     list_graphs,     []).  100:- http_handler(rdf_browser(list_graph),      list_graph,      []).  101:- http_handler(rdf_browser(list_classes),    list_classes,    []).  102:- http_handler(rdf_browser(list_instances),  list_instances,  []).  103:- http_handler(rdf_browser(list_predicates), list_predicates, []).  104:- http_handler(rdf_browser(list_predicate_resources),
  105                                              list_predicate_resources, []).  106:- http_handler(rdf_browser(list_resource),   list_resource,   []).  107:- http_handler(rdf_browser(list_triples),    list_triples,    []).  108:- http_handler(rdf_browser(list_triples_with_object),
  109                                              list_triples_with_object, []).  110:- http_handler(rdf_browser(list_triples_with_literal),
  111                                              list_triples_with_literal, []).  112
  113:- http_handler(rdf_browser(list_prefixes),   list_prefixes,   []).  114:- http_handler(rdf_browser(search),          search,          []).  115:- http_handler(rdf_browser(multigraph_action), multigraph_action,
  116                [ time_limit(infinite) ]).  117
  118
  119:- meta_predicate
  120    table_rows(3, +, ?, ?),
  121    table_rows_top_bottom(3, +, +, +, ?, ?),
  122    html_property_table(?, 0, ?, ?).
 list_graphs(+Request)
Display a page holding a table with all RDF graphs. The graphs are sorted to the number of triples.
  129list_graphs(_Request) :-
  130    findall(Count-Graph,
  131            (   rdf_graph(Graph),
  132                graph_triples(Graph, Count)
  133            ),
  134            Pairs),
  135    keysort(Pairs, Sorted),
  136    pairs_values(Sorted, UpCount),
  137    reverse(UpCount, DownCount),
  138    append(DownCount, [virtual(total)], Rows),
  139    reply_html_page(cliopatria(default),
  140                    title('RDF Graphs'),
  141                    [ h1('Named graphs in the RDF store'),
  142                      \warn_volatile,
  143                      \graph_table(Rows, [])
  144                    ]).
  145
  146:- if(current_predicate(rdf_persistency_property/1)).  147warn_volatile -->
  148    { rdf_persistency_property(access(read_only)),
  149      !,
  150      rdf_persistency_property(directory(Dir))
  151    },
  152    html(div(class(msg_warning),
  153             [ 'WARNING: The persistent store ', code(Dir), ' was loaded in ',
  154               b('read-only'), ' mode.  All changes will be lost when ',
  155               'the server is stopped.'
  156             ])).
  157:- endif.  158warn_volatile --> [].
  159
  160:- if((rdf_version(V),V>=30000)).  161graph_triples(Graph, Count) :-
  162    rdf_statistics(triples_by_graph(Graph, Count)).
  163:- else.  164graph_triples(Graph, Count) :-                  % RDF-DB < 3.0
  165    rdf_statistics(triples_by_file(Graph, Count)).
  166:- endif.  167
  168graph_table(Graphs, Options) -->
  169    { option(top_max(TopMax), Options, 500),
  170      option(top_max(BottomMax), Options, 500),
  171      http_link_to_id(multigraph_action, [], Action),
  172      graph_actions(Options, ActionOptions)
  173    },
  174    html_requires(css('rdf.css')),
  175    html(form([ action(Action),
  176                class('graph-table')
  177              ],
  178              [ table(class(block),
  179                      [ \graph_table_header
  180                      | \table_rows_top_bottom(
  181                             graph_row(ActionOptions), Graphs,
  182                             TopMax, BottomMax)
  183                      ]),
  184                \multigraph_actions(ActionOptions)
  185              ])),
  186    mgraph_action_script.
  187
  188graph_table_header -->
  189    html(tr([ th('RDF Graph'),
  190              th('Triples'),
  191              th('Modified'),
  192              th('Persistency')
  193            ])).
  194
  195graph_row(_, virtual(total)) -->
  196    !,
  197    { rdf_statistics(triples(Count))
  198    },
  199    html([ th(class(total), 'Total #triples:'),
  200           \nc('~D', Count, [class(total)]),
  201           td([],[]),  % Empty cell for persistency column
  202           td([],[])   % Empty cell for modified column
  203         ]).
  204graph_row(Options, Graph) -->
  205    { graph_triples(Graph, Count)
  206
  207    },
  208    html([ td(\graph_link(Graph)),
  209           \nc('~D', Count),
  210           \modified(Graph),
  211           td(style('text-align:center'), \persistency(Graph)),
  212           \graph_checkbox(Graph, Options)
  213         ]).
  214
  215modified(Graph) -->
  216    { rdf_graph_property(Graph, source_last_modified(Time)),
  217      format_time(string(Modified), '%+', Time), !
  218    },
  219    html(td([class('file-time')], Modified)).
  220modified(Graph) -->
  221    { rdf_journal_file(Graph, File),
  222      time_file(File, Time),
  223      format_time(string(Modified), '%+', Time)
  224    },
  225    html(td([class('file-time')], Modified)).
  226modified(_Graph) -->
  227    html(td([class('file-time')], '')).
  228
  229graph_link(Graph) -->
  230    { http_link_to_id(list_graph, [graph=Graph], URI)
  231    },
  232    html(a(href(URI), Graph)).
  233
  234persistency(Graph) -->
  235    { rdf_graph_property(Graph, persistent(true)) },
  236    !,
  237    snapshot(Graph),
  238    journal(Graph).
  239persistency(_) -->
  240    { http_absolute_location(icons('volatile.png'), Img, [])
  241    },
  242    html(img([ class('in-text'),
  243               title('Graph is not persistent'),
  244               src(Img)
  245             ])).
  246
  247snapshot(Graph) -->
  248    { rdf_snapshot_file(Graph, _),
  249      http_absolute_location(icons('snapshot.png'), Img, [])
  250    },
  251    html(img([ class('in-text'),
  252               title('Graph has persistent snapshot'),
  253               src(Img)
  254             ])).
  255snapshot(_) --> [].
  256
  257journal(Graph) -->
  258    { rdf_journal_file(Graph, _),
  259      http_absolute_location(icons('journal.png'), Img, [])
  260    },
  261    html(img([ class('in-text'),
  262               title('Graph has a journal'),
  263               src(Img)
  264             ])).
  265journal(_) --> [].
 graph_actions(+Options0, -Options)
 multigraph_actions(+Options)
Deal with actions on multiple graphs.
  272graph_actions(Options, [show_actions(true)|Options]) :-
  273    logged_on(User),
  274    !,
  275    catch(check_permission(User, write(_, unload(user))), _, fail),
  276    !.
  277graph_actions(Options, Options).
  278
  279graph_checkbox(Graph, Options) -->
  280    { option(show_actions(true), Options) },
  281    !,
  282    html(td(class('no-border'),
  283            input([type(checkbox),name(graph),value(Graph),
  284                   class('graph-select')]))).
  285graph_checkbox(_, _) --> [].
  286
  287multigraph_actions(Options) -->
  288    { option(show_actions(true), Options),
  289      !,
  290      findall(Action-Format,
  291              clause(graph_action(Action,Format,_), _),
  292              Pairs)
  293    },
  294    html([ ul([ class('multi-graph-actions')
  295              ],
  296              \li_graph_actions(Pairs))
  297         ]).
  298multigraph_actions(_) --> [].
  299
  300li_graph_actions([]) --> [].
  301li_graph_actions([H|T]) --> li_graph_action(H), li_graph_actions(T).
  302
  303li_graph_action(Action-Format) -->
  304    { atomic_list_concat([Pre,Post], '~w', Format) },
  305    html(li([ Pre,
  306              input([ type(submit), name(action), value(Action) ]),
  307              Post
  308            ])).
  309
  310mgraph_action_script -->
  311    html_requires(jquery),
  312    js_script({|javascript||
  313function showActions(time) {
  314  if ( time === undefined ) time = 400;
  315  var val = [];
  316  $('.graph-table :checkbox:checked').each(function(i) {
  317    val[i] = $(this).val();
  318  });
  319  if ( val.length == 0 )
  320    $(".multi-graph-actions").hide(time);
  321  else
  322    $(".multi-graph-actions").show(time);
  323}
  324
  325$(function() {
  326  showActions(0);
  327  $(".graph-table .graph-select").on('click', showActions);
  328});
  329              |}).
 multigraph_action(Request)
HTTP Handler for user actions on multiple graphs.
  335multigraph_action(Request) :-
  336    findall(Action, clause(graph_action(Action,_,_), _), Actions),
  337    http_parameters(Request,
  338                    [ graph(Graphs, [list(atom)]),
  339                      action(Action, [oneof(Actions)])
  340                    ]),
  341    clause(graph_action(Action,Format,_), _),
  342    api_action(Request, multigraph_action(Action, Graphs), html,
  343               Format-[Action]).
  344
  345multigraph_action(Action, Graphs) :-
  346    forall(member(Graph, Graphs),
  347           ( print_message(informational,
  348                           format('Processing ~w ...', [Graph])),
  349             graph_action(Action, _, Graph))).
  350
  351graph_action('Delete', '~w selected graphs', Graph) :-
  352    rdf_unload_graph(Graph).
  353graph_action(volatile, 'Make selected graphs ~w', Graph) :-
  354    rdf_persistency(Graph, false).
  355graph_action(persistent, 'Make selected graphs ~w', Graph) :-
  356    rdf_persistency(Graph, true).
  357graph_action('Merge journals', '~w for selected graphs', Graph) :-
  358    rdf_flush_journals([graph(Graph)]).
 list_graph(+Request)
HTTP handler that provides information about an individual RDF graph. The output is an HTML table.
  366list_graph(Request) :-
  367    http_parameters(Request,
  368                    [ graph(Graph,
  369                            [description('Name of the graph to describe')])
  370                    ]),
  371    (   rdf_graph(Graph)
  372    ->  true
  373    ;   http_404([], Request)
  374    ),
  375    reply_html_page(cliopatria(default),
  376                    title('RDF Graph ~w'-[Graph]),
  377                    [ h1('Summary information for graph "~w"'-[Graph]),
  378                      \simple_search_form([ id(ac_find_in_graph),
  379                                            filter(graph(Graph)),
  380                                            label('Search this graph')
  381                                          ]),
  382                      \graph_info(Graph),
  383                      \graph_as_resource(Graph, []),
  384                      \graph_persistency(Graph),
  385                      \graph_actions(Graph),
  386                      \uri_info(Graph, Graph)
  387                    ]).
 graph_info(+Graph)//
HTML component that shows -statistical- properties about the given named graph.
  394graph_info(Graph) -->
  395    html_property_table(row(P,V),
  396                        graph_property(Graph,P,V)).
  397
  398:- dynamic
  399    graph_property_cache/3.  400
  401graph_property(Graph, P, V) :-
  402    graph_property_cache(Graph, MD5, Pairs),
  403    rdf_md5(Graph, MD5),
  404    !,
  405    member(P0-V, Pairs),
  406    P =.. [P0,Graph].
  407graph_property(Graph, P, V) :-
  408    retractall(graph_property_cache(Graph, _, _)),
  409    findall(P-V, graph_property_nc(Graph, P, V), Pairs),
  410    rdf_md5(Graph, MD5),
  411    assert(graph_property_cache(Graph, MD5, Pairs)),
  412    member(P0-V, Pairs),
  413    P =.. [P0,Graph].
  414
  415graph_property_nc(Graph, source, Source) :-
  416    rdf_source(Graph, Source).
  417graph_property_nc(Graph, triples, int(Triples)) :-
  418    graph_triples(Graph, Triples).
  419graph_property_nc(Graph, predicate_count, int(Count)) :-
  420    aggregate_all(count, predicate_in_graph(Graph, _P), Count).
  421graph_property_nc(Graph, subject_count, int(Count)) :-
  422    aggregate_all(count, subject_in_graph(Graph, _P), Count).
  423graph_property_nc(Graph, bnode_count, int(Count)) :-
  424    aggregate_all(count, bnode_in_graph(Graph, _P), Count).
  425graph_property_nc(Graph, type_count, int(Count)) :-
  426    aggregate_all(count, type_in_graph(Graph, _P), Count).
  427
  428predicate_in_graph(Graph, P) :-
  429    rdf_current_predicate(P),
  430    once(rdf(_,P,_,Graph)).
 subject_in_graph(+Graph, -Subject)
Generate the distinct subjects in a graph. There are two ways to do this: first the subjects and then whether they appear in the graph or the other way around. At least this has the advantage that we get distinct subjects for free.
  439subject_in_graph(Graph, S) :-
  440    graph_triples(Graph, Count),
  441    rdf_statistics(triples(Total)),
  442    Count * 10 > Total,            % Graph has more than 10% of triples
  443    !,
  444    rdf_subject(S),
  445    once(rdf(S, _, _, Graph)).
  446subject_in_graph(Graph, S) :-
  447    findall(S, rdf(S,_,_,Graph), List),
  448    sort(List, Subjects),
  449    member(S, Subjects).
  450
  451bnode_in_graph(Graph, S) :-
  452    graph_triples(Graph, Count),
  453    rdf_statistics(triples(Total)),
  454    Count * 10 > Total,
  455    !,
  456    rdf_subject(S),
  457    rdf_is_bnode(S),
  458    once(rdf(S, _, _, Graph)).
  459bnode_in_graph(Graph, S) :-
  460    findall(S, (rdf(S,_,_,Graph), rdf_is_bnode(S)), List),
  461    sort(List, Subjects),
  462    member(S, Subjects).
 type_in_graph(+Graph, -Class)
Generate the unique types in Graph
  470:- thread_local
  471    type_seen/1.  472
  473type_in_graph(Graph, Class) :-
  474    call_cleanup(type_in_graph2(Graph, Class),
  475                 retractall(type_seen(_))).
  476
  477type_in_graph2(Graph, Class) :-
  478    subject_in_graph(Graph, S),
  479    (   rdf_has(S, rdf:type, Class)
  480    *-> true
  481    ;   rdf_equal(Class, rdfs:'Resource')
  482    ),
  483    (   type_seen(Class)
  484    ->  fail
  485    ;   assert(type_seen(Class))
  486    ).
 graph_persistency(+Graph)//
Show information about the persistency of the graph
  493graph_persistency(Graph) -->
  494    { rdf_graph_property(Graph, persistent(true)),
  495      (   rdf_journal_file(Graph, _)
  496      ;   rdf_snapshot_file(Graph, _)
  497      )
  498    },
  499    !,
  500    html([ h1('Persistency information'),
  501           table(class(block),
  502                 [ tr([ td(class('no-border'),[]),
  503                        th('File'), th('Size'),th('Modified'),
  504                        td(class('no-border'),[])
  505                      ]),
  506                   \graph_shapshot(Graph),
  507                   \graph_journal(Graph)
  508                 ])
  509         ]).
  510graph_persistency(Graph) -->
  511    { rdf_graph_property(Graph, persistent(true))
  512    },
  513    !,
  514    html([ h1('Persistency information'),
  515           p('The graph has no associated persistency files')
  516         ]).
  517graph_persistency(_Graph) -->
  518    [].
  519
  520graph_shapshot(Graph) -->
  521    { rdf_snapshot_file(Graph, File)
  522    },
  523    html(tr([ th(class('file-role'), 'Snapshot'),
  524              \file_info(File)
  525            ])).
  526graph_shapshot(_) --> [].
  527
  528
  529graph_journal(Graph) -->
  530    { rdf_journal_file(Graph, File)
  531    },
  532    html(tr([ th(class('file-role'), 'Journal'),
  533              \file_info(File),
  534              \flush_journal_button(Graph)
  535            ])).
  536graph_journal(_) --> [].
  537
  538flush_journal_button(Graph) -->
  539    { http_link_to_id(flush_journal, [], HREF)
  540    },
  541    html(td(class('no-border'),
  542            form(action(HREF),
  543                 [ input([type(hidden), name(graph), value(Graph)]),
  544                   input([type(hidden), name(resultFormat), value(html)]),
  545                   input([type(submit), value('Merge journal')])
  546                 ]))).
  547
  548
  549file_info(File) -->
  550    { size_file(File, Size),
  551      time_file(File, Time),
  552      format_time(string(Modified), '%+', Time)
  553    },
  554    html([ td(class('file-name'), File),
  555           td(class('int'), \n(human, Size)),
  556           td(class('file-time'), Modified)
  557         ]).
 graph_actions(+Graph)// is det
Provide a form for basic actions on the graph
  564graph_actions(Graph) -->
  565    html([ h2('Actions'),
  566           ul(class(graph_actions),
  567              [ \li_export_graph(Graph, show),
  568                \li_export_graph(Graph, download),
  569                \li_schema_graph(Graph),
  570                \li_delete_graph(Graph),
  571                \li_persistent_graph(Graph)
  572              ])
  573         ]).
  574
  575li_delete_graph(Graph) -->
  576    { logged_on(User),
  577      catch(check_permission(User, write(_, unload(Graph))), _, fail),
  578      !,
  579      http_link_to_id(unload_graph, [], Action)
  580    },
  581    html(li(form(action(Action),
  582                 [ input([type(hidden), name(graph), value(Graph)]),
  583                   input([type(hidden), name(resultFormat), value(html)]),
  584                   input([class(gaction), type(submit), value('Delete')]),
  585                   ' this graph'
  586                 ]))).
  587li_delete_graph(_) --> [].
  588
  589li_persistent_graph(Graph) -->
  590    { logged_on(User),
  591      catch(check_permission(User, write(_, persistent(Graph))), _, fail),
  592      !,
  593      http_link_to_id(modify_persistency, [], Action),
  594      (   rdf_graph_property(Graph, persistent(true))
  595      ->  Op = (volatile),   Value = off
  596      ;   Op = (persistent), Value = on
  597      )
  598    },
  599    !,
  600    html(li(form(action(Action),
  601                 [ input([type(hidden), name(graph), value(Graph)]),
  602                   input([type(hidden), name(resultFormat), value(html)]),
  603                   input([type(hidden), name(persistent), value(Value)]),
  604                   'Make this graph ',
  605                   input([class(gaction), type(submit), value(Op)])
  606                 ]))).
  607li_persistent_graph(_) --> [].
  608
  609li_schema_graph(Graph) -->
  610    { http_link_to_id(export_graph_schema, [], Action),
  611      download_options(show, Label, MimeType, Title)
  612    },
  613    html(li(form(action(Action),
  614                 [ input([type(hidden), name(graph), value(Graph)]),
  615                   input([type(hidden), name(mimetype), value(MimeType)]),
  616                   'Compute a schema for this graph and ',
  617                   input([class(saction), type(submit), value(Label),
  618                          title(Title)
  619                         ]),
  620                   ' the result as ',
  621                   \dl_format_menu
  622                 ]))).
  623
  624li_export_graph(Graph, How) -->
  625    { http_link_to_id(export_graph, [], Action),
  626      download_options(How, Label, MimeType, Title)
  627    },
  628    html(li(form(action(Action),
  629                 [ input([type(hidden), name(graph), value(Graph)]),
  630                   input([type(hidden), name(mimetype), value(MimeType)]),
  631                   input([class(gaction), type(submit), value(Label),
  632                          title(Title)
  633                         ]),
  634                   ' this graph as ',
  635                   \dl_format_menu
  636                 ]))).
  637
  638download_options(show,     'Show',     'text/plain',
  639                 'Returns graph with MIME-type text/plain, \n\c
  640                  so it will be displayed in your browser').
  641download_options(download, 'Download', default,
  642                 'Return graph with its RDF MIME-type, \n\c
  643                  so most browsers will save it').
  644
  645dl_format_menu -->
  646    html(select(name(format),
  647                [ option([value(turtle),selected],  'Turtle'),
  648                  option([value(canonical_turtle)], 'Canonical Turtle'),
  649                  option([value(rdfxml)],           'RDF/XML')
  650                ])).
 list_classes(+Request)
HTTP handler that lists all classes of all subjects that appear in the named graph. The output is an HTML page holding all referenced classes sorted by their label.
  659list_classes(Request) :-
  660    http_parameters(Request,
  661                    [ graph(Graph, [description('Name of the graph')])
  662                    ]),
  663    types_in_graph(Graph, Map),
  664    sort_pairs_by_label(Map, Sorted),
  665    reply_html_page(cliopatria(default),
  666                    title('Classes in graph ~w'-[Graph]),
  667                    [ h1(['Classes in graph ', \graph_link(Graph)]),
  668                      \class_table(Sorted, Graph, [])
  669                    ]).
  670
  671class_table(Pairs, Graph, Options) -->
  672    { option(top_max(TopMax), Options, 500),
  673      option(top_max(BottomMax), Options, 500)
  674    },
  675    html_requires(css('rdf.css')),
  676    html(table(class(block),
  677               [ \class_table_header
  678               | \table_rows_top_bottom(class_row(Graph), Pairs,
  679                                        TopMax, BottomMax)
  680               ])).
  681
  682class_table_header -->
  683    html(tr([ th('Class'),
  684              th('#Instances')
  685            ])).
  686
  687class_row(Graph, Class) -->
  688    { atom(Class),
  689      !,
  690      findall(I, rdf_has(I, rdf:type, Class, Graph), IL),
  691      sort(IL, Classes),
  692      length(Classes, InstanceCount)
  693    },
  694    class_row(Graph, Class-InstanceCount).
  695class_row(Graph, Class-InstanceCount) -->
  696    { (   var(Graph)
  697      ->  Params = [class(Class)]
  698      ;   Params = [graph(Graph), class(Class)]
  699      ),
  700      http_link_to_id(list_instances, Params, ILink)
  701    },
  702    html([ td(\rdf_link(Class, [role(class)])),
  703           td(class(int), a(href(ILink), InstanceCount))
  704         ]).
 types_in_graph(+Graph, -Map:list(Type-InstanceCount))
Generate a map of all types that appear in Graph with a count on the number of instances.
  711types_in_graph(Graph, Map) :-
  712    findall(S, subject_in_graph(Graph, S), Subjects),
  713    types(Subjects, Pairs),
  714    transpose_pairs(Pairs, TypeSubj),
  715    group_pairs_by_key(TypeSubj, TypeSubjs),
  716    maplist(instance_count, TypeSubjs, Map).
  717
  718types([], []).
  719types([S|T0], Types) :-
  720    call_det(type_of(S,C), Det),
  721    !,
  722    (   Det == true
  723    ->  Types = [S-C|T],
  724        types(T0, T)
  725    ;   findall(C2, type_of(S,C2), Cs),
  726        multi_class(Cs, S, Types, PT),
  727        types(T0, PT)
  728    ).
  729
  730multi_class([], _, Pairs, Pairs).
  731multi_class([H|T], S, [S-H|Pairs], PT) :-
  732    multi_class(T, S, Pairs, PT).
  733
  734
  735type_of(Subject, Type) :-
  736    (   rdf_has(Subject, rdf:type, Type)
  737    *-> true
  738    ;   rdf_equal(Type, rdfs:'Resource')
  739    ).
  740
  741:- meta_predicate
  742    call_det(0, -).  743
  744call_det(G, Det) :-
  745    call(G),
  746    deterministic(Det).
  747
  748instance_count(Type-Instances, Type-Count) :-
  749    length(Instances, Count).
 instance_in_graph(?Graph, ?Class, +Type, -Subject, -PropertyCount) is nondet
True of Subject is an instance of Class with PropertyCount properties provided from Graph.
  757instance_in_graph(Graph, Class, any, S, C) :-
  758    !,
  759    instance_in_graph(Graph, Class, S, C).
  760instance_in_graph(Graph, Class, bnode, S, C) :-
  761    !,
  762    freeze(S, rdf_is_bnode(S)),
  763    instance_in_graph(Graph, Class, S, C).
  764
  765
  766instance_in_graph(Graph, Class, S, C) :-
  767    var(Class),
  768    !,
  769    subject_in_graph(Graph, S),
  770    property_count(Graph, S, C).
  771instance_in_graph(Graph, Class, S, C) :-
  772    rdf_equal(Class, rdfs:'Resource'),
  773    !,
  774    (   rdf_has(S, rdf:type, Class),
  775        once(rdf(S, _, _, Graph))
  776    ;   subject_in_graph(Graph, S),
  777        \+ rdf_has(S, rdf:type, _)
  778    ),
  779    property_count(Graph, S, C).
  780instance_in_graph(Graph, Class, S, C) :-
  781    rdf_has(S, rdf:type, Class),
  782    once(rdf(S, _, _, Graph)),
  783    property_count(Graph, S, C).
  784
  785property_count(Graph, S, Count) :-
  786    aggregate_all(count, rdf(S, _, _, Graph), Count).
 graph_as_resource(+Graph, Options)// is det
Show resource info for a graph if it is described.
  792graph_as_resource(Graph, Options) -->
  793    { (   rdf(Graph, _, _)
  794      ;   rdf(_, Graph, _)
  795      ;   rdf(_, _, Graph)
  796      ), !
  797    },
  798    html([ h2([ 'Local view for "',
  799                \location(Graph, _), '"'
  800              ]),
  801           \local_view(Graph, _, Options)
  802         ]).
  803graph_as_resource(_, _) --> [].
  804
  805
  806                 /*******************************
  807                 *        LIST INSTANCES        *
  808                 *******************************/
 list_instances(+Request)
HTTP handler that lists instances that satisfy certain criteria.
  814list_instances(Request) :-
  815    http_parameters(Request,
  816                    [ class(Class,
  817                            [ optional(true),
  818                              description('Limit to instances of this class')
  819                            ]),
  820                      graph(Graph,
  821                            [ optional(true),
  822                              description('Limit to have at least \c
  823                                               one property in graph')
  824                            ]),
  825                      type(Type,
  826                           [ oneof([any, bnode]),
  827                             default(any),
  828                             description('Any instance or only bnodes?')
  829                           ]),
  830                      resource_format(Format,
  831                            [ default(DefaultFormat),
  832                              atom,
  833                              description('Display format as passed to rdf_link//2 ')
  834                            ]),
  835                      sortBy(Sort,
  836                             [ oneof([label,properties]),
  837                               default(label),
  838                               description('How to sort the result-table')
  839                             ])
  840                    ]),
  841    setting(resource_format, DefaultFormat),
  842    findall(I-PC, instance_in_graph(Graph, Class, Type, I, PC), IPairs),
  843    sort_pairs_by_label(IPairs, TableByName),
  844    (   Sort == properties
  845    ->  reverse(TableByName, RevTableByName),
  846        transpose_pairs(RevTableByName, FPairsUp),
  847        reverse(FPairsUp, FPairsDown),
  848        flip_pairs(FPairsDown, Table)
  849    ;   Table = TableByName
  850    ),
  851
  852    reply_html_page(cliopatria(default),
  853                    title(\instance_table_title(Graph, Class, Sort)),
  854                    [ h1(\html_instance_table_title(Graph, Class, Sort)),
  855                      \instance_table(Table, [resource_format(Format)])
  856                    ]).
  857
  858instance_table_title(Graph, Class, Sort) -->
  859    { var(Class) },
  860    !,
  861    html('Instances in ~w sorted by ~w'-
  862         [Graph, Sort]).
  863instance_table_title(Graph, Class, Sort) -->
  864    { rdf_display_label(Class, Label) },
  865    html('Instances of ~w in ~w sorted by ~w'-
  866         [Label, Graph, Sort]).
  867
  868html_instance_table_title(Graph, Class, Sort) -->
  869    html([ 'Instances',
  870           \of_class(Class),
  871           \in_graph(Graph),
  872           \sorted_by(Sort)
  873         ]).
  874
  875of_class(Class) -->
  876    { var(Class) },
  877    !.
  878of_class(Class) -->
  879    html([' of class ', \rdf_link(Class, [role(class)])]).
  880
  881in_graph(Graph) -->
  882    { var(Graph) },
  883    !.
  884in_graph(Graph) -->
  885    html([' in graph ', \graph_link(Graph)]).
  886
  887sorted_by(Sort) -->
  888    html(' sorted by ~w'-[Sort]).
  889
  890
  891instance_table(Pairs, Options) -->
  892    { option(top_max(TopMax), Options, 500),
  893      option(top_max(BottomMax), Options, 500)
  894    },
  895    html_requires(css('rdf.css')),
  896    html(table(class(block),
  897               [ \instance_table_header
  898               | \table_rows_top_bottom(instance_row(Options), Pairs,
  899                                        TopMax, BottomMax)
  900               ])).
  901
  902instance_table_header -->
  903    html(tr([ th('Instance'),
  904              th('#Properties')
  905            ])).
  906
  907instance_row(Options, R-C) -->
  908    html([ td(\rdf_link(R, [role(inst)|Options])),
  909           td(class(int), C)
  910         ]).
  911
  912
  913                 /*******************************
  914                 *           PREDICATES         *
  915                 *******************************/
 list_predicates(+Request)
List all predicates used in graph, sorted by label.
  921list_predicates(Request) :-
  922    http_parameters(Request,
  923                    [ graph(Graph, [])
  924                    ]),
  925    findall(Pred, predicate_in_graph(Graph, Pred), Preds),
  926    sort_by_label(Preds, Sorted),
  927    reply_html_page(cliopatria(default),
  928                    title('Predicates in graph ~w'-[Graph]),
  929                    [ h1(['Predicates in graph ', \graph_link(Graph)]),
  930                      \predicate_table(Sorted, Graph, [])
  931                    ]).
  932
  933predicate_table(Preds, Graph, Options) -->
  934    { option(top_max(TopMax), Options, 500),
  935      option(bottom_max(BottomMax), Options, 500)
  936    },
  937    html_requires(css('rdf.css')),
  938    html(table(class(block),
  939               [ \predicate_table_header
  940               | \table_rows_top_bottom(predicate_row(Graph), Preds,
  941                                        TopMax, BottomMax)
  942               ])).
  943
  944predicate_table_header -->
  945    html(tr([ th('Predicate'),
  946              th('#Triples'),
  947              th('#Distinct subjects'),
  948              th('#Distinct objects'),
  949              th('Domain(s)'),
  950              th('Range(s)')
  951            ])).
 predicate_row(?Graph, +Pred) is det
  955predicate_row(Graph, Pred) -->
  956    { predicate_statistics(Graph, Pred, Triples,
  957                           Subjects, Objects, Doms, Ranges),
  958      (   var(Graph)
  959      ->  Params = [predicate(Pred)]
  960      ;   Params = [graph(Graph), predicate(Pred)]
  961      ),
  962      http_link_to_id(list_triples,   Params, PLink)
  963    },
  964    html([ td(\rdf_link(Pred, [role(pred)])),
  965           td(class(int), a(href(PLink), Triples)),
  966           \resources(Subjects, subject, Params, [role(subj)]),
  967           \resources(Objects, object, Params, [role(obj)]),
  968           \resources(Doms, domain, Params, [role(domain)]),
  969           \resources(Ranges, range, Params, [role(range)])
  970         ]).
  971
  972resources([], _, _, _) -->
  973    !,
  974    html(td(class(empty), -)).
  975resources([One], _, _, Options) -->
  976    !,
  977    html(td(\rdf_link(One, Options))).
  978resources(Many, What, Params, _) -->
  979    !,
  980    { (   integer(Many)
  981      ->  Count = Many
  982      ;   length(Many, Count)
  983      ),
  984      http_link_to_id(list_predicate_resources, [side(What)|Params], Link)
  985    },
  986    html(td(class(int_c), a(href(Link), Count))).
  987
  988:- dynamic
  989    predicate_statistics_cache/8.  990
  991predicate_statistics(Graph, P, C, Subjects, Objects, Domains, Ranges) :-
  992    var(Graph),
  993    !,
  994    predicate_statistics_(Graph, P, C, Subjects, Objects, Domains, Ranges).
  995predicate_statistics(Graph, P, C, Subjects, Objects, Domains, Ranges) :-
  996    rdf_md5(Graph, MD5),
  997    predicate_statistics_cache(MD5, Graph, P, C,
  998                               Subjects, Objects, Domains, Ranges),
  999    !.
 1000predicate_statistics(Graph, P, C, Subjects, Objects, Domains, Ranges) :-
 1001    rdf_md5(Graph, MD5),
 1002    debug(rdf_browse, 'Recomputing pred stats for ~p in ~w, MD5=~w',
 1003          [P, Graph, MD5]),
 1004    retractall(predicate_statistics_cache(MD5, Graph, P, _,
 1005                                          _, _, _, _)),
 1006    predicate_statistics_(Graph, P, C, SubjectL, ObjectL, DomainL, RangeL),
 1007    res_summary(SubjectL, Subjects),
 1008    res_summary(ObjectL, Objects),
 1009    res_summary(DomainL, Domains),
 1010    res_summary(RangeL, Ranges),
 1011    assertz(predicate_statistics_cache(MD5, Graph, P, C,
 1012                                       Subjects, Objects, Domains, Ranges)).
 1013
 1014
 1015res_summary([], []) :- !.
 1016res_summary([One], [One]) :- !.
 1017res_summary(Many, Count) :-
 1018    length(Many, Count).
 1019
 1020
 1021predicate_statistics_(Graph, P, C, Subjects, Objects, Domains, Ranges) :-
 1022    findall(S-O, rdf(S,P,O,Graph), Pairs),
 1023    length(Pairs, C),
 1024    pairs_keys_values(Pairs, Ss, Os),
 1025    sort(Ss, Subjects),
 1026    sort(Os, Objects),
 1027    resources_types(Subjects, Graph, Domains),
 1028    resources_types(Objects, Graph, Ranges).
 1029
 1030resources_types(URIs, Graph, Types) :-
 1031    findall(T, resource_type_in(URIs, Graph, T), TList),
 1032    sort(TList, Types).
 1033
 1034resource_type_in(List, Graph, T) :-
 1035    member(URI, List),
 1036    resource_type(URI, Graph, T).
 resource_type(+URI, +Graph, -Type) is multi
 1040resource_type(literal(Lit), _, Type) :-
 1041    !,
 1042    (   Lit = type(Type, _)
 1043    ->  true
 1044    ;   rdf_equal(Type, rdfs:'Literal')
 1045    ).
 1046resource_type(^^(_, Type0), _, Type) :-
 1047    !,
 1048    Type = Type0.
 1049resource_type(@(_,_), _, Type) :-
 1050    !,
 1051    rdf_equal(Type, rdf:langString).
 1052resource_type(URI, Graph, Type) :-
 1053    (   string(URI)
 1054    ->  rdf_equal(Type, xsd:string)
 1055    ;   rdf(URI, rdf:type, Type, Graph)
 1056    *-> true
 1057    ;   rdf_equal(Type, rdfs:'Resource')
 1058    ).
 1059
 1060
 1061                 /*******************************
 1062                 *        LIST RESOURCES        *
 1063                 *******************************/
 list_predicate_resources(+Request)
List resources related to a predicate. The side argument is one of:
subject
Display all subject values for the predicate
object
Display all object values for the predicate
domain
Display the types of all subject values
range
Display the types of all object values.

If the skosmap attribute is true, an extra column is added that shows SKOS concepts that match literals. This only makes sense if side = object and (some) objects are literals.

 1083list_predicate_resources(Request) :-
 1084    http_parameters(Request,
 1085                    [ graph(Graph,
 1086                            [ optional(true),
 1087                              description('Limit search to this graph')
 1088                            ]),
 1089                      predicate(Pred,
 1090                                [ description('Predicate to list')
 1091                                ]),
 1092                      side(Which,
 1093                           [ oneof([subject,object,domain,range]),
 1094                             description('Relation to the predicate (see docs)')
 1095                           ]),
 1096                      sortBy(Sort,
 1097                             [ oneof([label,frequency]),
 1098                               default(frequency),
 1099                               description('How to sort results')
 1100                             ]),
 1101                      skosmap(SkosMap,
 1102                              [ boolean,
 1103                                optional(true),
 1104                                description('Show SKOS concepts for literals')
 1105                              ])
 1106                    ]),
 1107    do_skos(SkosMap, Which, Pred),
 1108    findall(R, predicate_resource(Graph, Pred, Which, R), Set),
 1109    term_frequency_list(Set, FPairs),
 1110    sort_pairs_by_label(FPairs, TableByName),
 1111    (   Sort == frequency
 1112    ->  reverse(TableByName, RevTableByName),
 1113        transpose_pairs(RevTableByName, FPairsUp),
 1114        reverse(FPairsUp, FPairsDown),
 1115        flip_pairs(FPairsDown, Table)
 1116    ;   Table = TableByName
 1117    ),
 1118
 1119    pred_resource_options(Pred, Which, Options),
 1120
 1121    reply_html_page(cliopatria(default),
 1122                    title(\resource_table_title(Graph, Pred, Which, Sort)),
 1123                    [ h1(\html_resource_table_title(Graph, Pred, Which,
 1124                                                    Sort, SkosMap)),
 1125                      \resource_frequency_table(Table,
 1126                                                [ skosmap(SkosMap),
 1127                                                  predicate(Pred),
 1128                                                  side(Which),
 1129                                                  sort(Sort)
 1130                                                | Options
 1131                                                ])
 1132                    ]).
 1133
 1134pred_resource_options(_, domain, [label('Class')]) :- !.
 1135pred_resource_options(_, range, [label('Class')]) :- !.
 1136pred_resource_options(_, _, []).
 1137
 1138do_skos(SkosMap, _, _) :-
 1139    nonvar(SkosMap),
 1140    !.
 1141do_skos(SkosMap, object, Pred) :-
 1142    \+ rdf(_, Pred, literal(_)),
 1143    !,
 1144    SkosMap = false.
 1145do_skos(SkosMap, object, _) :-
 1146    rdfs_individual_of(_, skos:'ConceptScheme'),
 1147    !,
 1148    SkosMap = true.
 1149do_skos(false, _, _).
 1150
 1151
 1152resource_table_title(Graph, Pred, Which, Sort) -->
 1153    { rdf_display_label(Pred, PLabel)
 1154    },
 1155    html('Distinct ~ws for ~w in ~w sorted by ~w'-
 1156         [Which, PLabel, Graph, Sort]
 1157         ).
 1158
 1159html_resource_table_title(Graph, Pred, Which, Sort, SkosMap) -->
 1160    html([ 'Distinct ~ws'-[Which],
 1161           \for_predicate(Pred),
 1162           \in_graph(Graph),
 1163           \sorted_by(Sort),
 1164           \showing_skosmap(SkosMap)
 1165         ]).
 1166
 1167for_predicate(Pred) -->
 1168    { var(Pred) },
 1169    !.
 1170for_predicate(Pred) -->
 1171    html([' for predicate ', \rdf_link(Pred, [role(pred)])]).
 1172
 1173showing_skosmap(true) -->
 1174    !,
 1175    html(' with mapping to SKOS').
 1176showing_skosmap(_) --> [].
 1177
 1178resource_frequency_table(Pairs, Options) -->
 1179    { option(top_max(TopMax), Options, 500),
 1180      option(top_max(BottomMax), Options, 500),
 1181      option(predicate(Pred), Options, _),
 1182      option(side(Side), Options)
 1183    },
 1184    html_requires(css('rdf.css')),
 1185    html(table(class(block),
 1186               [ \resource_table_header(Options)
 1187               | \table_rows_top_bottom(resource_row(Pred, Side, [role(pred)|Options]), Pairs,
 1188                                        TopMax, BottomMax)
 1189               ])).
 1190
 1191resource_table_header(Options) -->
 1192    { option(label(Label), Options, 'Resource'),
 1193      (   option(sort(Sort), Options)
 1194      ->  (   Sort == frequency
 1195          ->  A1 = [],
 1196              A2 = [class(sorted)]
 1197          ;   A1 = [class(sorted)],
 1198              A2 = []
 1199          )
 1200      ;   A1 = [],
 1201          A2 = []
 1202      )
 1203    },
 1204    html(tr([ th(A1, Label),
 1205              th(A2, 'Count'),
 1206              \skosmap_head(Options)
 1207            ])).
 1208
 1209skosmap_head(Options) -->
 1210    { option(skosmap(true), Options) },
 1211    !,
 1212    html(th('SKOS mapping')).
 1213skosmap_head(_) --> [].
 1214
 1215resource_row(Pred, object, Options, R-C) -->
 1216    !,
 1217    { object_param(R, Param),
 1218      http_link_to_id(list_triples_with_object,
 1219           [ p(Pred),
 1220             Param
 1221           ], HREF)
 1222    },
 1223    html([ td(\rdf_link(R, Options)),
 1224           td(class(int), a(href(HREF), C)),
 1225           \skosmap(R, Options)
 1226         ]).
 1227resource_row(Pred, Side, Options, R-C) -->
 1228    { domain_range_parameter(Side, R, Param),
 1229      !,
 1230      http_link_to_id(list_triples,
 1231           [ predicate(Pred),
 1232             Param
 1233           ], HREF)
 1234    },
 1235    html([ td(\rdf_link(R, Options)),
 1236           td(class(int), a(href(HREF), C)),
 1237           \skosmap(R, Options)
 1238         ]).
 1239resource_row(_, _, Options, R-C) -->
 1240    html([ td(\rdf_link(R, Options)),
 1241           td(class(int), C),
 1242           \skosmap(R, Options)
 1243         ]).
 1244
 1245object_param(R, r=R) :-
 1246    atom(R),
 1247    !.
 1248object_param(L, l=A) :-
 1249    term_to_atom(L, A).
 1250
 1251domain_range_parameter(domain, R, domain(R)).
 1252domain_range_parameter(range,  R, range(R)).
 skosmap(+Literal, +Options)//
Component that emits a td cell with links to SKOS concepts that are labeled Literal.
 1259skosmap(Literal, Options) -->
 1260    { Literal = literal(_),
 1261      option(skosmap(true), Options),
 1262      findall(Concept-Scheme, skos_find(Literal, Concept, Scheme), Pairs),
 1263      Pairs \== [],
 1264      sort_pairs_by_label(Pairs, Sorted)
 1265    },
 1266    html(td(\skos_references(Sorted))).
 1267skosmap(_, _) --> [].
 1268
 1269skos_find(Literal, Concept, Scheme) :-
 1270    rdf_has(Concept, skos:prefLabel, Literal),
 1271    rdf_has(Concept, skos:inScheme, Scheme).
 1272
 1273skos_references([]) --> [].
 1274skos_references([H|T]) -->
 1275    skos_reference(H),
 1276    (   { T == [] }
 1277    ->  []
 1278    ;   html('; '),
 1279        skos_references(T)
 1280    ).
 1281
 1282skos_reference(Concept-Scheme) -->
 1283    html([\rdf_link(Concept, [role(concept)]), ' in ', \rdf_link(Scheme, [role(scheme)])]).
 1284
 1285
 1286flip_pairs([], []).
 1287flip_pairs([Key-Val|Pairs], [Val-Key|Flipped]) :-
 1288    flip_pairs(Pairs, Flipped).
 1289
 1290predicate_resource(Graph, Pred, subject, R) :-
 1291    !,
 1292    rdf(R, Pred, _, Graph).
 1293predicate_resource(Graph, Pred, object, R) :-
 1294    !,
 1295    rdf(_, Pred, R, Graph).
 1296predicate_resource(Graph, Pred, domain, D) :-
 1297    !,
 1298    rdf(R, Pred, _, Graph),
 1299    rdf(R, rdf:type, D, Graph).
 1300predicate_resource(Graph, Pred, range, R) :-
 1301    rdf(_, Pred, O, Graph),
 1302    resource_type(O, Graph, R).
 term_frequency_list(+Terms, -TermFrequencyPairs)
TermFrequencyPairs is a list if pairs Value-Count of equivalent term in Terms. Equivalence is determined using ==/2. The terms themselves are sorted on the standard order of terms.
 1310term_frequency_list(Resources, Pairs) :-
 1311    msort(Resources, Sorted),
 1312    fpairs(Sorted, Pairs).
 1313
 1314fpairs([], []).
 1315fpairs([H|T0], [H-C|T]) :-
 1316    pick_same(T0, T1, H, 1, C),
 1317    fpairs(T1, T).
 1318
 1319pick_same([H1|T0], L, H, F0, F) :-
 1320    H == H1,
 1321    !,
 1322    F1 is F0 + 1,
 1323    pick_same(T0, L, H, F1, F).
 1324pick_same(L, L, _, F, F).
 1325
 1326
 1327                 /*******************************
 1328                 *    LIST A SINGLE RESOURCE    *
 1329                 *******************************/
 list_resource(+Request)
HTTP handler that lists the property table for a single resource (=local view)
See also
- The functionality of this handler is also available as an embedable component through list_resource//2.
 1339list_resource(Request) :-
 1340    http_parameters(Request,
 1341                    [ r(URI,
 1342                        [ description('URI to describe')]),
 1343                      sorted(Sorted,
 1344                             [ oneof([default,none]),
 1345                               default(default),
 1346                               description('How to sort properties')
 1347                             ]),
 1348                      graph(Graph,
 1349                            [ optional(true),
 1350                              description('Limit to properties from graph')
 1351                            ]),
 1352                      resource_format(Format,
 1353                            [ default(DefaultFormat),
 1354                              atom,
 1355                              description('Display format as passed to rdf_link//2 ')
 1356                            ]),
 1357                      raw(Raw,
 1358                          [ default(false),
 1359                            boolean,
 1360                            description('If true, omit application hook')
 1361                          ])
 1362                    ]),
 1363    setting(resource_format, DefaultFormat),
 1364    rdf_display_label(URI, Label),
 1365    reply_html_page(cliopatria(default),
 1366                    title('Resource ~w'-[Label]),
 1367                    \list_resource(URI,
 1368                                   [ graph(Graph),
 1369                                     sorted(Sorted),
 1370                                     raw(Raw),
 1371                                     resource_format(Format)
 1372                                   ])).
 list_resource(+URI, +Options)// is det
Component that emits the `local view' for URI. The local view shows the basic properties of URI, the context in which is appears and the graphs from which the information is extracted. Options is one of:
graph(Graph)
Limit properties in the table to the given graph
sorted(Sorted)
One of default or none.

Calls the hook cliopatria:list_resource//2. For compatibility reasons, it also tries the hook list_resource//1.

See also
- list_resource/1 is the corresponding HTTP handler. The component rdf_link//1 creates a link to list_resource/1.
 1392:- multifile
 1393    cliopatria:list_resource//1. 1394
 1395list_resource(URI, Options) -->
 1396    { \+ option(raw(true), Options) },
 1397    (   cliopatria:list_resource(URI, Options)
 1398    ->  []
 1399    ;   cliopatria:list_resource(URI) % deprecated
 1400    ).
 1401list_resource(URI, Options) -->
 1402    { option(graph(Graph), Options, _)
 1403    },
 1404    html([ h1([ 'Local view for "',
 1405                \location(URI, Graph), '"'
 1406              ]),
 1407           \define_prefix(URI),
 1408           \local_view(URI, Graph, Options),
 1409           p(\as_object(URI, Graph)),
 1410           p(\as_graph(URI)),
 1411           \uri_info(URI, Graph)
 1412         ]).
 define_prefix(+URI)//
Allow defining a new prefix if the resource is not covered by a prefix.
 1419define_prefix(URI) -->
 1420    { rdf_global_id(_Prefix:_Local, URI) },
 1421    !.
 1422define_prefix(URI) -->
 1423    { iri_xml_namespace(URI, Namespace, LocalName),
 1424      LocalName \== '',
 1425      http_link_to_id(add_prefix, [], Action)
 1426    },
 1427    html(form(action(Action),
 1428              ['No prefix for ', a(href(Namespace),Namespace), '. ',
 1429               \hidden(uri, Namespace),
 1430               input([name(prefix), size(8),
 1431                      title('Short unique abbreviation')
 1432                     ]),
 1433               input([type(submit), value('Add prefix')])
 1434              ])).
 1435define_prefix(_) -->                    % Not a suitable URI.  Warn?
 1436    [].
 location(+URI, ?Graph) is det
Show the URI. If the URI is a blank node, show its context using Turtle notation.
 1444location(URI, _Graph) -->
 1445    { rdf_is_bnode(URI),
 1446      !,
 1447      findall(Path, path_to_non_bnode(URI, Path), Paths),
 1448      sort_by_length(Paths, PathsByLen),
 1449      partition(starts_bnode, PathsByLen, StartsBNode, StartsReal),
 1450      (   StartsReal = [Path|_]
 1451      ->  true
 1452      ;   last(StartsBNode, Path)
 1453      )
 1454    },
 1455    bnode_location(Path).
 1456location(URI, _) -->
 1457    html(URI).
 1458
 1459bnode_location([P-URI]) -->
 1460    !,
 1461    html([ '[', \rdf_link(P,  [role(pred)]), ' ',
 1462                \rdf_link(URI,[role(bnode)]),
 1463           ']'
 1464         ]).
 1465bnode_location([P-URI|More]) -->
 1466    !,
 1467    html([ '[', div(class(bnode_attr),
 1468                    [ div(\rdf_link(P,  [ role(pred)])),
 1469                      div(\rdf_link(URI,[ role(bnode)]))
 1470                    ]), ' ',
 1471           \bnode_location(More),
 1472           ']'
 1473         ]).
 1474bnode_location([URI|More]) -->
 1475    !,
 1476    rdf_link(URI, [role(subj)]),
 1477    html(' '),
 1478    bnode_location(More).
 1479bnode_location([]) -->
 1480    [].
 1481
 1482path_to_non_bnode(URI, Path) :-
 1483    path_to_non_bnode_rev(URI, [URI], RevPath),
 1484    reverse(RevPath, Path).
 1485
 1486path_to_non_bnode_rev(URI, Seen, [P-URI|Path]) :-
 1487    (   rdf_is_bnode(URI),
 1488        rdf(S, P, URI),
 1489        \+ memberchk(S, Seen)
 1490    *-> path_to_non_bnode_rev(S, [S|Seen], Path)
 1491    ;   fail
 1492    ).
 1493path_to_non_bnode_rev(URI, _, [URI]).
 1494
 1495starts_bnode([URI|_]) :-
 1496    rdf_is_bnode(URI).
 1497
 1498sort_by_length(ListOfLists, ByLen) :-
 1499    map_list_to_pairs(length, ListOfLists, Pairs),
 1500    keysort(Pairs, Sorted),
 1501    pairs_values(Sorted, ByLen).
 as_graph(+URI) is det
Show the places where URI is used as a named graph
 1507as_graph(URI) --> { \+ rdf_graph(URI) }, !.
 1508as_graph(URI) -->
 1509    html([ 'This resource is also a ',
 1510           a([href(location_by_id(list_graph)+'?graph='+encode(URI))],
 1511             'named graph'),
 1512           '.']).
 as_object(+URI, +Graph) is det
Show the places where URI is used as an object.
 1519as_object(URI, Graph) -->
 1520    { findall(S-P, rdf(S,P,URI,Graph), Pairs),
 1521      sort(Pairs, Unique)
 1522    },
 1523    as_object_locations(Unique, URI, Graph).
 1524
 1525as_object_locations([], _URI, _) -->
 1526    !,
 1527    html([ 'The resource does not appear as an object' ]).
 1528as_object_locations([S-P], URI, _) -->
 1529    !,
 1530    html([ 'The resource appears as object in one triple:',
 1531           blockquote(class(triple),
 1532                      [ '{ ',
 1533                        \rdf_link(S, [role(subj)]), ', ',
 1534                        \rdf_link(P, [role(pred)]), ', ',
 1535                        \rdf_link(URI, [role(obj)]),
 1536                        ' }'
 1537                      ])
 1538         ]).
 1539as_object_locations(List, URI, Graph) -->
 1540    !,
 1541    { length(List, Len),
 1542      (   var(Graph)
 1543      ->  Extra = []
 1544      ;   Extra = [graph=Graph]
 1545      ),
 1546      http_link_to_id(list_triples_with_object, [r=URI|Extra], Link)
 1547    },
 1548    html([ 'The resource appears as object in ',
 1549           a(href(Link), [Len, ' triples'])
 1550         ]).
 local_view(+URI, ?Graph, +Options) is det
Show the local-view table for URI. If Graph is given, only show triples from the given graph. Options processed:
top_max(+Count)
bottom_max(+Count)
sorted(+How)
Defines the order of the predicates. One of none (database order) or default
show_graph(+Bool)

In addition, Options are passed to rdf_link//2.

 1566local_view(URI, Graph, Options) -->
 1567    { option(top_max(TopMax), Options, 500),
 1568      option(bottom_max(BottomMax), Options, 500),
 1569      po_pairs(URI, Graph, Pairs, Options),
 1570      lview_graphs(URI, Graph, Graphs)
 1571    },
 1572    (   { Pairs \== []
 1573        }
 1574    ->  html_requires(css('rdf.css')),
 1575        html(table(class(block),
 1576                   [ \lview_header(Options)
 1577                   | \table_rows_top_bottom(lview_row(Options, URI, Graphs),
 1578                                            Pairs,
 1579                                            TopMax, BottomMax)
 1580                   ])),
 1581        graph_footnotes(Graphs, Options)
 1582    ;   { lod_uri_graph(URI, LODGraph),
 1583          rdf_graph(LODGraph)
 1584        }
 1585    ->  html(p([ 'No triples for ', \show_link(URI), '. ',
 1586                 'Linked Data was loaded into ', \graph_link(LODGraph),
 1587                 '.'
 1588               ]))
 1589    ;   { sane_uri(URI) }
 1590    ->  { http_link_to_id(lod_crawl, [], FetchURL),
 1591          http_current_request(Request),
 1592          memberchk(request_uri(Here), Request)
 1593        },
 1594        html(form(action(FetchURL),
 1595                  [ \hidden(r, URI),
 1596                    \hidden(return_to, Here),
 1597                    'No triples for ', \show_link(URI),
 1598                    '.  Would you like to ',
 1599                    input([ type(submit),
 1600                            value('Query the Linked Data cloud')
 1601                          ]),
 1602                    '?'
 1603                  ]))
 1604    ;   html_requires(css('rdf.css')),
 1605        html(p([ 'No triples for ', \show_link(URI),
 1606                 ' (unknown URI scheme).']))
 1607    ).
 1608
 1609show_link(URI) -->
 1610    { sane_uri(URI) },
 1611    !,
 1612    html(a(href(URI), 'this URI')).
 1613show_link(URI) -->
 1614    html(span(class('insecure-uri'), URI)).
 1615
 1616sane_uri(URI) :-
 1617    uri_components(URI, Components),
 1618    uri_data(scheme, Components, Scheme),
 1619    valid_scheme(Scheme),
 1620    uri_data(authority, Components, Authority),
 1621    nonvar(Authority).
 1622
 1623valid_scheme(http).
 1624valid_scheme(https).
 1625valid_scheme(ftp).
 1626valid_scheme(ftps).
 1627
 1628lview_header(Options) -->
 1629    { option(sorted(Sorted), Options, default),
 1630      alt_sorted(Sorted, Alt),
 1631      http_current_request(Request),
 1632      http_reload_with_parameters(Request, [sorted(Alt)], HREF)
 1633    },
 1634    html(tr([ th('Predicate'),
 1635              th(['Value (sorted: ', a(href(HREF), Sorted), ')'])
 1636            ])).
 1637
 1638alt_sorted(default, none).
 1639alt_sorted(none, default).
 1640
 1641
 1642lview_row(Options, S, Graphs, P-OList) -->
 1643    html([ td(class(predicate), \rdf_link(P, [role(pred)|Options])),
 1644           td(class(object), \object_list(OList, S, P, Graphs, Options, 1))
 1645         ]).
 1646
 1647object_list([], _, _, _, _, _) --> [].
 1648object_list([H|T], S, P, Graphs, Options, Row) -->
 1649    { NextRow is Row + 1,
 1650      obj_class(Row, Class)
 1651    },
 1652    html(div(class(Class),
 1653             [ \rdf_link(H, [role(obj)|Options]),
 1654               \graph_marks(S, P, H, Graphs)
 1655             ])),
 1656    object_list(T, S, P, Graphs, Options, NextRow).
 1657
 1658obj_class(N, Class) :-
 1659    (   N mod 2 =:= 0
 1660    ->  Class = even
 1661    ;   Class = odd
 1662    ).
 1663
 1664graph_marks(_,_,_,[_]) --> !.
 1665graph_marks(S,P,O,Graphs) -->
 1666    html(sup(class(graph), \graphs(S,P,O,Graphs))).
 1667
 1668graphs(S, P, O, Graphs) -->
 1669    { findall(G, rdf(S,P,O,G:_), GL) },
 1670    graphs(GL, Graphs).
 1671
 1672graphs([], _) --> [].
 1673graphs([H|T], Graphs) -->
 1674    { nth1(N, Graphs, H) -> true },
 1675    html(N),
 1676    (   { T == [] }
 1677    ->  []
 1678    ;   html(','),
 1679        graphs(T, Graphs)
 1680    ).
 graph_footnotes(+GraphList, +Options)//
Describe footnote marks in the local view table that indicate the origin of triples.
 1687graph_footnotes([], _Options) --> !.
 1688graph_footnotes([Graph], _Options) -->
 1689    !,
 1690    html(p(class('graphs-used'),
 1691           [ 'All properties reside in the graph ',
 1692             \graph_link(Graph)
 1693           ])).
 1694graph_footnotes(Graphs, Options) -->
 1695    html(p(class('graphs-used'),
 1696           'Named graphs describing this resource:')),
 1697    graph_footnotes(Graphs, 1, Options).
 1698
 1699graph_footnotes([], _, _) --> [].
 1700graph_footnotes([H|T], N, Options) -->
 1701    html(div(class('graph-fn'),
 1702             [ sup(class(graph), N),
 1703               \graph_link(H)
 1704             ])),
 1705    { N2 is N + 1 },
 1706    graph_footnotes(T, N2, Options).
 lview_graphs(+Subject, ?Graph, -Graphs) is det
 1710lview_graphs(_Subject, Graph, Graphs) :-
 1711    nonvar(Graph),
 1712    !,
 1713    Graphs = [Graph].
 1714lview_graphs(Subject, Graph, Graphs) :-
 1715    findall(Graph, rdf(Subject, _, _, Graph:_), Graphs0),
 1716    sort(Graphs0, Graphs).
 po_pairs(+Subject, ?Graph, -Pairs, +Options) is det
Pairs is a list of P-ObjectList for the S,P,O triples on Subject. The list is normally sorted by predicate as defined by p_order/2 below.
 1724po_pairs(S, Graph, Pairs, Options) :-
 1725    option(sorted(none), Options),
 1726    !,
 1727    findall(P-[O], rdf(S,P,O,Graph), Pairs).
 1728po_pairs(S, Graph, Pairs, _Options) :-
 1729    var(Graph),
 1730    !,
 1731    findall(P-OL,
 1732            setof(O, rdf(S,P,O), OL),
 1733            Pairs0),
 1734    sort_po(Pairs0, Pairs).
 1735po_pairs(S, Graph, Pairs, _Options) :-
 1736    findall(P-OL,
 1737            setof(O, rdf(S,P,O,Graph), OL),
 1738            Pairs0),
 1739    sort_po(Pairs0, Pairs).
 sort_po(+Pairs, -Sorted) is det
Sort a list of P-ValueList. This is used to keep the dominant rdf, rdfs, skos, etc. properties in a fixed order at the start of the table.
 1747sort_po(Pairs, Sorted) :-
 1748    map_list_to_pairs(po_key, Pairs, Keyed),
 1749    keysort(Keyed, KeySorted),
 1750    exclude(=(0-_), KeySorted, Remaining),
 1751    pairs_values(Remaining, Sorted).
 1752
 1753po_key(P-_, Key) :-
 1754    p_order(P, Key),
 1755    !.
 1756po_key(P-_, Key) :-
 1757    label_sort_key(P, Key).
 p_order(+P, -SortKey) is semidet
SortKey is the key used for sorting the predicate P.
To be done
- Make this hookable.
 1765:- rdf_meta
 1766    p_order(r,?). 1767
 1768p_order(P, Order) :-
 1769    cliopatria:predicate_order(P, Order),
 1770    !.
 1771p_order(P, 100) :-
 1772    label_property(P),
 1773    !.
 1774p_order(P, 110) :-
 1775    rdfs_subproperty_of(P, skos:altLabel),
 1776    !.
 1777p_order(rdf:type,         210).
 1778p_order(rdfs:subClassOf,  220).
 1779p_order(rdfs:domain,      230).
 1780p_order(rdfs:range,       240).
 1781p_order(rdfs:comment,     310).
 1782p_order(rdfs:isDefinedBy, 320).
 uri_info(+URI, +Graph)// is det
Display additional info and actions about a URI in the context of the given graph.
 1790uri_info(URI, Graph) -->
 1791    uri_class_info(URI, Graph),
 1792    uri_predicate_info(URI, Graph),
 1793    html(h2('Context graph')),
 1794    context_graph(URI, []).
 1795
 1796uri_class_info(URI, Graph) -->
 1797    { rdf_current_predicate(URI)
 1798    },
 1799    !,
 1800    html(h2('Predicate statistics')),
 1801    predicate_table([URI], Graph, []).
 1802uri_class_info(_,_) --> [].
 1803
 1804uri_predicate_info(URI, Graph) -->
 1805    { \+ \+ rdf(_, rdf:type, URI, Graph)
 1806    },
 1807    !,
 1808    html(h2('Class statistics')),
 1809    class_table([URI], Graph, []).
 1810uri_predicate_info(_, _) --> [].
 context_graph(+URI, +Options)// is det
Show graph with the context of URI. Options is passed to cliopatria:context_graph/3 and cliopatria:node_shape/3. Two options have special meaning:
style(?Style)
If this option is not specified, it is passed as a variable. It can be tested or filled by cliopatria:context_graph/3 and subsequently used by cliopatria:node_shape/3.
start(+URI)
Passed to cliopatria:node_shape/3 to indicate the origin of the context graph.
 1828context_graph(URI, Options) -->
 1829    { merge_options(Options, [style(_)], GraphOption),
 1830      rdf_equal(owl:sameAs, SameAs)
 1831    },
 1832    html([ \graphviz_graph(context_graph(URI, GraphOption),
 1833                           [ object_attributes([width('100%')]),
 1834                             wrap_url(resource_link),
 1835                             graph_attributes([ rankdir('RL')
 1836                                              ]),
 1837                             shape_hook(shape(URI, GraphOption)),
 1838                             bag_shape_hook(bag_shape(GraphOption)),
 1839                             edge_hook(edge(URI, GraphOption)),
 1840                             label_hook(cliopatria:node_label),
 1841                             smash([SameAs])
 1842                           ])
 1843         ]).
 1844
 1845:- public
 1846    shape/5,
 1847    edge/5,
 1848    bag_shape/3.
 shape(+Start, +Options, +URI, -Shape, +GVOptions) is semidet
Specify GraphViz shape for URI. This predicate calls the hook cliopatria:node_shape/3.
 1855shape(Start, Options, URI, Shape, GVOptions) :-
 1856    append(Options, GVOptions, AllOptions),
 1857    cliopatria:node_shape(URI, Shape, [start(Start)|AllOptions]),
 1858    !.
 1859shape(Start, _Options, Start,
 1860      [ shape(tripleoctagon),style(filled),fillcolor('#ff85fd'),id(start) ],
 1861      _GVOptions).
 bag_shape(+Options, +Members, -Shape) is semidet
Compute properties for a bag
 1867bag_shape(Options, Members, Shape) :-
 1868    cliopatria:bag_shape(Members, Shape, Options),
 1869    !.
 1870bag_shape(_, _, []).
 1871
 1872edge(Start, Options, Predicate, Shape, GVOptions) :-
 1873    append(Options, GVOptions, AllOptions),
 1874    cliopatria:edge_shape(Predicate, Shape, [start(Start)|AllOptions]),
 1875    !.
 context_graph(+URI, -Triples, +Options) is det
Triples is a graph that describes the environment of URI. Currently, the environment is defined as:

This predicate can be hooked using context_graph/2.

 1887context_graph(URI, Options, RDF) :-
 1888    cliopatria:context_graph(URI, RDF, Options),
 1889    !.
 1890context_graph(URI, _Options, RDF) :-            % Compatibility
 1891    cliopatria:context_graph(URI, RDF),
 1892    !.
 1893context_graph(URI, _, RDF) :-
 1894    findall(T, context_triple(URI, T), RDF0),
 1895    sort(RDF0, RDF1),
 1896    minimise_graph(RDF1, RDF2),             % remove inverse/symmetric/...
 1897    bagify_graph(RDF2, RDF3, Bags, []),     % Create bags of similar resources
 1898    append(RDF3, Bags, RDF).
 1899
 1900:- rdf_meta
 1901    transitive_context(r),
 1902    context(r). 1903
 1904context_triple(URI, Triple) :-
 1905    transitive_context(CP),
 1906    parents(URI, CP, Triples, [URI], 3),
 1907    member(Triple, Triples).
 1908context_triple(URI, Triple) :-
 1909    cliopatria:context_predicate(URI, R),
 1910    rdf_has(URI, R, O, P),
 1911    normalize_triple(rdf(URI, P, O), Triple).
 1912context_triple(URI, Triple) :-
 1913    context(R),
 1914    rdf_has(URI, R, O, P),
 1915    normalize_triple(rdf(URI, P, O), Triple).
 1916context_triple(URI, Triple) :-
 1917    context(R),
 1918    rdf_has(S, R, URI, P),
 1919    normalize_triple(rdf(S, P, URI), Triple).
 1920
 1921normalize_triple(rdf(S, inverse_of(P0), O),
 1922                 rdf(O, P, S)) :-
 1923    !,
 1924    rdf_predicate_property(P0, inverse_of(P)).
 1925normalize_triple(RDF, RDF).
 1926
 1927
 1928
 1929parents(URI, Up, [Triple|T], Visited, MaxD) :-
 1930    succ(MaxD2, MaxD),
 1931    rdf_has(URI, Up, Parent, P),
 1932    normalize_triple(rdf(URI, P, Parent), Triple),
 1933    \+ memberchk(Parent, Visited),
 1934    parents(Parent, Up, T, [Parent|Visited], MaxD2).
 1935parents(_, _, [], _, _).
 1936
 1937transitive_context(owl:sameAs).
 1938transitive_context(rdfs:subClassOf).
 1939transitive_context(rdfs:subPropertyOf).
 1940transitive_context(skos:broader).
 1941transitive_context(P) :-
 1942    rdfs_individual_of(P, owl:'TransitiveProperty'),
 1943    rdf_predicate_property(P, rdfs_subject_branch_factor(BF)),
 1944    BF < 2.0.
 1945
 1946context(skos:related).
 1947context(skos:mappingRelation).
 list_triples(+Request)
List triples for a given predicate. The triple-set can optionally be filtered on the graph, type of the subject or type of the object.
 1955list_triples(Request) :-
 1956    http_parameters(Request,
 1957                    [ predicate(P,
 1958                                [ optional(true),
 1959                                  description('Limit triples to this pred')]),
 1960                      graph(Graph, [ optional(true),
 1961                                     description('Limit triples to this graph')
 1962                                   ]),
 1963                      domain(Dom,  [ optional(true),
 1964                                     description('Restrict to subjects of this class')
 1965                                   ]),
 1966                      range(Range, [ optional(true),
 1967                                     description('Restrict to objects of this class')
 1968                                   ])
 1969                    ]),
 1970    (   atom(Dom)
 1971    ->  findall(rdf(S,P,O), rdf_in_domain(S,P,O,Dom,Graph), Triples0)
 1972    ;   atom(Range)
 1973    ->  findall(rdf(S,P,O), rdf_in_range(S,P,O,Range,Graph), Triples0)
 1974    ;   findall(rdf(S,P,O), rdf(S,P,O,Graph), Triples0)
 1975    ),
 1976    sort(Triples0, Triples),
 1977    sort_triples_by_label(Triples, Sorted),
 1978    length(Sorted, Count),
 1979    (   var(P)
 1980    ->  Title = 'Triples in graph ~w'-[Graph]
 1981    ;   rdf_display_label(P, PLabel),
 1982        Title = 'Triples for ~w in graph ~w'-[PLabel, Graph]
 1983    ),
 1984    reply_html_page(cliopatria(default),
 1985                    title(Title),
 1986                    [ h1(\triple_header(Count, P, Dom, Range, Graph)),
 1987                      \triple_table(Sorted, P, [resource_format(nslabel)])
 1988                    ]).
 1989
 1990rdf_in_domain(S,P,O,Dom,Graph) :-
 1991    rdf(S, P, O, Graph),
 1992    rdf_has(S, rdf:type, Dom).
 1993
 1994rdf_in_range(S,P,O,Lit,Graph) :-
 1995    rdf_equal(rdfs:'Literal', Lit),
 1996    !,
 1997    O = literal(_),
 1998    rdf(S, P, O, Graph).
 1999rdf_in_range(S,P,O,Rng,Graph) :-
 2000    rdf_equal(rdfs:'Resource', Rng),
 2001    !,
 2002    rdf(S, P, O, Graph),
 2003    atom(O).
 2004rdf_in_range(S,P,O,Rng,Graph) :-
 2005    rdf(S, P, O, Graph),
 2006    rdf_has(O, rdf:type, Rng).
 2007
 2008
 2009triple_header(Count, Pred, Dom, Range, Graph) -->
 2010    html([ 'Table for the ~D triples'-[Count],
 2011           \for_predicate(Pred),
 2012           \with_domain(Dom),
 2013           \with_range(Range),
 2014           \in_graph(Graph)
 2015         ]).
 2016
 2017with_domain(Dom) -->
 2018    { var(Dom) },
 2019    !.
 2020with_domain(Dom) -->
 2021    html([' with domain ', \rdf_link(Dom, [role(domain)])]).
 2022
 2023with_range(Range) -->
 2024    { var(Range) },
 2025    !.
 2026with_range(Range) -->
 2027    html([' with range ', \rdf_link(Range, [role(range)])]).
 triple_table(+Triples, +Predicate, +Options)// is det
Show a list of triples. If Predicate is given, omit the predicate from the table.
 2034triple_table(Triples, Pred, Options) -->
 2035    { option(top_max(TopMax), Options, 500),
 2036      option(top_max(BottomMax), Options, 500)
 2037    },
 2038    html(table(class(block),
 2039               [ \spo_header(Pred)
 2040               | \table_rows_top_bottom(spo_row(Options, Pred), Triples,
 2041                                        TopMax, BottomMax)
 2042               ])).
 2043
 2044spo_header(P) -->
 2045    { nonvar(P) },
 2046    html(tr([ th('Subject'),
 2047              th('Object')
 2048            ])).
 2049spo_header(_) -->
 2050    html(tr([ th('Subject'),
 2051              th('Predicate'),
 2052              th('Object')
 2053            ])).
 2054
 2055spo_row(Options, Pred, rdf(S,_,O)) -->
 2056    { nonvar(Pred) },
 2057    !,
 2058    html([ td(class(subject), \rdf_link(S, [role(subj)|Options])),
 2059           td(class(object),  \rdf_link(O, [role(obj) |Options]))
 2060         ]).
 2061spo_row(Options, _, rdf(S,P,O)) -->
 2062    html([ td(class(subject),   \rdf_link(S, [role(subj)|Options])),
 2063           td(class(predicate), \rdf_link(P, [role(pred)|Options])),
 2064           td(class(object),    \rdf_link(O, [role(obj) |Options]))
 2065         ]).
 list_triples_with_object(+Request)
HTTP handler that creates a subject/predicate table for triples that have the gived object. Object is specified using either the r or l parameter. Optionally, results can be limited to a predicate and/or graph.
 2075list_triples_with_object(Request) :-
 2076    http_parameters(Request,
 2077                    [ r(RObject,   [optional(true),
 2078                                    description('Object as resource (URI)')
 2079                                   ]),
 2080                      l(LObject,   [optional(true),
 2081                                    description('Object as literal (Prolog notation)')
 2082                                   ]),
 2083                      p(P,         [optional(true),
 2084                                    description('Limit to a given predicate (URI)')
 2085                                   ]),
 2086                      graph(Graph, [optional(true),
 2087                                    description('Limit to a given graph (URI)')
 2088                                   ]),
 2089                      sortBy(Sort,
 2090                             [ oneof([label, subject, predicate]),
 2091                               default(label),
 2092                               description('How to sort the result')
 2093                             ])
 2094                    ]),
 2095    target_object(RObject, LObject, Object),
 2096    list_triples_with_object(Object, P, Graph, [sortBy(Sort)]).
 2097
 2098target_object(RObject, _LObject, RObject) :-
 2099    atom(RObject),
 2100    !.
 2101target_object(_, LObject, Object) :-
 2102    atom(LObject),
 2103    !,
 2104    term_to_atom(Object0, LObject),
 2105    rdf11_rdf_db(Object0, Object).
 2106target_object(_, _, _) :-
 2107    throw(existence_error(http_parameter, r)).
 2108
 2109rdf11_rdf_db(^^(String, Type), literal(type(Type, Atom))) :-
 2110    atom_string(Atom, String).
 2111rdf11_rdf_db(@(String, Lang), literal(lang(Lang, Atom))) :-
 2112    atom_string(Atom, String).
 2113rdf11_rdf_db(literal(Lit),   literal(Lit)).
 list_triples_with_literal(+Request)
List triples that have a literal that matches the q-parameter. This is used for finding objects through the autocompletion interface.
 2122list_triples_with_literal(Request) :-
 2123    http_parameters(Request,
 2124                    [ q(Text,
 2125                        [optional(true),
 2126                         description('Object as resource (URI)')
 2127                        ])
 2128                    ]),
 2129    list_triples_with_object(literal(Text), _, _, [sortBy(subject)]).
 2130
 2131
 2132list_triples_with_object(Object, P, Graph, Options) :-
 2133    findall(S-P, rdf(S,P,Object,Graph), Pairs),
 2134    (   option(sortBy(label), Options)
 2135    ->  sort_pairs_by_label(Pairs, Sorted)
 2136    ;   option(sortBy(predicate), Options)
 2137    ->  transpose_pairs(Pairs, Transposed), % flip pairs and sort on new key
 2138        flip_pairs(Transposed, Sorted)      % flip back without sort
 2139    ;   sort(Pairs, Sorted)
 2140    ),
 2141    length(Pairs, Count),
 2142    label_of(Object, OLabel),
 2143    reply_html_page(cliopatria(default),
 2144                    title('Triples with object ~w'-[OLabel]),
 2145                    [ h1(\otriple_header(Count, Object, P, Graph, Options)),
 2146                      \otriple_table(Sorted, Object, [resource_format(nslabel)])
 2147                    ]).
 2148
 2149otriple_header(Count, Object, Pred, Graph, Options) -->
 2150    { option(sortBy(SortBy), Options) },
 2151    html([ 'Table for the ~D triples'-[Count],
 2152           \with_object(Object),
 2153           \on_predicate(Pred),
 2154           \in_graph(Graph),
 2155           \sorted_by(SortBy)
 2156         ]).
 2157
 2158with_object(Obj) -->
 2159    { var(Obj)},
 2160    !.
 2161with_object(Obj) -->
 2162    html([' with object ', \rdf_link(Obj, [role(obj)])]).
 2163
 2164on_predicate(P) -->
 2165    { var(P) },
 2166    !.
 2167on_predicate(P) -->
 2168    html([' on predicate ', \rdf_link(P, [role(pred)])]).
 2169
 2170
 2171otriple_table(SPList, Object, Options) -->
 2172    { option(top_max(TopMax), Options, 500),
 2173      option(top_max(BottomMax), Options, 500)
 2174    },
 2175    html(table(class(block),
 2176               [ \sp_header(Object)
 2177               | \table_rows_top_bottom(sp_row(Options,Object), SPList,
 2178                                        TopMax, BottomMax)
 2179               ])).
 2180
 2181sp_header(_) -->
 2182    html(tr([ th('Subject'),
 2183              th('Predicate')
 2184            ])).
 2185
 2186sp_row(Options, _O, S-P) -->
 2187    html([ td(class(subject),   \rdf_link(S, [role(subj)|Options])),
 2188           td(class(predicate), \rdf_link(P, [role(pred)|Options]))
 2189         ]).
 2190
 2191
 2192
 2193
 2194
 2195                 /*******************************
 2196                 *            RDF UTIL          *
 2197                 *******************************/
 sort_by_label(+URIs, -Sorted) is det
Sort a list of URIs by their label using locale-based ordering.
 2203sort_by_label(URIs, Sorted) :-
 2204    map_list_to_pairs(label_sort_key, URIs, LabelPairs),
 2205    keysort(LabelPairs, SortedPairs),
 2206    pairs_values(SortedPairs, Sorted).
 2207
 2208label_sort_key(URI, Key) :-
 2209    label_of(URI, Label),
 2210    (   atom(Label)
 2211    ->  collation_key(Label, Key)
 2212    ;   Key = Label
 2213    ).
 2214
 2215label_of(URI, Label) :-
 2216    rdf_is_resource(URI),
 2217    !,
 2218    rdf_display_label(URI, Label).
 2219label_of(Literal, Label) :-
 2220    literal_text(Literal, Label).
 sort_triples_by_label(+Triples, -Sorted)
Sort a list of rdf(S,P,O) by the labels.
 2227sort_triples_by_label(Pairs, Sorted) :-
 2228    map_list_to_pairs(key_triple_by_label, Pairs, LabelPairs),
 2229    keysort(LabelPairs, SortedPairs),
 2230    pairs_values(SortedPairs, Sorted).
 2231
 2232key_triple_by_label(rdf(S,P,O), rdf(SK,PK,OK)) :-
 2233    label_sort_key(S, SK),
 2234    label_sort_key(P, PK),
 2235    label_sort_key(O, OK).
 sort_pairs_by_label(+Pairs, -Sorted)
Sort a pair-list where the keys are resources by their label.
 2241sort_pairs_by_label(Pairs, Sorted) :-
 2242    map_list_to_pairs(key_label_sort_key, Pairs, LabelPairs),
 2243    keysort(LabelPairs, SortedPairs),
 2244    pairs_values(SortedPairs, Sorted).
 2245
 2246key_label_sort_key(R-_, Key) :-
 2247    label_sort_key(R, Key).
 2248
 2249
 2250                 /*******************************
 2251                 *        CUSTOMIZATION         *
 2252                 *******************************/
 p_label(+Id, -Label)
Defines the visible label for a property.
See also
- html_property_table//2.
 2260p_label(source(_), 'Source URL').
 2261p_label(triples(G),
 2262        ['# ', a(href(Link), triples)]) :-
 2263    http_link_to_id(list_triples, [graph=G], Link).
 2264p_label(subject_count(G),
 2265        ['# ', a(href(Link), subjects)]) :-
 2266    http_link_to_id(list_instances, [graph=G], Link).
 2267p_label(bnode_count(G),
 2268        ['# ', a(href(Link), 'bnode subjects')]) :-
 2269    http_link_to_id(list_instances, [graph=G, type=bnode], Link).
 2270p_label(predicate_count(G),
 2271        ['# ', a(href(Link), predicates)]) :-
 2272    http_link_to_id(list_predicates, [graph=G], Link).
 2273p_label(type_count(G),
 2274        ['# Referenced ', a(href(Link), classes)]) :-
 2275    http_link_to_id(list_classes, [graph=G], Link).
 2276
 2277
 2278                 /*******************************
 2279                 *            SEARCH            *
 2280                 *******************************/
 search(+Request)
HTTP handler to search for triples that contain a literal that matches a query.
To be done
- Produce a sensible search language.
 2289search(Request) :-
 2290    http_parameters(Request,
 2291                    [ q(QueryText,
 2292                        [ description('Query to search for')
 2293                        ]),
 2294                      filter(FilterAtom,
 2295                             [ optional(true),
 2296                               description('Filter on raw matches (a Prolog term)')
 2297                             ])
 2298                    ]),
 2299    (   var(FilterAtom)
 2300    ->  Filter = true
 2301    ;   atom_to_term(FilterAtom, Filter0, []),
 2302        rdf_global_term(Filter0, Filter)
 2303    ),
 2304
 2305    find_literals(QueryText, Literals, Query),
 2306    literal_triples(Literals, Filter, Triples),
 2307    reply_html_page(cliopatria(default),
 2308                    title('Search results for ~q'-[Query]),
 2309                    [ h1('Search results for token "~q"'-[Query]),
 2310                      \rdf_table(Triples, [])
 2311                    ]).
 2312
 2313find_literals(QueryText, [Query], exact(Query)) :-
 2314    % Check if Q starts and ends with double quotes:
 2315    sub_atom(QueryText,0,1,Remainder,'"'),
 2316    sub_atom(QueryText,Remainder,1,0,'"'),
 2317    !,
 2318    sub_atom(QueryText,1,_,1,Query).
 2319find_literals(QueryText, Literals, Query) :-
 2320    % if not quoted, perform search on tokenized query
 2321    tokenize_atom(QueryText, Tokens),
 2322    once(phrase(query(Query), Tokens)),
 2323    rdf_find_literals(Query, Literals).
 2324
 2325query(Query) -->
 2326    simple_query(Q1),
 2327    (   eos
 2328    ->  {Query = Q1}
 2329    ;   query(Q2),
 2330        {Query = and(Q1,Q2)}
 2331    ).
 2332
 2333eos([],[]).
 2334
 2335simple_query(Token) -->
 2336    ['"',Token,'"'],
 2337    !.
 2338simple_query(not(Token)) -->
 2339    [-, Token].
 2340simple_query(case(Token)) -->
 2341    [Token].
 literal_triples(+ListOfLiterals, +Filter, -Triples) is det
Find the list of triples with a literal in ListOfLiterals and whose subject satisfies Filter.
 2348literal_triples(Literals, Filter, Triples) :-
 2349    sub_term(graph(Graph), Filter),
 2350    !,
 2351    phrase(ltriples(Literals, Graph, Filter), Triples).
 2352literal_triples(Literals, Filter, Triples) :-
 2353    phrase(ltriples(Literals, Filter), Triples).
 2354
 2355
 2356ltriples([], _, _) --> [].
 2357ltriples([H|T], G, F) -->
 2358    findall(rdf(S,P,literal(L)),
 2359            (   rdf(S,P,literal(exact(H), L),G),
 2360                search_filter(F, S)
 2361            )),
 2362    ltriples(T, G, F).
 2363
 2364ltriples([], _) --> [].
 2365ltriples([H|T], F) -->
 2366    findall(rdf(S,P,literal(L)),
 2367            (   rdf(S,P,literal(exact(H), L)),
 2368                search_filter(F, S)
 2369            )),
 2370    ltriples(T, F).
 rdf_table(+Triples, +Options)// is det
Emit a table of triples.
Arguments:
Triples- is a list of rdf(S,P,O).
 2378rdf_table(Triples, Options) -->
 2379    { option(top_max(TopMax), Options, 500),
 2380      option(top_max(BottomMax), Options, 500)
 2381    },
 2382    html(table(class(block),
 2383               [ tr([ th('Subject'), th('Predicate'), th('Object') ])
 2384               | \table_rows_top_bottom(triple, Triples,
 2385                                        TopMax, BottomMax)
 2386               ])).
 2387
 2388triple(rdf(S,P,O)) -->
 2389    html([ td(class(subject),   \rdf_link(S, [role(subj)])),
 2390           td(class(predicate), \rdf_link(P, [role(pred)])),
 2391           td(class(object),    \rdf_link(O, [role(obj) ]))
 2392         ]).
 2393
 2394
 2395                 /*******************************
 2396                 *     HTML INFRASTRUCTURE      *
 2397                 *******************************/
 html_property_table(+Template, :Goal)// is det
Create a table for all instantiations of Template for which Goal is true. Template is a term row(C1, C2, ...). The first column (C1) is considered the property-name and emitted as a cell of class p_name. The label for the property is derived using p_label/2. The remainder is emited as normal td value-cells.
 2407html_property_table(Template, Goal) -->
 2408    { findall(Template, Goal, Rows) },
 2409    html(table(class(block),
 2410               \table_rows(prow, Rows))).
 2411
 2412prow(Row) -->
 2413    { Row =.. [_,H|Cells],
 2414      (   p_label(H, Label0)
 2415      ->  true
 2416      ;   functor(H, Label0, _)
 2417      ),
 2418      (   is_list(Label0)
 2419      ->  append(Label0, [:], Label)
 2420      ;   Label = [Label0, :]
 2421      )
 2422    },
 2423    html([ th(class(p_name), Label)
 2424         | \pcells(Cells)
 2425         ]).
 2426
 2427pcells([]) --> [].
 2428pcells([H|T]) -->
 2429    pcell(H),
 2430    pcells(T).
 2431
 2432pcell(int(Value)) -->
 2433    { integer(Value) },
 2434    !,
 2435    nc('~D', Value).
 2436pcell(H) -->
 2437    { compound(H),
 2438      H =.. [Class,Value], !
 2439    },
 2440    html(td(class(Class), Value)).
 2441pcell(H) -->
 2442    html(td(H)).
 table_rows(:Goal, +DataList)// is det
 table_rows(:Goal, +DataList, +MaxTop, +MaxBottom)// is det
Emit a number of table rows (tr). The content of each row is created by calling call(Goal, Data) as a DCG. The rows have alternating classes even and odd. The first row is odd.

The variation table_rows//4 limits the size of the table, placing a cell with class skip, indicating the number of skipped rows.

Note that we can also achieve alternate colouring using the CSS pseudo classes tr:nth-child(odd) and tr:nth-child(even).

 2459table_rows(Goal, Rows) -->
 2460    table_rows(Rows, Goal, 1, -1).
 2461
 2462table_rows_top_bottom(Goal, Rows, inf, inf) -->
 2463    !,
 2464    table_rows(Rows, Goal, 1, -1).
 2465table_rows_top_bottom(Goal, Rows, MaxTop, MaxBottom) -->
 2466    { length(Rows, Count) },
 2467    (   { MaxTop+MaxBottom >= Count }
 2468    ->  table_rows(Rows, Goal, 1, -1)
 2469    ;   { Skip is Count-MaxBottom,
 2470          delete_list_prefix(Skip, Rows, BottomRows),
 2471          Skipped is Count-(MaxTop+MaxBottom)
 2472        },
 2473        table_rows(Rows, Goal, 1, MaxTop),
 2474        html(tr(class(skip),
 2475                [ th(colspan(10), 'Skipped ~D rows'-[Skipped])
 2476                ])),
 2477        table_rows(BottomRows, Goal, 1, -1)
 2478    ).
 2479
 2480table_rows(_, _, _, 0) --> !, [].
 2481table_rows([], _, _, _) --> [].
 2482table_rows([H|T], Goal, N, Left) -->
 2483    { N2 is N + 1,
 2484      (   N mod 2 =:= 0
 2485      ->  Class = even
 2486      ;   Class = odd
 2487      ),
 2488      Left2 is Left - 1
 2489    },
 2490    html(tr(class(Class), \call(Goal, H))),
 2491    table_rows(T, Goal, N2, Left2).
 2492
 2493delete_list_prefix(0, List, List) :- !.
 2494delete_list_prefix(_, [], []) :- !.
 2495delete_list_prefix(N, [_|T], List) :-
 2496    N2 is N - 1,
 2497    delete_list_prefix(N2, T, List).
 list_prefixes(+Request)
List known RDF prefixes in various formats
 2503list_prefixes(Request) :-
 2504    Formats = [html,turtle],
 2505    http_parameters(Request,
 2506                    [ format(Format,
 2507                             [ oneof(Formats),
 2508                               description('Output format'),
 2509                               default(html)
 2510                             ])
 2511                    ]),
 2512    findall(Prefix-URI,
 2513            rdf_current_ns(Prefix, URI),
 2514            Pairs),
 2515    keysort(Pairs, Sorted),
 2516    prefix_actions(Options),
 2517    reply_html_page(cliopatria(default),
 2518                    title('RDF prefixes (namespaces)'),
 2519                    [ h1('Known RDF prefixes (namespaces)'),
 2520                      \explain_prefixes,
 2521                      \prefix_table(Format, Sorted, Options),
 2522                      \prefix_formats(Formats, Format, Request)
 2523                    ]).
 2524
 2525prefix_actions([edit(true)]) :-
 2526    logged_on(User),
 2527    !,
 2528    catch(check_permission(User, write(_, del_prefix(_))), _, fail),
 2529    !.
 2530prefix_actions([]).
 2531
 2532explain_prefixes -->
 2533    html(p([ 'The following prefixes are known and may be used \c
 2534                  without declaration in SPARQL queries to this server.'
 2535           ])).
 2536
 2537prefix_formats(Formats, Format, Request) -->
 2538    { select(Format, Formats, Alt)
 2539    },
 2540    html(p(class('prefix-format'),
 2541           [ 'Also available in ',
 2542             \alt_formats(Alt, Request)
 2543           ])).
 2544
 2545alt_formats([], _) --> [].
 2546alt_formats([H|T], Request) -->
 2547    { http_reload_with_parameters(Request, [format(H)], HREF)
 2548    },
 2549    html(a(href(HREF), H)),
 2550    (   {T==[]}
 2551    ->  []
 2552    ;   html(' and '),
 2553        alt_formats(T, Request)
 2554    ).
 2555
 2556prefix_table(html, Pairs, Options) -->
 2557    html(table(class(block),
 2558               [ \prefix_table_header,
 2559                 \table_rows(prefix_row(Options), Pairs)
 2560               ])).
 2561prefix_table(turtle, Pairs, _) -->
 2562    html(pre(class(code),
 2563             \turtle_prefixes(Pairs))).
 2564
 2565prefix_table_header -->
 2566    html(tr([ th('Prefix'),
 2567              th('URI')
 2568            ])).
 2569
 2570prefix_row(Options, Prefix-URI) -->
 2571    { option(edit(true), Options),
 2572      !,
 2573      http_link_to_id(del_prefix, [prefix(Prefix)], HREF)
 2574    },
 2575    html([ td(Prefix),
 2576           td(URI),
 2577           td(a([ href(HREF),
 2578                  class('delete'),
 2579                  title('Remove prefix')
 2580                ], '\u232B'))
 2581         ]).
 2582prefix_row(_Options, Prefix-URI) -->
 2583    html([ td(Prefix),
 2584           td(URI)
 2585         ]).
 2586
 2587turtle_prefixes(Pairs) -->
 2588    { longest_prefix(Pairs, 0, Length),
 2589      PrefixCol is Length+10
 2590    },
 2591    turtle_prefixes(Pairs, PrefixCol).
 2592
 2593longest_prefix([], L, L).
 2594longest_prefix([Prefix-_|T], L0, L) :-
 2595    atom_length(Prefix, L1),
 2596    L2 is max(L0, L1),
 2597    longest_prefix(T, L2, L).
 2598
 2599turtle_prefixes([], _) --> [].
 2600turtle_prefixes([Prefix-URI|T], Col) -->
 2601    html('@prefix ~t~w: ~*|<~w> .~n'-[Prefix, Col, URI]),
 2602    turtle_prefixes(T, Col)