{-
	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@]	The state which is threaded through successive calls to 'Search.Search.search'.
-}

module BishBosh.Search.SearchState(
-- * Types
-- ** Data-types
	SearchState(
--		MkSearchState,
		getPositionHashQuantifiedGameTree,
		getDynamicMoveData
	),
-- * Functions
-- ** Constructors
	mkSearchState,
	initialise
 ) where

import qualified	BishBosh.Data.Exception					as Data.Exception
import qualified	BishBosh.Evaluation.PositionHashQuantifiedGameTree	as Evaluation.PositionHashQuantifiedGameTree
import qualified	BishBosh.Evaluation.QuantifiedGame			as Evaluation.QuantifiedGame
import qualified	BishBosh.Model.Game					as Model.Game
import qualified	BishBosh.Property.Empty					as Property.Empty
import qualified	BishBosh.Search.DynamicMoveData				as Search.DynamicMoveData
import qualified	BishBosh.Search.EphemeralData				as Search.EphemeralData
import qualified	Control.Exception

-- | The data which is both received & returned by 'Search.Search.search', so that it is transported through the entire game.
data SearchState x y positionHash	= MkSearchState {
	SearchState x y positionHash
-> PositionHashQuantifiedGameTree x y positionHash
getPositionHashQuantifiedGameTree	:: Evaluation.PositionHashQuantifiedGameTree.PositionHashQuantifiedGameTree x y positionHash,
	SearchState x y positionHash -> DynamicMoveData x y positionHash
getDynamicMoveData			:: Search.DynamicMoveData.DynamicMoveData x y positionHash
}

instance Show (SearchState x y positionHash) where
	show :: SearchState x y positionHash -> String
show SearchState x y positionHash
_	= String
"SearchState {...}"

-- | Constructor.
mkSearchState
	:: Evaluation.PositionHashQuantifiedGameTree.PositionHashQuantifiedGameTree x y positionHash
	-> Search.DynamicMoveData.DynamicMoveData x y positionHash
	-> SearchState x y positionHash
mkSearchState :: PositionHashQuantifiedGameTree x y positionHash
-> DynamicMoveData x y positionHash -> SearchState x y positionHash
mkSearchState	= PositionHashQuantifiedGameTree x y positionHash
-> DynamicMoveData x y positionHash -> SearchState x y positionHash
forall x y positionHash.
PositionHashQuantifiedGameTree x y positionHash
-> DynamicMoveData x y positionHash -> SearchState x y positionHash
MkSearchState

-- | Smart constructor.
initialise :: Evaluation.PositionHashQuantifiedGameTree.PositionHashQuantifiedGameTree x y positionHash -> SearchState x y positionHash
initialise :: PositionHashQuantifiedGameTree x y positionHash
-> SearchState x y positionHash
initialise PositionHashQuantifiedGameTree x y positionHash
positionHashQuantifiedGameTree
	| Game x y -> Bool
forall x y. Game x y -> Bool
Model.Game.isTerminated Game x y
game	= Exception -> SearchState x y positionHash
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> SearchState x y positionHash)
-> Exception -> SearchState x y positionHash
forall a b. (a -> b) -> a -> b
$ String -> Exception
Data.Exception.mkResultUndefined String
"BishBosh.Search.SearchState.initialise:\tcan't search for a move from a terminated game."
	| Bool
otherwise			= MkSearchState :: forall x y positionHash.
PositionHashQuantifiedGameTree x y positionHash
-> DynamicMoveData x y positionHash -> SearchState x y positionHash
MkSearchState {
		getPositionHashQuantifiedGameTree :: PositionHashQuantifiedGameTree x y positionHash
getPositionHashQuantifiedGameTree	= PositionHashQuantifiedGameTree x y positionHash
positionHashQuantifiedGameTree,
		getDynamicMoveData :: DynamicMoveData x y positionHash
getDynamicMoveData			= DynamicMoveData x y positionHash
forall a. Empty a => a
Property.Empty.empty
	}
	where
		game :: Game x y
game	= QuantifiedGame x y -> Game x y
forall x y. QuantifiedGame x y -> Game x y
Evaluation.QuantifiedGame.getGame (QuantifiedGame x y -> Game x y) -> QuantifiedGame x y -> Game x y
forall a b. (a -> b) -> a -> b
$ PositionHashQuantifiedGameTree x y positionHash
-> QuantifiedGame x y
forall x y positionHash.
PositionHashQuantifiedGameTree x y positionHash
-> QuantifiedGame x y
Evaluation.PositionHashQuantifiedGameTree.getRootQuantifiedGame PositionHashQuantifiedGameTree x y positionHash
positionHashQuantifiedGameTree

instance Search.EphemeralData.MaybeEphemeralData (SearchState x y positionHash) where
	maybeEuthanise :: Int
-> MaybeRetireAfterNMoves
-> MaybeRetireAfterNMoves
-> SearchState x y positionHash
-> SearchState x y positionHash
maybeEuthanise Int
nPlies MaybeRetireAfterNMoves
maybeRetireKillerMovesAfter MaybeRetireAfterNMoves
maybeRetireTranspositionsAfter searchState :: SearchState x y positionHash
searchState@MkSearchState { getDynamicMoveData :: forall x y positionHash.
SearchState x y positionHash -> DynamicMoveData x y positionHash
getDynamicMoveData = DynamicMoveData x y positionHash
dynamicMoveData }	= SearchState x y positionHash
searchState {
		getDynamicMoveData :: DynamicMoveData x y positionHash
getDynamicMoveData	= Int
-> MaybeRetireAfterNMoves
-> MaybeRetireAfterNMoves
-> DynamicMoveData x y positionHash
-> DynamicMoveData x y positionHash
forall a.
MaybeEphemeralData a =>
Int -> MaybeRetireAfterNMoves -> MaybeRetireAfterNMoves -> a -> a
Search.EphemeralData.maybeEuthanise Int
nPlies MaybeRetireAfterNMoves
maybeRetireKillerMovesAfter MaybeRetireAfterNMoves
maybeRetireTranspositionsAfter DynamicMoveData x y positionHash
dynamicMoveData	-- Forward the request.
	}