/* define tic tac toe in terms of a term to represent a state: s(Player,Board) where Player is 1 or 2 and Board is a list with nine atoms representing the mark in each of the nine positions with a "1" where player 1 has a piece, a "2" where player 2 has a piece and a b where there is no piece. e.g., [b,b,b,b,b,b,b,b] coresponds to the initial position. */ :- use_module(library(lists)). :- ensure_loaded(mm). player(1). player(2). % the initial state for tic tac toe: player 1 to move and all blanks. start(s(1,[b,b,b,b,b,b,b,b,b])). % move(S1,S2) if there is a legal move from state S1 to state S2. move(s(1,B1),s(2,B2)) :- replace(b,1,B1,B2). move(s(2,B1),s(1,B2)) :- replace(b,2,B1,B2). % replace/4 returns a list Lout in which some (one!) element % matching Old is replaced by New in Lin replace(Old,New,Lin,Lout) :- append(Left,[Old|Right],Lin), append(Left,[New|Right],Lout). % win(Player,State) : state State is a win for player Player iff she % has three marks in a row in the state's board. win(Player,s(_,Board)) :- player(Player), row3(Player,Board). % it's a draw if there are no moves to make. draw(s(_,B)) :- \+ member(b,B). % row3(Player,Board) is true if player Player has three marks in a row % on board Board. row3(P,B) :- line(B,[P,P,P]). % player P has an pen line L on board B. AN open line is a % horizontal, vertical or diagonal line of three positions, one of which % has player P's mark and none of which have the other player's mark. openLine(P,B,L) :- other(P,P2), line(B,L), member(P,L), \+ member(P2,L). % other(+P1,-P2) is true P1 is a player and P2 is another player. other(P1,P2) :- player(P1), player(P2), \+ P1=P2. % line(Board,Line) is true iff board Board has a line of three % positions in a row represented by the list Line. line([A,B,C, _,_,_, _,_,_], [A,B,C]). line([_,_,_, A,B,C, _,_,_], [A,B,C]). line([_,_,_, _,_,_, A,B,C], [A,B,C]). line([A,_,_, B,_,_, C,_,_], [A,B,C]). line([_,A,_, _,B,_, _,C,_], [A,B,C]). line([_,_,A, _,_,B, _,_,C], [A,B,C]). line([A,_,_, _,B,_, _,_,C], [A,B,C]). line([_,_,A, _,B,_, C,_,_], [A,B,C]). % a static evaluation function for tic tac toe. eval(S,999) :- win(1,S),!. eval(S,-999) :- win(2,S),!. eval(s(_,B),N) :- findall(L,openLine(1,B,L),P1s), findall(L,openLine(2,B,L),P2s), length(P1s,N1), length(P2s,N2), N is N1-N2. % print a nice representation of the board. printBoard(L) :- replaceChars(L,[A,B,C,D,E,F,G,H,I]), format(" ~p~p~p\n",[A,B,C]), format(" ~p~p~p\n",[D,E,F]), format(" ~p~p~p\n",[G,H,I]), nl. replaceChars([],[]). replaceChars([C1|Rest1],[C2|Rest2]) :- replaceChar(C1,C2), replaceChars(Rest1,Rest2). replaceChar(b,'.') :- !. replaceChar(1,'X') :- !. replaceChar(2,'O') :- !. replaceChar(Any,Any).