{-
	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@]	Searches for the optimal /move/ from those currently available.
-}

module BishBosh.Search.Search(
-- * Types
-- ** Data-types
	Result (
--		MkResult,
		getSearchState,
		getQuantifiedGames,
		getNPositionsEvaluated
	),
-- * Constants
	showsSeparator,
-- * Functions
	search
--	calculateBranchingFactor,
-- ** Constructor
--	mkResult
 ) where

import			Control.Arrow((&&&))
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.Input.SearchOptions				as Input.SearchOptions
import qualified	BishBosh.Model.Game					as Model.Game
import qualified	BishBosh.Notation.MoveNotation				as Notation.MoveNotation
import qualified	BishBosh.Search.AlphaBeta				as Search.AlphaBeta
import qualified	BishBosh.Search.EphemeralData				as Search.EphemeralData
import qualified	BishBosh.Search.SearchState				as Search.SearchState
import qualified	BishBosh.State.TurnsByLogicalColour			as State.TurnsByLogicalColour
import qualified	BishBosh.Text.ShowList					as Text.ShowList
import qualified	BishBosh.Type.Count					as Type.Count
import qualified	BishBosh.Type.Crypto					as Type.Crypto
import qualified	BishBosh.Type.Length					as Type.Length
import qualified	Control.DeepSeq
import qualified	Control.Exception
import qualified	Control.Monad.Reader
import qualified	Data.Maybe

-- | The type returned by 'search'.
data Result x y positionHash	= MkResult {
	Result x y positionHash -> SearchState x y positionHash
getSearchState		:: Search.SearchState.SearchState x y positionHash,
	Result x y positionHash -> [QuantifiedGame x y]
getQuantifiedGames	:: [Evaluation.QuantifiedGame.QuantifiedGame x y],	-- ^ The optimal path down the /positionHashQuantifiedGameTree/.
	Result x y positionHash -> NPositions
getNPositionsEvaluated	:: Type.Count.NPositions				-- ^ The total number of nodes in the /positionHashQuantifiedGameTree/ which were analysed.
}

instance Control.DeepSeq.NFData (Result x y positionHash) where
	rnf :: Result x y positionHash -> ()
rnf MkResult { getQuantifiedGames :: forall x y positionHash.
Result x y positionHash -> [QuantifiedGame x y]
getQuantifiedGames = [QuantifiedGame x y]
quantifiedGames }	= [QuantifiedGame x y] -> ()
forall a. NFData a => a -> ()
Control.DeepSeq.rnf [QuantifiedGame x y]
quantifiedGames	-- CAVEAT: don't evaluate the search-state, since this contains the PositionHashQuantifiedGameTree !

-- | Used to format output.
showsSeparator :: ShowS
showsSeparator :: ShowS
showsSeparator	= String -> ShowS
showString String
" -> "

instance (Enum x, Enum y) => Notation.MoveNotation.ShowNotationFloat (Result x y positionHash) where
	showsNotationFloat :: MoveNotation
-> (Double -> ShowS) -> Result x y positionHash -> ShowS
showsNotationFloat MoveNotation
moveNotation Double -> ShowS
showsDouble result :: Result x y positionHash
result@MkResult {
		getQuantifiedGames :: forall x y positionHash.
Result x y positionHash -> [QuantifiedGame x y]
getQuantifiedGames	= [QuantifiedGame x y]
quantifiedGames,
		getNPositionsEvaluated :: forall x y positionHash. Result x y positionHash -> NPositions
getNPositionsEvaluated	= NPositions
nPositionsEvaluated
	} = ShowS
-> (QuantifiedGame x y -> ShowS) -> [QuantifiedGame x y] -> ShowS
forall a. ShowS -> (a -> ShowS) -> [a] -> ShowS
Text.ShowList.showsFormattedList ShowS
showsSeparator (
		MoveNotation -> (Double -> ShowS) -> QuantifiedGame x y -> ShowS
forall a.
ShowNotationFloat a =>
MoveNotation -> (Double -> ShowS) -> a -> ShowS
Notation.MoveNotation.showsNotationFloat MoveNotation
moveNotation Double -> ShowS
showsDouble
	 ) [QuantifiedGame x y]
