Skip to content

Instantly share code, notes, and snippets.

@yamashita1238
Created October 17, 2014 13:46
Show Gist options
  • Save yamashita1238/efa8e8fc74ad4e181d96 to your computer and use it in GitHub Desktop.
Save yamashita1238/efa8e8fc74ad4e181d96 to your computer and use it in GitHub Desktop.
:- use_module(library(socket)).
write_atom(Stream,Atom) :-
atom_codes(Atom,Codes),
write_codes(Stream,Codes).
write_codes(_,[]) :- !.
write_codes(Stream,[Code|Tail]) :-
put_code(Stream,Code),
write_codes(Stream,Tail).
receive_word(Stream,X) :-
get_until_space(Stream,X,[]).
get_until_space(Stream,X,CodeList) :-
atom_codes(' ',Space_),
head(Space,Space_),
atom_codes('\n',NL_),
head(NL,NL_),
get_code(Stream,Code),
(Code == Space ->
atom_codes(X,CodeList);
(Code == NL ->
atom_codes(X,CodeList);
(append(CodeList,[Code],NewList),
get_until_space(Stream,X,NewList)))).
head(H,[H|_]).
main([Host,Port,Name]) :-
client(Host,Port,Name).
client(Host,Port,Name) :-
tcp_socket(Socket),
atom_number(Port,Port_num),
tcp_connect(Socket,Host:Port_num,Read,Write),
set_stream(Write,buffer(false)),
swritef(S,'OPEN %w',[Name]),
write_atom(Write,S),write_atom(Write,'\n'),
wait_for_input([Read],_Readable,0),
receive_word(Read,Message),
(Message == 'START' ->
start_game(Read,Write);
(close(Read),
close(Write))).
wait_game(Read,Write) :-
receive_word(Read,Mes),
(Mes == 'START' ->
start_game(Read,Write);
(close(Read),
close(Write))).
start_game(Read,Write) :-
init_board(Black,White),
receive_word(Read,BW),
receive_word(Read,OppName),
receive_word(Read,Time_),
atom_number(Time_,Time),
writef('The game starts.\nMy color is %w.\nOppName is %w.\n',
[BW,OppName]),
(BW == 'BLACK' ->
my_turn(Black,White,b,Read,Write,Time);
opp_turn(Black,White,w,Read,Write,Time)).
my_turn(Black,White,BW,Read,Write,Time) :-
play(Black,White,BW,Time,Pos),
move(Pos,BW,Black,White,NewBlack,NewWhite),
convert_pos(Pos,POS),
swritef(S,'MOVE %w\n',[POS]),
print('my move:'),print(POS),print('\n'),
show_board(NewBlack,NewWhite),
print(S),print('\n'),
write_atom(Write,S),
wait_ack(NewBlack,NewWhite,BW,Read,Write).
opp_turn(Black,White,BW,Read,Write,Time) :-
receive_word(Read,Mes),
(Mes == 'MOVE' ->
opp_move(Black,White,BW,Read,Write,Time);
(Mes == 'END' ->
end_game(BW,Read,Write))).
opp_move(Black,White,BW,Read,Write,Time) :-
receive_word(Read,POS),
convert_pos(Pos,POS),
opp(BW,WB),
move(Pos,WB,Black,White,NewBlack,NewWhite),
print('opp move:'),print(POS),print('\n'),
legal(NewBlack,NewWhite,BW,Legal),
show_board_with_legal(NewBlack,NewWhite,Legal),
my_turn(NewBlack,NewWhite,BW,Read,Write,Time).
wait_ack(Black,White,BW,Read,Write) :-
receive_word(Read,Mes),
(Mes == 'ACK' ->
ack(Black,White,BW,Read,Write);
(Mes == 'END' ->
end_game(BW,Read,Write))).
ack(Black,White,BW,Read,Write) :-
receive_word(Read,Time),
opp_turn(Black,White,BW,Read,Write,Time).
end_game(_,Read,Write) :-
receive_word(Read,WL),
receive_word(Read,N),
receive_word(Read,M),
receive_word(Read,Reason),
writef('%w\n%w vs %w\n%w\n',[WL,N,M,Reason]),
wait_game(Read,Write).
%% %% The program written above is to client.
%% %% The program written below is to play othello.
%% %% The othello board is presented by a pair of 64 bits integer.
pair([H,T],H,T).
log2(1,0) :- !.
log2(N,X) :-
N > 1,
M is N >> 1,
log2(M,Y),
X is Y+1.
convert_pos(-1,'PASS') :- !.
convert_pos(Pow_of_two,POS) :-
var(POS),!,
A is "A",
log2(Pow_of_two,N),
Line is 1 + (N div 8),
Row_ is A + (N mod 8),
Row = [Row_],
number_codes(Line,LineCodes),
append(Row,LineCodes,PosCodes),
atom_codes(POS,PosCodes).
convert_pos(PosNum,POS) :-
atom_codes(POS,PosCodes),
pair(PosCodes,RowCode,LineCode),
LineCodes = [LineCode],
number_codes(Line,LineCodes),
A is "A",
Row is RowCode - A,
N is (Line - 1)*8 + Row,
PosNum is 1 << N.
init_board(Black,White) :-
Black is 34628173824, %% = 2^28+2^35.
White is 68853694464. %% = 2^27+2^36.
show_point(Black,White,Legal) :-
(Black mod 2 =:= 0 ->
(White mod 2 =:= 0 ->
(Legal mod 2 =:= 0 ->
writef('| ',[]);
writef('|L',[]));
writef('|o',[]));
writef('|x',[])).
show_line(Black,White,Legal) :-
forall(between(0,7,X),
(B is Black div 2^X,
W is White div 2^X,
L is Legal div 2^X,
show_point(B,W,L))),
writef('|\n',[]).
show_board_with_legal(Black,White,Legal) :-
writef(' A B C D E F G H\n',[]),
forall(between(0,7,X),
(B is Black div 2^(8*X),
W is White div 2^(8*X),
L is Legal div 2^(8*X),
Y is X + 1,
writef('%w',[Y]),
show_line(B,W,L))),
writef('\n',[]).
show_board(Black,White) :-
show_board_with_legal(Black,White,0).
opp(b,w).
opp(w,b).
legal_in_a_direction(Mine,Opp,D,X) :-
edge(D,Edge),
NotEdge is (1 << 64) -1 - Edge,
Space is ((1 << 64) - 1) - Mine - Opp,
Mine_ is Mine /\ NotEdge,
Opp1 is (Mine_ << D) /\ Opp /\ NotEdge,
Sand1 is (Opp1 << D) /\ Space,
Opp2 is (Opp1 << D) /\ Opp /\ NotEdge,
Sand2 is (Opp2 << D) /\ Space,
Opp3 is (Opp2 << D) /\ Opp /\ NotEdge,
Sand3 is (Opp3 << D) /\ Space,
Opp4 is (Opp3 << D) /\ Opp /\ NotEdge,
Sand4 is (Opp4 << D) /\ Space,
Opp5 is (Opp4 << D) /\ Opp /\ NotEdge,
Sand5 is (Opp5 << D) /\ Space,
Opp6 is (Opp5 << D) /\ Opp /\ NotEdge,
Sand6 is (Opp6 << D) /\ Space,
X is Sand1 \/ Sand2 \/ Sand3 \/ Sand4 \/ Sand5 \/ Sand6.
legal(Black,White,w,Legal) :-
legal(White,Black,b,Legal),!.
legal(Black,White,b,Legal) :-
legal_in_a_direction(Black,White,-9,L1),
legal_in_a_direction(Black,White,-8,L2),
legal_in_a_direction(Black,White,-7,L3),
legal_in_a_direction(Black,White,-1,L4),
legal_in_a_direction(Black,White, 1,L5),
legal_in_a_direction(Black,White, 7,L6),
legal_in_a_direction(Black,White, 8,L7),
legal_in_a_direction(Black,White, 9,L8),
Legal is L1 \/ L2 \/ L3 \/ L4 \/ L5 \/ L6 \/ L7 \/ L8.
edge(D,Edge) :-
((D == -9;D == -1;D == 7) ->
Edge = 72340172838076673;
((D == -7;D == 1;D == 9) ->
Edge = 9259542123273814144;
Edge = 0)).
sandwich_in_a_direction(Pos,Mine,Opp,D,N) :-
member(D,[-9,-8,-7,-1,1,7,8,9]),
edge(D,Edge),
Pos /\ Edge =:= 0,
Pos_ is Pos << D,
Pos_ /\ Opp =\= 0,
sandwich_in_a_direction_(Pos_,Mine,Opp,D,M),
N is M+1.
sandwich_in_a_direction_(Pos,Mine,_,D,0) :-
edge(D,Edge),
Pos /\ Edge =:= 0,
(Pos << D) /\ Mine =\= 0,!.
sandwich_in_a_direction_(Pos,Mine,Opp,D,N) :-
edge(D,Edge),
Pos /\ Edge =:= 0,
Pos_ is Pos << D,
Pos_ /\ Opp =\= 0,
sandwich_in_a_direction_(Pos_,Mine,Opp,D,M),
N is M+1.
sandwich(_,[],0) :- !.
sandwich(Pos,[Head|Tail],Sand) :-
sandwich(Pos,Tail,Sand_),
sandwich_(Pos,Head,Sum),
Sand is Sand_ + Sum.
sandwich_(_,[_,0],0) :- !.
sandwich_(Pos,[D,N],Sum) :-
Pos_ is Pos << D,
M is N-1,
sandwich_(Pos_,[D,M],Sum_),
Sum is Sum_ + (Pos << D).
move(-1,_,Black,White,Black,White) :- !.
move(Pos,b,Black,White,NewBlack,NewWhite) :-
findall([D,N],
sandwich_in_a_direction(Pos,Black,White,D,N),List),
sandwich(Pos,List,Sand),
NewBlack is Black + Sand + Pos,
NewWhite is White - Sand,!.
move(Pos,w,Black,White,NewBlack,NewWhite) :-
move(Pos,b,White,Black,NewWhite,NewBlack).
play(Black,White,BW,_Time,Pos) :-
legal(Black,White,BW,Legal),
Legal =\= 0,
between(0,63,X),
(1 << X) /\ Legal =\= 0,!,
Pos is 1 << X.
play(_,_,_,_,-1).
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment