View source with formatted comments or as raw
    1/*  Part of ClioPatria SeRQL and SPARQL server
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2007-2015, University of Amsterdam,
    7			      VU University Amsterdam
    8
    9    This program is free software; you can redistribute it and/or
   10    modify it under the terms of the GNU General Public License
   11    as published by the Free Software Foundation; either version 2
   12    of the License, or (at your option) any later version.
   13
   14    This program is distributed in the hope that it will be useful,
   15    but WITHOUT ANY WARRANTY; without even the implied warranty of
   16    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   17    GNU General Public License for more details.
   18
   19    You should have received a copy of the GNU General Public
   20    License along with this library; if not, write to the Free Software
   21    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   22
   23    As a special exception, if you link this library with other files,
   24    compiled with a Free Software compiler, to produce an executable, this
   25    library does not by itself cause the resulting executable to be covered
   26    by the GNU General Public License. This exception does not however
   27    invalidate any other reasons why the executable file might be covered by
   28    the GNU General Public License.
   29*/
   30
   31:- module(rdf_graphviz,
   32	  [ gviz_write_rdf/3		% +Stream, +Triples, +Options
   33	  ]).   34:- use_module(library(semweb/rdf_db)).   35:- use_module(library(semweb/rdfs)).   36:- use_module(library(http/http_dispatch)).   37:- use_module(library(http/http_path)).   38:- use_module(library(http/html_write)).   39:- use_module(library(http/url_cache)).   40:- use_module(library(assoc)).   41:- use_module(library(option)).   42:- use_module(library(gensym)).   43:- use_module(library(lists)).   44:- use_module(library(apply)).   45:- use_module(library(ugraphs)).   46:- use_module(library(semweb/rdf_label)).   47
   48:- rdf_register_ns(graphviz, 'http://www.graphviz.org/').   49
   50/** <module> Interface to graphviz for RDF graphs
   51
   52Graphviz is a general purpose graph vizualization library. Its home-page
   53is  http://www.graphviz.org/  This  module  translates    an  RDF  graph
   54represented as a list of rdf(S,P,O) into a .dot file.
   55
   56@author	Jan Wielemaker
   57*/
   58
   59%%	gviz_write_rdf(+Stream, +Graph, +Options) is det.
   60%
   61%	Write the graph Triples to Stream in =dot= compatible format.
   62%	Options:
   63%
   64%	    * graph_attributes(+Attributes)
   65%	    Additional overall graphs attributes for dot.  Each
   66%	    attribute is of the format Name(Value) and written
   67%	    as Name="Value".  The term size(W,H) is accepted as
   68%	    well.
   69%
   70%	    * max_label_length(+Len)
   71%	    Truncate labels to Len characters.  Default is 25.
   72%	    Use =inf= to print the full label.
   73%
   74%	    * lang(+Lang)
   75%	    Lang is the language used for the labels.  See
   76%	    resource_label/4.
   77%
   78%	    * smash(+Properties)
   79%	    Smash networks connected by one of the given properties.
   80%	    Currently only [owl:sameAs].
   81%
   82%	    * bags(Bags)
   83%	    How to handle bags.  Values are
   84%
   85%	        * graph
   86%	        Show as normal nodes (i.e. handles as normal RDF)
   87%
   88%	        * merge(Shape, Max)
   89%	        Put the members in a dot node using Shape.  Only
   90%	        place the first Max members and add a note stating
   91%	        '... showing N of M' to indicate the actual number
   92%
   93%	    * edge_links(+Boolean)
   94%	    If =false= (default =true=) do not put href atributes on
   95%	    edges.
   96%
   97%	    * wrap_url(:Goal)
   98%	    If present, URLs of the graph are replaced with the
   99%	    result of call(Goal, URL0, URL)
  100%
  101%	    * shape_hook(:Goal)
  102%	    Called to define the shape of a resource as call(Goal, URI,
  103%	    Shape).  Shape is a list of Name(Value) terms.  See
  104%	    shape/3.
  105%
  106%	    * bag_shape_hook(:Goal)
  107%	    Called to define the shape parameters for a bag (Table).
  108%	    called as call(Goal, Members, Shape) Shape is a list of
  109%	    Name(Value) terms.
  110%
  111%	    * label_hook(:Goal)
  112%	    Called to define the label of a resource as call(Goal, URI,
  113%	    Language, MaxLength, Label). Label is an atom.
  114%
  115%	    * target(Target)
  116%	    If present, add target=Target to all attribute lists that
  117%	    have an =href= attribute.
  118%
  119%           * display_lang(+Boolean)
  120%           Display the language of literal nodes, defaults to true.
  121%
  122
  123:- meta_predicate gviz_write_rdf(+,+,:).  124:- rdf_meta gviz_write_rdf(+,t,t).  125
  126gviz_write_rdf(Stream, Graph0, Options0) :-
  127	exclude(exclude_triple, Graph0, Graph1),
  128	meta_options(is_meta, Options0, Options),
  129	format(Stream, 'digraph G~n{ ', []),
  130	option(graph_attributes(Attrs), Options, []),
  131	write_graph_attributes(Attrs, Stream),
  132	smash_graph(Graph1, Graph2, Options),
  133	combine_bags(Graph2, Triples, Bags, Options),
  134	gv_write_edges(Triples, Done, Stream, Options),
  135	assoc_to_list(Done, Nodes),
  136	gv_write_nodes(Nodes, Stream, [bag_assoc(Bags)|Options]),
  137	format(Stream, '~n}~n', []).
  138
  139is_meta(wrap_url).
  140is_meta(shape_hook).
  141is_meta(bag_shape_hook).
  142is_meta(label_hook).
  143
  144%%	write_graph_attributes(+List, +Out)
  145%
  146%	Write attributes for the graph as a whole
  147
  148write_graph_attributes([], _).
  149write_graph_attributes([H|T], Out) :-
  150	write_graph_attribute(H, Out),
  151	write_graph_attributes(T, Out).
  152
  153write_graph_attribute(size(W,H), Out) :- !,
  154	format(Out, '  size="~w,~w";~n', [W, H]).
  155write_graph_attribute(AttVal, Out) :-
  156	AttVal =.. [Name, Value],
  157	format(Out, '  ~w="~w";~n', [Name, Value]).
  158
  159
  160%%	combine_bags(+Graph, -Triples, -Bags, +Options) is det.
  161%
  162%	Seperate  the  bags  from  the   graph.  Triples  represent  the
  163%	remaining graph (in which a bag is a single node) and Bags is an
  164%	assoc BagID-Members storing the members of the bags.
  165
  166combine_bags(Graph, Graph, Bags, Options) :-
  167	option(bags(graph), Options), !,
  168	empty_assoc(Bags).
  169combine_bags(Graph, Triples, Bags, _Options) :-
  170	empty_assoc(Bags0),
  171	find_bags(Graph, Graph1, Bags0, Bags1),
  172	collect_bags(Graph1, Triples, Bags1, Bags).
  173
  174:- rdf_meta find_bags(t, -, +, -).  175
  176find_bags([], [], Bags, Bags).
  177find_bags([rdf(S,rdf:type,rdf:'Bag')|Graph], Triples, Bags0, Bags) :- !,
  178	put_assoc(S, Bags0, [], Bags1),
  179	find_bags(Graph, Triples, Bags1, Bags).
  180find_bags([H|T0], [H|T], Bags0, Bags) :-
  181	find_bags(T0, T, Bags0, Bags).
  182
  183collect_bags([], [], Bags, Bags).
  184collect_bags([rdf(S,P,O)|Graph], Triples, Bags0, Bags) :-
  185	bagid_property(P, _),
  186	get_assoc(S, Bags0, L, Bags1, [O|L]), !,
  187	collect_bags(Graph, Triples, Bags1, Bags).
  188collect_bags([H|T0], [H|T], Bags0, Bags) :-
  189	collect_bags(T0, T, Bags0, Bags).
  190
  191
  192%%	bagid_property(+P, -I) is semidet.
  193%
  194%	True if P is of the format   =|_:N|=,  where N is a non-negative
  195%	integer.
  196
  197bagid_property(P, I) :-
  198	atom(P), !,
  199	string_concat('_:', N, P),
  200	number_string(I, N),
  201	integer(I), I >= 0.
  202bagid_property(P, I) :-
  203	atom_concat('_:', I, P).
  204
  205%%	smash_graph(+GraphIn, -GraphOut, +Options)
  206%
  207%	Smash networks of equivalent properties.
  208
  209smash_graph(GraphIn, GraphOut, Options) :-
  210	option(smash(Props), Options, []), !,
  211	smash_graph_(Props, GraphIn, GraphOut).
  212
  213smash_graph_([], Graph, Graph).
  214smash_graph_([H|T], Graph0, Graph) :-
  215	smash_on_property(H, Graph0, Graph1),
  216	smash_graph_(T, Graph1, Graph).
  217
  218%%	smash_on_property(+P, +GraphIn, -GraphOut)
  219%
  220%	Merge owl:sameAs nodes, replacing the node with a bag.
  221
  222smash_on_property(P, GraphIn, GraphOut) :-
  223	smash_edges(GraphIn, P, Edges, Rest),
  224	vertices_edges_to_ugraph([], Edges, Graph),
  225	partition_ugraph(Graph, VerticeSets),
  226	make_eq_bags(VerticeSets, VerticeBags, MapAssoc),
  227	maplist(smash_triple(MapAssoc), Rest, Mapped),
  228	append(Mapped, VerticeBags, GraphOut).
  229
  230smash_edges([], _, [], []).
  231smash_edges([rdf(S,P,O)|T0], P, [S-O,O-S|T], Rest) :- !,
  232	smash_edges(T0, P, T, Rest).
  233smash_edges([H|T0], P, Edges, [H|T]) :-
  234	smash_edges(T0, P, Edges, T).
  235
  236partition_ugraph([], []) :- !.
  237partition_ugraph(G0, [Vs0|Vs]) :-
  238	G0 = [V-_|_],
  239	reachable(V, G0, Vs0),
  240	del_vertices(G0, Vs0, G1),
  241	partition_ugraph(G1, Vs).
  242
  243make_eq_bags(Vertices, Bags, MapAssoc) :-
  244	make_eq_bags(Vertices, 1, Bags, Mapping),
  245	list_to_assoc(Mapping, MapAssoc).
  246
  247:- rdf_meta make_eq_bags(+, +, t, -).  248
  249make_eq_bags([], _, [], []).
  250make_eq_bags([Vs|T0], I, [rdf(BagId, rdf:type, rdf:'Bag')|Bags], Mapping) :-
  251	atom_concat('_:sameAs', I, BagId),
  252	make_eq_bag(Vs, 1, BagId, Bags, BagsT),
  253	make_mapping(Vs, BagId, Mapping, MappingT),
  254	I2 is I + 1,
  255	make_eq_bags(T0, I2, BagsT, MappingT).
  256
  257make_eq_bag([], _, _, Triples, Triples).
  258make_eq_bag([H|T], I, BagId, [rdf(BagId, P, H)|Triples0], Triples) :-
  259	bagid_property(P, I),
  260	I2 is I + 1,
  261	make_eq_bag(T, I2, BagId, Triples0, Triples).
  262
  263make_mapping([], _, Mapping, Mapping).
  264make_mapping([H|T], BagId, [H-BagId|Mapping0], Mapping) :-
  265	make_mapping(T, BagId, Mapping0, Mapping).
  266
  267smash_triple(Mapping, rdf(S0,P,O0), rdf(S,P,O)) :-
  268	smash(Mapping, S0, S),
  269	smash(Mapping, O0, O).
  270
  271smash(Assoc, R0, R) :-
  272	get_assoc(R0, Assoc, R), !.
  273smash(_, R, R).
  274
  275
  276%%	gv_write_edges(+Graph, -Done, +Stream, +Options) is det.
  277%
  278%	Write the edges of an RDF graph   in  =dot= format. It invents a
  279%	dot identifier for each node  as   it  processes  the nodes. The
  280%	mapping from node to dot  identifier   is  returned in the assoc
  281%	Done.
  282
  283gv_write_edges(Graph, Done, Stream, Options) :-
  284	empty_assoc(Done0),
  285	gv_write_edges(Graph, Done0, Done, Stream, Options).
  286
  287gv_write_edges([], Done, Done, _, _).
  288gv_write_edges([Triple|T], Done0, Done, Stream, Options) :-
  289	write_edge(Triple, Done0, Done1, Stream, Options),
  290	gv_write_edges(T, Done1, Done, Stream, Options).
  291
  292write_edge(rdf(S,P,O), Done0, Done2, Stream, Options) :-
  293	format(Stream, '  ', []),
  294	write_node_id(S, Done0, Done1, Stream),
  295	write(Stream, ' -> '),
  296	write_node_id(O, Done1, Done2, Stream),
  297	resource_label(P, Label, Options),
  298	(   option(edge_links(true), Options, true)
  299	->  wrap_url(P, URL, Options),
  300	    target_option([href(URL), label(Label)], Attrs, Options),
  301	    write_attributes(Attrs, Stream)
  302	;   write_attributes([label(Label)], Stream)
  303	),
  304	nl(Stream).
  305
  306write_node_id(S, Done, Done, Stream) :-
  307	get_assoc(S, Done, Id), !,
  308	write(Stream, Id).
  309write_node_id(S, Done0, Done, Stream) :-
  310	gensym(n, Id),
  311	put_assoc(S, Done0, Id, Done),
  312	write(Stream, Id).
  313
  314%%	gv_write_nodes(+Nodes:list(pair), +Stream, +Options)
  315%
  316%	Write information about the nodes, defining  the share and label
  317%	of the node.
  318
  319gv_write_nodes([], _, _).
  320gv_write_nodes([RDF-ID|T], Stream, Options) :-
  321	format(Stream, '~w ', [ID]),
  322	write_node_attributes(RDF, Stream, Options),
  323	write(Stream, ';\n  '),
  324	gv_write_nodes(T, Stream, Options).
  325
  326%%	write_node_attributes(+RDF, +Stream, +Options) is det.
  327%
  328%	Write attributes for an RDF node.   The node identifier matching
  329%	the declared edges is alreadu written to Stream.
  330
  331write_node_attributes(R, Stream, Options) :-
  332	rdf_is_resource(R),
  333	option(bag_assoc(Bags), Options),
  334	get_assoc(R, Bags, Members), !,
  335	Members = [First|_],
  336	shape(First, MemberShape0, Options),
  337	bag_shape(Members, BagShape0, Options),
  338	exclude(no_bag_option, MemberShape0, MemberShape),
  339	option(bags(merge(BagShape1, Max0)), Options,
  340	       merge([ shape(box),
  341		       style('rounded,filled,bold'),
  342		       fillcolor('#ffff80')
  343		     ], 5)),
  344	select_option(max(Max), BagShape0, BagShape2, Max0),
  345	partition(label_option, BagShape2, LabelOptions0, BagShape2a),
  346	merge_options(BagShape1, MemberShape, BagShape3),
  347	merge_options(BagShape2a, BagShape3, BagShape),
  348	merge_options(LabelOptions0, Options, LabelOptions),
  349	bag_label(Members, Max, Label, LabelOptions),
  350	write_attributes([html(Label)|BagShape], Stream).
  351write_node_attributes(R, Stream, Options) :-
  352	rdf_is_resource(R), !,
  353	shape(R, Shape, Options),
  354	wrap_url(R, URL, Options),
  355	resource_label(R, Label, Options),
  356	target_option([href(URL), label(Label)|Shape], Attrs, Options),
  357	(   select(img(IMGOptions), Attrs, RAttrs),
  358	    catch(write_image_node(IMGOptions, RAttrs, Stream, Options),
  359		  error(existence_error(url,URL2),Context),
  360		  ( print_message(warning,
  361				  error(existence_error(url,URL2),Context)),
  362		    fail))
  363	->  true
  364	;   delete(Attrs, img(_), RAttrs),
  365	    write_attributes(RAttrs, Stream)
  366	).
  367write_node_attributes(Lit, Stream, Options) :-
  368	shape(Lit, Shape, Options),
  369	option(max_label_length(MaxLen), Options, 25),
  370	literal_text(Lit, Text),
  371	truncate_atom(Text, MaxLen, Summary0),
  372	(   ( option(display_lang(true), Options, true),
  373	      Lit = literal(lang(Lang, _)))
  374	->  atomic_list_concat([Summary0, '@', Lang], Summary)
  375	;   Summary = Summary0
  376	),
  377	write_attributes([label(Summary)|Shape], Stream).
  378
  379target_option(Attrs0, Attrs, Options) :-
  380	option(target(Target), Options), !,
  381	Attrs = [target(Target)|Attrs0].
  382target_option(Attrs, Attrs, _).
  383
  384no_bag_option(img(_)).
  385no_bag_option(width(_)).
  386no_bag_option(height(_)).
  387no_bag_option(cellpadding(_)).
  388no_bag_option(fixedsize(_)).
  389no_bag_option(label(_)).
  390no_bag_option(border(_)).
  391
  392label_option(max_label_length(_)).
  393
  394%%	bag_label(+Members, +Max, -Label, +Options) is det.
  395%
  396%	Create an HTML description for describing a bag of objects.
  397%
  398%	@param Max is the maximum # members to show.  If there are more,
  399%	       a text "... showing N of M" is displayed.
  400%	@param Label is a Prolog packed string with HTML text.
  401
  402bag_label(Members, Max, Label, Options) :-
  403	length(Members, Len),
  404	phrase(html(table([ border(0) ],
  405			  \html_bag_label(Members, 1, Max, Len, Options))),
  406	       Tokens),
  407	with_output_to(string(Label), print_html(Tokens)).
  408
  409html_bag_label([], _, _, _, _) --> !.
  410html_bag_label(_, I, Max, Len, _Options) -->
  411	{ I > Max }, !,
  412	html(tr(td([align(right), cellpadding(5)],
  413		   font(face('Helvetica:style=Italic'), '... showing ~D of ~D'-[Max, Len])))).
  414html_bag_label([H|T], I, Max, Len, Options) -->
  415	{ (   atom(H)
  416	  ->  wrap_url(H, URL, Options),
  417	      target_option([href(URL)], Atts, Options)
  418	  ;   Atts=[]
  419	  )
  420	},
  421	html(tr(td([align(left)|Atts], \html_resource_label(H, Options)))),
  422	{ I2 is I + 1 },
  423	html_bag_label(T, I2, Max, Len, Options).
  424
  425html_resource_label(Resource, Options) -->
  426	{ resource_label(Resource, Label, Options)
  427	},
  428	html(Label).
  429
  430%%	write_image_node(+ImgAttrs, +Attrs, +Stream, +Options) is det.
  431%
  432%	Render a node using an image. The   image  location is either an
  433%	external URL or a local file   specification  using the notation
  434%	icons(File), a term that must  resolve   in  an image file using
  435%	absolute_file_name/3. In the default setup,  this means that the
  436%	image must be in the directory =|web/icons|= of a package.
  437
  438write_image_node(ImgAttrs, Attrs, Stream, _Options) :-
  439	selectchk(src(Src), ImgAttrs, ImgAttrs1),
  440	(   Src = icons(_)
  441	->  absolute_file_name(Src, AbsFile, [access(read)]),
  442	    working_directory(CWD, CWD),
  443	    relative_file_name(AbsFile, CWD, File)
  444	;   url_cache(Src, File, _MimeType)
  445	),
  446	filter_attributes(Attrs, td, TDAttrs, _Attrs1),
  447	html_current_option(dialect(Dialect)),
  448	html_set_options([dialect(xhtml)]),
  449	label_row(Attrs, Extra),
  450	option(border(Border), Attrs),
  451	phrase(html(table(border(Border),
  452			  [ tr(td(TDAttrs, img([src(File)|ImgAttrs1], [])))
  453			  | Extra
  454			  ])),
  455	       Tokens),
  456	html_set_options([dialect(Dialect)]),
  457	with_output_to(string(HTML), print_html(Tokens)),
  458	write_attributes([html(HTML),shape(plaintext)], Stream).
  459
  460label_row(Attrs, Extra) :-
  461	option(label(Label), Attrs), !,
  462	Extra = [tr(td([align(center)], Label))].
  463label_row(_, []).
  464
  465
  466%%	resource_label(+Resource, -Label:atom, +Options) is det.
  467%
  468%	Label is the textual label to show for Resource. Process the
  469%	options
  470%
  471%	    * lang(+Lang)
  472%	    * max_label_length(+Len)
  473
  474resource_label(Resource, Label, Options) :-
  475	option(label_hook(Hook), Options),
  476	option(lang(Lang), Options, _),
  477	option(max_label_length(MaxLen), Options, 25),
  478	call(Hook, Resource, Lang, MaxLen, Label), !.
  479resource_label(Resource, Label, Options) :-
  480	option(lang(Lang), Options, _),
  481	rdf_display_label(Resource, Lang, Text),
  482	option(max_label_length(MaxLen), Options, 25),
  483	truncate_atom(Text, MaxLen, Label).
  484
  485
  486
  487%%	write_attributes(+Attributes:list, +Out:stream) is det.
  488%
  489%	Write attribute values.  We define some special attributes:
  490%
  491%		* html(HTML)
  492%		Emit as label=<HTML>
  493
  494write_attributes([], Out) :- !,
  495	format(Out, ' []').
  496write_attributes(List, Out) :- !,
  497	format(Out, ' [', []),
  498	write_attributes_2(List, Out),
  499	format(Out, ']', []).
  500
  501write_attributes_2([], _).
  502write_attributes_2([H|T], Out) :-
  503	(   string_attribute(H)
  504	->  H =.. [Att, Value],
  505	    c_escape(Value, String),
  506	    format(Out, ' ~w="~s"', [Att, String])
  507	;   html_attribute(H, Att)
  508	->  arg(1, H, Value),
  509	    format(Out, ' ~w=<~s>', [Att, Value])
  510	;   H =.. [Name, Value],
  511	    format(Out, ' ~w=~w', [Name, Value])
  512	),
  513	write_attributes_2(T, Out).
  514
  515
  516string_attribute(label(_)).
  517string_attribute(url(_)).
  518string_attribute(href(_)).
  519string_attribute(id(_)).
  520string_attribute('URL'(_)).
  521string_attribute(fillcolor(_)).
  522string_attribute(style(_)).
  523
  524html_attribute(html(_), label).
  525
  526
  527c_escape(Atom, String) :-
  528	atom_codes(Atom, Codes),
  529	phrase(cstring(Codes), String).
  530
  531%%	filter_attributes(+AllAttrs, +Element,
  532%%			  -ForElement, -Rest) is det.
  533
  534filter_attributes([], _, [], []).
  535filter_attributes([H|T], E, ForE, Rest) :-
  536	(   H =.. [Name,Value],
  537	    gv_attr(Name, E, Type),
  538	    is_of_type(Type, Value)
  539	->  ForE = [H|R],
  540	    filter_attributes(T, E, R, Rest)
  541	;   Rest = [H|R],
  542	    filter_attributes(T, E, ForE, R)
  543	).
  544
  545%%	gv_attr(?AttrName, ?Element, ?Type) is nondet.
  546%
  547%	Name and type-declarations for GraphViz   attributes.  Types are
  548%	defined my must_be/2.
  549%
  550%	@see http://www.graphviz.org/doc/info/shapes.html
  551
  552gv_attr(align,	      table, oneof([center,left,right])).
  553gv_attr(bgcolor,      table, atom).
  554gv_attr(border,	      table, atom).
  555gv_attr(cellborder,   table, atom).
  556gv_attr(cellpadding,  table, atom).
  557gv_attr(cellspacing,  table, atom).
  558gv_attr(color,	      table, atom).
  559gv_attr(fixedsize,    table, boolean).
  560gv_attr(height,	      table, atom).
  561gv_attr(href,	      table, atom).
  562gv_attr(port,	      table, atom).
  563gv_attr(target,	      table, atom).
  564gv_attr(title,	      table, atom).
  565gv_attr(tooltip,      table, atom).
  566gv_attr(valign,	      table, oneof([middle,bottom,top])).
  567gv_attr(width,	      table, atom).
  568
  569gv_attr(align,	      td,    oneof([center,left,right,text])).
  570gv_attr(balign,	      td,    oneof([center,left,right])).
  571gv_attr(bgcolor,      td,    atom).
  572gv_attr(border,	      td,    atom).
  573gv_attr(cellpadding,  td,    atom).
  574gv_attr(cellspacing,  td,    atom).
  575gv_attr(color,	      td,    atom).
  576gv_attr(colspan,      td,    integer).
  577gv_attr(fixedsize,    td,    boolean).
  578gv_attr(height,	      td,    atom).
  579gv_attr(href,	      td,    atom).
  580gv_attr(port,	      td,    atom).
  581gv_attr(rowspan,      td,    integer).
  582gv_attr(target,	      td,    atom).
  583gv_attr(title,	      td,    atom).
  584gv_attr(tooltip,      td,    atom).
  585gv_attr(valign,	      td,    oneof([middle,bottom,top])).
  586gv_attr(width,	      td,    atom).
  587
  588gv_attr(color,	      font,  atom).
  589gv_attr(face,	      font,  atom).
  590gv_attr('point-size', font,  integer).
  591
  592gv_attr(align,	      br,    oneof([center,left,right])).
  593
  594gv_attr(scale,	      img,   oneof([false,true,width,height,both])).
  595gv_attr(src,	      img,   atom).
  596
  597
  598%%	cstring(+Codes)//
  599%
  600%	Create a C-string. Normally =dot=  appears   to  be  using UTF-8
  601%	encoding. Would there be a  safer   way  to  transport non-ascii
  602%	characters, such as \uXXXX?
  603
  604cstring([]) -->
  605	[].
  606cstring([H|T]) -->
  607	(   cchar(H)
  608	->  []
  609	;   [H]
  610	),
  611	cstring(T).
  612
  613cchar(0'") --> "\\\"".
  614cchar(0'\n) --> "\\n".
  615cchar(0'\t) --> "\\t".
  616cchar(0'\b) --> "\\b".
  617
  618wrap_url(URL0, URL, Options) :-
  619	option(wrap_url(Wrap), Options),
  620	call(Wrap, URL0, URL), !.
  621wrap_url(URL, URL, _).
  622
  623
  624%%	bag_shape(+Members, -BagShape, +Options) is det.
  625%
  626%	Compute parameters for a bag of resources.
  627
  628bag_shape(Members, Shape, Options) :-
  629	option(bag_shape_hook(Hook), Options),
  630	call(Hook, Members, Shape), !.
  631bag_shape(_, [], _).
  632
  633%%	shape(+Resource, -Attributes, +Options) is det.
  634%
  635%	Shape is the shape of the node to use for Resource.  Shapes
  636%	can be modified in two ways:
  637%
  638%	    * through the option shape_hook(Closure), which must
  639%	    return a valid Attributes list for GraphViz
  640%	    * By addings sub-properties of graphviz:styleParameter
  641%	    to the class of the resource.  The value of this property
  642%	    defines the attribute value, while the label defines the
  643%	    attribute-name.
  644
  645shape(Resource, Shape, Options) :-
  646	option(shape_hook(Hook), Options),
  647	call(Hook, Resource, Shape), !.
  648shape(Resource, Shape, _Options) :-
  649	findall(Style, gv_style(Resource, Style), Shape),
  650	debug(gv, '~p: shape = ~q', [Resource, Shape]).
  651
  652gv_style(R, Style) :-
  653	rdfs_individual_of(R, Class),
  654	gv_class_style(Class, Style).
  655
  656gv_class_style(Class, Style) :-
  657	rdf_has(Class, graphviz:styleParameter, literal(V), P),
  658	rdf_has(P, rdfs:label, literal(A)),
  659	Style =.. [A,V].
  660
  661
  662		 /*******************************
  663		 *	   IMAGE SERVER		*
  664		 *******************************/
  665
  666% These handlers are relative to the handler of send_graph.  Possibly
  667% it would be better to merge that code.
  668
  669:- http_handler(root('graphviz/cache/url/'), cached_image_in_svg, [prefix]).  670:- http_handler(root('graphviz/'),	     local_image_in_svg,  [prefix]).  671
  672%%	cached_image_in_svg(+Request)
  673%
  674%	HTTP handler to serve an image we have included in an SVG file.
  675%
  676%	@tbd	Should we restrict files served to files that are part of
  677%		recently served SVG files?
  678
  679cached_image_in_svg(Request) :-
  680	memberchk(path_info(PathInfo), Request),
  681	atom_concat('cache/url/', PathInfo, File),
  682	url_cached(URL, file(File)),
  683	url_cached(URL, mime_type(MimeType)),
  684	http_reply_file(File,
  685			[ mime_type(MimeType),
  686			  unsafe(true)
  687			],
  688			Request).
  689
  690local_image_in_svg(Request) :-
  691	memberchk(path_info(PathInfo), Request),
  692	file_base_name(PathInfo, ImageFile),
  693	http_reply_file(icons(ImageFile), [], Request).
  694
  695
  696
  697		 /*******************************
  698		 *   RDF BASED CUSTOMIZATION	*
  699		 *******************************/
  700
  701:- rdf_meta
  702	exclude_triple(r,r,o).  703
  704exclude_triple(rdf(S,P,O)) :-
  705	exclude_triple(S,P,O).
  706
  707exclude_triple(_,rdf:type,C) :-
  708	rdf_has(C, graphviz:hideType, literal(type(xsd:boolean, true)))