quantifiedGames ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"; selected after analysing " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NPositions -> ShowS
forall a. Show a => a -> ShowS
shows NPositions
nPositionsEvaluated ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" nodes" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (
		if [QuantifiedGame x y] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [QuantifiedGame x y]
quantifiedGames Bool -> Bool -> Bool
|| NPositions
nPositionsEvaluated NPositions -> NPositions -> Bool
forall a. Eq a => a -> a -> Bool
== NPositions
0
			then ShowS
forall a. a -> a
id
			else String -> ShowS
showString String
" (branching-factor" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
Text.ShowList.showsAssociation ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> ShowS
showsDouble (Result x y positionHash -> Double
forall branchingFactor x y positionHash.
Floating branchingFactor =>
Result x y positionHash -> branchingFactor
calculateBranchingFactor Result x y positionHash
result) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
')'
	 )

-- | Smart constructor.
mkResult :: (
	Enum	x,
	Enum	y,
	Ord	x,
	Ord	y,
	Show	x,
	Show	y
 )
	=> Search.SearchState.SearchState x y positionHash
	-> [Evaluation.QuantifiedGame.QuantifiedGame x y]
	-> Type.Count.NPositions
	-> Result x y positionHash
mkResult :: SearchState x y positionHash
-> [QuantifiedGame x y] -> NPositions -> Result x y positionHash
mkResult SearchState x y positionHash
searchState [QuantifiedGame x y]
quantifiedGames NPositions
nPositionsEvaluated
	| [QuantifiedGame x y] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [QuantifiedGame x y]
quantifiedGames	= Exception -> Result x y positionHash
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> Result x y positionHash)
-> (String -> Exception) -> String -> Result x y positionHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Exception
Data.Exception.mkNullDatum (String -> Exception) -> ShowS -> String -> Exception
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"BishBosh.Search.Search.mkResult:\tnull quantifiedGames; " (String -> Result x y positionHash)
-> String -> Result x y positionHash
forall a b. (a -> b) -> a -> b
$ Game x y -> ShowS
forall a. Show a => a -> ShowS
shows Game x y
game String
"."
	| NPositions
nPositionsEvaluated NPositions -> NPositions -> Bool
forall a. Ord a => a -> a -> Bool
< NPositions
0	= Exception -> Result x y positionHash
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> Result x y positionHash)
-> (String -> Exception) -> String -> Result x y positionHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Exception
Data.Exception.mkOutOfBounds (String -> Exception) -> ShowS -> String -> Exception
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"BishBosh.Search.Search.mkResult:\tnPositionsEvaluated=" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NPositions -> ShowS
forall a. Show a => a -> ShowS
shows NPositions
nPositionsEvaluated ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" mustn't be negative; " (String -> Result x y positionHash)
-> String -> Result x y positionHash
forall a b. (a -> b) -> a -> b
$ Game x y -> ShowS
forall a. Show a => a -> ShowS
shows Game x y
game String
"."
	| Bool
otherwise		= MkResult :: forall x y positionHash.
SearchState x y positionHash
-> [QuantifiedGame x y] -> NPositions -> Result x y positionHash
MkResult {
		getSearchState :: SearchState x y positionHash
getSearchState		= SearchState x y positionHash
searchState,
		getQuantifiedGames :: [QuantifiedGame x y]
getQuantifiedGames	= [QuantifiedGame x y]
quantifiedGames,
		getNPositionsEvaluated :: NPositions
getNPositionsEvaluated	= NPositions
nPositionsEvaluated
	}
	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)
-> (PositionHashQuantifiedGameTree x y positionHash
    -> QuantifiedGame x y)
-> PositionHashQuantifiedGameTree x y positionHash
-> Game x y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 -> Game x y)
-> PositionHashQuantifiedGameTree x y positionHash -> Game x y
forall a b. (a -> b) -> a -> b
$ SearchState x y positionHash
-> PositionHashQuantifiedGameTree x y positionHash
forall x y positionHash.
SearchState x y positionHash
-> PositionHashQuantifiedGameTree x y positionHash
Search.SearchState.getPositionHashQuantifiedGameTree SearchState x y positionHash
searchState

