Monday, December 5, 2011

Checkers AI, part 2

Today I’d like to wrap up the game logic of our checkers-playing AI. Last time we defined the players, pieces, and the board, and operations on them. Today let’s write the game-playing code.

moves module

The moves module simply links the position module to the board module, moving pieces around a board in accordance with the patterns defined in position.

Just at position defines two movement patterns (move and jump), we will define two predicates to update a board based on these patterns: do_move and do_jump.
:- pred do_move(color, position, position, board, board).
:- mode do_move(in, in, in, in, out) is semidet.
:- mode do_move(in, in, out, in, out) is nondet.
:- mode do_move(in, out, out, in, out) is nondet.

:- pred do_jump(color, position, position, board, board).
:- mode do_jump(in, in, in, in, out) is semidet.
:- mode do_jump(in, in, out, in, out) is nondet.
:- mode do_jump(in, out, out, in, out) is nondet.
The three modes defined for each predicate allow us to check if a given move or jump is valid for the given player, to enumerate the moves or jumps available to a piece at a given position, and to enumerate all moves and jumps available on the board, respectively. Implementation is straightforward:
:- import_module piece.

do_move(Color, From, To, !Board) :-
        move(Piece, From, To),  
        move_piece(From, To, Piece, !Board),
        color(Piece) = Color.

do_jump(Color, From, To, !Board) :-
        jump(Piece, From, Jumped, To),
        move_piece(From, To, Piece, !Board),
        color(Piece) = Color,
        remove_piece(Jumped, Other, !Board),
        opponent(color(Piece), color(Other)).
Since in checkers, a piece must jump if it can jump, we will later find it useful to check whether a piece can jump from a given position without the overhead of actually updating the board. Checking whether a piece can move will also be useful for determining the end of game, so let’s define both can_move and can_jump:
:- pred can_move(color, position, board).
:- mode can_move(in, in, in) is semidet.
:- mode can_move(in, out, in) is nondet.

can_move(Color, From, Board) :-
        move(Piece, From, To),
        piece_at(Board, From, Piece),
        no_piece_at(Board, To),
        color(Piece) = Color.

:- pred can_jump(color, position, board).
:- mode can_jump(in, in, in) is semidet.
:- mode can_jump(in, out, in) is nondet.

can_jump(Color, From, Board) :-
        jump(Piece, From, Jumped, To),
        piece_at(Board, From, Piece),
        no_piece_at(Board, To),  
        color(Piece) = Color,
        piece_at(Board, Jumped, Other),
        opponent(color(Piece), color(Other)).
