bishbosh-0.0.0.6: Plays chess.

Safe HaskellNone
LanguageHaskell2010

BishBosh.Evaluation.PositionHashQuantifiedGameTree

Contents

Description

AUTHOR
Dr. Alistair Ward
DESCRIPTION
  • Constructs a tree in which each node contains, a zobrist-hash, a quantifiedGame with one of the moves available to its parent node applied & evaluation of the fitness of the resulting position.
  • Each forest in the tree is sorted, before evaluation of its fitness is performed.
  • CAVEAT: promotions are insufficiently frequent to be treated specially when sorting.
Synopsis

Types

Type-synonyms

type Forest x y positionHash criterionValue weightedMean = [BarePositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean] Source #

Self-documentation.

Data-types

data NodeLabel x y positionHash criterionValue weightedMean Source #

Define a node in the tree to contain the hash of a game & an evaluation of the fitness of that game.

Instances
(Enum x, Enum y, Ord x, Ord y, Eq positionHash, Eq weightedMean, Eq criterionValue) => Eq (NodeLabel x y positionHash criterionValue weightedMean) Source # 
Instance details

Defined in BishBosh.Evaluation.PositionHashQuantifiedGameTree

Methods

(==) :: NodeLabel x y positionHash criterionValue weightedMean -> NodeLabel x y positionHash criterionValue weightedMean -> Bool #

(/=) :: NodeLabel x y positionHash criterionValue weightedMean -> NodeLabel x y positionHash criterionValue weightedMean -> Bool #

(Enum x, Enum y, Ord x, Ord y, Show positionHash, Show x, Show y, Show weightedMean, Show criterionValue) => Show (NodeLabel x y positionHash criterionValue weightedMean) Source # 
Instance details

Defined in BishBosh.Evaluation.PositionHashQuantifiedGameTree

Methods

showsPrec :: Int -> NodeLabel x y positionHash criterionValue weightedMean -> ShowS #

show :: NodeLabel x y positionHash criterionValue weightedMean -> String #

showList :: [NodeLabel x y positionHash criterionValue weightedMean] -> ShowS #

Null (NodeLabel x y positionHash criterionValue weightedMean) Source # 
Instance details

Defined in BishBosh.Evaluation.PositionHashQuantifiedGameTree

Methods

isNull :: NodeLabel x y positionHash criterionValue weightedMean -> Bool Source #

(Enum x, Enum y, Real weightedMean) => ShowNotationFloat (NodeLabel x y positionHash criterionValue weightedMean) Source # 
Instance details

Defined in BishBosh.Evaluation.PositionHashQuantifiedGameTree

Methods

showsNotationFloat :: MoveNotation -> (Double -> ShowS) -> NodeLabel x y positionHash criterionValue weightedMean -> ShowS Source #

newtype PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean Source #

Wrap the bare tree.

Constructors

MkPositionHashQuantifiedGameTree 

Fields

  • deconstruct :: BarePositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean
     
Instances
(Enum x, Enum y, Ord x, Ord y, Eq positionHash, Eq weightedMean, Eq criterionValue) => Eq (PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean) Source # 
Instance details

Defined in BishBosh.Evaluation.PositionHashQuantifiedGameTree

Methods

(==) :: PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean -> PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean -> Bool #

(/=) :: PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean -> PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean -> Bool #

Prunable (PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean) Source # 
Instance details

Defined in BishBosh.Evaluation.PositionHashQuantifiedGameTree

Methods

prune :: Depth -> PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean -> PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean Source #

(Enum x, Enum y, Real weightedMean) => ShowNotationFloat (PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean) Source # 
Instance details

Defined in BishBosh.Evaluation.PositionHashQuantifiedGameTree

Methods

showsNotationFloat :: MoveNotation -> (Double -> ShowS) -> PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean -> ShowS Source #

Functions

reduce :: IsMatch (NodeLabel x y positionHash criterionValue weightedMean) -> PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean -> Maybe (PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean) Source #

Forward request.

traceRoute :: (Turn x y -> IsMatch (NodeLabel x y positionHash criterionValue weightedMean)) -> PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean -> [Turn x y] -> Maybe [NodeLabel x y positionHash criterionValue weightedMean] Source #

Forward request.

resign :: PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean -> PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean Source #

Amend the apex-game to reflect the resignation of the next player.

traceMatchingMoves Source #

Arguments

:: (Eq x, Eq y) 
=> PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean 
-> [Move x y] 
-> Maybe [NodeLabel x y positionHash criterionValue weightedMean]

Returns Nothing on failure to match a move.

Follow the specified move-sequence down the positionHashQuantifiedGameTree.

promoteMatchingMoves Source #

Arguments

:: (Eq x, Eq y) 
=> [Move x y]

The list of moves, which should be promoted at successively deeper levels in the tree.

-> Forest x y positionHash criterionValue weightedMean 
-> Maybe (Forest x y positionHash criterionValue weightedMean)

Returns Nothing on failure to match a move.

  • Promotes the first matching move to the head of the forest, then descends & recursively promotes the next matching move in the sub-forest.
  • N.B.: this can be used to dynamically re-order the forest when a transposition is detected.

sortNonCaptureMoves :: (Forest x y positionHash criterionValue weightedMean -> Forest x y positionHash criterionValue weightedMean) -> Forest x y positionHash criterionValue weightedMean -> Forest x y positionHash criterionValue weightedMean Source #

  • Sorts the forest, starting just after any initial capture-moves.
  • N.B.: this can be used to dynamically re-order the forest using the killer heuristic.

Accessors

getRootQuantifiedGame' :: BarePositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean -> QuantifiedGame x y criterionValue weightedMean Source #

Accessor.

getRootPositionHash :: PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean -> positionHash Source #

Accessor.

getRootQuantifiedGame :: PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean -> QuantifiedGame x y criterionValue weightedMean Source #

Accessor.

Constructor

fromBarePositionHashQuantifiedGameTree :: BarePositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean -> PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean Source #

Constructor.

mkPositionHashQuantifiedGameTree Source #

Arguments

:: (Ix x, Bits positionHash, Fractional criterionValue, Fractional pieceSquareValue, Fractional rankValue, Fractional weightedMean, Integral x, Integral y, Real criterionValue, Real criterionWeight, Real pieceSquareValue, Real rankValue, Show x, Show y) 
=> EvaluationOptions criterionWeight pieceSquareValue rankValue x y 
-> SearchOptions 
-> Zobrist x y positionHash 
-> MoveFrequency x y 
-> Game x y

The current state of the game.

-> PositionHashQuantifiedGameTree x y positionHash criterionValue weightedMean 

Constructor.

Predicates