1/*
    2  tracesearch.pl
    3  
    4@author Francois Fages
    5@email Francois.Fages@inria.fr
    6@license LGPL-2
    7@version 1.1.5
    8
    9  Tracing of search trees and representation of the search tree by a term or a string for drawing it in LaTeX tikz.
   10  
   11*/
   12
   13
   14:- module(tracesearch,
   15	  [
   16	   start_tracing/0,
   17	   currently_tracing/0,
   18	   stop_tracing/0,
   19	   clear_tracing/0,
   20
   21	   add_node/1,
   22	   
   23	   current_search_tree_depth/1,
   24
   25	   search_tree_term/1,	   
   26
   27	   search_tree_latex/1,	   
   28	   search_tree_latex/0,
   29	   search_tree_tikz/1,	   
   30	   search_tree_tikz/0,	   
   31
   32	   search_tree_text/0,	   
   33	   search_tree_text/1
   34	  ]
   35	 ).

Tracing of search trees and representation of the search tree by a term or a string for drawing it in LaTeX tikz.

author
- Francois Fages
version
- 0.0.1

General purpose tracing predicates for Prolog and representation of the search tree by a term.

Used in library(clp) of pack modeling for implementing a new option trace for labeling/2 predicate.

This library uses global variables trace_search_flag, search_tree_depth and search_tree_prefix, which should not be manipulated.

?- start_tracing, add_node(choice), (add_node(X=f(Y)), X=f(Y), add_node(Y=g(a)), Y=g(a) ; (add_node(X=h(b)), X=h(b))).
X = f(g(a)),
Y = g(a) ;
X = h(b).

?- search_tree_text.
choice
 _18984=f(_18980)
  _18980=g(a)
 _18984=h(b)
true.

Below is an example from library(clp) of pack modeling with new option trace added to labeling/2 predicate.

?- use_module(library(modeling)).
true.

?- N=4, int_array(Queens, [N], 1..N),
   for_all([I in 1..N-1, D in 1..N-I],
           (Queens[I] #\= Queens[I+D],
            Queens[I] #\= Queens[I+D]+D,
            Queens[I] #\= Queens[I+D]-D)),
   labeling([ff, trace('Q')], Queens).
N = 4,
Queens = array(2, 4, 1, 3) ;
N = 4,
Queens = array(3, 1, 4, 2) ;
false.

?- search_tree_text.
labeling([Q1,Q2,Q3,Q4])
 Q1=1
  Q2=3
  Q2$\neq$3
 Q1$\neq$1
  Q1=2
   [2,4,1,3]
  Q1$\neq$2
   Q1=3
    [3,1,4,2]
   Q1$\neq$3
    Q2=1
    Q2$\neq$1
true.

*/

   99:- use_module(library(drawtree)). % useful for pack documentation online ?
  100:- reexport(library(drawtree)).  101%:- catch(reexport(library(drawtree)), _, (throw(error(pack_drawtree_is_not_installed)), fail)).
  102
  103:- nb_setval(trace_search_flag, 0).  104:- nb_setval(search_tree_depth, 0).  105:- nb_setval(search_tree_prefix, []).
 start_tracing
Backtrackable initialization of a new search tree for possible building of several search trees in sequence. This is automatically done in labeling/2 predicates defined in library(clp) of pack modeling with new trace/0 option.
  113start_tracing :-
  114    b_setval(trace_search_flag, 1),
  115    b_setval(search_tree_depth, 0),
  116    b_setval(search_tree_prefix, []). % backtrackable for successive search trees
 currently_tracing
succeeds if currently tracing in mode.
  122currently_tracing :-
  123    catch(b_getval(trace_search_flag, 1), _, fail).
 stop_tracing
Backtrackable stop of the tracing mode.
  129stop_tracing :-
  130    b_setval(trace_search_flag, 0).
 clear_tracing
Non-backtrackable stop of the tracing mode and clearance of search tree information.
  136clear_tracing :-
  137    nb_setval(trace_search_flag, 0),
  138    nb_setval(search_tree_depth, 0),
  139    nb_setval(search_tree_prefix, []).
 add_node(+Term)
adds a new node labelled by an atom obtained by writing Term, if currently_tracing/0 is true. It is worth noting that special characters like _ or \ in Term can create LaTeX errors. In that case, the label term passed to add_node/1 should use copy_term/4, for instance to name the variables.
  148add_node(Term) :-
  149    (b_getval(trace_search_flag, 1)
  150    ->
  151     %writeln(add(Term)),
  152     with_output_to(atom(Atom), write(Term)),
  153     b_getval(search_tree_depth, Depth),
  154     nb_getval(search_tree_prefix, List),
  155     L = [Depth-Atom | List],
  156     nb_setval(search_tree_prefix, L), % non backtrackable
  157     D1 is Depth+1,
  158     b_setval(search_tree_depth, D1) % backtrackable
  159    ;
  160     true).
 search_tree_term(?Term)
returns a term formed with the labels of the current search tree.
  167search_tree_term(Term):-
  168    nb_getval(search_tree_prefix, List),
  169    reverse(List, Prefix),
  170    prefix_term(Prefix, Term, _Prefix).
  171
  172% returns the term encoded by the first argument prefix list
  173prefix_term([], true, []).
  174prefix_term([Depth-Label | Prefix], Term, PrefixTail) :-
  175    ((Prefix=[] ; (Prefix=[D1-_ |_], D1=<Depth))
  176    ->
  177     PrefixTail=Prefix,
  178     Term=Label
  179    ;
  180     DepthSubterms is Depth+1,
  181     prefix_subterms(Prefix, DepthSubterms, Subterms, PrefixTail),
  182     Term =.. [Label | Subterms]).
  183
  184% returns the list of terms at same depth encoded by the first argument prefix
  185prefix_subterms([], _DepthTerm, [], []) :- !.
  186prefix_subterms(Prefix, DepthTerm, Terms, PrefixTail) :-
  187    Prefix = [Depth-_Label | _Tail],
  188    (Depth < DepthTerm
  189    ->
  190     PrefixTail=Prefix,
  191     Terms=[]
  192    ;
  193     Depth = DepthTerm
  194    ->
  195     prefix_term(Prefix, Term1, Prefix1),
  196     prefix_subterms(Prefix1, DepthTerm, Terms2, PrefixTail),
  197     Terms=[Term1 | Terms2]
  198    ;
  199     fail). % ill-formed term prefix list
 search_tree_text(Output)
pretty print the search tree in Output file or stream as standard text.
  207search_tree_text(Output) :-
  208    search_tree_term(Term),
  209    term_to_text(Output, Term).
 search_tree_text
pretty print the search tree as standard text.
  216search_tree_text :-
  217    search_tree_text(current_output).
 search_tree_tikz(Output)
writes LaTeX tikz code on Output stream or file name for drawing the current search tree.
  224search_tree_tikz(Output) :-
  225    search_tree_term(Term),
  226    term_to_tikz(Output, Term).
 search_tree_tikz
writes LaTeX tikz code on current_output for drawing the current search tree.
  233search_tree_tikz :-
  234    search_tree_tikz(current_output).
 search_tree_latex(Output)
writes a LaTeX document on Output fstream or file name or drawing the current search tree.
  241search_tree_latex(Output) :-
  242    search_tree_term(Term),
  243    term_to_latex(Output, Term).
 search_tree_latex
writes a LaTeX document on current_output for drawing the current search tree.
  250search_tree_latex :-
  251    search_tree_latex(current_output).
 current_search_tree_depth(?Number)
returns the current depth of the search tree. This may be used by the goal of trace/2 option of labeling/2 predicate of library(clp) of pack modeling.
  260current_search_tree_depth(Depth) :-
  261    nb_getval(search_tree_depth, Depth)