Note that we could simply have defined can_move(Color, From, Board) :- do_move(Color, From, _, Board, _). (and similarly for can_jump, but, since Mercury neither is lazy nor tracks unused arguments, this would entail the unnecessary computational overhead of updating the board.

game module

The game module will house the state of the game, and logic for generating possible successor states based on the rules of the game. The state of the game is given by whose turn it is, whether they are in the middle of a jump or not (in checkers, after jumping a piece, you may immediately jump another with the same piece), the history of moves (to check for draws) and the state of the board:
:- import_module board, color, position.
:- type game --->
    game(turn::color,
         jumping_state::jumping,
         history::history,      
         board::board).
:- type jumping_state ---> not_jumping; jumping(position).
In history, we need only remember past board states for each player. (This is because, as we’ll see later, we don’t need to track history of jumps.)
:- import_module set.
:- type history == set({color, board}).

Initialization of the game

Initializing the game state is easy. Red goes first and is not in the middle of a jump:
:- func init(int, int) = game.
init(Width, Height) = game(red, not_jumping, init, init(Width, Height)).
Checkers is played on an 8×8 board by default, so let’s provide initializers for this case as well:
:- func init = game.
init = init(8, 8).

:- pred init(game::out) is det.
init(init).
(The init predicate is redundant but some programmers prefer that style over zero-argument functions so we’ll provide it.)

Rules of the game

The change from one game state to the next is uniquely identified by the starting and ending locations of some piece on the board. We can declare a predicate which updates the game state based on this information, or generates possible new game states, as follows:
:- pred step(position, position, game, game).
:- mode step(in, in, in, out) is semidet.
:- mode step(in, out, in, out) is nondet.
:- mode step(out, out, in, out) is nondet.
The definition of step itself is slightly hairy, as it must follow the rules of checkers. I’ve broken it into two cases, corresponding to when a player begins their move (jumping_state is not_jumping), and when a player is forced to continue a move because a further jump is available (jumping_state is jumping):
step(From, To, game(Color0, not_jumping, !.History, !.Board) @ Game0,
               game(Color, Jumping, !:History, !:Board)) :-          
    % The game can only proceed if it is not a draw.
    not is_draw(Game0),
    % We must jump if it is possible.
    (can_jump(Color0, _, !.Board) ->
        % Since are removing a piece, history doesn't matter any more.
        init(!:History),
        % Update the board.
        do_jump(Color0, From, To, !Board),
        % If more jumps are possible, remember this fact.
        (can_jump(Color0, To, !.Board) ->
            Color = Color0,              
            Jumping = jumping(To)
        ;
            opponent(Color, Color0),
            Jumping = not_jumping   
        )
    ;    
        % Add the last position to our history.
        insert({Color0, !.Board}, !History),
        % Update the board.
        do_move(Color0, From, To, !Board),
        % It is now our opponent’s turn.
        opponent(Color0, Color),
        Jumping = not_jumping
    ),
    % If our move or jump ended in the king’s row, king it.
    (in_kings_row(!.Board, Color0, To), king_piece(To, !Board) -> true; true).

step(From, To, game(Color0, jumping(Pos), _, !.Board),
               game(Color, Jumping, init, !:Board)) :-
    % History is ignored while we are jumping.
    % We can only continue a jump from where we left off.
    From = Pos,
    % Update the board.
    do_jump(Color0, From, To, !Board),
    % If more jumps are possible, remember this fact.
    (can_jump(Color0, To, !.Board) ->
        Color = Color0,
        Jumping = jumping(To)
    ;
        opponent(Color, Color0),
        Jumping = not_jumping
    ),
    % If our jump ended in the king’s row, king it.
    (in_kings_row(!.Board, Color0, To), king_piece(To, !Board) -> true; true).
(is_draw is defined below.) Phew! That, fortunately, is the single most complex chunk of code in the entire implementation.

Checking the state of the game

It is important to provide predicates to determine whether a game has finished, and if so, who (if anyone) has won. First, we define can_step as a proxy for step which does not actually create a new game state:
:- pred can_step(game::in) is semidet.

can_step(game(Color, not_jumping, _, Board) @ Game) :-
    not is_draw(Game),
    (can_jump(Color, _, Board); can_move(Color, _, Board)).

can_step(game(_, jumping(_), _, _)).
(Again, as with can_move and can_jump, we could have defined this in terms of step, but we would perform unnecessary computation.)

We can then define is_draw to determine whether the current game state is a draw or not (i.e. whether the current state exists in previous history):
:- pred is_draw(game::in) is semidet.

is_draw(game(Color, not_jumping, History, Board)) :-
    member({Color, Board}, History).
Finally, we can determine whether a game is over, and if so, who the winner is (if any) as follows:
:- pred game_over(game::in, maybe(color)::out) is semidet.

game_over(Game, Winner) :-
    if is_draw(Game) then Winner = no
    else
        not can_step(Game),
        Winner = yes(opponent(Game^turn)).

game_io module

We’re almost ready to test our game logic with human players. To do this, we’ll first need to declare predicates to print the state of the game, and to allow the human player(s) to choose a move:
:- import_module board, color, game, piece.
:- import_module io, maybe.

:- pred print_color(color::in, io::di, io::uo) is det.
:- pred print_piece(piece::in, io::di, io::uo) is det.
:- pred print_board(board::in, io::di, io::uo) is det.
:- pred print_game(game::in, io::di, io::uo) is det.
:- pred print_winner(maybe(color)::in, io::di, io::uo) is det.

:- pred choose_move(list(game)::in(non_empty_list), result(game)::out,
        io::di, io::uo) is det.
These predicates are all fairly straightforward, so I’ll elide most of them here to save space. Of note is choose_move, which presents each game state in the list in turn to the player, asking if the player wishes to choose that move. If the player chooses none, the sequence is repeated. Note that the mode of this argument is given as in(non_empty_list) to ensure that an empty list of moves is not passed, which would result in an infinite loop. Here is the code, which is mostly implemented by choose_move_aux:
choose_move(Games, Chosen, !IO) :- choose_move_aux(Games, Games, Chosen, !IO).

:- pred choose_move_aux(list(game)::in(non_empty_list), list(game)::in,
    result(game)::out, io::di, io::uo) is det.

choose_move_aux(AllGames, [], Chosen, !IO) :-
    write_string("Repeating...\n\n", !IO),
    choose_move_aux(AllGames, AllGames, Chosen, !IO).

choose_move_aux(AllGames, [Game | Games], Chosen, !IO) :-
    print_board(Game^board, !IO), nl(!IO),
    write_string("Ok? ", !IO),
    read_line_as_string(Res, !IO), nl(!IO),
    (
        Res = ok(String),
        (prefix(String, "y") -> Chosen = ok(Game);
         choose_move_aux(AllGames, Games, Chosen, !IO))
    ;
        Res = eof, Chosen = eof
    ;
        Res = error(Err), Chosen = error(Err)
    ).

checkers module

Finally we can wrap everything together with our main module, checkers.

Players

To make our code modular, let’s define a typeclass player:
:- import_module game, io.
:- typeclass player(Player) where [
    pred make_move(Player::in, game::in, game::out, io::di, io::uo)
        is cc_multi
].
This means that a player is any type Player which has defined for it a make_move predicate with the given signature. This allows us to implement various “players”, each with a different choose_move predicate.

By including the IO state and declaring the determinism of make_move as cc_multi, we allow both for players which must interact with IO (e.g., humans), and for players which may choose a move arbitrarily (e.g., search algorithms which find several optimal choices).

Now we can implement various human and AI players which conform to this interface. Since we’re just testing for now, we’ll define a human player like so:
:- import_module game_io, list, require, solutions.

:- type human_player ---> human_player.
:- instance player(human_player) where [
    (choose_move(human_player, Game0, Game1, !IO) :-
        unsorted_solutions(
            pred(Game::out) is nondet :- step(_, _, Game0, Game),
            Moves),                                              
        (
            Moves = [_|_],
            make_move(Moves, Res, !IO),
            (                            
                Res = ok(Game1)
            ;                  
                Res = eof, error("End of file")
            ;                                  
                Res = error(Err), error(error_message(Err))
            )                                              
        ;    
            Moves = [],
            unexpected($module, $pred, "Game is not over but no more moves!")
        )
    )    
].
(The dummy type human_player is needed so we can declare it as an instance of the typeclass player.) unsorted_solutions returns an arbitrarily ordered list of all the possible moves from a given position. We assert that this list should not be empty (as the player should not have been asked to make a move when there are no moves available, as this means that the game is over!), and forward the rest of the work to our previously-defined game_io.choose_move.

We can also define a dummy AI that chooses a move arbitrarily like so:
:- type dummy_player ---> dummy_player.
:- instance player(dummy_player) where [
    (make_move(dummy_player, Game0, Game1, !IO) :-
        unsorted_solutions(                       
            pred(Game::out) is nondet :- step(_, _, Game0, Game),
            Moves),                                              
        Game1 = det_head(Moves))
].

Why typeclasses?
You may rightly ask, “why not simply declare a type player ---> human_player; dummy_player and forget the whole typeclass business?” By using typeclasses, we can provide new player implementations in other modules, rather than stuffing them all into one possibly large module.

Of course, another way of doing this would be using higher-order predicates: we could declare players as a predicate type. The problem with this approach is that we may at some point determine that a player should have more predicates associated with it (such as one defining their name or difficulty), at which point we will need to pass around multiple predicates having messy types and instantiations. Using typeclasses allows us to redefine what a player is more easily.

The main loop

Last but not least, we will define a loop play_game, which takes a game state and two values whose types are instances of the player typeclass to represent the two players. The implementation is straightforward:
:- pred play_game(game::in, Red::in, White::in, io::di, io::uo) is cc_multi
    <= (player(Red), player(White)).

play_game(Game0, Red, White, !IO) :-
    print_game(Game0, !IO), nl(!IO),
    (game_over(Game0, _) -> true;
        (
            Game0^turn = red,
            make_move(Red, Game0, Game1, !IO)
        ;
            Game0^turn = white,
            make_move(White, Game0, Game1, !IO)
        ),
        play_game(Game1, Red, White, !IO)
    ).
In this predicate, make_move will call the make_move predicate associated with the type of Red or White as appropriate.

Last but not least, the main predicate will start a game between two players (in this case, a human_player and a dummy_player):
:- pred main(io::di, io::uo) is cc_multi.
main(!IO) :- play_game(init, human_player, dummy_player, !IO).

Trying it out

Thanks to Mercury’s built-in build system, we can compile the whole shebang with simply mmc --make checkers. Running it lets us play a game versus the dummy AI:
 o o o o
o o o o 
 o o o o
· · · · 
 · · · ·
x x x x 
 x x x x
x x x x 

X's move.
It’s our move first. Let’s cycle through the options:
 o o o o
o o o o 
 o o o o
· · · · 
 · · · x
x x x · 
 x x x x
x x x x 

Ok? n

 o o o o
o o o o 
 o o o o
· · · · 
 · · x ·
x x x · 
 x x x x
x x x x 

Ok? n

 o o o o
o o o o 
 o o o o
· · · · 
 · · x ·
x x · x 
 x x x x
x x x x 

Ok? n

 o o o o
o o o o 
 o o o o
· · · · 
 · x · ·
x x · x 
 x x x x
x x x x 

Ok? n

 o o o o
o o o o 
 o o o o
· · · · 
 · x · ·
x · x x 
 x x x x
x x x x 

Ok? n

 o o o o
o o o o 
 o o o o
· · · · 
 x · · ·
x · x x 
 x x x x
x x x x 

Ok? n

 o o o o
o o o o 
 o o o o
· · · · 
 x · · ·
· x x x 
 x x x x
x x x x 

Ok? n

Repeating...
OK, we’ve seen all of them. Let’s choose the first:
 o o o o
o o o o 
 o o o o
· · · · 
 · · · x
x x x · 
 x x x x
x x x x 

Ok? y

 o o o o
o o o o 
 o o o o
· · · · 
 · · · x
x x x · 
 x x x x
x x x x 
Let’s make sure the computer picks a valid move.
O's move.

 o o o o
o o o o 
 o o o ·
· · · o 
 · · · x
x x x · 
 x x x x
x x x x 
Hooray! Of course, now it’s our move again. This could go on for a while. Testing it proves that everything works however!

Conclusion

Today we covered building the game logic in the moves and game module, and I/O and the main loop in the game_io and checkers modules. Next week we’ll finish up by adding an AI based on the minimax algorithm.

2 comments:

  1. I guess you never got around to making part 3?

    ReplyDelete
  2. Oh no, sorry, this was so long ago. I remember I wasn't able to satisfactorily code up minimax using Mercury's constraint system, and then got distracted by something else. I will see if I can find a draft somewhere and post if I'm able to find it.

    ReplyDelete