1:- module(
    2  dot,
    3  [
    4    dot_arc/3,            % +Out, +FromTerm, +ToTerm
    5    dot_arc/4,            % +Out, +FromTerm, +ToTerm. +Options
    6    dot_arc_id/3,         % +Out, +FromId, +ToId
    7    dot_arc_id/4,         % +Out, +FromId, +ToId. +Options
    8    dot_cluster/3,        % +Out, +Term, :Goal_1
    9    dot_cluster/4,        % +Out, +Term, :Goal_1, +Options
   10    dot_cluster_arc/3,    % +Out, +FromTerm, +ToTerm
   11    dot_cluster_arc/4,    % +Out, +FromTerm, +ToTerm, +Options
   12    dot_cluster_arc_id/3, % +Out, +FromTerm, +ToTerm
   13    dot_cluster_arc_id/4, % +Out, +FromTerm, +ToTerm, +Options
   14    dot_cluster_id/3,     % +Out, +Id, :Goal_1
   15    dot_cluster_id/4,     % +Out, +Id, :Goal_1, +Options
   16    dot_edge/3,           % +Out, +FromTerm, +ToTerm
   17    dot_edge/4,           % +Out, +FromTerm, +ToTerm. +Options
   18    dot_edge_id/3,        % +Out, +FromId, +ToId
   19    dot_edge_id/4,        % +Out, +FromId, +ToId. +Options
   20    dot_graph/2,          % +Out, :Goal_1
   21    dot_graph/3,          % +Out, :Goal_1, +Options
   22    dot_html_replace/2,   % +Unescaped, -Escaped
   23    dot_node/2,           % +Out, +Term
   24    dot_node/3,           % +Out, +Term, +Options
   25    dot_node_id/2,        % +Out, +Id
   26    dot_node_id/3         % +Out, +Id, +Options
   27  ]
   28).   29
   30/* <module> DOT serialization
   31
   32@see https://www.graphviz.org
   33
   34*/
   35
   36:- use_module(library(apply)).   37:- use_module(library(error)).   38:- use_module(library(yall)).   39
   40:- use_module(library(dcg)).   41:- use_module(library(dict)).   42:- use_module(library(debug_ext)).   43:- use_module(library(file_ext)).   44:- use_module(library(term_ext)).   45
   46:- use_module(dot_html).   47
   48:- meta_predicate
   49    dot_graph(+, 1),
   50    dot_graph(+, 1, +),
   51    dot_cluster(+, +, 1),
   52    dot_cluster(+, +, 1, +),
   53    dot_cluster_id(+, +, 1),
   54    dot_cluster_id(+, +, 1, +).
 dot_arc(+Out:ostream, +FromTerm:term, +ToTerm:term) is det
 dot_arc(+Out:ostream, +FromTerm:term, +ToTerm:term, +Options:options) is det
Emits an arc (directed edge) from one Prolog term to another in the DOT language.

Since Prolog terms cannot be used as DOT IDs, dot_arc/[3,4] and automatically creates compatible DOT IDs under the hood. The same Prolog term is always denoted by the same DOT ID.

See also
- Most of the time, the use of Prolog terms instead of DOT IDs is preferable. However, there are legitimate use cases where the programmer would like to generate and use the DOT IDs herself. For these purposes, dot_arc_id/[3,4] can be used -- in combination with ascii_id/2 -- instead.
   76dot_arc(Out, FromTerm, ToTerm) :-
   77  dot_arc(Out, FromTerm, ToTerm, options{}).
   78
   79
   80dot_arc(Out, FromTerm, ToTerm, Options) :-
   81  maplist(ascii_id, [FromTerm,ToTerm], [FromId,ToId]),
   82  dot_arc_id(Out, FromId, ToId, Options).
 dot_arc_id(+Out:ostream, +FromId:atom, +ToId:atom) is det
 dot_arc_id(+Out:ostream, +FromId:atom, +ToId:atom, +Options:options) is det
