Search code examples
prologclpfd

Trying to solve a game in Prolog


Suppose, we have the following game:

There is a pair of numbers (x, y), 2 players are making moves. During the move a player can increase any number by 1 or multiply it by 2. The player, who makes a move after which (x + y) >= 77 wins.

The initial position is (8, x), find the minimal x such as the second player wins in minimal number of turns.

This problem can be easily solved analytically: both players multiply x by 2 and we get the following inequality:

8 + 2*2*x >= 77 => 4*x >= 69 => x >= (69 / 4) => x >= 17,25
x = ceil(17,25)
x = 18

Now we tried to solve it using Prolog:

:- use_module(library(clpfd)).

top(77).

% possible moves for player
next_state(X1, X2, Y1, Y2) :- Y1 #= X1 + 1,
                              Y2 #= X2.

next_state(X1, X2, Y1, Y2) :- Y1 #= X1,
                              Y2 #= X2 + 1.

next_state(X1, X2, Y1, Y2) :- Y1 #= 2*X1,
                              Y2 #= X2.

next_state(X1, X2, Y1, Y2) :- Y1 #= X1,
                              Y2 #= 2*X2.

% winning pair
win(X1, X2) :- top(X),
               X1 + X2 #>= X.

% we have a sequence of states
sequence_correct([[X1, X2]]) :- win(X1, X2).
sequence_correct([[X1, X2], [Y1, Y2] | T]) :- next_state(X1, X2, Y1, Y2),
                                              sequence_correct([[Y1, Y2] | T]).

% find X such as there is a sequence of 3 states, and there is no Y such as
% Y < X => X is minimum
min(X) :- sequence_correct([[8, X], _, _]), \+ (sequence_correct([[8, Y], _, _]), Y #< X).

But unfortunately when we try to find minimal X, it fails:

?- min(X).
false.

?- min(18). % <- this is good
true.

?- min(17).
false.

?- min(19).
false.
  • What is wrong?
  • How to fix?

Solution

  • You are using (\+)/1 which explains:

    ?- min(X).
    false.
    

    No position is negative [X0,Y0] ins 0..sup. Assuming the game doesn't start in the winning position (X0+Y0 #< 77), only the last move is winning (X+Y #>= 77).

    move_(s(X,Y), s(X0,Y0), s(X,Y)) :-
        [X0,Y0] ins 0..sup,
        X0+Y0 #< 77,
        next_state(X0, Y0, X, Y).
    
    moves([S0|Ss]) :-
        foldl(move_, Ss, S0, s(X,Y)),
        X+Y #>= 77.
    
    min(Y) :-
        Y0 in 0..77,
        labeling([min], [Y0]),
        moves([s(8,Y0),_,_]),
        !, % commit to the minimum.
        Y = Y0.
    

    The search for the minimum is done with labeling([min], [Y0]).

    Improved solution for any depth:

    move_(s(P,X,Y), s(P0,X0,Y0), s(P,X,Y)) :-
        P #= 1-P0,
        X0+Y0 #< 77,
        next_state(X0, Y0, X, Y).
    
    min(Depth, s(P0,X0,Y0), s(P,X,Y)) :-
        [X0,Y0] ins 0..sup,
        X0+Y0 #< 77,
        length(Ss, Depth),
        foldl(move_, Ss, s(P0,X0,Y0), s(P,X,Y)),
        X+Y #>= 77.
    
    min(Y) :-
        length(_, Depth),
        Y0 in 0..77,
        labeling([min], [Y0]),
        min(Depth, s(0,8,Y0), s(P,_,_)), % Start with player 0. Player 1-P wins.
        P = 0,
        !, % commit to the minimum.
        Y = Y0.