-- | Initiates the recursive function 'Search.AlphaBeta.negaMax', then unpacks the results.
search :: (
	Enum	x,
	Enum	y,
	Ord	positionHash,
	Ord	x,
	Ord	y,
	Show	x,
	Show	y
 )
	=> Type.Count.NPlies	-- ^ How deep down the tree to search.
	-> Search.SearchState.SearchState x y positionHash
	-> Input.SearchOptions.Reader (Result x y positionHash)
{-# SPECIALISE search :: Type.Count.NPlies -> Search.SearchState.SearchState Type.Length.X Type.Length.Y Type.Crypto.PositionHash -> Input.SearchOptions.Reader (Result Type.Length.X Type.Length.Y Type.Crypto.PositionHash) #-}
search :: NPositions
-> SearchState x y positionHash -> Reader (Result x y positionHash)
search NPositions
0 SearchState x y positionHash
_	= Exception -> Reader (Result x y positionHash)
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> Reader (Result x y positionHash))
-> (String -> Exception)
-> String
-> Reader (Result x y positionHash)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Exception
Data.Exception.mkOutOfBounds (String -> Exception) -> ShowS -> String -> Exception
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"BishBosh.Search.Search.search:\t" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
forall a. Show a => a -> ShowS
shows String
Input.SearchOptions.searchDepthTag ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" must be at least " (String -> Reader (Result x y positionHash))
-> String -> Reader (Result x y positionHash)
forall a b. (a -> b) -> a -> b
$ NPositions -> ShowS
forall a. Show a => a -> ShowS
shows NPositions
Input.SearchOptions.minimumSearchDepth String
"."
search NPositions
searchDepth SearchState x y positionHash
searchState
	| Just GameTerminationReason
terminationReason <- Game x y -> Maybe GameTerminationReason
forall x y. Game x y -> Maybe GameTerminationReason
Model.Game.getMaybeTerminationReason Game x y
game	= Exception -> Reader (Result x y positionHash)
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> Reader (Result x y positionHash))
-> (String -> Exception)
-> String
-> Reader (Result x y positionHash)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Exception
Data.Exception.mkInvalidDatum (String -> Exception) -> ShowS -> String -> Exception
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"BishBosh.Search.Search.search:\tthe game has already terminated; " (String -> Reader (Result x y positionHash))
-> String -> Reader (Result x y positionHash)
forall a b. (a -> b) -> a -> b
$ GameTerminationReason -> ShowS
forall a. Show a => a -> ShowS
shows GameTerminationReason
terminationReason String
"."
	| Bool
otherwise								= do
		(MaybeRetireAfterNMoves, MaybeRetireAfterNMoves)
pair	<- (SearchOptions -> (MaybeRetireAfterNMoves, MaybeRetireAfterNMoves))
-> ReaderT
     SearchOptions
     Identity
     (MaybeRetireAfterNMoves, MaybeRetireAfterNMoves)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
Control.Monad.Reader.asks ((SearchOptions
  -> (MaybeRetireAfterNMoves, MaybeRetireAfterNMoves))
 -> ReaderT
      SearchOptions
      Identity
      (MaybeRetireAfterNMoves, MaybeRetireAfterNMoves))
-> (SearchOptions
    -> (MaybeRetireAfterNMoves, MaybeRetireAfterNMoves))
-> ReaderT
     SearchOptions
     Identity
     (MaybeRetireAfterNMoves, MaybeRetireAfterNMoves)
forall a b. (a -> b) -> a -> b
$ SearchOptions -> MaybeRetireAfterNMoves
Input.SearchOptions.getMaybeRetireKillerMovesAfter (SearchOptions -> MaybeRetireAfterNMoves)
-> (SearchOptions -> MaybeRetireAfterNMoves)
-> SearchOptions
-> (MaybeRetireAfterNMoves, MaybeRetireAfterNMoves)
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& SearchOptions -> MaybeRetireAfterNMoves
Input.SearchOptions.maybeRetireTranspositionsAfter

		let nPlies :: NPositions
