1/*
    2  tikz.pl
    3  
    4@author Francois Fages
    5@email Francois.Fages@inria.fr
    6@license LGPL-2
    7@version 0.0.1 
    8
    9  General purpose predicates for drawing the tree structure of a term, in LaTeX tikz (for creating a picture in pdf) or in text.
   10  
   11*/
   12
   13
   14:- module(
   15	  tikz,
   16	  [
   17	   term_to_text/1,
   18	   term_to_text/2,
   19	   
   20	   term_to_tikz/1,
   21	   term_to_tikz/2,
   22	   
   23	   term_to_latex/1,
   24	   term_to_latex/2
   25	  ]
   26	 ).

General purpose predicates for drawing the tree structure of a term, in LaTeX tikz (for creating a picture in pdf) or text.

author
- Francois Fages
version
- 0.0.1
?- term_to_text(this(is, not, a(pipe))).
this
 is
 not
 a
  pipe
true.

Used in library(tracesearch) to draw search trees with predicate search_tree_tikz/1

Used in library((clp) and library(modeling) to draw labeling search trees with a new option trace/0 added to predicate labeling/2. E.g. traced search tree for the 4 queens problem and written in tikz:

\begin{tikzpicture}[
           ->,
           level/.style={sibling distance=6cm/#1}, % sensitive parameter to adjust manually
           level distance=2cm
          ]
\node {{labeling([x1,x2,x3,x4])}}
child {
 node {{x1=1}}
 child {
  node {{x2=3}}
 }
 child {
  node {{x2$\neq$3}}
 }
}
child {
 node {{x1$\neq$1}}
 child {
  node {{x1=2}}
  child {
   node {{[2,4,1,3]}}
  }
 }
 child {
  node {{x1$\neq$2}}
  child {
   node {{x1=3}}
   child {
    node {{[3,1,4,2]}}
   }
  }
  child {
   node {{x1$\neq$3}}
   child {
    node {{x2=1}}
   }
   child {
    node {{x2$\neq$1}}
   }
  }
 }
}
;
\end{tikzpicture}

Note that in the generated LaTeX tikz picture, the distance parameters generally needs to be ajusted manually. */

   97%:- nb_setval(tree_structure_width, 0).
   98
   99output_stream(Output, Stream) :-
  100    is_stream(Output)
  101    ->
  102    Stream=Output
  103    ;
  104    must_be((atom ; string), Output),
  105    open(Output, write, Stream).
 term_to_latex(+Term)
same as term_to_latex(current_output, Term).
  112term_to_latex(Term):-
  113    term_to_latex(current_output, Term).
 term_to_latex(+Output, +Term)
writes on Output file or stream a complete LaTeX document that generates an image in pdf of the tree structure of Term. Unfortunately tikz does not accept verbatim mode for node labels, hence special characters like _ or \ in the writing of Term create LaTeX errors and should be treated first.
  122term_to_latex(Output, Term):-
  123    output_stream(Output, Stream),
  124    format(Stream, "% LaTeX document generated by Prolog library(tikz)\n\\documentclass[tikz,border=10pt]{standalone}\n\\begin{document}\n\\begin{tikzpicture}
  125  [
  126   ->,
  127   level/.style={sibling distance=6cm/#1}, % sensitive parameter to adjust manually
  128   level distance=2cm
  129  ]\n\\", []),
  130    term_to_tikz(Stream, 0, Term),
  131    format(Stream, ";\n\\end{tikzpicture}\n\\end{document}\n", []),
  132    close(Stream).
 term_to_tikz(+Term)
same as term_to_tikz(current_output, Term).
  138term_to_tikz(Term):-
  139    term_to_tikz(current_output, Term).
 term_to_tikz(+Output, +Term)
writes on output Output LaTeX tikz picture code for drawing the tree structure of Term. Unfortunately tikz does not accept verbatim mode for node labels, hence special characters like _ or \ in the writing of Term create LaTeX errors and should be treated first.
  148term_to_tikz(Output, Term):-
  149    output_stream(Output, Stream),
  150    format(Stream, "% LaTeX tikz code generated by Prolog library(tikz)\n\\begin{tikzpicture}
  151  [
  152   ->,
  153   level/.style={sibling distance=6cm/#1}, % sensitive parameter to adjust manually
  154   level distance=2cm
  155  ]\n\\", []),
  156    term_to_tikz(Stream, 0, Term),
  157    format(Stream, ";\n\\end{tikzpicture}", []),
  158    close(Stream).
  159
  160    
  161term_to_tikz(Stream, N, Term):-
  162    foreach(between(1, N, _), write(Stream, ' ')),
  163    (
  164     compound(Term)
  165    ->
  166     functor(Term, F, A),
  167     %format(Stream, "node {{\\verb|~w|}}\n", [F]),
  168     format(Stream, "node {{~w}}\n", [F]),
  169     N1 is N+1,
  170     foreach(between(1, A, I), tikz_child(Stream, I, Term, N, N1))
  171    ;
  172     %format(Stream, "node {{\\verb|~w|}}\n", [Term])
  173     format(Stream, "node {{~w}}\n", [Term])
  174    ).
  175
  176tikz_child(Stream, I, Term, N, N1) :-
  177    foreach(between(1, N, _), write(Stream, ' ')), writeln(Stream, "child {"),
  178    arg(I, Term, Ti),
  179    term_to_tikz(Stream, N1, Ti),
  180    foreach(between(1, N, _), write(Stream, ' ')), writeln(Stream, "}").
 term_to_text(+Term)
% draws the tree structure of Term in text.
  189term_to_text(T):-
  190    term_to_text(current_output, T).
 term_to_text(+Output, +Term)
% draws the tree structure of Term in text on Output.
  197term_to_text(Output, T):-
  198    output_stream(Output, Stream),
  199    term_to_text(Stream, 0, T).
  200
  201term_to_text(Stream, N, Term):-
  202    foreach(between(1, N, _), write(Stream, ' ')),
  203    (
  204     compound(Term)
  205    ->
  206     functor(Term, F, A),
  207     writeln(Stream, F),
  208     N1 is N+1,
  209     foreach((between(1, A, I), arg(I, Term, Ti)), term_to_text(Stream, N1, Ti))
  210    ;
  211     writeln(Stream, Term)
  212    )