{-
	Copyright (C) 2018 Dr. Alistair Ward

	This file is part of BishBosh.

	BishBosh is free software: you can redistribute it and/or modify
	it under the terms of the GNU General Public License as published by
	the Free Software Foundation, either version 3 of the License, or
	(at your option) any later version.

	BishBosh is distributed in the hope that it will be useful,
	but WITHOUT ANY WARRANTY; without even the implied warranty of
	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
	GNU General Public License for more details.

	You should have received a copy of the GNU General Public License
	along with BishBosh.  If not, see <http://www.gnu.org/licenses/>.
-}
{- |
 [@AUTHOR@]	Dr. Alistair Ward

 [@DESCRIPTION@]

	* Itemises the ways in which a game may be declared a draw.

	* Each reason corresponds to a rule in chess.
-}

module BishBosh.Rule.DrawReason(
-- * Types
-- ** Data-types
	DrawReason(),
-- * Constants
	maximumConsecutiveRepeatablePlies,
	maximumConsecutiveRepeatablePositions,
	byAgreement,
--	fiftyMoveRule,
	seventyFiveMoveRule,
	insufficientMaterial,
	staleMate,
--	threeFoldRepetition,
	fiveFoldRepetition
) where

import qualified	BishBosh.Component.Move			as Component.Move
import qualified	BishBosh.Property.FixedMembership	as Property.FixedMembership
import qualified	BishBosh.Type.Count			as Type.Count
import qualified	Control.DeepSeq

-- | The sum-type of ways in which a game can be drawn.
data DrawReason
	= ByAgreement		-- ^ Both players have agreed to a draw.
	| FiftyMoveRule		-- ^ A draw can be claimed if fifty consecutive full /move/s have occured without any capture or any @Pawn@ being moved.
	| SeventyFiveMoveRule	-- ^ Seventy-five consecutive full /move/s have occured without either capture or @Pawn@-movement; <https://www.chessprogramming.org/Repetitions#Fide_Rule>.
	| InsufficientMaterial	-- ^ Neither player as the fire-power to force /check-mate/.
	| StaleMate		-- ^ The next player hasn't any legal moves, but isn't /in check/.
	| ThreeFoldRepetition	-- ^ A draw can be claimed if the same /position/ has been reached on any three occasions.
	| FiveFoldRepetition	-- ^ The same /position/ has been reached on five successive occasions.
	deriving (DrawReason -> DrawReason -> Bool
(DrawReason -> DrawReason -> Bool)
-> (DrawReason -> DrawReason -> Bool) -> Eq DrawReason
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DrawReason -> DrawReason -> Bool
$c/= :: DrawReason -> DrawReason -> Bool
== :: DrawReason -> DrawReason -> Bool
$c== :: DrawReason -> DrawReason -> Bool
Eq, Eq DrawReason
Eq DrawReason
-> (DrawReason -> DrawReason -> Ordering)
-> (DrawReason -> DrawReason -> Bool)
-> (DrawReason -> DrawReason -> Bool)
-> (DrawReason -> DrawReason -> Bool)
-> (DrawReason -> DrawReason -> Bool)
-> (DrawReason -> DrawReason -> DrawReason)
-> (DrawReason -> DrawReason -> DrawReason)
-> Ord DrawReason
DrawReason -> DrawReason -> Bool
DrawReason -> DrawReason -> Ordering
DrawReason -> DrawReason -> DrawReason
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DrawReason -> DrawReason -> DrawReason
$cmin :: DrawReason -> DrawReason -> DrawReason
max :: DrawReason -> DrawReason -> DrawReason
$cmax :: DrawReason -> DrawReason -> DrawReason
>= :: DrawReason -> DrawReason -> Bool
$c>= :: DrawReason -> DrawReason -> Bool
> :: DrawReason -> DrawReason -> Bool
$c> :: DrawReason -> DrawReason -> Bool
<= :: DrawReason -> DrawReason -> Bool
$c<= :: DrawReason -> DrawReason -> Bool
< :: DrawReason -> DrawReason -> Bool
$c< :: DrawReason -> DrawReason -> Bool
compare :: DrawReason -> DrawReason -> Ordering
$ccompare :: DrawReason -> DrawReason -> Ordering
$cp1Ord :: Eq DrawReason
Ord, ReadPrec [DrawReason]
ReadPrec DrawReason
Int -> ReadS DrawReason
ReadS [DrawReason]
(Int -> ReadS DrawReason)
-> ReadS [DrawReason]
-> ReadPrec DrawReason
-> ReadPrec [DrawReason]
-> Read DrawReason
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DrawReason]
$creadListPrec :: ReadPrec [DrawReason]
readPrec :: ReadPrec DrawReason
$creadPrec :: ReadPrec DrawReason
readList :: ReadS [DrawReason]
$creadList :: ReadS [DrawReason]
readsPrec :: Int -> ReadS DrawReason
$creadsPrec :: Int -> ReadS DrawReason
Read, Int -> DrawReason -> ShowS
[DrawReason] -> ShowS
DrawReason -> String
(Int -> DrawReason -> ShowS)
-> (DrawReason -> String)
-> ([DrawReason] -> ShowS)
-> Show DrawReason
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DrawReason] -> ShowS
$cshowList :: [DrawReason] -> ShowS
show :: DrawReason -> String
$cshow :: DrawReason -> String
showsPrec :: Int -> DrawReason -> ShowS
$cshowsPrec :: Int -> DrawReason -> ShowS
Show)

