/* define hexapawn in terns of a term to represent a state: s(Player,Board) where Player is 1 or 2 and Board is a term with nine numbers representing the piece in each of the nine positions with a 1 where player 1 has a pice, a 2 where player 2 has a piece and a 0 where there is no piece. e.g., (1,1,1,0,0,0,2,2,2) coresponds to the initial position: 1,1,1 0,0,0 2,2,2 */ :- use_module(library(lists)). :- ensure_loaded(mm). % start(S) is true for the initial position of the game. start(s(1,(1,1,1,0,0,0,2,2,2))). % win(P,S) is true of state S is a win for player P. win(1,s(_,(_,_,_,_,_,_,G,H,I))) :- (G=1;H=1;I=1),!. win(2,s(_,(A,B,C,_,_,_,_,_,_))) :- (A=2;B=2;C=2),!. % move(S1,S2) is ture if there is a legal move from state S1 to state S2. % Note: player 1 has 14 possible moves and player 2 14. %Player one moves from A move(s(1,(1,B,C,0,E,F,G,H,I)),s(2,(0,B,C,1,E,F,G,H,I))). move(s(1,(1,B,C,D,2,F,G,H,I)),s(2,(0,B,C,D,1,F,G,H,I))). %Player one moves from B move(s(1,(A,1,C,2,E,F,G,H,I)),s(2,(A,0,C,1,E,F,G,H,I))). move(s(1,(A,1,C,D,0,F,G,H,I)),s(2,(A,0,C,D,1,F,G,H,I))). move(s(1,(A,1,C,D,E,2,G,H,I)),s(2,(A,0,C,D,E,1,G,H,I))). %Player one moves from C move(s(1,(A,B,1,D,E,0,G,H,I)),s(2,(A,B,0,D,E,1,G,H,I))). move(s(1,(A,B,1,D,2,F,G,H,I)),s(2,(A,B,0,D,1,F,G,H,I))). %Player one moves from D move(s(1,(A,B,C,1,E,F,0,H,I)),s(2,(A,B,C,0,E,F,1,H,I))). move(s(1,(A,B,C,1,E,F,G,2,I)),s(2,(A,B,C,0,E,F,G,1,I))). %Player one moves from E move(s(1,(A,B,C,D,1,F,2,H,I)),s(2,(A,B,C,D,0,F,1,H,I))). move(s(1,(A,B,C,D,1,F,G,0,I)),s(2,(A,B,C,D,0,F,G,1,I))). move(s(1,(A,B,C,D,1,F,G,H,2)),s(2,(A,B,C,D,0,F,G,H,0))). %Player one moves from F move(s(1,(A,B,C,D,E,1,G,2,I)),s(2,(A,B,C,D,E,0,G,1,I))). move(s(1,(A,B,C,D,E,1,G,H,0)),s(2,(A,B,C,D,E,0,G,H,1))). % Player 2 moves from G move(s(2,(A,B,C,0,E,F,2,H,I)),s(1,(A,B,C,2,E,F,0,H,I))). move(s(2,(A,B,C,D,1,F,2,H,I)),s(1,(A,B,C,D,2,F,0,H,I))). % Player 2 moves from H move(s(2,(A,B,C,1,E,F,G,2,I)),s(1,(A,B,C,2,E,F,G,0,I))). move(s(2,(A,B,C,D,0,F,G,2,I)),s(1,(A,B,C,D,2,F,G,0,I))). move(s(2,(A,B,C,D,E,1,G,2,I)),s(1,(A,B,C,D,E,2,G,0,I))). % Player 2 moves from I move(s(2,(A,B,C,D,E,0,G,H,2)),s(1,(A,B,C,D,E,2,G,H,0))). move(s(2,(A,B,C,D,1,F,G,H,2)),s(1,(A,B,C,D,2,F,G,H,0))). % Player 2 moves from D move(s(2,(0,B,C,2,E,F,G,H,I)),s(1,(2,B,C,0,E,F,G,H,I))). move(s(2,(A,1,C,2,E,F,G,H,I)),s(1,(A,2,C,0,E,F,G,H,I))). % Player 2 moves from E move(s(2,(1,B,C,D,2,F,G,H,I)),s(1,(2,B,C,D,0,F,G,H,I))). move(s(2,(A,0,C,D,2,F,G,H,I)),s(1,(A,2,C,D,0,F,G,H,I))). move(s(2,(A,B,1,D,2,F,G,H,I)),s(1,(A,B,2,D,0,F,G,H,I))). % Player 2 moves from F move(s(2,(A,1,C,D,E,2,G,H,I)),s(1,(A,2,C,D,E,0,G,H,I))). move(s(2,(A,B,0,D,E,2,G,H,I)),s(1,(A,B,2,D,E,0,G,H,I))). % eval(S,V) is true if the static evaluator for state S is V. eval(S,999) :- win(1,S),!. eval(S,-999) :- win(2,S),!. eval(s(_,(_,_,_,D,E,F,_,_,_)),N) :- score(D,Sd), score(E,Se), score(F,Sf), N is Sd+Se+Sf, !. score(1,1). score(2,-1). score(0,0). printBoard((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.