Emits a directed edge or arc from one DOT ID to another in the DOT language.
See also
- dot_arc/[3,4] allows arcs to be asserted between Prolog terms.
   94dot_arc_id(Out, FromId, ToId) :-
   95  dot_arc_id(Out, FromId, ToId, options{}).
   96
   97
   98dot_arc_id(Out, FromId, ToId, Options) :-
   99  dot_attributes(Options, String),
  100  format_debug(dot, Out, "    ~a -> ~a~s;", [FromId,ToId,String]).
 dot_attribute(+Pair:pair(atom,term), -String:string) is semidet
  106dot_attribute(Name-Value, String) :-
  107  dot_attribute_(Name, Value, String).
  108
  109% HTML-like label
  110dot_attribute_(html, Spec, Attr) :- !,
  111  string_phrase(("label=<",dot_html(Spec),">"), Attr).
  112% multi-line label
  113dot_attribute_(label, Values, Attr) :-
  114  is_list(Values), !,
  115  maplist([Value,Line]>>format(string(Line), "~w", [Value]), Values, Lines1),
  116  maplist(dot_html_replace, Lines1, Lines2),
  117  atomics_to_string(Lines2, "<BR/>", Lines3),
  118  format(string(Attr), "label=<~s>", [Lines3]).
  119% single-line label
  120dot_attribute_(label, Value, Attr) :- !,
  121  dot_attribute_(label, [Value], Attr).
  122% Another DOT attribute.
  123dot_attribute_(Key, Value, Attr) :-
  124  dot_attribute_(Key), !,
  125  format(string(Attr), "~a=\"~w\"", [Key,Value]).
  126
  127dot_attribute_(arrowhead).
  128dot_attribute_(charset).
  129dot_attribute_(colorscheme).
  130dot_attribute_(compound).
  131dot_attribute_(lhead).
  132dot_attribute_(ltail).
  133dot_attribute_(shape).
 dot_attributes(+Options:options, -String:string) is det
  139dot_attributes(options{}, "") :- !.
  140dot_attributes(Options, String) :-
  141  dict_pairs(Options, Pairs),
  142  findall(
  143    String,
  144    (
  145      member(Pair, Pairs),
  146      dot_attribute(Pair, String)
  147    ),
  148    Strings
  149  ),
  150  atomics_to_string(Strings, ",", String0),
  151  format(string(String), " [~s]", [String0]).
 dot_cluster(+Out:ostream, +Term:term, :Goal_1) is det
 dot_cluster(+Out:ostream, +Term:term, :Goal_1, +Options:options) is det
  158dot_cluster(Out, Term, Goal_1) :-
  159  dot_cluster(Out, Term, Goal_1, options{label: Term}).
  160
  161
  162dot_cluster(Out, Term, Goal_1, Options) :-
  163  ascii_id(Term, Id),
  164  dot_cluster_id(Out, Id, Goal_1, Options).
 dot_cluster_arc(+Out:ostream, +FromTerm:term, +ToTerm:term) is det
 dot_cluster_arc(+Out:ostream, +FromTerm:term, +ToTerm:term, +Options:options) is det
  171dot_cluster_arc(Out, FromTerm, ToTerm) :-
  172  dot_cluster_arc(Out, FromTerm, ToTerm, options{}).
  173
  174
  175dot_cluster_arc(Out, FromTerm, ToTerm, Options) :-
  176  maplist(ascii_id, [FromTerm,ToTerm], [FromId,ToId]),
  177  dot_cluster_arc_id(Out, FromId, ToId, Options).
 dot_cluster_arc_id(+Out:ostream, +FromId:atom, +ToId:atom) is det
 dot_cluster_arc_id(+Out:ostream, +FromId:atom, +ToId:atom, +Options:options) is det
  184dot_cluster_arc_id(Out, FromId, ToId) :-
  185  dot_cluster_arc_id(Out, FromId, ToId, options{}).
  186
  187
  188dot_cluster_arc_id(Out, FromId0, ToId0, Options0) :-
  189  maplist(atom_concat(cluster_), [FromId0,ToId0], [LTail,LHead]),
  190  maplist(atom_concat(dummy_), [FromId0,ToId0], [FromId,ToId]),
  191  merge_dicts(options{lhead: LHead, ltail: LTail}, Options0, Options),
  192  dot_arc_id(Out, FromId, ToId, Options).
 dot_cluster_id(+Out:ostream, +Id:atom, :Goal_1) is det
 dot_cluster_id(+Out:ostream, +Id:atom, :Goal_1, +Options:options) is det
  199dot_cluster_id(Out, Id, Goal_1) :-
  200  dot_cluster_id(Out, Id, Goal_1, options{}).
  201
  202
  203dot_cluster_id(Out, Id, Goal_1, Options) :-
  204  format_debug(dot, Out, "  subgraph cluster_~a {", [Id]),
  205  dot_attributes(Options, String),
  206  format_debug(dot, Out, "    graph~s;", [String]),
  207  format_debug(dot, Out, '    dummy_~a [label="",shape="none"];', [Id]),
  208  call(Goal_1, Out),
  209  format_debug(dot, Out, "  }").
 dot_edge(+Out:ostream, +FromTerm:term, +ToTerm:term) is det
 dot_edge(+Out:ostream, +FromTerm:term, +ToTerm:term, +Options:options) is det
