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