How to find unexpected choicepoints?

I have a reasonably complex predicate that’s giving me more solutions than expected - it is unexpectedly not deterministic.
Is there a trick to debugging this kind of situation? For example, is it possible to set a breakpoint each time a new choicepoint is created?

Thanks in advance,

  • Stuart
1 Like

Have you checked: Bug hunting toolbox

1 Like

In general when you get too many answers is because you are missing an extra predicate in the conjunction.

p(A) :-
  a(A),
  b(A).

will produce (in general) more answers than:

p(A) :-
  a(A),
  b(A),
  c(A).

where c/1 restrains the conditions some more.

1 Like

You can use setup_call_cleanup/3 to check for individual calls being deterministic, but it’s a cumbersome to do this – you could use the wrapping technique (using wrap_predicate/4) from library(rdet) to make this easier.

1 Like

Thanks all. Here’s what I did.

f(X):-  % problem predicate. Unexpected multiple solutions.

Replace with:

f_(X):-  % rename the problem predicate

f(X):-
   f_(X), gtrace.

?- f(X).

… and gtrace will continue at the problem choicepoint.

1 Like

… at least in my case, it was because of an overlapping rule definition:

%make_trees(Roots, Childre, Trees)
make_trees([], [], [tree(nil,[])]).
make_trees([], [tree(Data,Children)], [tree(Data,Children)]).
make_trees([], [H|T], [tree(nil, [H|T])]).
...

…needed to be

make_trees([], [], [tree(nil,[])]).
make_trees([], [tree(Data,Children)], [tree(Data,Children)]), !.    % Add cut
make_trees([], [H|T], [tree(nil, [H|T])]).
...

or

make_trees([], [], [tree(nil,[])]).                                                 % len ==0
make_trees([], [tree(Data,Children)], [tree(Data,Children)]).   % len ==1
make_trees([], [H0, H1|T], [tree(nil, [H0, H1|T])]).                   % len >=2
...

Debugging this kind of thing is a PITA.

1 Like

I struggled with the same problem. My solution was to wrap my “entry point” to the program in a setup-call-cleanup that throws if there is a choice point after the first success, and test very often during development so that I immediately notice any problems.

The predicate itself:

goal_is_det(Goal) :-
        setup_call_cleanup(true, Goal, Det = true),
        (       Det == true
        ->      true
        ;       !,
                throw(error(mode_error(notdet),_))
        ).

It seems to provide similar functionality as library(rdet). (But not sure about that).

And of course it only helps if you run your “integration tests” or “end-to-end tests” or whatever you prefer to call them often enough so you notice the problem when you introduce it.

2 Likes

I guess you can also use leash/1 for the redo port only on the prediate you are debugging? I wish I had the time to properly document my experiences with debugging in particular, but sadly external circumstances usually force me to move faster than I would like :frowning:

rdet looks like a good solution.

As seen, there are a large number of ways to get more info. My personal solution is typically

?- gspy(suspect_pred).
?- go.

As the debugger hits suspect_pred, use s (skip) to jump to the end and examine the choice points in the top-right window. You can click on these to see the source location. You can also use u (up) to get to the caller of the open choice point (etc).

If you have a predicate that is most of the time deterministic but under some circumstances not, the rdet or cleanup/2 tricks can help you to fine the problematic case and start the debugger only in that case. I don’t recall using that. But then, experienced Prolog programmers do not make determinism mistakes very often :slight_smile:

Note that there are a number of cases. Fighting determinism this way makes most sense for recursive code that mostly has a procedural flavor. Here, non-determinism kills LCO (Last Call Optimization) making your code a lot slower and using a lot more memory.

In the typical case where a set of predicates define a logic formula that specify valid solutions, backtracking is typically desired. Using cuts to avoid exploring parts of the search space is typically better avoided. Adding additional constraints keeps the logical reading while the semantics of the code with cuts is often hard to grasp. If performance and/or multiple solutions is an issue here, you have some options. Ordering, stratification, distinct/1,2, order_by/3 may help. Tabling can be attractive as it avoids multiple solution, repeated computation of the same goal, deals with cycles and negation.

edit especially for numerical problems, constraints as e.g., library(clpfd) can solve the problem.

3 Likes

Thank you for the good summary of the tools available to avoid dangling choice points.

By “dangling choice point” I mean an unintentional, seemingly benign choice point that comes back some time later to bite you in the butt.

:slight_smile: We all must learn to walk before we can run, right?

I think I first heard this from Chen Stormstout.

Now that I think about it, our oldest daughter started running (sideways and backwards mostly) as soon as she stood up and had to wear a helmet for a while.

This one is better, because you don’t use cuts.

2 Likes

I’d like to make this an option for rdet, but so far haven’t done it. If you want to try it yourself, it’s a 1-line change to rdet.pl. (Making it an option would require multiple versions of the rdet/1 directive.)

The current version of rdet transforms (using wrap_predicate/4) a call to Pred into something like (Pred->true;throw(...)) … so it’s really a test for whether a predicate that’s expected to succeed actually does succeed (which is very useful in my experience). As a side-effect, it turns call(Pred) into once(Pred), which might not be what you want. That’s another change I want to make to rdet, namely changing the call to Pred into something like (Pred*->true;throw(...)). Not sure when I’ll get around to making these enhancements, but probably soon because they would be useful for me.

[BTW, is the cut in your goal_is_det/1 needed?]

It would be nice to have a library of predicate assert-checking:

:- expect_det(p/a).              
:- expect_true(p/a).               % This predicate should never be false.
:- expect_number(p/a, 2).     % arg2 should be a number
:- expect_grounded(p/a, 2).   % arg2 should always be grounded   
....

Or better, have these assumptions formally (and optionally) part of the language syntax:

p(X:grounded, Y:number) : det, true  :-
    ...

or, perhaps just:

:- constraints( p(grounded, number), [det, true] )
    ...

Do such tools exist?

Mercury has something similar, but I think it breaks compatibility with standard Prolog, which is a shame.

Oh … similar thoughts here.

I’ve opened an issue on rdet’s github repository: https://github.com/rla/rdet/issues/9
Don’t know when I’ll get around to it (it’s not hard, but will take a bit of time).

1 Like

I think it is needed to get rid of the unexpected choice point.

This predicate, exactly as it is defined, was provided on the old mailing list by Jan W. It was because I asked how to do the following (from memory!):

How do I notice that there is a choice point in my program that I did not put there myself?

I can no longer easily find the original thread.

As already discussed, this is for writing code that is deterministic in nature and does not take advantage of backtracking, multiple solutions and so on. You could call it “writing regular procedures with standard Prolog”. With such code, a choice point means (to me) that I made a mistake somewhere.

You can think of it as a crutch that I need until I learn to not make such errors in the first place.