View source with formatted comments or as raw
    1:- module(scasp_verbose,
    2          [ verbose/1,                  % :Goal
    3            scasp_warning/1,            % +Term
    4            scasp_warning/2,            % +When, +Term
    5            scasp_trace/2,              % +When, +Term
    6            scasp_info/2,		% +When, +Term
    7            print_goal/1,               % +Goal
    8            print_check_calls_calling/2 % ?Goal, ?StackIn
    9          ]).   10:- use_module(library(apply)).   11:- use_module(library(lists)).   12:- use_module(library(clpqr/dump)).   13
   14:- use_module(clp/disequality).   15:- use_module(clp/clpq).   16
   17:- meta_predicate
   18    verbose(0).   19
   20/** <module> Print goal and stack in Ciao compatible format
   21
   22This module prints the goal  and  stack  in   as  close  as  we can Ciao
   23compatible format such tha we can compare   the traces created by
   24
   25    scasp -v program.pl
   26*/
   27
   28:- create_prolog_flag(scasp_verbose,        false, []).   29:- create_prolog_flag(scasp_warnings,       false, []).   30:- create_prolog_flag(scasp_warn_pos_loops, false, []).   31:- create_prolog_flag(scasp_trace_failures, false, []).   32
   33verbose(Goal) :-
   34    current_prolog_flag(scasp_verbose, true),
   35    !,
   36    with_output_to(user_error, call(Goal)).
   37verbose(_).
   38
   39%!  scasp_warning(+Term) is det.
   40%
   41%   Emit a warning through print_message/2.
   42
   43scasp_warning(Term) :-
   44    current_prolog_flag(scasp_warnings, true),
   45    !,
   46    print_message(warning, scasp(Term)).
   47scasp_warning(_).
   48
   49%!  scasp_warning(+When, +Term) is det.
   50%
   51%   Emit a warning through print_message/2.
   52
   53scasp_warning(When, Term) :-
   54    current_prolog_flag(When, true),
   55    !,
   56    print_message(warning, scasp(Term)).
   57scasp_warning(_, _).
   58
   59%!  scasp_trace(+When, +Term) is det.
   60%
   61%   Emit a debug messages through print_message/2.
   62
   63scasp_trace(When, Term) :-
   64    current_prolog_flag(When, true),
   65    !,
   66    print_message(debug, scasp(Term)).
   67scasp_trace(_, _).
   68
   69%!  scasp_info(+When, +Term) is det.
   70%
   71%   Emit an informational through print_message/2.
   72
   73scasp_info(When, Term) :-
   74    current_prolog_flag(When, true),
   75    !,
   76    print_message(informational, scasp(Term)).
   77scasp_info(_, _).
   78
   79%!  print_check_calls_calling(?Goal, ?StackIn)
   80%
   81%   Auxiliar predicate to print StackIn the current stack and Goal. This
   82%   predicate is executed when the flag `check_calls` is _on_. NOTE: use
   83%   check_calls/0 to activate the flag
   84
   85:- det(print_check_calls_calling/2).   86
   87print_check_calls_calling(Goal, I) :-
   88    fail,                               % TBD: New Ciao -v mode
   89    !,
   90    identation(I, 0, Ident),
   91    format('(~d) ~@~n', [Ident, print_goal(Goal)]).
   92print_check_calls_calling(Goal, I) :-
   93    reverse(I,RI),
   94    format('\n--------------------- Calling: ~@ -------------',
   95           [print_goal(Goal)]),
   96    print_check_stack(RI,4), !,
   97    nl.
   98
   99identation([],Id,Id).
  100identation([[]|I],Id1,Id) :- !,
  101    Id2 is Id1 - 1,
  102    identation(I,Id2,Id).
  103identation([_|I],Id1,Id) :- !,
  104    Id2 is Id1 + 1,
  105    identation(I,Id2,Id).
  106
  107
  108%!  print_check_stack(A, B)
  109%
  110%   simple output of the stack to run faster during verboser
  111
  112print_check_stack([],_).
  113print_check_stack([[]|As],I) :- !,
  114    I1 is I - 4,
  115    print_check_stack(As,I1).
  116print_check_stack([A|As],I) :-
  117    nl, tab(I),
  118    print_goal(A),
  119    I1 is I + 4,
  120    print_check_stack(As,I1).
  121
  122%!  print_goal(+Goal)
  123%
  124%   Print an sCASP goal. The first clause   does  the actual work at the
  125%   moment to emit the goal as closely as we can to the Ciao output such
  126%   that we can compare traces created   using  ``scasp -v``. The second
  127%   uses default notation for constraints.
  128
  129print_goal(goal_origin(Goal, _)) :- !,
  130    print_goal(Goal).
  131print_goal(Goal) :- !,
  132    ciao_goal(Goal, Ciao),
  133    print(Ciao).
  134
  135ciao_goal(Goal, Ciao) :-
  136    copy_term(Goal, Ciao),
  137    term_attvars(Ciao, AttVars),
  138    maplist(ciao_constraints, AttVars, Constraints),
  139    maplist(del_attrs, AttVars),
  140    maplist(ciao_attvar, AttVars, Constraints).
  141
  142:- use_module(library(clpqr/dump), [dump/3]).  143
  144ciao_constraints(Var, Constraints) :-
  145    (   is_clpq_var(Var),
  146        dump([Var], [NV], Constraints0),
  147        Constraints0 \== []
  148    ->  Constraints = NV-Constraints0
  149    ;   get_neg_var(Var, List),
  150        List \== []
  151    ->  Constraints = neg(_NV, List)
  152    ;   Constraints = []
  153    ).
  154
  155:- op(700, xfx, user:'~').  156:- op(700, xfx, ~).  157
  158ciao_attvar(_, []) :- !.
  159ciao_attvar({NV~Constraints}, NV-Constraints) :- !.
  160ciao_attvar({'\u2209'(Var, List)}, neg(Var, List))