nPlies	= TurnsByLogicalColour (Turn x y) -> NPositions
forall turn. TurnsByLogicalColour turn -> NPositions
State.TurnsByLogicalColour.getNPlies (TurnsByLogicalColour (Turn x y) -> NPositions)
-> TurnsByLogicalColour (Turn x y) -> NPositions
forall a b. (a -> b) -> a -> b
$ Game x y -> TurnsByLogicalColour (Turn x y)
forall x y. Game x y -> TurnsByLogicalColour x y
Model.Game.getTurnsByLogicalColour Game x y
game

		Result x y positionHash
searchResult	<- NPositions
-> SearchState x y positionHash -> Reader (Result x y positionHash)
forall x y positionHash.
(Enum x, Enum y, Ord positionHash, Ord x, Ord y, Show x, Show y) =>
NPositions
-> SearchState x y positionHash -> Reader (Result x y positionHash)
Search.AlphaBeta.negaMax NPositions
searchDepth (SearchState x y positionHash -> Reader (Result x y positionHash))
-> SearchState x y positionHash -> Reader (Result x y positionHash)
forall a b. (a -> b) -> a -> b
$ (MaybeRetireAfterNMoves
 -> MaybeRetireAfterNMoves
 -> SearchState x y positionHash
 -> SearchState x y positionHash)
-> (MaybeRetireAfterNMoves, MaybeRetireAfterNMoves)
-> SearchState x y positionHash
-> SearchState x y positionHash
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (NPositions
-> MaybeRetireAfterNMoves
-> MaybeRetireAfterNMoves
-> SearchState x y positionHash
-> SearchState x y positionHash
forall a.
MaybeEphemeralData a =>
NPositions
-> MaybeRetireAfterNMoves -> MaybeRetireAfterNMoves -> a -> a
Search.EphemeralData.maybeEuthanise NPositions
nPlies) (MaybeRetireAfterNMoves, MaybeRetireAfterNMoves)
pair SearchState x y positionHash
searchState

		case NPositions
-> Result x y positionHash
-> (DynamicMoveData x y positionHash, [Turn x y], NPositions)
forall x y positionHash.
NPositions
-> Result x y positionHash
-> (DynamicMoveData x y positionHash, [Turn x y], NPositions)
Search.AlphaBeta.extractSelectedTurns NPositions
nPlies Result x y positionHash
searchResult of
			(DynamicMoveData x y positionHash
dynamicMoveData, turns :: [Turn x y]
turns@(Turn x y
turn : [Turn x y]
_), NPositions
nPositionsEvaluated)	-> let
				isMatch :: Turn x y -> NodeLabel x y positionHash -> Bool
isMatch Turn x y
turn'	= (Turn x y -> Turn x y -> Bool
forall a. Eq a => a -> a -> Bool
== Turn x y
turn') (Turn x y -> Bool)
-> (NodeLabel x y positionHash -> Turn x y)
-> NodeLabel x y positionHash
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QuantifiedGame x y -> Turn x y
forall x y. QuantifiedGame x y -> Turn x y
Evaluation.QuantifiedGame.getLastTurn (QuantifiedGame x y -> Turn x y)
-> (NodeLabel x y positionHash -> QuantifiedGame x y)
-> NodeLabel x y positionHash
-> Turn x y
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NodeLabel x y positionHash -> QuantifiedGame x y
forall x y positionHash.
NodeLabel x y positionHash -> QuantifiedGame x y
Evaluation.PositionHashQuantifiedGameTree.getQuantifiedGame
			 in Result x y positionHash -> Reader (Result x y positionHash)
