bishbosh-0.0.0.6: Plays chess.

Safe HaskellNone
LanguageHaskell2010

BishBosh.Cartesian.Coordinates

Contents

Description

AUTHOR
Dr. Alistair Ward
DESCRIPTION
The location of a square on the board.
Synopsis

Types

Data-types

data Coordinates x y Source #

The coordinates of a square on the board.

Instances
(Enum x, Enum y) => Bounded (Coordinates x y) Source # 
Instance details

Defined in BishBosh.Cartesian.Coordinates

(Eq x, Eq y) => Eq (Coordinates x y) Source # 
Instance details

Defined in BishBosh.Cartesian.Coordinates

Methods

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

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

(Ord x, Ord y) => Ord (Coordinates x y) Source # 
Instance details

Defined in BishBosh.Cartesian.Coordinates

Methods

compare :: Coordinates x y -> Coordinates x y -> Ordering #

(<) :: Coordinates x y -> Coordinates x y -> Bool #

(<=) :: Coordinates x y -> Coordinates x y -> Bool #

(>) :: Coordinates x y -> Coordinates x y -> Bool #

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

max :: Coordinates x y -> Coordinates x y -> Coordinates x y #

min :: Coordinates x y -> Coordinates x y -> Coordinates x y #

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

Defined in BishBosh.Cartesian.Coordinates

(Show x, Show y) => Show (Coordinates x y) Source # 
Instance details

Defined in BishBosh.Cartesian.Coordinates

Methods

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

show :: Coordinates x y -> String #

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

(Enum x, Enum y, Ord x, Ord y) => Ix (Coordinates x y) Source # 
Instance details

Defined in BishBosh.Cartesian.Coordinates

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

Defined in BishBosh.Cartesian.Coordinates

Methods

rnf :: Coordinates x y -> () #

Enum x => ReflectableOnY (Coordinates x y) Source # 
Instance details

Defined in BishBosh.Cartesian.Coordinates

Enum y => ReflectableOnX (Coordinates x y) Source # 
Instance details

Defined in BishBosh.Cartesian.Coordinates

(Enum x, Enum y) => Rotatable (Coordinates x y) Source # 
Instance details

Defined in BishBosh.Cartesian.Coordinates

(Enum x, Enum y) => ShowNotation (Coordinates x y) Source # 
Instance details

Defined in BishBosh.Notation.MoveNotation

Type-synonyms

type ByCoordinates x y = Array (Coordinates x y) Source #

A boxed array indexed by coordinates, of arbitrary elements.

Constants

topLeft :: (Enum x, Enum y) => Coordinates x y Source #

Constant.

bottomRight :: (Enum x, Enum y) => Coordinates x y Source #

Constant.

nSquares :: Int Source #

The constant number of squares on the board.

radiusSquared :: (Fractional radiusSquared, Integral x, Integral y) => ByCoordinates x y radiusSquared Source #

The constant square of the radius of all coordinates.

Functions

extrapolate Source #

Arguments

:: (Enum x, Enum y) 
=> Direction

The direction in which to proceed.

-> Coordinates x y

The point from which to start.

-> [Coordinates x y] 
  • Generates a line of coordinates, starting just after the specified source & proceeding in the specified direction to the edge of the board.
  • CAVEAT: this is a performance-hotspot (it's also responsible for the allocation of a third of the application's memory); refactor => re-profile. In consequence, it is typically automatically avoided using a rewrite-rule to lookup an array of the results from all possible calls.

interpolate Source #

Arguments

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

Source.

-> Coordinates x y

Destination.

-> [Coordinates x y] 
  • Generates a line of coordinates covering the half open interval (source, destination].
  • CAVEAT: the destination-coordinates must be a valid Queen's move from the source; so that all intermediate points lie on a square of the board.

range :: (Enum x, Enum y) => [Coordinates x y] Source #

Generates a raster over all the board's coordinates.

getLogicalColourOfSquare :: (Enum x, Enum y) => Coordinates x y -> LogicalColourOfSquare Source #

The logical colour of the specified square.

kingsStartingCoordinates :: (Enum x, Enum y) => LogicalColour -> Coordinates x y Source #

The conventional starting coordinates for the King of the specified logical colour.

rooksStartingCoordinates :: (Enum x, Enum y) => LogicalColour -> [Coordinates x y] Source #

The conventional starting coordinates for each Rook.

measureDistance Source #

Arguments

:: (Enum x, Enum y, Num distance) 
=> Coordinates x y

Source.

-> Coordinates x y

Destination.

-> (distance, distance) 
  • Measures the signed distance between source & destination coordinates.
  • CAVEAT: beware the potential fence-post error.

translate :: (Enum x, Enum y, Ord x, Ord y) => ((x, y) -> (x, y)) -> Coordinates x y -> Coordinates x y Source #

Translate the specified coordinates.

maybeTranslate Source #

Arguments

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

Translation.

-> Coordinates x y 
-> Maybe (Coordinates x y) 

Where legal, translate the specified coordinates.

translateX :: (Enum x, Ord x) => (x -> x) -> Transformation x y Source #

Translate the specified abscissa.

maybeTranslateX Source #

Arguments

:: (Enum x, Ord x) 
=> (x -> x)

Translation.

-> Coordinates x y 
-> Maybe (Coordinates x y) 

Where legal, translate the x-component of the specified coordinates.

translateY :: (Enum y, Ord y) => (y -> y) -> Transformation x y Source #

Translate the specified ordinate.

maybeTranslateY Source #

Arguments

:: (Enum y, Ord y) 
=> (y -> y)

Translation.

-> Coordinates x y 
-> Maybe (Coordinates x y) 

Where legal, translate the y-component of the specified coordinates.

getAdjacents :: (Enum x, Eq x) => Coordinates x y -> [Coordinates x y] Source #

Get the coordinates immediately left & right.

advance Source #

Arguments

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

The logical colour of the piece which is to advance.

-> Transformation x y 

Move one step towards the opponent.

retreat Source #

Arguments

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

The logical colour of the piece which is to retreat.

-> Transformation x y 

Move one step away from the opponent.

maybeRetreat Source #

Arguments

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

The logical colour of the piece which is to retreat.

-> Coordinates x y

The location from which to retreat.

-> Maybe (Coordinates x y) 

Where legal, move one step away from the opponent.

Constructors

mkCoordinates Source #

Arguments

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

Abscissa.

-> y

Ordinate.

-> Coordinates x y 

Constructor.

mkMaybeCoordinates Source #

Arguments

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

Abscissa.

-> y

Ordinate.

-> Maybe (Coordinates x y) 

Safe constructor.

fromIx :: (Enum x, Enum y) => Int -> Coordinates x y Source #

  • Construct from the specified array-index.
  • CAVEAT: assumes that the array is indexed by the whole range of coordinates.

mkRelativeCoordinates Source #

Arguments

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

Translation.

-> Coordinates x y 

Construct coordinates relative to minBound.

listArrayByCoordinates :: (IArray a e, Enum x, Enum y, Ord x, Ord y) => [e] -> a (Coordinates x y) e Source #

Array-constructor.

Predicates

isPawnsFirstRank :: (Enum y, Eq y) => LogicalColour -> Coordinates x y -> Bool Source #

Whether the specified coordinates are where a Pawn of the specified logical colour starts.

isEnPassantRank :: (Enum y, Eq y) => LogicalColour -> Coordinates x y -> Bool Source #

Whether a Pawn is currently on the appropriate rank to take an opponent's Pawn en-passant.

areSquaresIsochromatic :: (Enum x, Enum y) => [Coordinates x y] -> Bool Source #

Whether the specified squares have the same logical colour.