Node:FDBG Showing Selected Constraints (advanced version), Next:, Previous:FDBG Showing Selected Constraints (simple version), Up:FDBG Advanced Usage



Showing Selected Constraints (advanced version)

Suppose that you want to give the constraints that you are interested in as an argument to the visualizer, instead of defining them in a table. The following visualizer implements this.

:- use_module(library(lists), [append/3]).

%% filter_events(+CtrSpecs, +Constraint, +Actions):  This predicate will
%%   only show constraint events if they match an element in the list CtrSpecs,
%%   or if CtrSpecs is wrapped in -/1, then all the non-matching events will
%%   be shown.
%%   CtrSpecs can contain the following types of elements:
%%     ctr_name             - matches all constraints of the given name
%%     ctr_name/arity       - matches constraints with the given name and arity
%%     ctr_name(...args...) - matches constraints unifyable with the given term
%%
%%   For the selected events fdbg_show(Constraint, Actions) is called.
%%   This visualizer can be specified when turning fdbg on, e.g.:
%%     fdbg_on([constraint_hook(filter_events([count/4]))]), or
%%     fdbg_on([constraint_hook(filter_events(-[in_set]))]).
filter_events(CtrSpecs, Constraint, Actions) :-
        filter_events(CtrSpecs, fdbg_show, Constraint, Actions).

%% filter_events(+CtrSpecs, +Visualizer, +Constraint, +Actions):  Same as
%%   the above predicate, but the extra argument Visualizer specifies the
%%   predicate to be called for the selected events (in the same form as
%%   in the constraint_hook option, i.e. without the last two arguments). E.g.
%%     fdbg_on([constraint_hook(filter_events([count/4],my_show))]).
filter_events(-CtrSpecs, Visualizer, Constraint, Actions) :- !,
        \+ show_constraint(CtrSpecs, Constraint),
        add_args(Visualizer, [Constraint, Actions], Goal),
        call(Goal).
filter_events(CtrSpecs, Visualizer, Constraint, Actions) :-
        show_constraint(CtrSpecs, Constraint),
        add_args(Visualizer, [Constraint, Actions], Goal),
        call(Goal).

show_constraint([C|_], Constraint) :-
        matches(C, Constraint), !.
show_constraint([_|Cs], Constraint) :-
        show_constraint(Cs, Constraint).

matches(Name/Arity, Constraint) :- !,
        functor(Constraint, Name, Arity).
matches(Name, Constraint) :-
        atom(Name), !,
        functor(Constraint, Name, _).
matches(C, Constraint) :-
        C = Constraint.

add_args(Goal0, NewArgs, Goal) :-
        Goal0 =.. [F|Args0],
        append(Args0, NewArgs, Args),
        Goal =.. [F|Args].

Here is a session using the visualizer, filtering out everything but all_different/1 constraints:

| ?- [library('clpfd/examples/suudoku')].
[...]
| ?- fdbg_on(constraint_hook(filter_events([all_different/1]))).
% The clp(fd) debugger is switched on
% advice
| ?- suudoku([], 1, P).
all_different([1,<fdvar_1>,<fdvar_2>,8,<fdvar_3>,
               4,<fdvar_4>,<fdvar_5>,<fdvar_6>])
    fdvar_1 = 1..9 -> (2..3)\/(5..7)\/{9}
    fdvar_2 = 1..9 -> (2..3)\/(5..7)\/{9}
    fdvar_3 = 1..9 -> (2..3)\/(5..7)\/{9}
    fdvar_4 = 1..9 -> (2..3)\/(5..7)\/{9}
    fdvar_5 = 1..9 -> (2..3)\/(5..7)\/{9}
    fdvar_6 = 1..9 -> (2..3)\/(5..7)\/{9}

[...]

all_different([7,6,2,5,8,4,1,3,9])
    Constraint exited.

P = [...] ;
no
% advice
| ?- fdbg_off.
% The clp(fd) debugger is switched off

In the next session, all constraints named all_different are ignored, irrespective of arity. Also, we explicitly specified the visualizer to be called for the events that are kept (here, we have written the default, fdbg_show, so the actual behavior is not changed).

| ?- [library('clpfd/examples/suudoku')].
[...]
| ?- fdbg_on(constraint_hook(filter_events(-[all_different],fdbg_show))).
% The clp(fd) debugger is switched on
% advice
| ?- suudoku([], 1, P).
domain([1,<fdvar_1>,<fdvar_2>,8,<fdvar_3>,
        4,<fdvar_4>,<fdvar_5>,<fdvar_6>],1,9)
    fdvar_1 = inf..sup -> 1..9
    fdvar_2 = inf..sup -> 1..9
    fdvar_3 = inf..sup -> 1..9
    fdvar_4 = inf..sup -> 1..9
    fdvar_5 = inf..sup -> 1..9
    fdvar_6 = inf..sup -> 1..9
    Constraint exited.
    Constraint exited.

[...]

domain([2,<fdvar_46>,5,<fdvar_47>,<fdvar_48>,
       <fdvar_49>,<fdvar_50>,<fdvar_51>,9],1,9)
    fdvar_46 = inf..sup -> 1..9
    fdvar_47 = inf..sup -> 1..9
    fdvar_48 = inf..sup -> 1..9
    fdvar_49 = inf..sup -> 1..9
    fdvar_50 = inf..sup -> 1..9
    fdvar_51 = inf..sup -> 1..9
    Constraint exited.

P = [...] ;
no
% advice
| ?- fdbg_off.
% The clp(fd) debugger is switched off

In the last session, we specify a list of constraints to ignore, using a pattern to select the appropriate constraints. Since all constraints in the example match one of the items in the given list, no events are printed.

| ?- [library('clpfd/examples/suudoku')].
[...]
| ?- fdbg_on(constraint_hook(filter_events(-[domain(_,1,9),all_different(_)]))).
% The clp(fd) debugger is switched on
% advice
| ?- suudoku([], 1, P).
P = [...] ;
no
% advice
| ?- fdbg_off.
% The clp(fd) debugger is switched off