forall (m :: * -> *) a. Monad m => a -> m a
return {-to Reader-monad-} (Result x y positionHash -> Reader (Result x y positionHash))
-> Result x y positionHash -> Reader (Result x y positionHash)
forall a b. (a -> b) -> a -> b
$ SearchState x y positionHash
-> [QuantifiedGame x y] -> NPositions -> Result x y positionHash
forall x y positionHash.
(Enum x, Enum y, Ord x, Ord y, Show x, Show y) =>
SearchState x y positionHash
-> [QuantifiedGame x y] -> NPositions -> Result x y positionHash
mkResult (
				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
Search.SearchState.mkSearchState (
					PositionHashQuantifiedGameTree x y positionHash
-> Maybe (PositionHashQuantifiedGameTree x y positionHash)
-> PositionHashQuantifiedGameTree x y positionHash
forall a. a -> Maybe a -> a
Data.Maybe.fromMaybe (
						Exception -> PositionHashQuantifiedGameTree x y positionHash
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> PositionHashQuantifiedGameTree x y positionHash)
-> (String -> Exception)
-> String
-> PositionHashQuantifiedGameTree x y positionHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Exception
Data.Exception.mkIncompatibleData (String -> Exception) -> ShowS -> String -> Exception
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"BishBosh.Search.Search.search:\tBishBosh.Evaluation.PositionHashQuantifiedGameTree.reduce failed; " (String -> PositionHashQuantifiedGameTree x y positionHash)
-> String -> PositionHashQuantifiedGameTree x y positionHash
forall a b. (a -> b) -> a -> b
$ Turn x y -> ShowS
forall a. Show a => a -> ShowS
shows Turn x y
turn String
"."
					) (Maybe (PositionHashQuantifiedGameTree x y positionHash)
 -> PositionHashQuantifiedGameTree x y positionHash)
-> Maybe (PositionHashQuantifiedGameTree x y positionHash)
-> PositionHashQuantifiedGameTree x y positionHash
forall a b. (a -> b) -> a -> b
$ IsMatch (NodeLabel x y positionHash)
-> PositionHashQuantifiedGameTree x y positionHash
-> Maybe (PositionHashQuantifiedGameTree x y positionHash)
forall x y positionHash.
IsMatch (NodeLabel x y positionHash)
-> PositionHashQuantifiedGameTree x y positionHash
-> Maybe (PositionHashQuantifiedGameTree x y positionHash)
Evaluation.PositionHashQuantifiedGameTree.reduce (Turn x y -> IsMatch (NodeLabel x y positionHash)
forall x y positionHash.
(Eq x, Eq y) =>
Turn x y -> NodeLabel x y positionHash -> Bool
isMatch Turn x y
turn) PositionHashQuantifiedGameTree x y positionHash
positionHashQuantifiedGameTree
				) DynamicMoveData x y positionHash
dynamicMoveData
			 ) (
				(NodeLabel x y positionHash -> QuantifiedGame x y)
-> [NodeLabel x y positionHash] -> [QuantifiedGame x y]
forall a b. (a -> b) -> [a] -> [b]
map NodeLabel x y positionHash -> QuantifiedGame x y
forall x y positionHash.
NodeLabel x y positionHash -> QuantifiedGame x y
Evaluation.PositionHashQuantifiedGameTree.getQuantifiedGame ([NodeLabel x y positionHash] -> [QuantifiedGame x y])
-> (Maybe [NodeLabel x y positionHash]
    -> [NodeLabel x y positionHash])
-> Maybe [NodeLabel x y positionHash]
-> [QuantifiedGame x y]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [NodeLabel x y positionHash]
-> Maybe [NodeLabel x y positionHash]
-> [NodeLabel x y positionHash]
forall a. a -> Maybe a -> a
Data.Maybe.fromMaybe (
					Exception -> [NodeLabel x y positionHash]
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> [NodeLabel x y positionHash])
-> (String -> Exception) -> String -> [NodeLabel x y positionHash]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Exception
Data.Exception.mkSearchFailure (String -> Exception) -> ShowS -> String -> Exception
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"BishBosh.Search.Search.search:\tEvaluation.PositionHashQuantifiedGameTree.traceRoute failed; " (String -> [NodeLabel x y positionHash])
-> String -> [NodeLabel x y positionHash]
forall a b. (a -> b) -> a -> b
$ [Turn x y] -> ShowS
forall a. Show a => a -> ShowS
shows [Turn x y]
turns String
"."
				) (Maybe [NodeLabel x y positionHash] -> [QuantifiedGame x y])
