{-
	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 positionHash	= MkSearchState {
	SearchState positionHash
-> PositionHashQuantifiedGameTree positionHash
getPositionHashQuantifiedGameTree	:: Evaluation.PositionHashQuantifiedGameTree.PositionHashQuantifiedGameTree positionHash,
	SearchState positionHash -> DynamicMoveData positionHash
getDynamicMoveData			:: Search.DynamicMoveData.DynamicMoveData positionHash
}

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

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

-- | Smart constructor.
initialise :: Evaluation.PositionHashQuantifiedGameTree.PositionHashQuantifiedGameTree positionHash -> SearchState positionHash
initialise :: PositionHashQuantifiedGameTree positionHash
-> SearchState positionHash
initialise PositionHashQuantifiedGameTree positionHash
positionHashQuantifiedGameTree
	| Game -> Bool
Model.Game.isTerminated Game
game	= Exception -> SearchState positionHash
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> SearchState positionHash)
-> Exception -> SearchState 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 positionHash.
PositionHashQuantifiedGameTree positionHash
-> DynamicMoveData positionHash -> SearchState positionHash
MkSearchState {
		getPositionHashQuantifiedGameTree :: PositionHashQuantifiedGameTree positionHash
getPositionHashQuantifiedGameTree	= PositionHashQuantifiedGameTree positionHash
positionHashQuantifiedGameTree,
		getDynamicMoveData :: DynamicMoveData positionHash
getDynamicMoveData			= DynamicMoveData positionHash
forall a. Empty a => a
Property.Empty.empty
	}
	where
		game :: Game
game	= QuantifiedGame -> Game
Evaluation.QuantifiedGame.getGame (QuantifiedGame -> Game) -> QuantifiedGame -> Game
forall a b. (a -> b) -> a -> b
$ PositionHashQuantifiedGameTree positionHash -> QuantifiedGame
forall positionHash.
PositionHashQuantifiedGameTree positionHash -> QuantifiedGame
Evaluation.PositionHashQuantifiedGameTree.getRootQuantifiedGame PositionHashQuantifiedGameTree positionHash
positionHashQuantifiedGameTree

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