bishbosh-0.0.0.4: Plays chess.

Safe HaskellNone
LanguageHaskell2010

BishBosh.State.CastleableRooksByLogicalColour

Contents

Description

AUTHOR
Dr. Alistair Ward
DESCRIPTION
The abscissae of those Rooks, for the player of each logicalColour, which can still participate in castling.
Synopsis

Types

Type-synonyms

type TurnsByLogicalColour x y = TurnsByLogicalColour (Turn x y) Source #

Narrow the type, so the turn can be queried.

Data-types

data CastleableRooksByLogicalColour x Source #

For the players of each logical colour, identifies the abscissae of those Rooks which can still participate in castling (when other constraints are removed).

Instances
Eq x => Hashable1D CastleableRooksByLogicalColour x Source #

Get the list of random numbers required to represent the current castling potential.

Instance details

Defined in BishBosh.State.CastleableRooksByLogicalColour

Methods

listRandoms1D :: CastleableRooksByLogicalColour x -> Zobrist x y positionHash -> [positionHash] Source #

Eq x => Eq (CastleableRooksByLogicalColour x) Source # 
Instance details

Defined in BishBosh.State.CastleableRooksByLogicalColour

Ord x => Ord (CastleableRooksByLogicalColour x) Source # 
Instance details

Defined in BishBosh.State.CastleableRooksByLogicalColour

(Enum x, Ord x, Read x, Show x) => Read (CastleableRooksByLogicalColour x) Source # 
Instance details

Defined in BishBosh.State.CastleableRooksByLogicalColour

Show x => Show (CastleableRooksByLogicalColour x) Source # 
Instance details

Defined in BishBosh.State.CastleableRooksByLogicalColour

NFData x => NFData (CastleableRooksByLogicalColour x) Source # 
Instance details

Defined in BishBosh.State.CastleableRooksByLogicalColour

Enum x => Default (CastleableRooksByLogicalColour x) Source # 
Instance details

Defined in BishBosh.State.CastleableRooksByLogicalColour

(Enum x, Eq x) => ShowsFEN (CastleableRooksByLogicalColour x) Source # 
Instance details

Defined in BishBosh.State.CastleableRooksByLogicalColour

(Enum x, Ord x, Show x) => ReadsFEN (CastleableRooksByLogicalColour x) Source # 
Instance details

Defined in BishBosh.State.CastleableRooksByLogicalColour

ReflectableOnX (CastleableRooksByLogicalColour x) Source # 
Instance details

Defined in BishBosh.State.CastleableRooksByLogicalColour

Functions

locateForLogicalColour :: LogicalColour -> CastleableRooksByLogicalColour x -> Maybe [x] Source #

Find the abscissae of all Rooks of the specified logical colour, which can still participate in castling.

Constructors

fromAssocs :: (Enum x, Ord x, Show x) => [(LogicalColour, [x])] -> CastleableRooksByLogicalColour x Source #

Smart constructor.

fromBoard :: (Enum x, Enum y, Ord x, Ord y, Show x) => Board x y -> CastleableRooksByLogicalColour x Source #

  • Smart constructor.
  • CAVEAT: doesn't know the move-history, so the wrong answer is possible.

listIncrementalRandoms Source #

Arguments

:: Ix x 
=> CastleableRooksByLogicalColour x

The old value.

-> CastleableRooksByLogicalColour x

The new value.

-> Zobrist x y random 
-> [random] 

Generate the additional random-numbers required to correct the hash resulting from a change to the castleable Rooks.

Mutators

unify :: Transformation x Source #

Relinquish the ability to disambiguate between "have Castled" (& therefore can't subsequently), & "Have lost the option to castle".

takeTurn Source #

Arguments

:: (Enum x, Enum y, Ord x, Ord y) 
=> LogicalColour

Defines the side who took the specified turn.

-> Turn x y 
-> Transformation x 

Update with the latest turn.

Predicates

canCastleWith Source #

Arguments

:: (Enum x, Enum y, Ord x, Ord y) 
=> LogicalColour 
-> Coordinates x y

Rook's coordinates.

-> CastleableRooksByLogicalColour x 
-> Bool 

Predicate.

cantConverge :: CastleableRooksByLogicalColour x -> CastleableRooksByLogicalColour x -> Bool Source #

  • Determines whether two positions can't converge on each other.
  • N.B.: in this function, the two positions are considered to be peers; nothing is assumed regarding which must do the convergence, perhaps both.
  • From the initial board, one may converge onto any other position, but any of a set of irreversible changes may compromise this; the total number of pieces & specifically Pawns, of each logical colour, can't increase; Pawns can only advance; the difference in the ranks of all pieces of each logical colour, which can only be reduced through promotion of a Pawn; castling can't be undone. This function only assesses this final change.
  • CAVEAT: since the potential of one position to converge on another, depends on a wider set of criteria, this function can only be definitive regarding when convergence is impossible, rather than when is possible.
  • CAVEAT: this function depends on one side having lost the right to castle, when the other side already has; this is quite rare.