-> Maybe [NodeLabel x y positionHash] -> [QuantifiedGame x y]
forall a b. (a -> b) -> a -> b
$ (Turn x y -> IsMatch (NodeLabel x y positionHash))
-> PositionHashQuantifiedGameTree x y positionHash
-> [Turn x y]
-> Maybe [NodeLabel x y positionHash]
forall x y positionHash.
(Turn x y -> IsMatch (NodeLabel x y positionHash))
-> PositionHashQuantifiedGameTree x y positionHash
-> [Turn x y]
-> Maybe [NodeLabel x y positionHash]
Evaluation.PositionHashQuantifiedGameTree.traceRoute Turn x y -> IsMatch (NodeLabel x y positionHash)
forall x y positionHash.
(Eq x, Eq y) =>
Turn x y -> NodeLabel x y positionHash -> Bool
isMatch PositionHashQuantifiedGameTree x y positionHash
positionHashQuantifiedGameTree [Turn x y]
turns
			 ) NPositions
nPositionsEvaluated
			(DynamicMoveData x y positionHash, [Turn x y], NPositions)
_							-> Exception -> Reader (Result x y positionHash)
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> Reader (Result x y positionHash))
-> Exception -> Reader (Result x y positionHash)
forall a b. (a -> b) -> a -> b
$ String -> Exception
Data.Exception.mkNullDatum String
"BishBosh.Search.Search.search:\tzero turns selected."
	where
		positionHashQuantifiedGameTree :: PositionHashQuantifiedGameTree x y positionHash
positionHashQuantifiedGameTree	= SearchState x y positionHash
-> PositionHashQuantifiedGameTree x y positionHash
forall x y positionHash.
SearchState x y positionHash
-> PositionHashQuantifiedGameTree x y positionHash
Search.SearchState.getPositionHashQuantifiedGameTree SearchState x y positionHash
searchState
		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

-- | Calculate the geometric-mean of the number of plies evaluated at each node.
calculateBranchingFactor :: Floating branchingFactor => Result x y positionHash -> branchingFactor
calculateBranchingFactor :: Result x y positionHash -> branchingFactor
calculateBranchingFactor MkResult {
	getQuantifiedGames :: forall x y positionHash.
Result x y positionHash -> [QuantifiedGame x y]
getQuantifiedGames	= [QuantifiedGame x y]
quantifiedGames,
	getNPositionsEvaluated :: forall x y positionHash. Result x y positionHash -> NPositions
getNPositionsEvaluated	= NPositions
nPositionsEvaluated
}
	| [QuantifiedGame x y] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [QuantifiedGame x y]
quantifiedGames		= Exception -> branchingFactor
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> branchingFactor) -> Exception -> branchingFactor
forall a b. (a -> b) -> a -> b
$ String -> Exception
Data.Exception.mkNullDatum String
"BishBosh.Search.Search.calculateBranchingFactor:\tnull quantifiedGames."
	| NPositions
nPositionsEvaluated NPositions -> NPositions -> Bool
forall a. Eq a => a -> a -> Bool
== NPositions
0	= Exception -> branchingFactor
forall a e. Exception e => e -> a
Control.Exception.throw (Exception -> branchingFactor) -> Exception -> branchingFactor
forall a b. (a -> b) -> a -> b
$ String -> Exception
Data.Exception.mkOutOfBounds String
"BishBosh.Search.Search.calculateBranchingFactor:\tzero plies analysed."
	| Bool
otherwise			= NPositions -> branchingFactor
forall a b. (Integral a, Num b) => a -> b
fromIntegral NPositions
nPositionsEvaluated branchingFactor -> branchingFactor -> branchingFactor
forall a. Floating a => a -> a -> a
** branchingFactor -> branchingFactor
forall a. Fractional a => a -> a
recip (
		NPositions -> branchingFactor
forall a b. (Integral a, Num b) => a -> b
fromIntegral {-Int-} (NPositions -> branchingFactor) -> NPositions -> branchingFactor
forall a b. (a -> b) -> a -> b
$ [QuantifiedGame x y] -> NPositions
forall (t :: * -> *) a. Foldable t => t a -> NPositions
length [QuantifiedGame x y]
quantifiedGames	-- The search-depth.
	)