%==============================================================================
% Project:	Course "Logic Programming and Deductive Databases"
% Version:	Summer 2021, University of Halle
% Module:	gamestate.pl
% Purpose:	Manges "Connect Four" Game State
% Last Change:	07.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, Parts date back to 1992
% Copying:	You may do what you want with this, but you cannot make me
%       	responsible for anything. Please mark changed versions.
%==============================================================================

:- module(gamestate,
	[init_state/1, move/4, won/2, board_full/1, print/1, symbol/2]).

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

% The game state is represented as the term
%	game(Col1,...,Col7)
% where each column is represented as
%	col(Field1,...,Field6)
% where each field is one of
%	empty
%	yellow
%	red.

%------------------------------------------------------------------------------
% init_state(GameState): This returns the initial/empty game state.
%------------------------------------------------------------------------------

init_state(game(
	col(empty, empty, empty, empty, empty, empty),
	col(empty, empty, empty, empty, empty, empty),
	col(empty, empty, empty, empty, empty, empty),
	col(empty, empty, empty, empty, empty, empty),
	col(empty, empty, empty, empty, empty, empty),
	col(empty, empty, empty, empty, empty, empty),
	col(empty, empty, empty, empty, empty, empty))).

%------------------------------------------------------------------------------
% col_get(RowNo, Column, FieldColor):
%------------------------------------------------------------------------------

col_get(1, col(Field,_,_,_,_,_), Field).
col_get(2, col(_,Field,_,_,_,_), Field).
col_get(3, col(_,_,Field,_,_,_), Field).
col_get(4, col(_,_,_,Field,_,_), Field).
col_get(5, col(_,_,_,_,Field,_), Field).
col_get(6, col(_,_,_,_,_,Field), Field).

%------------------------------------------------------------------------------
% col_add(Old_Column, Field_Color, New_Column):
%------------------------------------------------------------------------------

col_add(col(empty,empty,empty,empty,empty,empty), F1,
	col(F1,empty,empty,empty,empty,empty)).
col_add(col(F1,empty,empty,empty,empty,empty), F2,
	col(F1,F2,empty,empty,empty,empty)) :-
	F1 \= empty.
col_add(col(F1,F2,empty,empty,empty,empty), F3,
	col(F1,F2,F3,empty,empty,empty)) :-
	F1 \= empty,
	F2 \= empty.
col_add(col(F1,F2,F3,empty,empty,empty), F4,
	col(F1,F2,F3,F4,empty,empty)) :-
	F1 \= empty,
	F2 \= empty,
	F3 \= empty.
col_add(col(F1,F2,F3,F4,empty,empty), F5,
	col(F1,F2,F3,F4,F5,empty)) :-
	F1 \= empty,
	F2 \= empty,
	F3 \= empty,
	F4 \= empty.
col_add(col(F1,F2,F3,F4,F5,empty), F6,
	col(F1,F2,F3,F4,F5,F6)) :-
	F1 \= empty,
	F2 \= empty,
	F3 \= empty,
	F4 \= empty,
	F5 \= empty.

%------------------------------------------------------------------------------
% move(OldState, Player, ColNo, NewState): Changes of the game state.
%------------------------------------------------------------------------------

move(game(Col1,Col2,Col3,Col4,Col5,Col6,Col7), Player, 1,
	game(New1,Col2,Col3,Col4,Col5,Col6,Col7)) :-
	col_add(Col1, Player, New1).

move(game(Col1,Col2,Col3,Col4,Col5,Col6,Col7), Player, 2,
	game(Col1,New2,Col3,Col4,Col5,Col6,Col7)) :-
	col_add(Col2, Player, New2).

move(game(Col1,Col2,Col3,Col4,Col5,Col6,Col7), Player, 3,
	game(Col1,Col2,New3,Col4,Col5,Col6,Col7)) :-
	col_add(Col3, Player, New3).

move(game(Col1,Col2,Col3,Col4,Col5,Col6,Col7), Player, 4,
	game(Col1,Col2,Col3,New4,Col5,Col6,Col7)) :-
	col_add(Col4, Player, New4).

move(game(Col1,Col2,Col3,Col4,Col5,Col6,Col7), Player, 5,
	game(Col1,Col2,Col3,Col4,New5,Col6,Col7)) :-
	col_add(Col5, Player, New5).

move(game(Col1,Col2,Col3,Col4,Col5,Col6,Col7), Player, 6,
	game(Col1,Col2,Col3,Col4,Col5,New6,Col7)) :-
	col_add(Col6, Player, New6).

move(game(Col1,Col2,Col3,Col4,Col5,Col6,Col7), Player, 7,
	game(Col1,Col2,Col3,Col4,Col5,Col6,New7)) :-
	col_add(Col7, Player, New7).

%------------------------------------------------------------------------------
% disc_or_empty(State, RowNo, ColNo, Player):
%------------------------------------------------------------------------------

% This can return yellow, red, or empty as Player for a given row and colum.

disc_or_empty(game(Col1,_Col2,_Col3,_Col4,_Col5,_Col6,_Col7),RowNo,1,Player) :-
	col_get(RowNo, Col1, Player).

disc_or_empty(game(_Col1,Col2,_Col3,_Col4,_Col5,_Col6,_Col7),RowNo,2,Player) :-
	col_get(RowNo, Col2, Player).

disc_or_empty(game(_Col1,_Col2,Col3,_Col4,_Col5,_Col6,_Col7),RowNo,3,Player) :-
	col_get(RowNo, Col3, Player).

