View source with formatted comments or as raw
    1/*  Part of SWISH
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2020, VU University Amsterdam
    7			 CWI Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(swish_render_term,
   37	  [ term_rendering//3                  % +Term, +Vars, +Options
   38	  ]).   39:- use_module(library(dcg/basics)).   40:- use_module(graphviz, [render_dot//3]).   41:- use_module(library(gensym)).   42:- use_module('../render').   43
   44:- register_renderer(term, "Render term structure as a graph").   45
   46/** <module> View complex terms using Graphviz
   47
   48This library translates complex Prolog terms  into Graphviz (dot) output
   49for graphical rendering.
   50*/
   51
   52term_rendering(Term, _Vars, Options) -->
   53	{ with_output_to(string(DotString), term_to_dot(Term))
   54	},
   55	render_dot(DotString, dot, Options).
   56
   57%%	term_to_dot(+Term) is det.
   58%
   59%	Emit a dot representation for Term to the curent output.
   60
   61term_to_dot(Term) :-
   62	term_to_dot(current_output, Term).
   63
   64
   65%%	term_to_dot(+Out:stream, Term) is det.
   66%
   67%	Emit a dot representation for Term to the stream Out.
   68
   69term_to_dot(Out, Term) :-
   70	\+ \+ ( numbervars(Term, 0, _, [singletons(true)]),
   71		'$factorize_term'(Term, Skel, Subst),
   72		label_factors(Subst),
   73		phrase(struct0(Skel), Codes),
   74		format(Out, 'digraph structs {\n  node [shape=record];\n~s}\n', [Codes])
   75	      ).
   76
   77
   78label_factors([]).
   79label_factors([V='$VAR'(X)|T]) :- !,
   80	V = '$VAR'(X),
   81	label_factors(T).
   82label_factors(['$SKEL'(_,C)=C|T]) :-
   83	label_factors(T).
   84
   85%%	struct0(+Term)//
   86%
   87%	Deal with the outer term.  Note that labels inside terms are
   88%	embedded in the term label.
   89
   90struct0(Prim) -->
   91	{ number(Prim), !,
   92	  format(codes(Codes), '~q', [Prim])
   93	},
   94	cstring(Codes).
   95struct0(Prim) -->
   96	{ primitive(Prim), !,
   97	  format(codes(Codes), '~q', [Prim])
   98	},
   99	"\"", cstring(Codes), "\"".
  100struct0(Term) -->
  101	struct(Term, -(_), Links, []),
  102	links(Links).
  103
  104%%	struct(+Term, Link, Links, RestLinks)//
  105%
  106%	Deal with compound and inner terms.
  107
  108struct('$SKEL'(Done, C), -(Id), Links, LinksT) -->
  109	{ var(Done), !,
  110	  Done = top(Id)
  111	},
  112	struct(C, -(Id), Links, LinksT).
  113struct('$SKEL'(Done, C), Id-Arg, [link_c(Id-Arg, Id2, C)|LinkT], LinkT) -->
  114	{ var(Done), !,
  115	  Done = id(Id2)
  116	},
  117	".".
  118struct('$SKEL'(top(Id), _), Id-Arg,
  119       [link(Id-Arg, Id)|LinksT], LinksT) --> !,
  120	".".
  121struct('$SKEL'(id(Id2), _), Id-Arg, [link(Id-Arg, Id2)|LinkT], LinkT) --> !,
  122	".".
  123struct(Prim, _, Links, Links) -->
  124	{ primitive(Prim), !,
  125	  format(codes(Codes), '~q', [Prim])
  126	},
  127	cstring(Codes).
  128struct(Compound, -(Id), Links, LinkT) --> !,
  129	{ compound_name_arguments(Compound, F, Args),
  130	  gensym(struct, Id),
  131	  format(codes(FCodes), '~q', [F])
  132	},
  133	"  ", atom(Id),
  134	" [", "label=\"<f> ", cstring(FCodes), " ",
  135	gv_args(Args, 0, Id, Links, LinkT), "\"];\n".
  136struct(Compound, Id-Arg, [link_c(Id-Arg, _, Compound)|LinkT], LinkT) -->
  137	".".
  138
  139gv_args([], _, _, Links, Links) --> [].
  140gv_args([H|T], N, Id, Links, LinksT) -->
  141	"|", gv_arg_id(N), " ",
  142	struct(H, Id-N, Links, LT0),
  143	{N2 is N + 1},
  144	gv_args(T, N2, Id, LT0, LinksT).
  145
  146gv_arg_id(N) -->
  147	"<a", integer(N), ">".
  148
  149links(Links) -->
  150	{ \+ memberchk(link_c(_,_,_), Links)
  151	}, !,
  152	"\n",
  153	link_f(Links).
  154links(Links) -->
  155	link_c(Links, RestLinks, []),
  156	links(RestLinks).
  157
  158link_c([], Links, Links) --> [].
  159link_c([link_c(Id-Arg, Id2, Compound)|T0],
  160       [link(Id-Arg, Id2)|LinksT0], LinkT) --> !,
  161	struct(Compound, -(Id2), LinksT0, LinkT1),
  162	link_c(T0, LinkT1, LinkT).
  163link_c([H|T0], [H|T], Links) -->
  164	link_c(T0, T, Links).
  165
  166link_f([]) --> [].
  167link_f([link(Id-Arg, Id2)|T]) -->
  168	"  ", atom(Id), ":a", integer(Arg), " -> ", atom(Id2), ":f;\n",
  169	link_f(T).
  170
  171
  172primitive('$VAR'(_)) :- !.
  173primitive(X) :-
  174	\+ compound(X).
  175
  176%%	cstring(+Codes)//
  177%
  178%	Create a C-string. Normally =dot=  appears   to  be  using UTF-8
  179%	encoding. Would there be a  safer   way  to  transport non-ascii
  180%	characters, such as \uXXXX?
  181
  182cstring([]) -->
  183	[].
  184cstring([H|T]) -->
  185	(   cchar(H)
  186	->  []
  187	;   [H]
  188	),
  189	cstring(T).
  190
  191cchar(0'") --> "\\\"".
  192cchar(0'\n) --> "\\n".
  193cchar(0'\t) --> "\\t".
  194cchar(0'\b) --> "\\b".
  195cchar(0'|) --> "\\|".
  196cchar(0'[) --> "\\[".
  197cchar(0']) --> "\\]"