Emits an edge between two Prolog terms in the DOT language.

Since Prolog terms cannot be immediate used as DOT IDs, dot_edge/[3,4] and dot_node/[2,3] automatically create compatible DOT IDs under the hood. When the same Prolog term is given to these predicates, it is guaranteed that the DOT ID will also be the same.

See also
- Most of the time, the use of Prolog terms instead of DOT ID is preferable. However, there are legitimate use cases where the programmer would like to generate and use the DOT IDs themselves. For these purposes, dot_edge_id/[3,4] can be used -- in combination with ascii_id/2 -- instead.
  229dot_edge(Out, FromTerm, ToTerm) :-
  230  dot_edge(Out, FromTerm, ToTerm, options{}).
  231
  232
  233dot_edge(Out, FromTerm, ToTerm, Options) :-
  234  maplist(ascii_id, [FromTerm,ToTerm], [FromId,ToId]),
  235  dot_edge_id(Out, FromId, ToId, Options).
 dot_edge_id(+Out:ostream, +FromId:atom, +ToId:atom) is det
 dot_edge_id(+Out:ostream, +FromId:atom, +ToId:atom, +Options:options) is det
Emits an edge between two DOT IDs in the DOT language.
See also
- dot_edge/[3,4] allows edges to be asserted between Prolog terms.
  246dot_edge_id(Out, FromId, ToId) :-
  247  dot_edge_id(Out, FromId, ToId, options{}).
  248
  249
  250dot_edge_id(Out, FromId, ToId, Options) :-
  251  dot_attributes(Options, String),
  252  format_debug(dot, Out, "    ~a -- ~a~s;", [FromId,ToId,String]).
 dot_graph(+Out:ostream, :Goal_1) is det
 dot_graph(+Out:ostream, :Goal_1, +Options:options) is det
Arguments:
Options- The following options are supported:
directed(+boolean)
Whether the graph is directed (true) or undirected (false, default).
name(+string)
The name of the graph. Default is "noname".
overlap(+boolean)
Whether or not nodes are allowed to overlap. Default is false.
strict(+boolean)
Value `true' indicates that the graph is strict, i.e., has no self-arcs and has not multi-edges. Default is `false'.

