Tuesday, August 10, 2010

Mastermind/Bulls and Cows Breaker

Introduction

Mastermind is a classical code breaking game. And I bet almost everyone has played it at least one time (at least, any geek[0]). I won't explain the rules here. If you really don't know the rules, here there is an explanation. Besides, we are playing Bulls and Cows, which is very similar, but has no copyright.

I sincerely find the game rather boring, though I find writing programs solving boring games quite entertaining. This is a very old prolog program I wrote to break the code. The algorithm is extremely trivial, and is more an example in how easy to solve are this class of problems in Prolog with native backtracking than anything else.

Wikipedia page also list some scientific papers on Mastermind/Bulls and Cows code breaking algorithms. I find them really interesting, indeed. But this is about Prolog and backtracking, indeed.

The code


:- use_module(library(lists)).
:- dynamic query/3.

mastermind(Code) :-
 cleanup, guess(Code), check(Code), announce.

guess(Code) :-
 Code = [_X1, _X2, _X3, _X4],
 selects(Code, [1,2,3,4,5,6,7,8,9]).

check(Guess) :-
 \+ inconsistent(Guess),
 ask(Guess).

inconsistent(Guess) :-
 query(OldGuess, Bulls, Cows),
 \+ bulls_and_cows_match(OldGuess, Guess, Bulls, Cows).

bulls_and_cows_match(OldGuess, Guess, Bulls, Cows):-
 exact_matches(OldGuess, Guess, N1),
 N1 =:= Bulls,
 common_members(OldGuess, Guess, N2),
 Cows =:= N2-Bulls.

ask(Guess) :-
 repeat,
 format('How many bulls and cows in ~p?~n', [Guess]),
 read((Bulls, Cows)),
 sensible(Bulls, Cows), !,
 assert(query(Guess, Bulls, Cows)),
 Bulls =:= 4.

sensible(Bulls, Cows) :-
 integer(Bulls),
 integer(Cows),
 Bulls + Cows =< 4.


%%  Helpers
exact_matches(Xs, Ys, N) :-
 exact_matches(Xs, Ys, 0, N).
exact_matches([X|Xs], [Y|Ys], K, N) :-
 (   X = Y ->
 K1 is K + 1
 ;   
 K1 is K),
 exact_matches(Xs, Ys, K1, N).
exact_matches([], [], N, N).

common_members(Xs, Ys, N) :-
 common_members(Xs, Ys, 0, N).
common_members([X|Xs], Ys, K, N) :-
 (   member(X, Ys) ->
 K1 is K+1
 ;   
 K1 is K),
 common_members(Xs, Ys, K1, N).
common_members([], _Ys, N, N).

cleanup :-
 retractall(query(_,_,_)), !.
cleanup.

announce :-
 size_of(X, query(X, _A, _B), N),
 format('Found the answer after ~d queries.~n', [N]).
%%  Utilities
selects([X|Xs], Ys) :-
 select(X, Ys, Ys1),
 selects(Xs, Ys1).
selects([], _Ys).

size_of(X, G, N) :-
 findall(X, G, Xs),
 length(Xs, N).

Notes

[0] Most of the type when you say "any" or "everyone" you are wrong. This applies to me as well.

No comments: