summaryrefslogtreecommitdiff
path: root/pd_client_swipl.pl
blob: 1739be75c544190e14dd510cba151393d5f619a2 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
start(Module):-start(Module, localhost).
start(Module, Host):-start(Module, Host, 8068).

start(Module, Host, Port):-
	tcp_socket(Socket),
	tcp_connect(Socket, Host:Port, StreamIn, StreamOut),
	launch(Module, StreamIn, StreamOut),
	tcp_close_socket(Socket).

launch(Module, StreamIn, StreamOut) :-
	atom_concat('rules/', Module, Path), consult(Path),
	do(StreamIn, StreamOut, Module, [], []).

do(_,  _, _, _, [e|_]) :- !.
do(StreamIn, StreamOut, Module, ModuleState, Hist) :-
	call(Module, Hist, ModuleDecision, ModuleState, NewModuleState),
	write(StreamOut, ModuleDecision), flush_output(StreamOut),
	format('Own choose:\t~w\n', [ModuleDecision]),
	loop(StreamIn, StreamOut, Module, NewModuleState, Hist).

loop(StreamIn, StreamOut, Module, ModuleState, Hist) :-
	get_code(StreamIn, ChoiceCode), byte_to_atom(ChoiceCode, Choice),
	format('Opponent chose:\t~w\n', [Choice]),
	do(StreamIn, StreamOut, Module, ModuleState, [Choice|Hist]).

% -1 = EOF
byte_to_atom(-1, e):-!.
byte_to_atom(Byte, Atom):-atom_codes(Atom, [Byte]).