Did you know ... Search Documentation:
Pack modeling -- prolog/tracesearch.pl
PublicShow source
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.
 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.
 currently_tracing
succeeds if currently tracing in mode.
 stop_tracing
Backtrackable stop of the tracing mode.
 clear_tracing
Non-backtrackable stop of the tracing mode and clearance of search tree information.
 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.
 search_tree_term(?Term)
returns a term formed with the labels of the current search tree.
 search_tree_text(Output)
pretty print the search tree in Output file or stream as standard text.
 search_tree_text
pretty print the search tree as standard text.
 search_tree_tikz(Output)
writes LaTeX tikz code on Output stream or file name for drawing the current search tree.
 search_tree_tikz
writes LaTeX tikz code on current_output for drawing the current search tree.
 search_tree_latex(Output)
writes a LaTeX document on Output fstream or file name or drawing the current search tree.
 search_tree_latex
writes a LaTeX document on current_output for drawing the current search tree.
 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.

Undocumented predicates

The following predicates are exported, but not or incorrectly documented.

 term_to_text(Arg1)
 term_to_text(Arg1, Arg2)
 term_to_tikz(Arg1)
 term_to_tikz(Arg1, Arg2)
 term_to_latex(Arg1)
 term_to_latex(Arg1, Arg2)