bishbosh-0.0.0.4: Plays chess.

Safe HaskellNone
LanguageHaskell2010

BishBosh.Model.Game

Contents

Description

AUTHOR
Dr. Alistair Ward
DESCRIPTION
  • This module augments State.Board with the history of the game.
  • It therefore understands not only the current state of the board, but also; whose turn it is, whether Castling has occured, which Pawns have been promoted, when pieces were taken.
  • Moves made in this domain conform to the rules of chess, c.f. those made in State.Board.
Synopsis

Types

Type-synonyms

type NGames = Int Source #

A number of games.

type Transformation x y = Game x y -> Game x y Source #

The type of a function which transforms a game.

Data-types

data Game x y Source #

  • The first three fields represent the state of the game.
  • These are augmented by the game's history, i.e. the sequence of moves.
  • For efficiency the list of available moves is stored.
Instances
(Ix x, Enum x, Enum y, Ord y) => Hashable2D Game x y Source # 
Instance details

Defined in BishBosh.Model.Game

Methods

listRandoms2D :: Game x y -> Zobrist x y positionHash -> [positionHash] Source #

(Enum x, Enum y, Ord x, Ord y) => Eq (Game x y) Source # 
Instance details

Defined in BishBosh.Model.Game

Methods

(==) :: Game x y -> Game x y -> Bool #

(/=) :: Game x y -> Game x y -> Bool #

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

Defined in BishBosh.Model.Game

Methods

readsPrec :: Int -> ReadS (Game x y) #

readList :: ReadS [Game x y] #

readPrec :: ReadPrec (Game x y) #

readListPrec :: ReadPrec [Game x y] #

(Enum x, Enum y, Ord x, Ord y, Show x, Show y) => Show (Game x y) Source # 
Instance details

Defined in BishBosh.Model.Game

Methods

showsPrec :: Int -> Game x y -> ShowS #

show :: Game x y -> String #

showList :: [Game x y] -> ShowS #

(NFData x, NFData y) => NFData (Game x y) Source # 
Instance details

Defined in BishBosh.Model.Game

Methods

rnf :: Game x y -> () #

(Enum x, Enum y, Ord x, Ord y, Show x, Show y) => Default (Game x y) Source # 
Instance details

Defined in BishBosh.Model.Game

Methods

def :: Game x y #

(Enum x, Enum y, Ord x, Ord y, Show x, Show y) => Empty (Game x y) Source # 
Instance details

Defined in BishBosh.Model.Game

Methods

empty :: Game x y Source #

(Enum x, Enum y, Ord x, Ord y) => ShowsFEN (Game x y) Source # 
Instance details

Defined in BishBosh.Model.Game

Methods

showsFEN :: Game x y -> ShowS Source #

(Enum x, Enum y, Ord x, Ord y, Read x, Read y, Show x, Show y) => ReadsFEN (Game x y) Source # 
Instance details

Defined in BishBosh.Model.Game

Methods

readsFEN :: ReadS (Game x y) Source #

Null (Game x y) Source # 
Instance details

Defined in BishBosh.Model.Game

Methods

isNull :: Game x y -> Bool Source #

(Enum x, Enum y, Ord x, Ord y, Show x, Show y) => ReflectableOnX (Game x y) Source #
Instance details

Defined in BishBosh.Model.Game

Methods

reflectOnX :: Game x y -> Game x y Source #

Functions

countMovesAvailableTo :: (Enum x, Enum y, Ord x, Ord y, Show x, Show y) => LogicalColour -> Game x y -> NMoves Source #

Count the number of moves available to the specified player.

rollBack :: (Enum x, Enum y, Ord x, Ord y, Show x, Show y) => Game x y -> [(Game x y, Turn x y)] Source #

  • Roll-back the specified game until the start, returning each previous game paired with the ply which was then made.
  • The list-head contains the most recent ply, while the tail contains the first.

sortAvailableQualifiedMoves :: (Ord x, Ord y) => AvailableQualifiedMoves x y -> AvailableQualifiedMoves x y Source #

Sort the lists of destinations to faciliate testing for equality.

findQualifiedMovesAvailableTo :: (Enum x, Enum y, Ord x, Ord y, Show x, Show y) => LogicalColour -> Game x y -> [QualifiedMove x y] Source #

  • Retrieve the recorded value, or generate the list of moves available to the player of the specified logical colour.
  • CAVEAT: doesn't account for game-termination.

findQualifiedMovesAvailableToNextPlayer :: (Enum x, Enum y, Ord x, Ord y, Show x, Show y) => Game x y -> [QualifiedMove x y] Source #

Retrieve the recorded value, or generate the list of moves available to the next player.

listTurns :: Game x y -> [Turn x y] Source #

Gets the sequence of turns, with the latest at the head & the opening one last.

listTurnsChronologically :: Game x y -> [Turn x y] Source #

Gets the sequence of turns in the order they occured.

maybeLastTurn :: Game x y -> Maybe (Turn x y) Source #

The last turn, if there was one.

validateQualifiedMove Source #