instance Control.DeepSeq.NFData DrawReason where
	rnf :: DrawReason -> ()
rnf DrawReason
_	= ()

instance Property.FixedMembership.FixedMembership DrawReason where
	members :: [DrawReason]
members	= [DrawReason
ByAgreement, DrawReason
FiftyMoveRule, DrawReason
SeventyFiveMoveRule, DrawReason
InsufficientMaterial, DrawReason
StaleMate, DrawReason
ThreeFoldRepetition, DrawReason
FiveFoldRepetition]

-- | Constant.
byAgreement :: DrawReason
byAgreement :: DrawReason
byAgreement	= DrawReason
ByAgreement

-- | Constant.
fiftyMoveRule :: DrawReason
fiftyMoveRule :: DrawReason
fiftyMoveRule	= DrawReason
FiftyMoveRule

-- | Constant.
seventyFiveMoveRule :: DrawReason
seventyFiveMoveRule :: DrawReason
seventyFiveMoveRule	= DrawReason
SeventyFiveMoveRule

-- | Constant.
insufficientMaterial :: DrawReason
insufficientMaterial :: DrawReason
insufficientMaterial	= DrawReason
InsufficientMaterial

-- | Constant.
staleMate :: DrawReason
staleMate :: DrawReason
staleMate	= DrawReason
StaleMate

-- | Constant.
threeFoldRepetition :: DrawReason
threeFoldRepetition :: DrawReason
threeFoldRepetition	= DrawReason
ThreeFoldRepetition

-- | Constant.
fiveFoldRepetition :: DrawReason
fiveFoldRepetition :: DrawReason
fiveFoldRepetition	= DrawReason
FiveFoldRepetition

-- | The number of consecutive plies required to trigger a draw by the seventy-five move rule.
maximumConsecutiveRepeatablePlies :: Type.Count.NPlies
maximumConsecutiveRepeatablePlies :: Int
maximumConsecutiveRepeatablePlies	= Int
Component.Move.nPliesPerMove Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
75

-- | The number of consecutive repeatable positions required for a draw by the five-fold repetition rule.
maximumConsecutiveRepeatablePositions :: Type.Count.NPositions
maximumConsecutiveRepeatablePositions :: Int
maximumConsecutiveRepeatablePositions	= Int
5