Search code examples
prologclpfdnegationlabeling

clpfd requires labeling to find any solutions (when using \+)


I'm trying to write something like "you have the ball if you previously got the ball, and didn't give it since":

:- use_module(library(clpfd)).

time(T1, has_ball) :-
    time(T2, get_ball),
    T2 #=< T1,
    \+ (time(T3, give_ball),
         T2 #< T3, T3 #< T1).

time(0, get_ball).
time(2, give_ball).

This correctly answers direct questions about a specific time T (by providing T, for example with labeling):

?- time(1, has_ball).
true.

?- T in 0..9, label([T]), time(T, has_ball).
T = 0 ;
T = 1 ;
T = 2 ;
false.

But when asked to find all valid times T, I simply get false:

?- time(T, has_ball).
false.

From my understanding, clpfd did some over approximation of the result without labeling, so I would have expected something like "T in inf..sup, time(T, has_ball)." telling me to use labeling. But it is clear that I am wrong, and now I am afraid I might miss solutions in other situations. Can someone help me understand?

EDIT: Isabelle Newbie's answer made me realize that I actually meant:

time(HasBall, has_ball) :-
    time(GetBall, get_ball),
    GetBall #=< HasBall,
    \+ (time(GiveBall, give_ball),
        GetBall #< GiveBall #/\ GiveBall #< HasBall).

Since the idea is that "you still have the ball at time HasBall if you got it at some previous time GetBall, and did NOT give it SINCE". So the time(GiveBall, give_ball) needs to be in the negation. Here replacing \+ with #\ gives a new error ("Domain error: `clpfd_reifiable_expression' expected") which I will investigate.


Solution

  • The short answer is that you shouldn't mix Prolog negation \+ with CLP(FD). CLP(FD) has its own negation operator that works on its constraints, written as #\. So you can write your predicate as:

    time(HasBall, has_ball) :-
        time(GetBall, get_ball),
        GetBall #=< HasBall,
        time(GiveBall, give_ball),
        #\ (GetBall #< GiveBall #/\ GiveBall #< HasBall).
    

    I renamed your variables because I didn't really understand what was going on. It's a bit clearer now, but shouldn't the negated constraint just be replaced by the positive HasBall #=< GiveBall?

    In any case this behaves as I believe you would like it to:

    ?- time(T, has_ball).
    T in 0..2.
    
    ?- time(T, has_ball), label([T]).
    T = 0 ;
    T = 1 ;
    T = 2.
    
    ?- time(1, has_ball).
    true.
    
    ?- T in 0..9, label([T]), time(T, has_ball).
    T = 0 ;
    T = 1 ;
    T = 2 ;
    false.
    

    To understand a bit more what was going on, we can take your original clause and replace variables by their constant values:

    step1(T1) :-
        T2 = 0,
        T2 #=< T1,
        \+ ( T3 = 2, T2 #< T3, T3 #< T1 ).
    
    step2(T1) :-
        0 #=< T1,
        \+ ( 0 #< 2, 2 #< T1 ).
    
    step3(T1) :-
        0 #=< T1,
        \+ ( 2 #< T1 ).
    

    So after the last step, your predicate behaves essentially as follows when called with a bound vs. an unbound variable:

    ?- T1 = 1, 0 #=< T1, \+ (2 #< T1).
    T1 = 1.
    
    ?-         0 #=< T1, \+ (2 #< T1).
    false.
    

    This is because in the first case the last goal is \+ (2 #< 1), which succeeds because 2 #< 1 fails.

    But if you don't bind T1, then 2 #< T1 succeeds:

    ?- 2 #< T1.
    T1 in 3..sup.
    

    So its negation \+ (2 #< T1) fails. This goal essentially says "there are no numbers larger than two", which is false. In contrast, the CLP(FD) negation succeeds with the "opposite" constraint:

    ?- #\ (2 #< T1).
    T1 in inf..2.
    

    This almost certainly makes more sense in the context of your program, since it respects the mathematical property that not (A < B) is equivalent to (A >= B):

    ?- 2 #>= T1.
    T1 in inf..2.
    

    EDIT: I missed the fact that maybe no give_ball event has been seen, in which case one would still hold the ball. You can't use #\ to model this the way you tried because #\ applies only to CLP(FD) constraints (specifically, "reifiable" ones) but not to "normal" Prolog goals. You can't mix these levels this way either.

    So you need to be more explicit about the two cases that exist: You have not given up the ball if either:

    • the ball is given up at a certain time, but that time has not arrived yet; or
    • the ball is not given up at all.

    Here is the same in Prolog, separating the places where Prolog negation is applied from where CLP(FD) negation is applied:

    has_not_given_up_ball(HasBall) :-
        time(GiveBall, give_ball),
        \# ( GetBall #< GiveBall #/\ GiveBall #< HasBall ).
    has_not_given_up_ball(_HasBall) :-
        \+ time(_GiveBall, give_ball).
    

    (Again, I think you should just use HasBall #=< GiveBall instead of the negated constraint.)

    And you can then adjust your definition like this:

    time(HasBall, has_ball) :-
        time(GetBall, get_ball),
        GetBall #=< HasBall,
        has_not_given_up_ball(HasBall).
    

    If a time(2, give_ball) fact is present, this behaves as before, but with an extra choice point. If I comment out that fact, it models correctly that the ball has not been given up, so one holds it for longer:

    ?- time(T, has_ball).
    T in 0..sup.
    
    ?- time(T, has_ball), label([T]).
    ERROR: Arguments are not sufficiently instantiated
    ...
    
    ?- time(1, has_ball).
    true.
    
    ?- T in 0..9, label([T]), time(T, has_ball).
    T = 0 ;
    T = 1 ;
    T = 2 ;
    T = 3 ;
    T = 4 ;
    T = 5 ;
    T = 6 ;
    T = 7 ;
    T = 8 ;
    T = 9.
    

    It's only the labeling of a time that is not constrained to a finite domain that errors, as it should.