%==============================================================================
% Project:	Course "Logic Programming and Deductive Databases"
% Version:	Summer 2021, University of Halle
% Module:	human.pl
% Purpose:	Human Player in "Connect Four" Match
% Last Change:	08.07.2021
% Language:	Prolog (Tested with SWI Prolog)
% Authors:	Stefan Brass
% Email:	brass@informatik.uni-halle.de
% Address:	Universitaet Halle, Inst. f. Informatik, D-06099 Halle, Germany
% Copyright:	(c) 2021 by Stefan Brass
% Copying:	You may do what you want with this, but you cannot make me
%       	responsible for anything. Please mark changed versions.
%==============================================================================

:- module(human, [init_yellow/1, init_red/1,
		choose_move_yellow/3, choose_move_red/3,
		opponent_move_red/3, opponent_move_yellow/3]).

:- use_module(gamestate, [symbol/2]).

%==============================================================================
% Representation of Game State:
%==============================================================================

% state(OwnColor,NumDiscsInCol1,...,NumDiscsInCol7),
% e.g. state(yellow,0,0,0,1,0,0,0).
% We store the number of discs in each column to avoid invalid moves.

%------------------------------------------------------------------------------
% init_yellow(-State):
%------------------------------------------------------------------------------

init_yellow(state(yellow,0,0,0,0,0,0,0)).

%------------------------------------------------------------------------------
% init_red(-State):
%------------------------------------------------------------------------------

init_red(state(red,0,0,0,0,0,0,0)).

%==============================================================================
% Auxiliary Predicates for Game State:
%==============================================================================

%------------------------------------------------------------------------------
% get_num_discs(+Col, +State, -NumDiscs):
%------------------------------------------------------------------------------

% Returns the number of discs in a given column.

get_num_discs(1, state(_Color, N1,_N2,_N3,_N4,_N5,_N6,_N7), N1).
get_num_discs(2, state(_Color,_N1, N2,_N3,_N4,_N5,_N6,_N7), N2).
get_num_discs(3, state(_Color,_N1,_N2, N3,_N4,_N5,_N6,_N7), N3).
get_num_discs(4, state(_Color,_N1,_N2,_N3, N4,_N5,_N6,_N7), N4).
get_num_discs(5, state(_Color,_N1,_N2,_N3,_N4, N5,_N6,_N7), N5).
get_num_discs(6, state(_Color,_N1,_N2,_N3,_N4,_N5, N6,_N7), N6).
get_num_discs(7, state(_Color,_N1,_N2,_N3,_N4,_N5,_N6, N7), N7).

%------------------------------------------------------------------------------
% inc_num_discs(+Col, +State, -NewState):
%------------------------------------------------------------------------------

inc_num_discs(1,state(C,N1,N2,N3,N4,N5,N6,N7),state(C,X1,N2,N3,N4,N5,N6,N7)) :-
		N1 < 6,
		X1 is N1 + 1.
inc_num_discs(2,state(C,N1,N2,N3,N4,N5,N6,N7),state(C,N1,X2,N3,N4,N5,N6,N7)) :-
		N2 < 6,
		X2 is N2 + 1.
inc_num_discs(3,state(C,N1,N2,N3,N4,N5,N6,N7),state(C,N1,N2,X3,N4,N5,N6,N7)) :-
		N3 < 6,
		X3 is N3 + 1.
inc_num_discs(4,state(C,N1,N2,N3,N4,N5,N6,N7),state(C,N1,N2,N3,X4,N5,N6,N7)) :-
		N4 < 6,
		X4 is N4 + 1.
inc_num_discs(5,state(C,N1,N2,N3,N4,N5,N6,N7),state(C,N1,N2,N3,N4,X5,N6,N7)) :-
		N5 < 6,
		X5 is N5 + 1.
inc_num_discs(6,state(C,N1,N2,N3,N4,N5,N6,N7),state(C,N1,N2,N3,N4,N5,X6,N7)) :-
		N6 < 6,
		X6 is N6 + 1.
