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