This can only be used in combination with option `directed(true)', and throws an exception otherwise.

  283dot_graph(Out, Goal_1) :-
  284  dot_graph(Out, Goal_1, options{}).
  285
  286
  287dot_graph(Out, Goal_1, Options0) :-
  288  % Set default option values.
  289  merge_dicts(
  290    Options0,
  291    options{directed: false, name: "noname", overlap: false, strict: false},
  292    Options1
  293  ),
  294  % Typecheck all option values.
  295  dict_select(directed, Options1, Options2, Directed),
  296  must_be(boolean, Directed),
  297  dict_select(name, Options2, Options3, Name),
  298  must_be(string, Name),
  299  dict_select(overlap, Options3, Options4, Overlap),
  300  must_be(boolean, Overlap),
  301  dict_select(strict, Options4, Options5, Strict),
  302  must_be(boolean, Strict),
  303  % Check for forbidden combinations of option values.
  304  (   Directed == false,
  305      Strict == true
  306  ->  throw(
  307        error(
  308          option_combination(directed(Directed),strict(Strict)),
  309          dot_graph/3
  310        )
  311      )
  312  ;   true
  313  ),
  314  dot_graph_type(Directed, Type),
  315  format_debug(dot, Out, "~a ~s {", [Type,Name]),
  316  merge_dicts(
  317    Options5,
  318    options{charset: 'UTF-8', colorscheme: svg, compound: true},
  319    Options6
  320  ),
  321  dot_attributes(Options6, GraphAttrsString),
  322  format_debug(dot, Out, "  graph~s;", [GraphAttrsString]),
  323  call(Goal_1, Out),
  324  format_debug(dot, Out, "}").
  325
  326dot_graph_type(false, graph).
  327dot_graph_type(true, digraph).
 dot_html_replace(+Unescaped:string, -Escaped:string) is det
Replaces the following characters that are not allowed to occur in DOT HTML labels with HTML elements: left and right angle bracket, ampersand.
  337dot_html_replace(String1, String2) :-
  338  string_phrase(html_replace, String1, String2).
  339
  340html_replace, "&lt;" --> "<", !, html_replace.
  341html_replace, "&gt;" --> ">", !, html_replace.
  342html_replace, "&amp;" --> "&", !, html_replace.
  343html_replace, [C] --> [C], !, html_replace.
  344html_replace --> "".
 dot_node(+Out:ostream, +Term:term) is det
 dot_node(+Out:ostream, +Term:term, +Options:options) is det
Arguments:
Out- is a handle to an output stream.
is- a Prolog term.
Options- is a list of compound terms, each of which denotes a GraphViz attribute. The following attributes are supported:
  • label(+or([string,list(string)])) Allows either a single string or a list of strings to be used as a node label. The strings are allowed to contain Unicode characters and a limited set of HTML tags for markup purposes (see README.org). Regular DOT labels do not allow such flexibility, so strings supplied through this option are exported as DOT HTML labels.
  • Other options are written as regular DOT attributes (KEY="VALUE"). See README.org for an overview of supported GraphViz attributes.
See also
- Most of the time, the use of Prolog terms instead of DOT ID is preferable. However, there are legitimate use cases where the programmer would like to generate and use the DOT IDs themselves. For these purposes, dot_node_id/[2,3] can be used -- in combination with ascii_id/2 -- instead.
  377dot_node(Out, Term) :-
  378  dot_node(Out, Term, options{label: Term}).
  379
  380
  381dot_node(Out, Term, Options) :-
  382  ascii_id(Term, Id),
  383  dot_node_id(Out, Id, Options).
 dot_node_id(+Out:ostream, +Id:atom) is det
 dot_node_id(+Out:ostream, +Id:atom, +Options:options) is det
See also
- dot_node/[2,3] allows nodes to be asserted for Prolog terms.
  392dot_node_id(Out, Id) :-
  393  dot_node_id(Out, Id, options{}).
  394
  395
  396dot_node_id(Out, Id, Options) :-
  397  dot_attributes(Options, String),
  398  format_debug(dot, Out, "    ~a~s;", [Id,String])