{-
	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@]	Defines an entry in the transposition-table.
-}

module BishBosh.Search.TranspositionValue (
-- * Types
-- ** Type-synonyms
	IsOptimal,
	FindFitness,
-- ** Data-types
	Value(
--		MkValue,
		getIsOptimal,
		getNPlies,
		getMoves
	),
-- * Functions
	inferSearchDepth,
-- ** Constructor
	mkValue,
-- ** Predicates
	isBetter
 ) where

import qualified	BishBosh.Component.Move	as Component.Move
import qualified	BishBosh.Data.Exception	as Data.Exception
import qualified	Control.Exception
import qualified	Data.Ord

-- | Whether the recorded move-sequence is known to be optimal.
type IsOptimal	= Bool

-- | The type of the values in the transposition-table.
data Value move	= MkValue {
	Value move -> IsOptimal
getIsOptimal	:: IsOptimal,
	Value move -> NPlies
getNPlies	:: Component.Move.NPlies,	-- ^ The number of plies applied to the /game/ before application of any of the specified moves.
	Value move -> [move]
getMoves	:: [move]			-- ^ The sequence of moves applied to the /game/, which caused the alpha-beta event.
}

-- | Smart constructor.
mkValue
	:: IsOptimal
	-> Component.Move.NPlies
	-> [move]
	-> Value move
mkValue :: IsOptimal -> NPlies -> [move] -> Value move
mkValue IsOptimal
_ NPlies
_ []	= Exception -> Value move
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> Value move) -> Exception -> Value move
forall a b. (a -> b) -> a -> b
$ String -> Exception
Data.Exception.mkNullDatum String
"BishBosh.Search.TranspositionValue.mkValue:\tnull list of moves."
mkValue IsOptimal
isOptimal NPlies
nPlies [move]
moves
	| NPlies
nPlies NPlies -> NPlies -> IsOptimal
forall a. Ord a => a -> a -> IsOptimal
< NPlies
0	= Exception -> Value move
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> Value move) -> Exception -> Value move
forall a b. (a -> b) -> a -> b
$ String -> Exception
Data.Exception.mkOutOfBounds String
"BishBosh.Search.TranspositionValue.mkValue:\tnPlies can't be negative."
	| IsOptimal
otherwise	= MkValue :: forall move. IsOptimal -> NPlies -> [move] -> Value move
MkValue {
		getIsOptimal :: IsOptimal
getIsOptimal	= IsOptimal
isOptimal,
		getNPlies :: NPlies
getNPlies	= NPlies
nPlies,
		getMoves :: [move]
getMoves	= [move]
moves
	}

-- | Infer the search-depth from the length of the move-sequence.
inferSearchDepth :: Value move -> Component.Move.NPlies
inferSearchDepth :: Value move -> NPlies
inferSearchDepth	= [move] -> NPlies
forall (t :: * -> *) a. Foldable t => t a -> NPlies
length ([move] -> NPlies)
-> (Value move -> [move]) -> Value move -> NPlies
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value move -> [move]
forall move. Value move -> [move]
getMoves

{- |
	* The type of a function which can find the fitness of the game resulting from the recorded sequence of moves.

	* CAVEAT: the fitness this function returns should be from the perspective of the player to make the first move.
-}
type FindFitness move weightedMean	= Value move -> weightedMean

{- |
	* Whether a proposed value is better than the incumbent.

	* CAVEAT: this is a narrower concept than addressed by 'Ord', which implies 'Eq'.
-}
isBetter
	:: Ord weightedMean
	=> FindFitness move weightedMean
	-> Value move	-- ^ The proposed value.
	-> Value move	-- ^ The incumbent value.
	-> Bool
isBetter :: FindFitness move weightedMean
-> Value move -> Value move -> IsOptimal
isBetter FindFitness move weightedMean
findFitness Value move
proposedValue Value move
incumbentValue	= case (Value move -> NPlies) -> Value move -> Value move -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
Data.Ord.comparing Value move -> NPlies
forall move. Value move -> NPlies
inferSearchDepth Value move
proposedValue Value move
incumbentValue of
	Ordering
GT	-> IsOptimal
True	-- The new search is deeper.
	Ordering
EQ	-> Value move -> IsOptimal
forall move. Value move -> IsOptimal
getIsOptimal Value move
proposedValue IsOptimal -> IsOptimal -> IsOptimal
|| FindFitness move weightedMean
-> Value move -> Value move -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
Data.Ord.comparing FindFitness move weightedMean
findFitness Value move
proposedValue Value move
incumbentValue Ordering -> Ordering -> IsOptimal
forall a. Eq a => a -> a -> IsOptimal
== Ordering
GT
	Ordering
_	-> IsOptimal
False