inc_num_discs(7,state(C,N1,N2,N3,N4,N5,N6,N7),state(C,N1,N2,N3,N4,N5,N6,X7)) :-
		N7 < 6,
		X7 is N7 + 1.

%------------------------------------------------------------------------------
% get_color(+State, -Color):
%------------------------------------------------------------------------------

get_color(state(Color,_,_,_,_,_,_,_), Color).

%==============================================================================
% Choose Move:
%==============================================================================

%------------------------------------------------------------------------------
% choose_move_yellow(+State, -Col, -NewState):
%------------------------------------------------------------------------------

choose_move_yellow(State, Col, NewState) :-
	choose_move(State, Col),
	inc_num_discs(Col, State, NewState).

%------------------------------------------------------------------------------
% choose_move_red(+State, -Col, -NewState):
%------------------------------------------------------------------------------

choose_move_red(State, Col, NewState) :-
	choose_move(State, Col),
	inc_num_discs(Col, State, NewState).

%------------------------------------------------------------------------------
% choose_move(+State, -Col):
%------------------------------------------------------------------------------

choose_move(State, InputCol) :-
	get_color(State, Color),
	write('Bitte Zug fuer '),
	print_name(Color, ColorName),
	write(ColorName),
	symbol(Color, Symbol),
	write(' ('),
	write(Symbol),
	write(') eingeben [1..7]: '),
	flush_output,
	read_char(InputChar),
	opt_correct_input(State, InputChar, InputCol).

%------------------------------------------------------------------------------
% print_name(+Color, -Name):
%------------------------------------------------------------------------------

print_name(yellow, 'Gelb').
print_name(red,    'Rot').

%------------------------------------------------------------------------------
% opt_correct_input(+State, +InputChar, -FinalCol):
%------------------------------------------------------------------------------

opt_correct_input(_State, 'q', 0) :-
	!,
	fail.

opt_correct_input(State, InputChar, FinalCol) :-
	valid_input(State, InputChar, InputCol),
	!,
	FinalCol = InputCol.

opt_correct_input(State, InputChar, FinalCol) :-
	write('Eingabe '),
	write(InputChar),
	write(' ist ungueltig!'),
	nl,
	choose_move(State, FinalCol).

%------------------------------------------------------------------------------
% read_char(-InputChar):
%------------------------------------------------------------------------------

read_char(Char) :-
	get_char(NextChar),
	skip_space(NextChar, Char).

skip_space(InputChar, Char) :-
	is_space(InputChar),
	!,
	read_char(Char).

skip_space(InputChar, InputChar).

is_space(' ').
is_space('\n').
is_space('\r').
is_space('\t').

%------------------------------------------------------------------------------
% valid_input(+State, +InputChar, -InputCol):
%------------------------------------------------------------------------------

% This checks an input character and translates it to an integer column number.

valid_input(State, InputChar, InputCol) :-
	char_to_col(InputChar, InputCol),
	col_not_full(State, InputCol).

char_to_col('1', 1).
char_to_col('2', 2).
char_to_col('3', 3).
char_to_col('4', 4).
char_to_col('5', 5).
char_to_col('6', 6).
char_to_col('7', 7).

col_not_full(State, Col) :-
	get_num_discs(Col, State, N),
	N < 6.

%==============================================================================
% Record Opponent Move In State:
%==============================================================================

%------------------------------------------------------------------------------
% opponent_move_yellow(+State, +YellowCol, -NewState):
%------------------------------------------------------------------------------

% We are playing Red. This informs us about the column Yellow has chosen.

opponent_move_yellow(State, YellowCol, NewState) :-
	inc_num_discs(YellowCol, State, NewState).

%------------------------------------------------------------------------------
% opponent_move_red(+State, +RedCol, -NewState):
%------------------------------------------------------------------------------

% We are playing Yellow. This informs us about the column Red has chosen.

opponent_move_red(State, RedCol, NewState) :-
	inc_num_discs(RedCol, State, NewState).