Arguments

:: (Enum x, Enum y, Ord x, Ord y, Show x, Show y) 
=> QualifiedMove x y 
-> Game x y

Prior to playing the qualified move.

-> Maybe String

Error-message.

  • True if the specified move is valid, given the implied piece & the current state of the game.
  • N.B.: it is considered valid to take a King, one just never has the opportunity, since the game terminates the move before.

validateEitherQualifiedMove Source #

Arguments

:: (Enum x, Enum y, Ord x, Ord y, Show x, Show y) 
=> EitherQualifiedMove x y 
-> Game x y

Prior to playing the move.

-> Maybe String

Error-message.

Validates the move-type than forwards the request to validateQualifiedMove.

incrementalHash Source #

Arguments

:: (Ix x, Bits positionHash, Enum x, Enum y, Ord y) 
=> Game x y

The game before application of the last move.

-> positionHash

The value before application of the last move.

-> Game x y

The current game.

-> Zobrist x y positionHash 
-> positionHash 

Amend the position-hash of the game prior to application of the last move.

Constructors

mkPosition :: (Enum x, Enum y, Ord x, Ord y) => Game x y -> Position x y Source #

Constructor.

mkGame Source #

Arguments

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

The player who is required to move next.

-> CastleableRooksByLogicalColour x 
-> Board x y 
-> TurnsByLogicalColour x y 
-> Game x y 

Smart constructor.

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

Constructor. For convenience, the following assumptions are made in the absence of any move-history:

  • The next player's logical colour is assumed to be White;
  • Provided that the King is at its starting coordinates, then all Rooks which exist at their starting coordinates are considered to be castleable;
  • There're zero previous turns.

mkAvailableQualifiedMovesFor :: (Enum x, Enum y, Ord x, Ord y, Show x, Show y) => LogicalColour -> Game x y -> AvailableQualifiedMoves x y Source #

Construct AvailableQualifiedMoves for the player of the specified logical colour.

Mutators

takeTurn :: (Enum x, Enum y, Ord x, Ord y, Show x, Show y) => Turn x y -> Transformation x y Source #

  • Moves the referenced piece between the specified coordinates.
  • As a result of the turn, the next logical-colour is changed, the moves available to each player are updated, & any reason for game-termination recorded.
  • CAVEAT: no validation of the turn is performed since the move may have been automatically selected & therefore known to be valid.
  • CAVEAT: doesn't account for any previous game-termination when updating getAvailableQualifiedMovesByLogicalColour.

applyQualifiedMove :: (Enum x, Enum y, Ord x, Ord y, Show x, Show y) => QualifiedMove x y -> Transformation x y Source #

Construct a turn & relay the request to takeTurn.

applyEitherQualifiedMove :: (Enum x, Enum y, Ord x, Ord y, Show x, Show y) => EitherQualifiedMove x y -> Transformation x y Source #

Construct a qualifiedMove & relay the request to "applyQualifiedMove".

applyEitherQualifiedMoves Source #

Arguments

:: (Enum x, Enum y, Ord x, Ord y, Show x, Show y) 
=> (a -> Either String (EitherQualifiedMove x y))

A constructor which can return an error-message.

-> Game x y

The game to which the moves should be sequentially applied.

-> [a]

An ordered sequence of data from which moves are constructed.

-> Either (a, String) (Game x y)

Either a rogue datum & the corresponding error-message, or the resulting game.

Constructs eitherQualifiedMoves from the data provided, validating & applying each in the specified order.

updateTerminationReasonWith :: Result -> Transformation x y Source #

Provided that the game hasn't already terminated, update the termination-reason according to whether the specified result implies either a draw by agreement or a resignation.

resign :: Transformation x y Source #

Resignation by the player who currently holds the choice of move.

Predicates

isValidQualifiedMove :: (Enum x, Enum y, Ord x, Ord y, Show x, Show y) => QualifiedMove x y -> Game x y -> Bool Source #

Whether the specified qualifiedMove is valid.

isValidEitherQualifiedMove :: (Enum x, Enum y, Ord x, Ord y, Show x, Show y) => EitherQualifiedMove x y -> Game x y -> Bool Source #

Whether the specified eitherQualifiedMove is valid.

isTerminated :: Game x y -> Bool Source #

Whether the game has been terminated.

(=~) :: (Enum x, Enum y, Ord x, Ord y) => Game x y -> Game x y -> Bool infix 4 Source #

  • Whether the specified game's positions have converged, & despite perhaps having reached this position from different move-sequences, now have equal opportunities.
  • CAVEAT: this is different from equality.
  • CAVEAT: this test doesn't account for the possibility that one game may more quickly be drawn according to either the "Seventy-five-move Rule" or "Five-fold Repetition".
  • CAVEAT: though convenient, this function shouldn't be called for repeated tests against a constant position, resulting in unnecessary repeated construction of that position.

(/~) :: (Enum x, Enum y, Ord x, Ord y) => Game x y -> Game x y -> Bool infix 4 Source #

Whether the state of the specified games is different.