View source with raw comments or as raw
    1/*  Part of ClioPatria SeRQL and SPARQL server
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2009-2015, VU University Amsterdam
    7
    8    This program is free software; you can redistribute it and/or
    9    modify it under the terms of the GNU General Public License
   10    as published by the Free Software Foundation; either version 2
   11    of the License, or (at your option) any later version.
   12
   13    This program is distributed in the hope that it will be useful,
   14    but WITHOUT ANY WARRANTY; without even the implied warranty of
   15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   16    GNU General Public License for more details.
   17
   18    You should have received a copy of the GNU General Public
   19    License along with this library; if not, write to the Free Software
   20    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   21
   22    As a special exception, if you link this library with other files,
   23    compiled with a Free Software compiler, to produce an executable, this
   24    library does not by itself cause the resulting executable to be covered
   25    by the GNU General Public License. This exception does not however
   26    invalidate any other reasons why the executable file might be covered by
   27    the GNU General Public License.
   28*/
   29
   30:- module(cpa_browse,
   31	  [ graph_info//1,		% +Graph
   32	    graph_as_resource//2,	% +Graph, +Options
   33	    graph_actions//1,		% +Graph
   34	    list_resource//2,		% +URI, +Options
   35	    context_graph//2		% +URI, +Options
   36	  ]).   37:- use_module(library(http/http_dispatch)).   38:- use_module(library(http/http_parameters)).   39:- use_module(library(http/html_write)).   40:- use_module(library(http/js_write)).   41:- use_module(library(http/html_head)).   42:- use_module(library(http/http_wrapper)).   43:- use_module(library(http/yui_resources)).   44:- use_module(library(http/http_path)).   45:- use_module(library(http/cp_jquery)).   46
   47:- use_module(library(semweb/rdf_db)).   48:- use_module(library(semweb/rdfs)).   49:- use_module(library(semweb/rdf_litindex)).   50:- use_module(library(semweb/rdf_persistency)).   51
   52:- use_module(library(aggregate)).   53:- use_module(library(lists)).   54:- use_module(library(pairs)).   55:- use_module(library(debug)).   56:- use_module(library(option)).   57:- use_module(library(apply)).   58:- use_module(library(settings)).   59
   60:- use_module(components(label)).   61:- use_module(components(simple_search)).   62:- use_module(components(graphviz)).   63:- use_module(components(basics)).   64:- use_module(api(lod_crawler)).   65:- use_module(api(sesame)).   66:- use_module(library(semweb/rdf_abstract)).   67:- use_module(library(semweb/rdf_label)).   68
   69:- 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. */
   86		 /*******************************
   87		 *	      PATHS		*
   88		 *******************************/
   89
   90:- http_handler(rdf_browser(.),
   91		http_404([index(list_graphs)]),
   92		[spawn(cliopatria), prefix]).   93:- http_handler(rdf_browser(list_graphs),     list_graphs,     []).   94:- http_handler(rdf_browser(list_graph),      list_graph,      []).   95:- http_handler(rdf_browser(list_classes),    list_classes,    []).   96:- http_handler(rdf_browser(list_instances),  list_instances,  []).   97:- http_handler(rdf_browser(list_predicates), list_predicates, []).   98:- http_handler(rdf_browser(list_predicate_resources),
   99					      list_predicate_resources, []).  100:- http_handler(rdf_browser(list_resource),   list_resource,   []).  101:- http_handler(rdf_browser(list_triples),    list_triples,    []).  102:- http_handler(rdf_browser(list_triples_with_object),
  103					      list_triples_with_object,	[]).  104:- http_handler(rdf_browser(list_triples_with_literal),
  105					      list_triples_with_literal, []).  106
  107:- http_handler(rdf_browser(list_prefixes),   list_prefixes,   []).  108:- http_handler(rdf_browser(search),          search,	       []).  109:- http_handler(rdf_browser(multigraph_action), multigraph_action,
  110		[ time_limit(infinite) ]).  111
  112
  113:- meta_predicate
  114	table_rows(3, +, ?, ?),
  115	table_rows_top_bottom(3, +, +, +, ?, ?),
  116	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.
  123list_graphs(_Request) :-
  124	findall(Count-Graph,
  125		(   rdf_graph(Graph),
  126		    graph_triples(Graph, Count)
  127		),
  128		Pairs),
  129	keysort(Pairs, Sorted),
  130	pairs_values(Sorted, UpCount),
  131	reverse(UpCount, DownCount),
  132	append(DownCount, [virtual(total)], Rows),
  133	reply_html_page(cliopatria(default),
  134			title('RDF Graphs'),
  135			[ h1('Named graphs in the RDF store'),
  136			  \warn_volatile,
  137			  \graph_table(Rows, [])
  138			]).
  139
  140:- if(current_predicate(rdf_persistency_property/1)).  141warn_volatile -->
  142	{ rdf_persistency_property(access(read_only)), !,
  143	  rdf_persistency_property(directory(Dir))
  144	},
  145	html(div(class(msg_warning),
  146		 [ 'WARNING: The persistent store ', code(Dir), ' was loaded in ',
  147		   b('read-only'), ' mode.  All changes will be lost when ',
  148		   'the server is stopped.'
  149		 ])).
  150:- endif.  151warn_volatile --> [].
  152
  153:- if((rdf_version(V),V>=30000)).  154graph_triples(Graph, Count) :-
  155	rdf_statistics(triples_by_graph(Graph, Count)).
  156:- else.  157graph_triples(Graph, Count) :-			% RDF-DB < 3.0
  158	rdf_statistics(triples_by_file(Graph, Count)).
  159:- endif.  160
  161graph_table(Graphs, Options) -->
  162	{ option(top_max(TopMax), Options, 500),
  163	  option(top_max(BottomMax), Options, 500),
  164	  http_link_to_id(multigraph_action, [], Action),
  165	  graph_actions(Options, ActionOptions)
  166	},
  167	html_requires(css('rdf.css')),
  168	html(form([ action(Action),
  169		    class('graph-table')
  170		  ],
  171		  [ table(class(block),
  172			  [ \graph_table_header
  173			  | \table_rows_top_bottom(
  174				 graph_row(ActionOptions), Graphs,
  175				 TopMax, BottomMax)
  176			  ]),
  177		    \multigraph_actions(ActionOptions)
  178		  ])),
  179	mgraph_action_script.
  180
  181graph_table_header -->
  182	html(tr([ th('RDF Graph'),
  183		  th('Triples'),
  184		  th('Modified'),
  185		  th('Persistency')
  186		])).
  187
  188graph_row(_, virtual(total)) --> !,
  189	{ rdf_statistics(triples(Count))
  190	},
  191	html([ th(class(total), 'Total #triples:'),
  192	       \nc('~D', Count, [class(total)]),
  193	       td([],[]),  % Empty cell for persistency column
  194	       td([],[])   % Empty cell for modified column
  195	     ]).
  196graph_row(Options, Graph) -->
  197	{ graph_triples(Graph, Count)
  198
  199	},
  200	html([ td(\graph_link(Graph)),
  201	       \nc('~D', Count),
  202	       \modified(Graph),
  203	       td(style('text-align:center'), \persistency(Graph)),
  204	       \graph_checkbox(Graph, Options)
  205	     ]).
  206
  207modified(Graph) -->
  208	{ rdf_graph_property(Graph, source_last_modified(Time)),
  209	  format_time(string(Modified), '%+', Time), !
  210	},
  211	html(td([class('file-time')], Modified)).
  212modified(Graph) -->
  213	{ rdf_journal_file(Graph, File),
  214	  time_file(File, Time),
  215	  format_time(string(Modified), '%+', Time)
  216	},
  217	html(td([class('file-time')], Modified)).
  218modified(_Graph) -->
  219	html(td([class('file-time')], '')).
  220
  221graph_link(Graph) -->
  222	{ http_link_to_id(list_graph, [graph=Graph], URI)
  223	},
  224	html(a(href(URI), Graph)).
  225
  226persistency(Graph) -->
  227	{ rdf_graph_property(Graph, persistent(true)) }, !,
  228	snapshot(Graph),
  229	journal(Graph).
  230persistency(_) -->
  231	{ http_absolute_location(icons('volatile.png'), Img, [])
  232	},
  233	html(img([ class('in-text'),
  234		   title('Graph is not persistent'),
  235		   src(Img)
  236		 ])).
  237
  238snapshot(Graph) -->
  239	{ rdf_snapshot_file(Graph, _),
  240	  http_absolute_location(icons('snapshot.png'), Img, [])
  241	},
  242	html(img([ class('in-text'),
  243		   title('Graph has persistent snapshot'),
  244		   src(Img)
  245		 ])).
  246snapshot(_) --> [].
  247
  248journal(Graph) -->
  249	{ rdf_journal_file(Graph, _),
  250	  http_absolute_location(icons('journal.png'), Img, [])
  251	},
  252	html(img([ class('in-text'),
  253		   title('Graph has a journal'),
  254		   src(Img)
  255		 ])).
  256journal(_) --> [].
 graph_actions(+Options0, -Options)
 multigraph_actions(+Options)
Deal with actions on multiple graphs.
  263graph_actions(Options, [show_actions(true)|Options]) :-
  264	logged_on(User), !,
  265	catch(check_permission(User, write(_, unload(user))), _, fail), !.
  266graph_actions(Options, Options).
  267
  268graph_checkbox(Graph, Options) -->
  269	{ option(show_actions(true), Options) }, !,
  270	html(td(class('no-border'),
  271		input([type(checkbox),name(graph),value(Graph),
  272		       class('graph-select')]))).
  273graph_checkbox(_, _) --> [].
  274
  275multigraph_actions(Options) -->
  276	{ option(show_actions(true), Options), !,
  277	  findall(Action-Format,
  278		  clause(graph_action(Action,Format,_), _),
  279		  Pairs)
  280	},
  281	html([ ul([ class('multi-graph-actions')
  282		  ],
  283		  \li_graph_actions(Pairs))
  284	     ]).
  285multigraph_actions(_) --> [].
  286
  287li_graph_actions([]) --> [].
  288li_graph_actions([H|T]) --> li_graph_action(H), li_graph_actions(T).
  289
  290li_graph_action(Action-Format) -->
  291	{ atomic_list_concat([Pre,Post], '~w', Format) },
  292	html(li([ Pre,
  293		  input([ type(submit), name(action), value(Action) ]),
  294		  Post
  295		])).
  296
  297mgraph_action_script -->
  298	html_requires(jquery),
  299	js_script({|javascript||
  300function showActions(time) {
  301  if ( time === undefined ) time = 400;
  302  var val = [];
  303  $('.graph-table :checkbox:checked').each(function(i) {
  304    val[i] = $(this).val();
  305  });
  306  if ( val.length == 0 )
  307    $(".multi-graph-actions").hide(time);
  308  else
  309    $(".multi-graph-actions").show(time);
  310}
  311
  312$(function() {
  313  showActions(0);
  314  $(".graph-table .graph-select").on('click', showActions);
  315});
  316		   |}).
 multigraph_action(Request)