disc_or_empty(game(_Col1,_Col2,_Col3,Col4,_Col5,_Col6,_Col7),RowNo,4,Player) :-
	col_get(RowNo, Col4, Player).

disc_or_empty(game(_Col1,_Col2,_Col3,_Col4,Col5,_Col6,_Col7),RowNo,5,Player) :-
	col_get(RowNo, Col5, Player).

disc_or_empty(game(_Col1,_Col2,_Col3,_Col4,_Col5,Col6,_Col7),RowNo,6,Player) :-
	col_get(RowNo, Col6, Player).

disc_or_empty(game(_Col1,_Col2,_Col3,_Col4,_Col5,_Col6,Col7), RowNo,7,Player) :-
	col_get(RowNo, Col7, Player).

%------------------------------------------------------------------------------
% disc(State, RowNo, ColNo, Player):
%------------------------------------------------------------------------------

% This fails when the position is empty:

disc(State, RowNo, ColNo, Player) :-
	disc_or_empty(State, RowNo, ColNo, Player),
	player(Player).

%------------------------------------------------------------------------------
% player(Player):
%------------------------------------------------------------------------------

% Enumeration values for player:

player(yellow).
player(red).

%==============================================================================
% Printing of the Game Board:
%==============================================================================

print(State) :-
	print_top,
	print_row(State, 6),
	print_row(State, 5),
	print_row(State, 4),
	print_row(State, 3),
	print_row(State, 2),
	print_row(State, 1),
	print_bottom.

%------------------------------------------------------------------------------
% get_sym(GameState, RowNo, ColNo, Symbol):
%------------------------------------------------------------------------------

get_sym(State, RowNo, ColNo, Symbol) :-
	disc_or_empty(State, RowNo, ColNo, Color),
	symbol(Color, Symbol).

%------------------------------------------------------------------------------
% symbol(Color, Symbol):
%------------------------------------------------------------------------------

symbol(yellow, '*').
symbol(red,    '+').
symbol(empty,  ' ').

%------------------------------------------------------------------------------
% print_row(State, RowNo):
%------------------------------------------------------------------------------

print_row(State, RowNo) :-
	print_row(State, RowNo, 1).

print_row(_State, _RowNo, StartColNo) :-
	StartColNo > 7,
	write('|'),
	nl.

print_row(State, RowNo, StartColNo) :-
	StartColNo =< 7,
	get_sym(State, RowNo, StartColNo, Sym),
	write('|'),
	write(Sym),
	NextColNo is StartColNo + 1,
	print_row(State, RowNo, NextColNo).

%------------------------------------------------------------------------------
% print_top:
%------------------------------------------------------------------------------

print_top :-
	nl.

%------------------------------------------------------------------------------
% print_bottom:
%------------------------------------------------------------------------------

print_bottom :-
	write('---------------'),
	nl,
	write(' 1 2 3 4 5 6 7 '),
	nl,
	nl.

%==============================================================================
% Checking Whether a Player has Won the Game:
%==============================================================================

% Four in a row (deltaRow = 0, deltaCol = 1):
won(State, Player) :-
	col(ColNo),
	row(RowNo),
	ColNo =< 4,
	n_of_a_color(State, Player, RowNo, ColNo, 0, 1, 4).

% Four in a column (deltaRow = 1, deltaCol = 0):
won(State, Player) :-
	col(ColNo),
	row(RowNo),
	RowNo =< 3,
	n_of_a_color(State, Player, RowNo, ColNo, 1, 0, 4).

% Four in a diagonal up (deltaRow = 1, deltaCol = 1):
won(State, Player) :-
	col(ColNo),
	row(RowNo),
	ColNo =< 4,
	RowNo =< 3,
	n_of_a_color(State, Player, RowNo, ColNo, 1, 1, 4).

% Four in a diagonal down (deltaRow = -1, deltaCol = 1):
won(State, Player) :-
	col(ColNo),
	row(RowNo),
	ColNo =< 4,
	RowNo >= 4,
	n_of_a_color(State, Player, RowNo, ColNo, -1, 1, 4).

%------------------------------------------------------------------------------
% row(RowNo): Possible Row Numbers.
%------------------------------------------------------------------------------

row(1).
row(2).
row(3).
row(4).
row(5).
row(6).

%------------------------------------------------------------------------------
% col(ColNo): Possible Column Numbers.
%------------------------------------------------------------------------------

col(1).
col(2).
col(3).
col(4).
col(5).
col(6).
col(7).

%------------------------------------------------------------------------------
% n_of_a_color(State, Player, StartRow, StartCol, DeltaRow, DeltaCol, N):
%------------------------------------------------------------------------------

n_of_a_color(_State, _Player, _RowNo, _ColNo, _DeltaRow, _DeltaCol, 0).

n_of_a_color(State, Player, RowNo, ColNo, DeltaRow, DeltaCol, N) :-
	N > 0,
	disc(State, RowNo, ColNo, Player),
	NextRowNo is RowNo + DeltaRow,
	NextColNo is ColNo + DeltaCol,
	NextN is N - 1,
	n_of_a_color(State, Player, NextRowNo, NextColNo, DeltaRow, DeltaCol,
			NextN).


%==============================================================================
% Checking Whether the Game Board is Full:
%==============================================================================

board_full(State) :-
	disc(State, 6, 1, _),
	disc(State, 6, 2, _),
	disc(State, 6, 3, _),
	disc(State, 6, 4, _),
	disc(State, 6, 5, _),
	disc(State, 6, 6, _),
	disc(State, 6, 7, _).