HTTP Handler for user actions on multiple graphs.
  322multigraph_action(Request) :-
  323	findall(Action, clause(graph_action(Action,_,_), _), Actions),
  324	http_parameters(Request,
  325			[ graph(Graphs, [list(atom)]),
  326			  action(Action, [oneof(Actions)])
  327			]),
  328	clause(graph_action(Action,Format,_), _),
  329	api_action(Request, multigraph_action(Action, Graphs), html,
  330		   Format-[Action]).
  331
  332multigraph_action(Action, Graphs) :-
  333	forall(member(Graph, Graphs),
  334	       ( print_message(informational,
  335			       format('Processing ~w ...', [Graph])),
  336		 graph_action(Action, _, Graph))).
  337
  338graph_action('Delete', '~w selected graphs', Graph) :-
  339	rdf_unload_graph(Graph).
  340graph_action(volatile, 'Make selected graphs ~w', Graph) :-
  341	rdf_persistency(Graph, false).
  342graph_action(persistent, 'Make selected graphs ~w', Graph) :-
  343	rdf_persistency(Graph, true).
  344graph_action('Merge journals', '~w for selected graphs', Graph) :-
  345	rdf_flush_journals([graph(Graph)]).
 list_graph(+Request)
HTTP handler that provides information about an individual RDF graph. The output is an HTML table.
  353list_graph(Request) :-
  354	http_parameters(Request,
  355			[ graph(Graph,
  356				[description('Name of the graph to describe')])
  357			]),
  358	(   rdf_graph(Graph)
  359	->  true
  360	;   http_404([], Request)
  361	),
  362	reply_html_page(cliopatria(default),
  363			title('RDF Graph ~w'-[Graph]),
  364			[ h1('Summary information for graph "~w"'-[Graph]),
  365			  \simple_search_form([ id(ac_find_in_graph),
  366						filter(graph(Graph)),
  367						label('Search this graph')
  368					      ]),
  369			  \graph_info(Graph),
  370			  \graph_as_resource(Graph, []),
  371			  \graph_persistency(Graph),
  372			  \graph_actions(Graph),
  373			  \uri_info(Graph, Graph)
  374			]).
 graph_info(+Graph)//
HTML component that shows -statistical- properties about the given named graph.
  381graph_info(Graph) -->
  382	html_property_table(row(P,V),
  383			    graph_property(Graph,P,V)).
  384
  385:- dynamic
  386	graph_property_cache/3.  387
  388graph_property(Graph, P, V) :-
  389	graph_property_cache(Graph, MD5, Pairs),
  390	rdf_md5(Graph, MD5), !,
  391	member(P0-V, Pairs),
  392	P =.. [P0,Graph].
  393graph_property(Graph, P, V) :-
  394	retractall(graph_property_cache(Graph, _, _)),
  395	findall(P-V, graph_property_nc(Graph, P, V), Pairs),
  396	rdf_md5(Graph, MD5),
  397	assert(graph_property_cache(Graph, MD5, Pairs)),
  398	member(P0-V, Pairs),
  399	P =.. [P0,Graph].
  400
  401graph_property_nc(Graph, source, Source) :-
  402	rdf_source(Graph, Source).
  403graph_property_nc(Graph, triples, int(Triples)) :-
  404	graph_triples(Graph, Triples).
  405graph_property_nc(Graph, predicate_count, int(Count)) :-
  406	aggregate_all(count, predicate_in_graph(Graph, _P), Count).
  407graph_property_nc(Graph, subject_count, int(Count)) :-
  408	aggregate_all(count, subject_in_graph(Graph, _P), Count).
  409graph_property_nc(Graph, bnode_count, int(Count)) :-
  410	aggregate_all(count, bnode_in_graph(Graph, _P), Count).
  411graph_property_nc(Graph, type_count, int(Count)) :-
  412	aggregate_all(count, type_in_graph(Graph, _P), Count).
  413
  414predicate_in_graph(Graph, P) :-
  415	rdf_current_predicate(P),
  416	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.
  425subject_in_graph(Graph, S) :-
  426	graph_triples(Graph, Count),
  427	rdf_statistics(triples(Total)),
  428	Count * 10 > Total, !,		% Graph has more than 10% of triples
  429	rdf_subject(S),
  430	once(rdf(S, _, _, Graph)).
  431subject_in_graph(Graph, S) :-
  432	findall(S, rdf(S,_,_,Graph), List),
  433	sort(List, Subjects),
  434	member(S, Subjects).
  435
  436bnode_in_graph(Graph, S) :-
  437	graph_triples(Graph, Count),
  438	rdf_statistics(triples(Total)),
  439	Count * 10 > Total, !,
  440	rdf_subject(S),
  441	rdf_is_bnode(S),
  442	once(rdf(S, _, _, Graph)).
  443bnode_in_graph(Graph, S) :-
  444	findall(S, (rdf(S,_,_,Graph), rdf_is_bnode(S)), List),
  445	sort(List, Subjects),
  446	member(S, Subjects).
 type_in_graph(+Graph, -Class)
Generate the unique types in Graph
  454:- thread_local
  455	type_seen/1.  456
  457type_in_graph(Graph, Class) :-
  458	call_cleanup(type_in_graph2(Graph, Class),
  459		     retractall(type_seen(_))).
  460
  461type_in_graph2(Graph, Class) :-
  462	subject_in_graph(Graph, S),
  463	(   rdf_has(S, rdf:type, Class)
  464	*-> true
  465	;   rdf_equal(Class, rdfs:'Resource')
  466	),
  467	(   type_seen(Class)
  468	->  fail
  469	;   assert(type_seen(Class))
  470	).
 graph_persistency(+Graph)//
Show information about the persistency of the graph
  477graph_persistency(Graph) -->
  478	{ rdf_graph_property(Graph, persistent(true)),
  479	  (   rdf_journal_file(Graph, _)
  480	  ;   rdf_snapshot_file(Graph, _)
  481	  )
  482	}, !,
  483	html([ h1('Persistency information'),
  484	       table(class(block),
  485		     [ tr([ td(class('no-border'),[]),
  486			    th('File'), th('Size'),th('Modified'),
  487			    td(class('no-border'),[])
  488			  ]),
  489		       \graph_shapshot(Graph),
  490		       \graph_journal(Graph)
  491		     ])
  492	     ]).
  493graph_persistency(Graph) -->
  494	{ rdf_graph_property(Graph, persistent(true))
  495	}, !,
  496	html([ h1('Persistency information'),
  497	       p('The graph has no associated persistency files')
  498	     ]).
  499graph_persistency(_Graph) -->
  500	[].
  501
  502graph_shapshot(Graph) -->
  503	{ rdf_snapshot_file(Graph, File)
  504	},
  505	html(tr([ th(class('file-role'), 'Snapshot'),
  506		  \file_info(File)
  507		])).
  508graph_shapshot(_) --> [].
  509
  510
  511graph_journal(Graph) -->
  512	{ rdf_journal_file(Graph, File)
  513	},
  514	html(tr([ th(class('file-role'), 'Journal'),
  515		  \file_info(File),
  516		  \flush_journal_button(Graph)
  517		])).
  518graph_journal(_) --> [].
  519
  520flush_journal_button(Graph) -->
  521	{ http_link_to_id(flush_journal, [], HREF)
  522	},
  523	html(td(class('no-border'),
  524		form(action(HREF),
  525		     [ input([type(hidden), name(graph), value(Graph)]),
  526		       input([type(hidden), name(resultFormat), value(html)]),
  527		       input([type(submit), value('Merge journal')])
  528		     ]))).
  529
  530
  531file_info(File) -->
  532	{ size_file(File, Size),
  533	  time_file(File, Time),
  534	  format_time(string(Modified), '%+', Time)
  535	},
  536	html([ td(class('file-name'), File),
  537	       td(class('int'), \n(human, Size)),
  538	       td(class('file-time'), Modified)
  539	     ]).
 graph_actions(+Graph)// is det
Provide a form for basic actions on the graph
  546graph_actions(Graph) -->
  547	html([ h2('Actions'),
  548	       ul(class(graph_actions),
  549		  [ \li_export_graph(Graph, show),
  550		    \li_export_graph(Graph, download),
  551		    \li_schema_graph(Graph),
  552		    \li_delete_graph(Graph),
  553		    \li_persistent_graph(Graph)
  554		  ])
  555	     ]).
  556
  557li_delete_graph(Graph) -->
  558	{ logged_on(User),
  559	  catch(check_permission(User, write(_, unload(Graph))), _, fail), !,
  560	  http_link_to_id(unload_graph, [], Action)
  561	},
  562	html(li(form(action(Action),
  563		     [ input([type(hidden), name(graph), value(Graph)]),
  564		       input([type(hidden), name(resultFormat), value(html)]),
  565		       input([class(gaction), type(submit), value('Delete')]),
  566		       ' this graph'
  567		     ]))).
  568li_delete_graph(_) --> [].
  569
  570li_persistent_graph(Graph) -->
  571	{ logged_on(User),
  572	  catch(check_permission(User, write(_, persistent(Graph))), _, fail), !,
  573	  http_link_to_id(modify_persistency, [], Action),
  574	  (   rdf_graph_property(Graph, persistent(true))
  575	  ->  Op = (volatile),   Value = off
  576	  ;   Op = (persistent), Value = on
  577	  )
  578	}, !,
  579	html(li(form(action(Action),
  580		     [ input([type(hidden), name(graph), value(Graph)]),
  581		       input([type(hidden), name(resultFormat), value(html)]),
  582		       input([type(hidden), name(persistent), value(Value)]),
  583		       'Make this graph ',
  584		       input([class(gaction), type(submit), value(Op)])
  585		     ]))).
  586li_persistent_graph(_) --> [].
  587
  588li_schema_graph(Graph) -->
  589	{ http_link_to_id(export_graph_schema, [], Action),
  590	  download_options(show, Label, MimeType, Title)
  591	},
  592	html(li(form(action(Action),
  593		     [ input([type(hidden), name(graph), value(Graph)]),
  594		       input([type(hidden), name(mimetype), value(MimeType)]),
  595		       'Compute a schema for this graph and ',
  596		       input([class(saction), type(submit), value(Label),
  597			      title(Title)
  598			     ]),
  599		       ' the result as ',
  600		       \dl_format_menu
  601		     ]))).
  602
  603li_export_graph(Graph, How) -->
  604	{ http_link_to_id(export_graph, [], Action),
  605	  download_options(How, Label, MimeType, Title)
  606	},
  607	html(li(form(action(Action),
  608		     [ input([type(hidden), name(graph), value(Graph)]),
  609		       input([type(hidden), name(mimetype), value(MimeType)]),
  610		       input([class(gaction), type(submit), value(Label),
  611			      title(Title)
  612			     ]),
  613		       ' this graph as ',
  614		       \dl_format_menu
  615		     ]))).
  616
  617download_options(show,     'Show',     'text/plain',
  618		 'Returns graph with MIME-type text/plain, \n\c
  619		  so it will be displayed in your browser').
  620download_options(download, 'Download', default,
  621		 'Return graph with its RDF MIME-type, \n\c
  622		  so most browsers will save it').
  623
  624dl_format_menu -->
  625	html(select(name(format),
  626		    [ option([value(turtle),selected],  'Turtle'),
  627		      option([value(canonical_turtle)], 'Canonical Turtle'),
  628		      option([value(rdfxml)],           'RDF/XML')
  629		    ])).
 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.
  638list_classes(Request) :-
  639	http_parameters(Request,
  640			[ graph(Graph, [description('Name of the graph')])
  641			]),
  642	types_in_graph(Graph, Map),
  643	sort_pairs_by_label(Map, Sorted),
  644	reply_html_page(cliopatria(default),
  645			title('Classes in graph ~w'-[Graph]),
  646			[ h1(['Classes in graph ', \graph_link(Graph)]),
  647			  \class_table(Sorted, Graph, [])
  648			]).
  649
  650class_table(Pairs, Graph, Options) -->
  651	{ option(top_max(TopMax), Options, 500),
  652	  option(top_max(BottomMax), Options, 500)
  653	},
  654	html_requires(css('rdf.css')),
  655	html(table(class(block),
  656		   [ \class_table_header
  657		   | \table_rows_top_bottom(class_row(Graph), Pairs,
  658					    TopMax, BottomMax)
  659		   ])).
  660
  661class_table_header -->
  662	html(tr([ th('Class'),
  663		  th('#Instances')
  664		])).
  665
  666class_row(Graph, Class) -->
  667	{ atom(Class), !,
  668	  findall(I, rdf_has(I, rdf:type, Class, Graph), IL),
  669	  sort(IL, Classes),
  670	  length(Classes, InstanceCount)
  671	},
  672	class_row(Graph, Class-InstanceCount).
  673class_row(Graph, Class-InstanceCount) -->
  674	{ (   var(Graph)
  675	  ->  Params = [class(Class)]
  676	  ;   Params = [graph(Graph), class(Class)]
  677	  ),
  678	  http_link_to_id(list_instances, Params, ILink)
  679	},
  680	html([ td(\rdf_link(Class, [role(class)])),
  681	       td(class(int), a(href(ILink), InstanceCount))
  682	     ]).
 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.
  689types_in_graph(Graph, Map) :-
  690	findall(S, subject_in_graph(Graph, S), Subjects),
  691	types(Subjects, Pairs),
  692	transpose_pairs(Pairs, TypeSubj),
  693	group_pairs_by_key(TypeSubj, TypeSubjs),
  694	maplist(instance_count, TypeSubjs, Map).
  695
  696types([], []).
  697types([S|T0], Types) :-
  698	call_det(type_of(S,C), Det), !,
  699	(   Det == true
  700	->  Types = [S-C|T],
  701	    types(T0, T)
  702	;   findall(C2, type_of(S,C2), Cs),
  703	    multi_class(Cs, S, Types, PT),
  704	    types(T0, PT)
  705	).
  706
  707multi_class([], _, Pairs, Pairs).
  708multi_class([H|T], S, [S-H|Pairs], PT) :-
  709	multi_class(T, S, Pairs, PT).
  710
  711
  712type_of(Subject, Type) :-
  713	(   rdf_has(Subject, rdf:type, Type)
  714	*-> true
  715	;   rdf_equal(Type, rdfs:'Resource')
  716	).
  717
  718:- meta_predicate
  719	call_det(0, -).  720
  721call_det(G, Det) :-
  722	call(G),
  723	deterministic(Det).
  724
  725instance_count(Type-Instances, Type-Count) :-
  726	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.
  734instance_in_graph(Graph, Class, any, S, C) :- !,
  735	instance_in_graph(Graph, Class, S, C).
  736instance_in_graph(Graph, Class, bnode, S, C) :- !,
  737	freeze(S, rdf_is_bnode(S)),
  738	instance_in_graph(Graph, Class, S, C).
  739
  740
  741instance_in_graph(Graph, Class, S, C) :-
  742	var(Class), !,
  743	subject_in_graph(Graph, S),
  744	property_count(Graph, S, C).
  745instance_in_graph(Graph, Class, S, C) :-
  746	rdf_equal(Class, rdfs:'Resource'), !,
  747	(   rdf_has(S, rdf:type, Class),
  748	    once(rdf(S, _, _, Graph))
  749	;   subject_in_graph(Graph, S),
  750	    \+ rdf_has(S, rdf:type, _)
  751	),
  752	property_count(Graph, S, C).
  753instance_in_graph(Graph, Class, S, C) :-
  754	rdf_has(S, rdf:type, Class),
  755	once(rdf(S, _, _, Graph)),
  756	property_count(Graph, S, C).
  757
  758property_count(Graph, S, Count) :-
  759	aggregate_all(count, rdf(S, _, _, Graph), Count).
 graph_as_resource(+Graph, Options)// is det
Show resource info for a graph if it is described.
  765graph_as_resource(Graph, Options) -->
  766	{ (   rdf(Graph, _, _)
  767	  ;   rdf(_, Graph, _)
  768	  ;   rdf(_, _, Graph)
  769	  ), !
  770	},
  771	html([ h2([ 'Local view for "',
  772		    \location(Graph, _), '"'
  773		  ]),
  774	       \local_view(Graph, _, Options)
  775	     ]).
  776graph_as_resource(_, _) --> [].
  777
  778
  779		 /*******************************
  780		 *	  LIST INSTANCES	*
  781		 *******************************/
 list_instances(+Request)
HTTP handler that lists instances that satisfy certain criteria.
  787list_instances(Request) :-
  788	http_parameters(Request,
  789			[ class(Class,
  790				[ optional(true),
  791				  description('Limit to instances of this class')
  792				]),
  793			  graph(Graph,
  794				[ optional(true),
  795				  description('Limit to have at least \c
  796					       one property in graph')
  797				]),
  798			  type(Type,
  799			       [ oneof([any, bnode]),
  800				 default(any),
  801				 description('Any instance or only bnodes?')
  802			       ]),
  803			  resource_format(Format,
  804				[ default(DefaultFormat),
  805				  atom,
  806				  description('Display format as passed to rdf_link//2 ')
  807				]),
  808			  sortBy(Sort,
  809				 [ oneof([label,properties]),
  810				   default(label),
  811				   description('How to sort the result-table')
  812				 ])
  813			]),
  814	setting(resource_format, DefaultFormat),
  815	findall(I-PC, instance_in_graph(Graph, Class, Type, I, PC), IPairs),
  816	sort_pairs_by_label(IPairs, TableByName),
  817	(   Sort == properties
  818	->  reverse(TableByName, RevTableByName),
  819	    transpose_pairs(RevTableByName, FPairsUp),
  820	    reverse(FPairsUp, FPairsDown),
  821	    flip_pairs(FPairsDown, Table)
  822	;   Table = TableByName
  823	),
  824
  825	reply_html_page(cliopatria(default),
  826			title(\instance_table_title(Graph, Class, Sort)),
  827			[ h1(\html_instance_table_title(Graph, Class, Sort)),
  828			  \instance_table(Table, [resource_format(Format)])
  829			]).
  830
  831instance_table_title(Graph, Class, Sort) -->
  832	{ var(Class) }, !,
  833	html('Instances in ~w sorted by ~w'-
  834	     [Graph, Sort]).
  835instance_table_title(Graph, Class, Sort) -->
  836	{ rdf_display_label(Class, Label) },
  837	html('Instances of ~w in ~w sorted by ~w'-
  838	     [Label, Graph, Sort]).
  839
  840html_instance_table_title(Graph, Class, Sort) -->
  841	html([ 'Instances',
  842	       \of_class(Class),
  843	       \in_graph(Graph),
  844	       \sorted_by(Sort)
  845	     ]).
  846
  847of_class(Class) -->
  848	{ var(Class) }, !.
  849of_class(Class) -->
  850	html([' of class ', \rdf_link(Class, [role(class)])]).
  851
  852in_graph(Graph) -->
  853	{ var(Graph) }, !.
  854in_graph(Graph) -->
  855	html([' in graph ', \graph_link(Graph)]).
  856
  857sorted_by(Sort) -->
  858	html(' sorted by ~w'-[Sort]).
  859
  860
  861instance_table(Pairs, Options) -->
  862	{ option(top_max(TopMax), Options, 500),
  863	  option(top_max(BottomMax), Options, 500)
  864	},
  865	html_requires(css('rdf.css')),
  866	html(table(class(block),
  867		   [ \instance_table_header
  868		   | \table_rows_top_bottom(instance_row(Options), Pairs,
  869					    TopMax, BottomMax)
  870		   ])).
  871
  872instance_table_header -->
  873	html(tr([ th('Instance'),
  874		  th('#Properties')
  875		])).
  876
  877instance_row(Options, R-C) -->
  878	html([ td(\rdf_link(R, [role(inst)|Options])),
  879	       td(class(int), C)
  880	     ]).
  881
  882
  883		 /*******************************
  884		 *	     PREDICATES		*
  885		 *******************************/
 list_predicates(+Request)
List all predicates used in graph, sorted by label.
  891list_predicates(Request) :-
  892	http_parameters(Request,
  893			[ graph(Graph, [])
  894			]),
  895	findall(Pred, predicate_in_graph(Graph, Pred), Preds),
  896	sort_by_label(Preds, Sorted),
  897	reply_html_page(cliopatria(default),
  898			title('Predicates in graph ~w'-[Graph]),
  899			[ h1(['Predicates in graph ', \graph_link(Graph)]),
  900			  \predicate_table(Sorted, Graph, [])
  901			]).
  902
  903predicate_table(Preds, Graph, Options) -->
  904	{ option(top_max(TopMax), Options, 500),
  905	  option(bottom_max(BottomMax), Options, 500)
  906	},
  907	html_requires(css('rdf.css')),
  908	html(table(class(block),
  909		   [ \predicate_table_header
  910		   | \table_rows_top_bottom(predicate_row(Graph), Preds,
  911					    TopMax, BottomMax)
  912		   ])).
  913
  914predicate_table_header -->
  915	html(tr([ th('Predicate'),
  916		  th('#Triples'),
  917		  th('#Distinct subjects'),
  918		  th('#Distinct objects'),
  919		  th('Domain(s)'),
  920		  th('Range(s)')
  921		])).
 predicate_row(?Graph, +Pred) is det
  925predicate_row(Graph, Pred) -->
  926	{ predicate_statistics(Graph, Pred, Triples,
  927			       Subjects, Objects, Doms, Ranges),
  928	  (   var(Graph)
  929	  ->  Params = [predicate(Pred)]
  930	  ;   Params = [graph(Graph), predicate(Pred)]
  931	  ),
  932	  http_link_to_id(list_triples,   Params, PLink)
  933	},
  934	html([ td(\rdf_link(Pred, [role(pred)])),
  935	       td(class(int), a(href(PLink), Triples)),
  936	       \resources(Subjects, subject, Params, [role(subj)]),
  937	       \resources(Objects, object, Params, [role(obj)]),
  938	       \resources(Doms, domain, Params, [role(domain)]),
  939	       \resources(Ranges, range, Params, [role(range)])
  940	     ]).
  941
  942resources([], _, _, _) --> !,
  943	html(td(class(empty), -)).
  944resources([One], _, _, Options) --> !,
  945	html(td(\rdf_link(One, Options))).
  946resources(Many, What, Params, _) --> !,
  947	{ (   integer(Many)
  948	  ->  Count = Many
  949	  ;   length(Many, Count)
  950	  ),
  951	  http_link_to_id(list_predicate_resources, [side(What)|Params], Link)
  952	},
  953	html(td(class(int_c), a(href(Link), Count))).
  954
  955:- dynamic
  956	predicate_statistics_cache/8.  957
  958predicate_statistics(Graph, P, C, Subjects, Objects, Domains, Ranges) :-
  959	var(Graph), !,
  960	predicate_statistics_(Graph, P, C, Subjects, Objects, Domains, Ranges).
  961predicate_statistics(Graph, P, C, Subjects, Objects, Domains, Ranges) :-
  962	rdf_md5(Graph, MD5),
  963	predicate_statistics_cache(MD5, Graph, P, C,
  964				   Subjects, Objects, Domains, Ranges), !.
  965predicate_statistics(Graph, P, C, Subjects, Objects, Domains, Ranges) :-
  966	rdf_md5(Graph, MD5),
  967	debug(rdf_browse, 'Recomputing pred stats for ~p in ~w, MD5=~w',
  968	      [P, Graph, MD5]),
  969	retractall(predicate_statistics_cache(MD5, Graph, P, _,
  970					      _, _, _, _)),
  971	predicate_statistics_(Graph, P, C, SubjectL, ObjectL, DomainL, RangeL),
  972	res_summary(SubjectL, Subjects),
  973	res_summary(ObjectL, Objects),
  974	res_summary(DomainL, Domains),
  975	res_summary(RangeL, Ranges),
  976	assertz(predicate_statistics_cache(MD5, Graph, P, C,
  977					   Subjects, Objects, Domains, Ranges)).
  978
  979
  980res_summary([], []) :- !.
  981res_summary([One], [One]) :- !.
  982res_summary(Many, Count) :-
  983	length(Many, Count).
  984
  985
  986predicate_statistics_(Graph, P, C, Subjects, Objects, Domains, Ranges) :-
  987	findall(S-O, rdf(S,P,O,Graph), Pairs),
  988	length(Pairs, C),
  989	pairs_keys_values(Pairs, Ss, Os),
  990	sort(Ss, Subjects),
  991	sort(Os, Objects),
  992	resources_types(Subjects, Graph, Domains),
  993	resources_types(Objects, Graph, Ranges).
  994
  995resources_types(URIs, Graph, Types) :-
  996	findall(T, resource_type_in(URIs, Graph, T), TList),
  997	sort(TList, Types).
  998
  999resource_type_in(List, Graph, T) :-
 1000	member(URI, List),
 1001	resource_type(URI, Graph, T).
 resource_type(+URI, +Graph, -Type) is det
 1005resource_type(URI, Graph, T) :-
 1006	(   URI = literal(Lit)
 1007	->  (   Lit = type(T, _)
 1008	    ->	true
 1009	    ;	rdf_equal(T, rdfs:'Literal')
 1010	    )
 1011	;   rdf(URI, rdf:type, T, Graph)
 1012	*-> true
 1013	;   rdf_equal(T, rdfs:'Resource')
 1014	).
 1015
 1016
 1017		 /*******************************
 1018		 *	  LIST RESOURCES	*
 1019		 *******************************/
 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.

 1039list_predicate_resources(Request) :-
 1040	http_parameters(Request,
 1041			[ graph(Graph,
 1042				[ optional(true),
 1043				  description('Limit search to this graph')
 1044				]),
 1045			  predicate(Pred,
 1046				    [ description('Predicate to list')
 1047				    ]),
 1048			  side(Which,
 1049			       [ oneof([subject,object,domain,range]),
 1050				 description('Relation to the predicate (see docs)')
 1051			       ]),
 1052			  sortBy(Sort,
 1053				 [ oneof([label,frequency]),
 1054				   default(frequency),
 1055				   description('How to sort results')
 1056				 ]),
 1057			  skosmap(SkosMap,
 1058				  [ boolean,
 1059				    optional(true),
 1060				    description('Show SKOS concepts for literals')
 1061				  ])
 1062			]),
 1063	do_skos(SkosMap, Which, Pred),
 1064	findall(R, predicate_resource(Graph, Pred, Which, R), Set),
 1065	term_frequency_list(Set, FPairs),
 1066	sort_pairs_by_label(FPairs, TableByName),
 1067	(   Sort == frequency
 1068	->  reverse(TableByName, RevTableByName),
 1069	    transpose_pairs(RevTableByName, FPairsUp),
 1070	    reverse(FPairsUp, FPairsDown),
 1071	    flip_pairs(FPairsDown, Table)
 1072	;   Table = TableByName
 1073	),
 1074
 1075	pred_resource_options(Pred, Which, Options),
 1076
 1077	reply_html_page(cliopatria(default),
 1078			title(\resource_table_title(Graph, Pred, Which, Sort)),
 1079			[ h1(\html_resource_table_title(Graph, Pred, Which,
 1080							Sort, SkosMap)),
 1081			  \resource_frequency_table(Table,
 1082						    [ skosmap(SkosMap),
 1083						      predicate(Pred),
 1084						      side(Which),
 1085						      sort(Sort)
 1086						    | Options
 1087						    ])
 1088			]).
 1089
 1090pred_resource_options(_, domain, [label('Class')]) :- !.
 1091pred_resource_options(_, range, [label('Class')]) :- !.
 1092pred_resource_options(_, _, []).
 1093
 1094do_skos(SkosMap, _, _) :-
 1095	nonvar(SkosMap), !.
 1096do_skos(SkosMap, object, Pred) :-
 1097	\+ rdf(_, Pred, literal(_)), !,
 1098	SkosMap = false.
 1099do_skos(SkosMap, object, _) :-
 1100	rdfs_individual_of(_, skos:'ConceptScheme'), !,
 1101	SkosMap = true.
 1102do_skos(false, _, _).
 1103
 1104
 1105resource_table_title(Graph, Pred, Which, Sort) -->
 1106	{ rdf_display_label(Pred, PLabel)
 1107	},
 1108	html('Distinct ~ws for ~w in ~w sorted by ~w'-
 1109	     [Which, PLabel, Graph, Sort]
 1110	     ).
 1111
 1112html_resource_table_title(Graph, Pred, Which, Sort, SkosMap) -->
 1113	html([ 'Distinct ~ws'-[Which],
 1114	       \for_predicate(Pred),
 1115	       \in_graph(Graph),
 1116	       \sorted_by(Sort),
 1117	       \showing_skosmap(SkosMap)
 1118	     ]).
 1119
 1120for_predicate(Pred) -->
 1121	{ var(Pred) }, !.
 1122for_predicate(Pred) -->
 1123	html([' for predicate ', \rdf_link(Pred, [role(pred)])]).
 1124
 1125showing_skosmap(true) --> !,
 1126	html(' with mapping to SKOS').
 1127showing_skosmap(_) --> [].
 1128
 1129resource_frequency_table(Pairs, Options) -->
 1130	{ option(top_max(TopMax), Options, 500),
 1131	  option(top_max(BottomMax), Options, 500),
 1132	  option(predicate(Pred), Options, _),
 1133	  option(side(Side), Options)
 1134	},
 1135	html_requires(css('rdf.css')),
 1136	html(table(class(block),
 1137		   [ \resource_table_header(Options)
 1138		   | \table_rows_top_bottom(resource_row(Pred, Side, [role(pred)|Options]), Pairs,
 1139					    TopMax, BottomMax)
 1140		   ])).
 1141
 1142resource_table_header(Options) -->
 1143	{ option(label(Label), Options, 'Resource'),
 1144	  (   option(sort(Sort), Options)
 1145	  ->  (   Sort == frequency
 1146	      ->  A1 = [],
 1147		  A2 = [class(sorted)]
 1148	      ;	  A1 = [class(sorted)],
 1149		  A2 = []
 1150	      )
 1151	  ;   A1 = [],
 1152	      A2 = []
 1153	  )
 1154	},
 1155	html(tr([ th(A1, Label),
 1156		  th(A2, 'Count'),
 1157		  \skosmap_head(Options)
 1158		])).
 1159
 1160skosmap_head(Options) -->
 1161	{ option(skosmap(true), Options) }, !,
 1162	html(th('SKOS mapping')).
 1163skosmap_head(_) --> [].
 1164
 1165resource_row(Pred, object, Options, R-C) --> !,
 1166	{ object_param(R, Param),
 1167	  http_link_to_id(list_triples_with_object,
 1168	       [ p(Pred),
 1169		 Param
 1170	       ], HREF)
 1171	},
 1172	html([ td(\rdf_link(R, Options)),
 1173	       td(class(int), a(href(HREF), C)),
 1174	       \skosmap(R, Options)
 1175	     ]).
 1176resource_row(Pred, Side, Options, R-C) -->
 1177	{ domain_range_parameter(Side, R, Param), !,
 1178	  http_link_to_id(list_triples,
 1179	       [ predicate(Pred),
 1180		 Param
 1181	       ], HREF)
 1182	},
 1183	html([ td(\rdf_link(R, Options)),
 1184	       td(class(int), a(href(HREF), C)),
 1185	       \skosmap(R, Options)
 1186	     ]).
 1187resource_row(_, _, Options, R-C) -->
 1188	html([ td(\rdf_link(R, Options)),
 1189	       td(class(int), C),
 1190	       \skosmap(R, Options)
 1191	     ]).
 1192
 1193object_param(R, r=R) :-
 1194	atom(R), !.
 1195object_param(L, l=A) :-
 1196	term_to_atom(L, A).
 1197
 1198domain_range_parameter(domain, R, domain(R)).
 1199domain_range_parameter(range,  R, range(R)).
 skosmap(+Literal, +Options)//
Component that emits a td cell with links to SKOS concepts that are labeled Literal.
 1206skosmap(Literal, Options) -->
 1207	{ Literal = literal(_),
 1208	  option(skosmap(true), Options),
 1209	  findall(Concept-Scheme, skos_find(Literal, Concept, Scheme), Pairs),
 1210	  Pairs \== [],
 1211	  sort_pairs_by_label(Pairs, Sorted)
 1212	},
 1213	html(td(\skos_references(Sorted))).
 1214skosmap(_, _) --> [].
 1215
 1216skos_find(Literal, Concept, Scheme) :-
 1217	rdf_has(Concept, skos:prefLabel, Literal),
 1218	rdf_has(Concept, skos:inScheme, Scheme).
 1219
 1220skos_references([]) --> [].
 1221skos_references([H|T]) -->
 1222	skos_reference(H),
 1223	(   { T == [] }
 1224	->  []
 1225	;   html('; '),
 1226	    skos_references(T)
 1227	).
 1228
 1229skos_reference(Concept-Scheme) -->
 1230	html([\rdf_link(Concept, [role(concept)]), ' in ', \rdf_link(Scheme, [role(scheme)])]).
 1231
 1232
 1233flip_pairs([], []).
 1234flip_pairs([Key-Val|Pairs], [Val-Key|Flipped]) :-
 1235	flip_pairs(Pairs, Flipped).
 1236
 1237predicate_resource(Graph, Pred, subject, R) :- !,
 1238	rdf(R, Pred, _, Graph).
 1239predicate_resource(Graph, Pred, object, R) :- !,
 1240	rdf(_, Pred, R, Graph).
 1241predicate_resource(Graph, Pred, domain, D) :- !,
 1242	rdf(R, Pred, _, Graph),
 1243	rdf(R, rdf:type, D, Graph).
 1244predicate_resource(Graph, Pred, range, R) :-
 1245	rdf(_, Pred, O, Graph),
 1246	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.
 1254term_frequency_list(Resources, Pairs) :-
 1255	msort(Resources, Sorted),
 1256	fpairs(Sorted, Pairs).
 1257
 1258fpairs([], []).
 1259fpairs([H|T0], [H-C|T]) :-
 1260	pick_same(T0, T1, H, 1, C),
 1261	fpairs(T1, T).
 1262
 1263pick_same([H1|T0], L, H, F0, F) :-
 1264	H == H1, !,
 1265	F1 is F0 + 1,
 1266	pick_same(T0, L, H, F1, F).
 1267pick_same(L, L, _, F, F).
 1268
 1269
 1270		 /*******************************
 1271		 *    LIST A SINGLE RESOURCE	*
 1272		 *******************************/
 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.
 1282list_resource(Request) :-
 1283	http_parameters(Request,
 1284			[ r(URI,
 1285			    [ description('URI to describe')]),
 1286			  sorted(Sorted,
 1287				 [ oneof([default,none]),
 1288				   default(default),
 1289				   description('How to sort properties')
 1290				 ]),
 1291			  graph(Graph,
 1292				[ optional(true),
 1293				  description('Limit to properties from graph')
 1294				]),
 1295			  resource_format(Format,
 1296				[ default(DefaultFormat),
 1297				  atom,
 1298				  description('Display format as passed to rdf_link//2 ')
 1299				]),
 1300			  raw(Raw,
 1301			      [ default(false),
 1302				boolean,
 1303				description('If true, omit application hook')
 1304			      ])
 1305			]),
 1306	setting(resource_format, DefaultFormat),
 1307	rdf_display_label(URI, Label),
 1308	reply_html_page(cliopatria(default),
 1309			title('Resource ~w'-[Label]),
 1310			\list_resource(URI,
 1311				       [ graph(Graph),
 1312					 sorted(Sorted),
 1313					 raw(Raw),
 1314					 resource_format(Format)
 1315				       ])).
 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.
 1335:- multifile
 1336	cliopatria:list_resource//1. 1337
 1338list_resource(URI, Options) -->
 1339	{ \+ option(raw(true), Options) },
 1340	(   cliopatria:list_resource(URI, Options)
 1341	->  []
 1342	;   cliopatria:list_resource(URI) % deprecated
 1343	).
 1344list_resource(URI, Options) -->
 1345	{ option(graph(Graph), Options, _)
 1346	},
 1347	html([ h1([ 'Local view for "',
 1348		    \location(URI, Graph), '"'
 1349		  ]),
 1350	       \define_prefix(URI),
 1351	       \local_view(URI, Graph, Options),
 1352	       p(\as_object(URI, Graph)),
 1353	       p(\as_graph(URI)),
 1354	       \uri_info(URI, Graph)
 1355	     ]).
 define_prefix(+URI)//
Allow defining a new prefix if the resource is not covered by a prefix.
 1362define_prefix(URI) -->
 1363	{ rdf_global_id(_Prefix:_Local, URI) }, !.
 1364define_prefix(URI) -->
 1365	{ iri_xml_namespace(URI, Namespace, LocalName),
 1366	  LocalName \== '',
 1367	  http_link_to_id(add_prefix, [], Action)
 1368	},
 1369	html(form(action(Action),
 1370		  ['No prefix for ', a(href(Namespace),Namespace), '. ',
 1371		   \hidden(uri, Namespace),
 1372		   input([name(prefix), size(8),
 1373			  title('Short unique abbreviation')
 1374			 ]),
 1375		   input([type(submit), value('Add prefix')])
 1376		  ])).
 1377define_prefix(_) -->			% Not a suitable URI.  Warn?
 1378	[].
 location(+URI, ?Graph) is det
Show the URI. If the URI is a blank node, show its context using Turtle notation.
 1386location(URI, _Graph) -->
 1387	{ rdf_is_bnode(URI), !,
 1388	  findall(Path, path_to_non_bnode(URI, Path), Paths),
 1389	  sort_by_length(Paths, PathsByLen),
 1390	  partition(starts_bnode, PathsByLen, StartsBNode, StartsReal),
 1391	  (   StartsReal = [Path|_]
 1392	  ->  true
 1393	  ;   last(StartsBNode, Path)
 1394	  )
 1395	},
 1396	bnode_location(Path).
 1397location(URI, _) -->
 1398	html(URI).
 1399
 1400bnode_location([P-URI]) --> !,
 1401	html([ '[', \rdf_link(P,  [role(pred)]), ' ',
 1402	            \rdf_link(URI,[role(bnode)]),
 1403	       ']'
 1404	     ]).
 1405bnode_location([P-URI|More]) --> !,
 1406	html([ '[', div(class(bnode_attr),
 1407			[ div(\rdf_link(P,  [ role(pred)])),
 1408			  div(\rdf_link(URI,[ role(bnode)]))
 1409			]), ' ',
 1410	       \bnode_location(More),
 1411	       ']'
 1412	     ]).
 1413bnode_location([URI|More]) --> !,
 1414	rdf_link(URI, [role(subj)]),
 1415	html(' '),
 1416	bnode_location(More).
 1417bnode_location([]) -->
 1418	[].
 1419
 1420path_to_non_bnode(URI, Path) :-
 1421	path_to_non_bnode_rev(URI, [URI], RevPath),
 1422	reverse(RevPath, Path).
 1423
 1424path_to_non_bnode_rev(URI, Seen, [P-URI|Path]) :-
 1425	(   rdf_is_bnode(URI),
 1426	    rdf(S, P, URI),
 1427	    \+ memberchk(S, Seen)
 1428	*-> path_to_non_bnode_rev(S, [S|Seen], Path)
 1429	;   fail
 1430	).
 1431path_to_non_bnode_rev(URI, _, [URI]).
 1432
 1433starts_bnode([URI|_]) :-
 1434	rdf_is_bnode(URI).
 1435
 1436sort_by_length(ListOfLists, ByLen) :-
 1437	map_list_to_pairs(length, ListOfLists, Pairs),
 1438	keysort(Pairs, Sorted),
 1439	pairs_values(Sorted, ByLen).
 as_graph(+URI) is det
Show the places where URI is used as a named graph
 1445as_graph(URI) --> { \+ rdf_graph(URI) }, !.
 1446as_graph(URI) -->
 1447	 html([ 'This resource is also a ',
 1448		a([href(location_by_id(list_graph)+'?graph='+encode(URI))],
 1449		  'named graph'),
 1450		'.']).
 as_object(+URI, +Graph) is det
Show the places where URI is used as an object.
 1457as_object(URI, Graph) -->
 1458	{ findall(S-P, rdf(S,P,URI,Graph), Pairs),
 1459	  sort(Pairs, Unique)
 1460	},
 1461	as_object_locations(Unique, URI, Graph).
 1462
 1463as_object_locations([], _URI, _) --> !,
 1464	html([ 'The resource does not appear as an object' ]).
 1465as_object_locations([S-P], URI, _) --> !,
 1466	html([ 'The resource appears as object in one triple:',
 1467	       blockquote(class(triple),
 1468			  [ '{ ',
 1469			    \rdf_link(S, [role(subj)]), ', ',
 1470			    \rdf_link(P, [role(pred)]), ', ',
 1471			    \rdf_link(URI, [role(obj)]),
 1472			    ' }'
 1473			  ])
 1474	     ]).
 1475as_object_locations(List, URI, Graph) --> !,
 1476	{ length(List, Len),
 1477	  (   var(Graph)
 1478	  ->  Extra = []
 1479	  ;   Extra = [graph=Graph]
 1480	  ),
 1481	  http_link_to_id(list_triples_with_object, [r=URI|Extra], Link)
 1482	},
 1483	html([ 'The resource appears as object in ',
 1484	       a(href(Link), [Len, ' triples'])
 1485	     ]).
 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.

 1501local_view(URI, Graph, Options) -->
 1502	{ option(top_max(TopMax), Options, 500),
 1503	  option(bottom_max(BottomMax), Options, 500),
 1504	  po_pairs(URI, Graph, Pairs, Options),
 1505	  lview_graphs(URI, Graph, Graphs)
 1506	},
 1507	(   { Pairs \== []
 1508	    }
 1509	->  html_requires(css('rdf.css')),
 1510	    html(table(class(block),
 1511		       [ \lview_header(Options)
 1512		       | \table_rows_top_bottom(lview_row(Options, URI, Graphs),
 1513						Pairs,
 1514						TopMax, BottomMax)
 1515		       ])),
 1516	    graph_footnotes(Graphs, Options)
 1517	;   { lod_uri_graph(URI, LODGraph),
 1518	      rdf_graph(LODGraph)
 1519	    }
 1520	->  html(p([ 'No triples for ', \show_link(URI), '. ',
 1521		     'Linked Data was loaded into ', \graph_link(LODGraph),
 1522		     '.'
 1523		   ]))
 1524	;   { sane_uri(URI) }
 1525	->  { http_link_to_id(lod_crawl, [], FetchURL),
 1526	      http_current_request(Request),
 1527	      memberchk(request_uri(Here), Request)
 1528	    },
 1529	    html(form(action(FetchURL),
 1530		      [ \hidden(r, URI),
 1531			\hidden(return_to, Here),
 1532			'No triples for ', \show_link(URI),
 1533			'.  Would you like to ',
 1534			input([ type(submit),
 1535				value('Query the Linked Data cloud')
 1536			      ]),
 1537			'?'
 1538		      ]))
 1539	;   html_requires(css('rdf.css')),
 1540	    html(p([ 'No triples for ', \show_link(URI),
 1541		     ' (unknown URI scheme).']))
 1542	).
 1543
 1544show_link(URI) -->
 1545	{ sane_uri(URI) }, !,
 1546	html(a(href(URI), 'this URI')).
 1547show_link(URI) -->
 1548	html(span(class('insecure-uri'), URI)).
 1549
 1550sane_uri(URI) :-
 1551	uri_components(URI, Components),
 1552	uri_data(scheme, Components, Scheme),
 1553	valid_scheme(Scheme),
 1554	uri_data(authority, Components, Authority),
 1555	nonvar(Authority).
 1556
 1557valid_scheme(http).
 1558valid_scheme(https).
 1559valid_scheme(ftp).
 1560valid_scheme(ftps).
 1561
 1562lview_header(Options) -->
 1563	{ option(sorted(Sorted), Options, default),
 1564	  alt_sorted(Sorted, Alt),
 1565	  http_current_request(Request),
 1566	  http_reload_with_parameters(Request, [sorted(Alt)], HREF)
 1567	},
 1568	html(tr([ th('Predicate'),
 1569		  th(['Value (sorted: ', a(href(HREF), Sorted), ')'])
 1570		])).
 1571
 1572alt_sorted(default, none).
 1573alt_sorted(none, default).
 1574
 1575
 1576lview_row(Options, S, Graphs, P-OList) -->
 1577	html([ td(class(predicate), \rdf_link(P, [role(pred)|Options])),
 1578	       td(class(object), \object_list(OList, S, P, Graphs, Options, 1))
 1579	     ]).
 1580
 1581object_list([], _, _, _, _, _) --> [].
 1582object_list([H|T], S, P, Graphs, Options, Row) -->
 1583	{ NextRow is Row + 1,
 1584	  obj_class(Row, Class)
 1585	},
 1586	html(div(class(Class),
 1587		 [ \rdf_link(H, [role(obj)|Options]),
 1588		   \graph_marks(S, P, H, Graphs)
 1589		 ])),
 1590	object_list(T, S, P, Graphs, Options, NextRow).
 1591
 1592obj_class(N, Class) :-
 1593	(   N mod 2 =:= 0
 1594	->  Class = even
 1595	;   Class = odd
 1596	).
 1597
 1598graph_marks(_,_,_,[_]) --> !.
 1599graph_marks(S,P,O,Graphs) -->
 1600	html(sup(class(graph), \graphs(S,P,O,Graphs))).
 1601
 1602graphs(S, P, O, Graphs) -->
 1603	{ findall(G, rdf(S,P,O,G:_), GL) },
 1604	graphs(GL, Graphs).
 1605
 1606graphs([], _) --> [].
 1607graphs([H|T], Graphs) -->
 1608	{ nth1(N, Graphs, H) -> true },
 1609	html(N),
 1610	(   { T == [] }
 1611	->  []
 1612	;   html(','),
 1613	    graphs(T, Graphs)
 1614	).
 graph_footnotes(+GraphList, +Options)//
Describe footnote marks in the local view table that indicate the origin of triples.
 1621graph_footnotes([], _Options) --> !.
 1622graph_footnotes([Graph], _Options) --> !,
 1623	html(p(class('graphs-used'),
 1624	       [ 'All properties reside in the graph ',
 1625		 \graph_link(Graph)
 1626	       ])).
 1627graph_footnotes(Graphs, Options) -->
 1628	html(p(class('graphs-used'),
 1629	       'Named graphs describing this resource:')),
 1630	graph_footnotes(Graphs, 1, Options).
 1631
 1632graph_footnotes([], _, _) --> [].
 1633graph_footnotes([H|T], N, Options) -->
 1634	html(div(class('graph-fn'),
 1635		 [ sup(class(graph), N),
 1636		   \graph_link(H)
 1637		 ])),
 1638	{ N2 is N + 1 },
 1639	graph_footnotes(T, N2, Options).
 lview_graphs(+Subject, ?Graph, -Graphs) is det
 1643lview_graphs(_Subject, Graph, Graphs) :-
 1644	nonvar(Graph), !,
 1645	Graphs = [Graph].
 1646lview_graphs(Subject, Graph, Graphs) :-
 1647	findall(Graph, rdf(Subject, _, _, Graph:_), Graphs0),
 1648	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.
 1656po_pairs(S, Graph, Pairs, Options) :-
 1657	option(sorted(none), Options), !,
 1658	findall(P-[O], rdf(S,P,O,Graph), Pairs).
 1659po_pairs(S, Graph, Pairs, _Options) :-
 1660	var(Graph), !,
 1661	findall(P-OL,
 1662		setof(O, rdf(S,P,O), OL),
 1663		Pairs0),
 1664	sort_po(Pairs0, Pairs).
 1665po_pairs(S, Graph, Pairs, _Options) :-
 1666	findall(P-OL,
 1667		setof(O, rdf(S,P,O,Graph), OL),
 1668		Pairs0),
 1669	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.
 1677sort_po(Pairs, Sorted) :-
 1678	map_list_to_pairs(po_key, Pairs, Keyed),
 1679	keysort(Keyed, KeySorted),
 1680	exclude(=(0-_), KeySorted, Remaining),
 1681	pairs_values(Remaining, Sorted).
 1682
 1683po_key(P-_, Key) :-
 1684	p_order(P, Key), !.
 1685po_key(P-_, Key) :-
 1686	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.
 1694:- rdf_meta
 1695	p_order(r,?). 1696
 1697p_order(P, Order) :-
 1698	cliopatria:predicate_order(P, Order), !.
 1699p_order(P, 100) :-
 1700	label_property(P), !.
 1701p_order(P, 110) :-
 1702	rdfs_subproperty_of(P, skos:altLabel), !.
 1703p_order(rdf:type,	  210).
 1704p_order(rdfs:subClassOf,  220).
 1705p_order(rdfs:domain,	  230).
 1706p_order(rdfs:range,	  240).
 1707p_order(rdfs:comment,	  310).
 1708p_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.
 1716uri_info(URI, Graph) -->
 1717	uri_class_info(URI, Graph),
 1718	uri_predicate_info(URI, Graph),
 1719	html(h2('Context graph')),
 1720	context_graph(URI, []).
 1721
 1722uri_class_info(URI, Graph) -->
 1723	{ rdf_current_predicate(URI)
 1724	}, !,
 1725	html(h2('Predicate statistics')),
 1726	predicate_table([URI], Graph, []).
 1727uri_class_info(_,_) --> [].
 1728
 1729uri_predicate_info(URI, Graph) -->
 1730	{ \+ \+ rdf(_, rdf:type, URI, Graph)
 1731	}, !,
 1732	html(h2('Class statistics')),
 1733	class_table([URI], Graph, []).
 1734uri_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.
 1752context_graph(URI, Options) -->
 1753	{ merge_options(Options, [style(_)], GraphOption),
 1754	  rdf_equal(owl:sameAs, SameAs)
 1755	},
 1756	html([ \graphviz_graph(context_graph(URI, GraphOption),
 1757			       [ object_attributes([width('100%')]),
 1758				 wrap_url(resource_link),
 1759				 graph_attributes([ rankdir('RL')
 1760						  ]),
 1761				 shape_hook(shape(URI, GraphOption)),
 1762				 bag_shape_hook(bag_shape(GraphOption)),
 1763				 label_hook(cliopatria:node_label),
 1764				 smash([SameAs])
 1765			       ])
 1766	     ]).
 1767
 1768:- public
 1769	shape/4,
 1770	bag_shape/3.
 shape(+Start, +Options, +URI, -Shape) is semidet
Specify GraphViz shape for URI. This predicate calls the hook cliopatria:node_shape/3.
 1777shape(Start, Options, URI, Shape) :-
 1778	cliopatria:node_shape(URI, Shape, [start(Start)|Options]), !.
 1779shape(Start, _Options, Start,
 1780      [ shape(tripleoctagon),style(filled),fillcolor('#ff85fd'),id(start) ]).
 bag_shape(+Options, +Members, -Shape) is semidet
Compute properties for a bag
 1786bag_shape(Options, Members, Shape) :-
 1787	cliopatria:bag_shape(Members, Shape, Options), !.
 1788bag_shape(_, _, []).
 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.

 1802context_graph(URI, Options, RDF) :-
 1803	cliopatria:context_graph(URI, RDF, Options), !.
 1804context_graph(URI, _Options, RDF) :-		% Compatibility
 1805	cliopatria:context_graph(URI, RDF), !.
 1806context_graph(URI, _, RDF) :-
 1807	findall(T, context_triple(URI, T), RDF0),
 1808	sort(RDF0, RDF1),
 1809	minimise_graph(RDF1, RDF2),		% remove inverse/symmetric/...
 1810	bagify_graph(RDF2, RDF3, Bags, []),	% Create bags of similar resources
 1811	append(RDF3, Bags, RDF).
 1812
 1813:- rdf_meta
 1814	transitive_context(r),
 1815	context(r). 1816
 1817context_triple(URI, Triple) :-
 1818	transitive_context(CP),
 1819	parents(URI, CP, Triples, [URI], 3),
 1820	member(Triple, Triples).
 1821context_triple(URI, Triple) :-
 1822	cliopatria:context_predicate(URI, R),
 1823	rdf_has(URI, R, O, P),
 1824	normalize_triple(rdf(URI, P, O), Triple).
 1825context_triple(URI, Triple) :-
 1826	context(R),
 1827	rdf_has(URI, R, O, P),
 1828	normalize_triple(rdf(URI, P, O), Triple).
 1829context_triple(URI, Triple) :-
 1830	context(R),
 1831	rdf_has(S, R, URI, P),
 1832	normalize_triple(rdf(S, P, URI), Triple).
 1833
 1834normalize_triple(rdf(S, inverse_of(P0), O),
 1835		 rdf(O, P, S)) :- !,
 1836	rdf_predicate_property(P0, inverse_of(P)).
 1837normalize_triple(RDF, RDF).
 1838
 1839
 1840
 1841parents(URI, Up, [Triple|T], Visited, MaxD) :-
 1842	succ(MaxD2, MaxD),
 1843	rdf_has(URI, Up, Parent, P),
 1844	normalize_triple(rdf(URI, P, Parent), Triple),
 1845	\+ memberchk(Parent, Visited),
 1846	parents(Parent, Up, T, [Parent|Visited], MaxD2).
 1847parents(_, _, [], _, _).
 1848
 1849transitive_context(owl:sameAs).
 1850transitive_context(rdfs:subClassOf).
 1851transitive_context(rdfs:subPropertyOf).
 1852transitive_context(skos:broader).
 1853transitive_context(P) :-
 1854	rdfs_individual_of(P, owl:'TransitiveProperty'),
 1855	rdf_predicate_property(P, rdfs_subject_branch_factor(BF)),
 1856	BF < 2.0.
 1857
 1858context(skos:related).
 1859context(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.
 1867list_triples(Request) :-
 1868	http_parameters(Request,
 1869			[ predicate(P,
 1870				    [ optional(true),
 1871				      description('Limit triples to this pred')]),
 1872			  graph(Graph, [ optional(true),
 1873					 description('Limit triples to this graph')
 1874				       ]),
 1875			  domain(Dom,  [ optional(true),
 1876					 description('Restrict to subjects of this class')
 1877				       ]),
 1878			  range(Range, [ optional(true),
 1879					 description('Restrict to objects of this class')
 1880				       ])
 1881			]),
 1882	(   atom(Dom)
 1883	->  findall(rdf(S,P,O), rdf_in_domain(S,P,O,Dom,Graph), Triples0)
 1884	;   atom(Range)
 1885	->  findall(rdf(S,P,O), rdf_in_range(S,P,O,Range,Graph), Triples0)
 1886	;   findall(rdf(S,P,O), rdf(S,P,O,Graph), Triples0)
 1887	),
 1888	sort(Triples0, Triples),
 1889	sort_triples_by_label(Triples, Sorted),
 1890	length(Sorted, Count),
 1891	(   var(P)
 1892	->  Title = 'Triples in graph ~w'-[Graph]
 1893	;   rdf_display_label(P, PLabel),
 1894	    Title = 'Triples for ~w in graph ~w'-[PLabel, Graph]
 1895	),
 1896	reply_html_page(cliopatria(default),
 1897			title(Title),
 1898			[ h1(\triple_header(Count, P, Dom, Range, Graph)),
 1899			  \triple_table(Sorted, P, [resource_format(nslabel)])
 1900			]).
 1901
 1902rdf_in_domain(S,P,O,Dom,Graph) :-
 1903	rdf(S, P, O, Graph),
 1904	rdf_has(S, rdf:type, Dom).
 1905
 1906rdf_in_range(S,P,O,Lit,Graph) :-
 1907	rdf_equal(rdfs:'Literal', Lit), !,
 1908	O = literal(_),
 1909	rdf(S, P, O, Graph).
 1910rdf_in_range(S,P,O,Rng,Graph) :-
 1911	rdf_equal(rdfs:'Resource', Rng), !,
 1912	rdf(S, P, O, Graph),
 1913	atom(O).
 1914rdf_in_range(S,P,O,Rng,Graph) :-
 1915	rdf(S, P, O, Graph),
 1916	rdf_has(O, rdf:type, Rng).
 1917
 1918
 1919triple_header(Count, Pred, Dom, Range, Graph) -->
 1920	html([ 'Table for the ~D triples'-[Count],
 1921	       \for_predicate(Pred),
 1922	       \with_domain(Dom),
 1923	       \with_range(Range),
 1924	       \in_graph(Graph)
 1925	     ]).
 1926
 1927with_domain(Dom) -->
 1928	{ var(Dom) }, !.
 1929with_domain(Dom) -->
 1930	html([' with domain ', \rdf_link(Dom, [role(domain)])]).
 1931
 1932with_range(Range) -->
 1933	{ var(Range) }, !.
 1934with_range(Range) -->
 1935	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.
 1942triple_table(Triples, Pred, Options) -->
 1943	{ option(top_max(TopMax), Options, 500),
 1944	  option(top_max(BottomMax), Options, 500)
 1945	},
 1946	html(table(class(block),
 1947		   [ \spo_header(Pred)
 1948		   | \table_rows_top_bottom(spo_row(Options, Pred), Triples,
 1949					    TopMax, BottomMax)
 1950		   ])).
 1951
 1952spo_header(P) -->
 1953	{ nonvar(P) },
 1954	html(tr([ th('Subject'),
 1955		  th('Object')
 1956		])).
 1957spo_header(_) -->
 1958	html(tr([ th('Subject'),
 1959		  th('Predicate'),
 1960		  th('Object')
 1961		])).
 1962
 1963spo_row(Options, Pred, rdf(S,_,O)) -->
 1964	{ nonvar(Pred) }, !,
 1965	html([ td(class(subject), \rdf_link(S, [role(subj)|Options])),
 1966	       td(class(object),  \rdf_link(O, [role(obj) |Options]))
 1967	     ]).
 1968spo_row(Options, _, rdf(S,P,O)) -->
 1969	html([ td(class(subject),   \rdf_link(S, [role(subj)|Options])),
 1970	       td(class(predicate), \rdf_link(P, [role(pred)|Options])),
 1971	       td(class(object),    \rdf_link(O, [role(obj) |Options]))
 1972	     ]).
 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.
 1982list_triples_with_object(Request) :-
 1983	http_parameters(Request,
 1984			[ r(RObject,   [optional(true),
 1985					description('Object as resource (URI)')
 1986				       ]),
 1987			  l(LObject,   [optional(true),
 1988					description('Object as literal (Prolog notation)')
 1989				       ]),
 1990			  p(P,         [optional(true),
 1991					description('Limit to a given predicate (URI)')
 1992				       ]),
 1993			  graph(Graph, [optional(true),
 1994					description('Limit to a given graph (URI)')
 1995				       ]),
 1996			  sortBy(Sort,
 1997				 [ oneof([label, subject, predicate]),
 1998				   default(label),
 1999				   description('How to sort the result')
 2000				 ])
 2001			]),
 2002	target_object(RObject, LObject, Object),
 2003	list_triples_with_object(Object, P, Graph, [sortBy(Sort)]).
 2004
 2005target_object(RObject, _LObject, RObject) :-
 2006	atom(RObject), !.
 2007target_object(_, LObject, Object) :-
 2008	atom(LObject), !,
 2009	term_to_atom(Object, LObject).
 2010target_object(_, _, _) :-
 2011	throw(existence_error(http_parameter, r)).
 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.
 2019list_triples_with_literal(Request) :-
 2020	http_parameters(Request,
 2021			[ q(Text,
 2022			    [optional(true),
 2023			     description('Object as resource (URI)')
 2024			    ])
 2025			]),
 2026	list_triples_with_object(literal(Text), _, _, [sortBy(subject)]).
 2027
 2028
 2029list_triples_with_object(Object, P, Graph, Options) :-
 2030	findall(S-P, rdf(S,P,Object,Graph), Pairs),
 2031	(   option(sortBy(label), Options)
 2032	->  sort_pairs_by_label(Pairs, Sorted)
 2033	;   option(sortBy(predicate), Options)
 2034	->  transpose_pairs(Pairs, Transposed), % flip pairs and sort on new key
 2035	    flip_pairs(Transposed, Sorted)      % flip back without sort
 2036	;   sort(Pairs, Sorted)
 2037	),
 2038	length(Pairs, Count),
 2039	label_of(Object, OLabel),
 2040	reply_html_page(cliopatria(default),
 2041			title('Triples with object ~w'-[OLabel]),
 2042			[ h1(\otriple_header(Count, Object, P, Graph, Options)),
 2043			  \otriple_table(Sorted, Object, [resource_format(nslabel)])
 2044			]).
 2045
 2046otriple_header(Count, Object, Pred, Graph, Options) -->
 2047	{ option(sortBy(SortBy), Options) },
 2048	html([ 'Table for the ~D triples'-[Count],
 2049	       \with_object(Object),
 2050	       \on_predicate(Pred),
 2051	       \in_graph(Graph),
 2052	       \sorted_by(SortBy)
 2053	     ]).
 2054
 2055with_object(Obj) -->
 2056	{ var(Obj)}, !.
 2057with_object(Obj) -->
 2058	html([' with object ', \rdf_link(Obj, [role(obj)])]).
 2059
 2060on_predicate(P) -->
 2061	{ var(P) }, !.
 2062on_predicate(P) -->
 2063	html([' on predicate ', \rdf_link(P, [role(pred)])]).
 2064
 2065
 2066otriple_table(SPList, Object, Options) -->
 2067	{ option(top_max(TopMax), Options, 500),
 2068	  option(top_max(BottomMax), Options, 500)
 2069	},
 2070	html(table(class(block),
 2071		   [ \sp_header(Object)
 2072		   | \table_rows_top_bottom(sp_row(Options,Object), SPList,
 2073					    TopMax, BottomMax)
 2074		   ])).
 2075
 2076sp_header(_) -->
 2077	html(tr([ th('Subject'),
 2078		  th('Predicate')
 2079		])).
 2080
 2081sp_row(Options, _O, S-P) -->
 2082	html([ td(class(subject),   \rdf_link(S, [role(subj)|Options])),
 2083	       td(class(predicate), \rdf_link(P, [role(pred)|Options]))
 2084	     ]).
 2085
 2086
 2087
 2088
 2089
 2090		 /*******************************
 2091		 *	      RDF UTIL		*
 2092		 *******************************/
 sort_by_label(+URIs, -Sorted) is det
Sort a list of URIs by their label using locale-based ordering.
 2098sort_by_label(URIs, Sorted) :-
 2099	map_list_to_pairs(label_sort_key, URIs, LabelPairs),
 2100	keysort(LabelPairs, SortedPairs),
 2101	pairs_values(SortedPairs, Sorted).
 2102
 2103label_sort_key(URI, Key) :-
 2104	label_of(URI, Label),
 2105	(   atom(Label)
 2106	->  collation_key(Label, Key)
 2107	;   Key = Label
 2108	).
 2109
 2110label_of(URI, Label) :-
 2111	rdf_is_resource(URI), !,
 2112	rdf_display_label(URI, Label).
 2113label_of(Literal, Label) :-
 2114	literal_text(Literal, Label).
 sort_triples_by_label(+Triples, -Sorted)
Sort a list of rdf(S,P,O) by the labels.
 2121sort_triples_by_label(Pairs, Sorted) :-
 2122	map_list_to_pairs(key_triple_by_label, Pairs, LabelPairs),
 2123	keysort(LabelPairs, SortedPairs),
 2124	pairs_values(SortedPairs, Sorted).
 2125
 2126key_triple_by_label(rdf(S,P,O), rdf(SK,PK,OK)) :-
 2127	label_sort_key(S, SK),
 2128	label_sort_key(P, PK),
 2129	label_sort_key(O, OK).
 sort_pairs_by_label(+Pairs, -Sorted)
Sort a pair-list where the keys are resources by their label.
 2135sort_pairs_by_label(Pairs, Sorted) :-
 2136	map_list_to_pairs(key_label_sort_key, Pairs, LabelPairs),
 2137	keysort(LabelPairs, SortedPairs),
 2138	pairs_values(SortedPairs, Sorted).
 2139
 2140key_label_sort_key(R-_, Key) :-
 2141	label_sort_key(R, Key).
 2142
 2143
 2144		 /*******************************
 2145		 *	  CUSTOMIZATION		*
 2146		 *******************************/
 p_label(+Id, -Label)
Defines the visible label for a property.
See also
- html_property_table//2.
 2154p_label(source(_), 'Source URL').
 2155p_label(triples(G),
 2156	['# ', a(href(Link), triples)]) :-
 2157	http_link_to_id(list_triples, [graph=G], Link).
 2158p_label(subject_count(G),
 2159	['# ', a(href(Link), subjects)]) :-
 2160	http_link_to_id(list_instances, [graph=G], Link).
 2161p_label(bnode_count(G),
 2162	['# ', a(href(Link), 'bnode subjects')]) :-
 2163	http_link_to_id(list_instances, [graph=G, type=bnode], Link).
 2164p_label(predicate_count(G),
 2165	['# ', a(href(Link), predicates)]) :-
 2166	http_link_to_id(list_predicates, [graph=G], Link).
 2167p_label(type_count(G),
 2168	['# Referenced ', a(href(Link), classes)]) :-
 2169	http_link_to_id(list_classes, [graph=G], Link).
 2170
 2171
 2172		 /*******************************
 2173		 *	      SEARCH		*
 2174		 *******************************/
 search(+Request)
HTTP handler to search for triples that contain a literal that matches a query.
To be done
- Produce a sensible search language.
 2183search(Request) :-
 2184	http_parameters(Request,
 2185			[ q(QueryText,
 2186			    [ description('Query to search for')
 2187			    ]),
 2188			  filter(FilterAtom,
 2189				 [ optional(true),
 2190				   description('Filter on raw matches (a Prolog term)')
 2191				 ])
 2192			]),
 2193	(   var(FilterAtom)
 2194	->  Filter = true
 2195	;   atom_to_term(FilterAtom, Filter0, []),
 2196	    rdf_global_term(Filter0, Filter)
 2197	),
 2198
 2199	find_literals(QueryText, Literals, Query),
 2200	literal_triples(Literals, Filter, Triples),
 2201	reply_html_page(cliopatria(default),
 2202			title('Search results for ~q'-[Query]),
 2203			[ h1('Search results for token "~q"'-[Query]),
 2204			  \rdf_table(Triples, [])
 2205			]).
 2206
 2207find_literals(QueryText, [Query], exact(Query)) :-
 2208	% Check if Q starts and ends with double quotes:
 2209	sub_atom(QueryText,0,1,Remainder,'"'),
 2210	sub_atom(QueryText,Remainder,1,0,'"'),!,
 2211	sub_atom(QueryText,1,_,1,Query).
 2212find_literals(QueryText, Literals, Query) :-
 2213	% if not quoted, perform search on tokenized query
 2214	tokenize_atom(QueryText, Tokens),
 2215	once(phrase(query(Query), Tokens)),
 2216	rdf_find_literals(Query, Literals).
 2217
 2218query(Query) -->
 2219	simple_query(Q1),
 2220	(   eos
 2221	->  {Query = Q1}
 2222	;   query(Q2),
 2223	    {Query = and(Q1,Q2)}
 2224	).
 2225
 2226eos([],[]).
 2227
 2228simple_query(Token) -->
 2229	['"',Token,'"'], !.
 2230simple_query(not(Token)) -->
 2231	[-, Token].
 2232simple_query(case(Token)) -->
 2233	[Token].
 literal_triples(+ListOfLiterals, +Filter, -Triples) is det
Find the list of triples with a literal in ListOfLiterals and whose subject satisfies Filter.
 2240literal_triples(Literals, Filter, Triples) :-
 2241	sub_term(graph(Graph), Filter), !,
 2242	phrase(ltriples(Literals, Graph, Filter), Triples).
 2243literal_triples(Literals, Filter, Triples) :-
 2244	phrase(ltriples(Literals, Filter), Triples).
 2245
 2246
 2247ltriples([], _, _) --> [].
 2248ltriples([H|T], G, F) -->
 2249	findall(rdf(S,P,literal(L)),
 2250		(   rdf(S,P,literal(exact(H), L),G),
 2251		    search_filter(F, S)
 2252		)),
 2253	ltriples(T, G, F).
 2254
 2255ltriples([], _) --> [].
 2256ltriples([H|T], F) -->
 2257	findall(rdf(S,P,literal(L)),
 2258		(   rdf(S,P,literal(exact(H), L)),
 2259		    search_filter(F, S)
 2260		)),
 2261	ltriples(T, F).
 rdf_table(+Triples, +Options)// is det
Emit a table of triples.
Arguments:
Triples- is a list of rdf(S,P,O).
 2269rdf_table(Triples, Options) -->
 2270	{ option(top_max(TopMax), Options, 500),
 2271	  option(top_max(BottomMax), Options, 500)
 2272	},
 2273	html(table(class(block),
 2274		   [ tr([ th('Subject'), th('Predicate'), th('Object') ])
 2275		   | \table_rows_top_bottom(triple, Triples,
 2276					    TopMax, BottomMax)
 2277		   ])).
 2278
 2279triple(rdf(S,P,O)) -->
 2280	html([ td(class(subject),   \rdf_link(S, [role(subj)])),
 2281	       td(class(predicate), \rdf_link(P, [role(pred)])),
 2282	       td(class(object),    \rdf_link(O, [role(obj) ]))
 2283	     ]).
 2284
 2285
 2286		 /*******************************
 2287		 *     HTML INFRASTRUCTURE	*
 2288		 *******************************/
 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.
 2298html_property_table(Template, Goal) -->
 2299	{ findall(Template, Goal, Rows) },
 2300	html(table(class(block),
 2301		   \table_rows(prow, Rows))).
 2302
 2303prow(Row) -->
 2304	{ Row =.. [_,H|Cells],
 2305	  (   p_label(H, Label0)
 2306	  ->  true
 2307	  ;   functor(H, Label0, _)
 2308	  ),
 2309	  (   is_list(Label0)
 2310	  ->  append(Label0, [:], Label)
 2311	  ;   Label = [Label0, :]
 2312	  )
 2313	},
 2314	html([ th(class(p_name), Label)
 2315	     | \pcells(Cells)
 2316	     ]).
 2317
 2318pcells([]) --> [].
 2319pcells([H|T]) -->
 2320	pcell(H),
 2321	pcells(T).
 2322
 2323pcell(int(Value)) -->
 2324	{ integer(Value) }, !,
 2325	nc('~D', Value).
 2326pcell(H) -->
 2327	{ compound(H),
 2328	  H =.. [Class,Value], !
 2329	},
 2330	html(td(class(Class), Value)).
 2331pcell(H) -->
 2332	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).

 2349table_rows(Goal, Rows) -->
 2350	table_rows(Rows, Goal, 1, -1).
 2351
 2352table_rows_top_bottom(Goal, Rows, inf, inf) --> !,
 2353	table_rows(Rows, Goal, 1, -1).
 2354table_rows_top_bottom(Goal, Rows, MaxTop, MaxBottom) -->
 2355	{ length(Rows, Count) },
 2356	(   { MaxTop+MaxBottom >= Count }
 2357	->  table_rows(Rows, Goal, 1, -1)
 2358	;   { Skip is Count-MaxBottom,
 2359	      delete_list_prefix(Skip, Rows, BottomRows),
 2360	      Skipped is Count-(MaxTop+MaxBottom)
 2361	    },
 2362	    table_rows(Rows, Goal, 1, MaxTop),
 2363	    html(tr(class(skip),
 2364		    [ th(colspan(10), 'Skipped ~D rows'-[Skipped])
 2365		    ])),
 2366	    table_rows(BottomRows, Goal, 1, -1)
 2367	).
 2368
 2369table_rows(_, _, _, 0) --> !, [].
 2370table_rows([], _, _, _) --> [].
 2371table_rows([H|T], Goal, N, Left) -->
 2372	{ N2 is N + 1,
 2373	  (   N mod 2 =:= 0
 2374	  ->  Class = even
 2375	  ;   Class = odd
 2376	  ),
 2377	  Left2 is Left - 1
 2378	},
 2379	html(tr(class(Class), \call(Goal, H))),
 2380	table_rows(T, Goal, N2, Left2).
 2381
 2382delete_list_prefix(0, List, List) :- !.
 2383delete_list_prefix(_, [], []) :- !.
 2384delete_list_prefix(N, [_|T], List) :-
 2385	N2 is N - 1,
 2386	delete_list_prefix(N2, T, List).
 list_prefixes(+Request)
List known RDF prefixes in various formats
 2392list_prefixes(Request) :-
 2393	Formats = [html,turtle],
 2394	http_parameters(Request,
 2395			[ format(Format,
 2396				 [ oneof(Formats),
 2397				   description('Output format'),
 2398				   default(html)
 2399				 ])
 2400			]),
 2401	findall(Prefix-URI,
 2402		rdf_current_ns(Prefix, URI),
 2403		Pairs),
 2404	keysort(Pairs, Sorted),
 2405	reply_html_page(cliopatria(default),
 2406			title('RDF prefixes (namespaces)'),
 2407			[ h1('Known RDF prefixes (namespaces)'),
 2408			  \explain_prefixes,
 2409			  \ns_table(Format, Sorted),
 2410			  \prefix_formats(Formats, Format, Request)
 2411			]).
 2412
 2413explain_prefixes -->
 2414	html(p([ 'The following prefixes are known and may be used \c
 2415	          without declaration in SPARQL queries to this server.'
 2416	       ])).
 2417
 2418prefix_formats(Formats, Format, Request) -->
 2419	{ select(Format, Formats, Alt)
 2420	},
 2421	html(p(class('prefix-format'),
 2422	       [ 'Also available in ',
 2423		 \alt_formats(Alt, Request)
 2424	       ])).
 2425
 2426alt_formats([], _) --> [].
 2427alt_formats([H|T], Request) -->
 2428	{ http_reload_with_parameters(Request, [format(H)], HREF)
 2429	},
 2430	html(a(href(HREF), H)),
 2431	(   {T==[]}
 2432	->  []
 2433	;   html(' and '),
 2434	    alt_formats(T, Request)
 2435	).
 2436
 2437ns_table(html, Pairs) -->
 2438	html(table(class(block),
 2439		   [ \prefix_table_header,
 2440		     \table_rows(prefix_row, Pairs)
 2441		   ])).
 2442ns_table(turtle, Pairs) -->
 2443	html(pre(class(code),
 2444		 \turtle_prefixes(Pairs))).
 2445
 2446prefix_table_header -->
 2447	html(tr([ th('Prefix'),
 2448		  th('URI')
 2449		])).
 2450
 2451prefix_row(Prefix-URI) -->
 2452	html([ td(Prefix),
 2453	       td(URI)
 2454	     ]).
 2455
 2456turtle_prefixes(Pairs) -->
 2457	{ longest_prefix(Pairs, 0, Length),
 2458	  PrefixCol is Length+10
 2459	},
 2460	turtle_prefixes(Pairs, PrefixCol).
 2461
 2462longest_prefix([], L, L).
 2463longest_prefix([Prefix-_|T], L0, L) :-
 2464	atom_length(Prefix, L1),
 2465	L2 is max(L0, L1),
 2466	longest_prefix(T, L2, L).
 2467
 2468turtle_prefixes([], _) --> [].
 2469turtle_prefixes([Prefix-URI|T], Col) -->
 2470	html('@prefix ~t~w: ~*|<~w> .~n'-[Prefix, Col, URI]),
 2471	turtle_prefixes(T, Col)