chessIO-0.9.0.0: Basic chess library
Copyright(c) Mario Lang 2021
LicenseBSD3
Maintainermlang@blind.guru
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Game.Chess

Description

Types for representing positions and plies and functions for move generation and application. Internally, quad bitboards are employed and plies are stored as 16 bit values. The move generation is fully compliant to the standard rules of Chess.

This module does deliberately not implement any search or evaluation functionality. It is intended to be used to lay the ground for communicating with other programs or players, hence the package name chessIO.

The following modules implement more specific functionality:

Synopsis

Chess positions

data Color Source #

Constructors

Black 
White 

Instances

Instances details
Eq Color Source # 
Instance details

Defined in Game.Chess.Internal

Methods

(==) :: Color -> Color -> Bool #

(/=) :: Color -> Color -> Bool #

Ord Color Source # 
Instance details

Defined in Game.Chess.Internal

Methods

compare :: Color -> Color -> Ordering #

(<) :: Color -> Color -> Bool #

(<=) :: Color -> Color -> Bool #

(>) :: Color -> Color -> Bool #

(>=) :: Color -> Color -> Bool #

max :: Color -> Color -> Color #

min :: Color -> Color -> Color #

Show Color Source # 
Instance details

Defined in Game.Chess.Internal

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Ix Color Source # 
Instance details

Defined in Game.Chess.Internal

Generic Color Source # 
Instance details

Defined in Game.Chess.Internal

Associated Types

type Rep Color :: Type -> Type #

Methods

from :: Color -> Rep Color x #

to :: Rep Color x -> Color #

Binary Color Source # 
Instance details

Defined in Game.Chess.Internal

Methods

put :: Color -> Put #

get :: Get Color #

putList :: [Color] -> Put #

NFData Color Source # 
Instance details

Defined in Game.Chess.Internal

Methods

rnf :: Color -> () #

Hashable Color Source # 
Instance details

Defined in Game.Chess.Internal

Methods

hashWithSalt :: Int -> Color -> Int #

hash :: Color -> Int #

Lift Color Source # 
Instance details

Defined in Game.Chess.Internal

Methods

lift :: Color -> Q Exp #

liftTyped :: Color -> Q (TExp Color) #

type Rep Color Source # 
Instance details

Defined in Game.Chess.Internal

type Rep Color = D1 ('MetaData "Color" "Game.Chess.Internal" "chessIO-0.9.0.0-ofgfHeSSwdHddtrozNvtW" 'False) (C1 ('MetaCons "Black" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "White" 'PrefixI 'False) (U1 :: Type -> Type))

data Square where Source #

Bundled Patterns

pattern A1 :: Square 
pattern A2 :: Square 
pattern A3 :: Square 
pattern A4 :: Square 
pattern A5 :: Square 
pattern A6 :: Square 
pattern A7 :: Square 
pattern A8 :: Square 
pattern B1 :: Square 
pattern B2 :: Square 
pattern B3 :: Square 
pattern B4 :: Square 
pattern B5 :: Square 
pattern B6 :: Square 
pattern B7 :: Square 
pattern B8 :: Square 
pattern C1 :: Square 
pattern C2 :: Square 
pattern C3 :: Square 
pattern C4 :: Square 
pattern C5 :: Square 
pattern C6 :: Square 
pattern C7 :: Square 
pattern C8 :: Square 
pattern D1 :: Square 
pattern D2 :: Square 
pattern D3 :: Square 
pattern D4 :: Square 
pattern D5 :: Square 
pattern D6 :: Square 
pattern D7 :: Square 
pattern D8 :: Square 
pattern E1 :: Square 
pattern E2 :: Square 
pattern E3 :: Square 
pattern E4 :: Square 
pattern E5 :: Square 
pattern E6 :: Square 
pattern E7 :: Square 
pattern E8 :: Square 
pattern F1 :: Square 
pattern F2 :: Square 
pattern F3 :: Square 
pattern F4 :: Square 
pattern F5 :: Square 
pattern F6 :: Square 
pattern F7 :: Square 
pattern F8 :: Square 
pattern G1 :: Square 
pattern G2 :: Square 
pattern G3 :: Square 
pattern G4 :: Square 
pattern G5 :: Square 
pattern G6 :: Square 
pattern G7 :: Square 
pattern G8 :: Square 
pattern H1 :: Square 
pattern H2 :: Square 
pattern H3 :: Square 
pattern H4 :: Square 
pattern H5 :: Square 
pattern H6 :: Square 
pattern H7 :: Square 
pattern H8 :: Square 

Instances

Instances details
Bounded Square Source # 
Instance details

Defined in Game.Chess.Internal.Square

Enum Square Source # 
Instance details

Defined in Game.Chess.Internal.Square

Eq Square Source # 
Instance details

Defined in Game.Chess.Internal.Square

Methods

(==) :: Square -> Square -> Bool #

(/=) :: Square -> Square -> Bool #

Ord Square Source # 
Instance details

Defined in Game.Chess.Internal.Square

Show Square Source # 
Instance details

Defined in Game.Chess.Internal.Square

Ix Square Source # 
Instance details

Defined in Game.Chess.Internal.Square

data Rank where Source #

Bundled Patterns

pattern Rank1 :: Rank 
pattern Rank2 :: Rank 
pattern Rank3 :: Rank 
pattern Rank4 :: Rank 
pattern Rank5 :: Rank 
pattern Rank6 :: Rank 
pattern Rank7 :: Rank 
pattern Rank8 :: Rank 

Instances

Instances details
Bounded Rank Source # 
Instance details

Defined in Game.Chess.Internal.Square

Enum Rank Source # 
Instance details

Defined in Game.Chess.Internal.Square

Methods

succ :: Rank -> Rank #

pred :: Rank -> Rank #

toEnum :: Int -> Rank #

fromEnum :: Rank -> Int #

enumFrom :: Rank -> [Rank] #

enumFromThen :: Rank -> Rank -> [Rank] #

enumFromTo :: Rank -> Rank -> [Rank] #

enumFromThenTo :: Rank -> Rank -> Rank -> [Rank] #

Eq Rank Source # 
Instance details

Defined in Game.Chess.Internal.Square

Methods

(==) :: Rank -> Rank -> Bool #

(/=) :: Rank -> Rank -> Bool #

Ord Rank Source # 
Instance details

Defined in Game.Chess.Internal.Square

Methods

compare :: Rank -> Rank -> Ordering #

(<) :: Rank -> Rank -> Bool #

(<=) :: Rank -> Rank -> Bool #

(>) :: Rank -> Rank -> Bool #

(>=) :: Rank -> Rank -> Bool #

max :: Rank -> Rank -> Rank #

min :: Rank -> Rank -> Rank #

Show Rank Source # 
Instance details

Defined in Game.Chess.Internal.Square

Methods

showsPrec :: Int -> Rank -> ShowS #

show :: Rank -> String #

showList :: [Rank] -> ShowS #

data File where Source #

Bundled Patterns

pattern FileA :: File 
pattern FileB :: File 
pattern FileC :: File 
pattern FileD :: File 
pattern FileE :: File 
pattern FileF :: File 
pattern FileG :: File 
pattern FileH :: File 

Instances

Instances details
Bounded File Source # 
Instance details

Defined in Game.Chess.Internal.Square

Enum File Source # 
Instance details

Defined in Game.Chess.Internal.Square

Methods

succ :: File -> File #

pred :: File -> File #

toEnum :: Int -> File #

fromEnum :: File -> Int #

enumFrom :: File -> [File] #

enumFromThen :: File -> File -> [File] #

enumFromTo :: File -> File -> [File] #

enumFromThenTo :: File -> File -> File -> [File] #

Eq File Source # 
Instance details

Defined in Game.Chess.Internal.Square

Methods

(==) :: File -> File -> Bool #

(/=) :: File -> File -> Bool #

Ord File Source # 
Instance details

Defined in Game.Chess.Internal.Square

Methods

compare :: File -> File -> Ordering #

(<) :: File -> File -> Bool #

(<=) :: File -> File -> Bool #

(>) :: File -> File -> Bool #

(>=) :: File -> File -> Bool #

max :: File -> File -> File #

min :: File -> File -> File #

Show File Source # 
Instance details

Defined in Game.Chess.Internal.Square

Methods

showsPrec :: Int -> File -> ShowS #

show :: File -> String #

showList :: [File] -> ShowS #

data PieceType where Source #

Bundled Patterns

pattern Pawn :: PieceType 
pattern Knight :: PieceType 
pattern Bishop :: PieceType 
pattern Rook :: PieceType 
pattern Queen :: PieceType 
pattern King :: PieceType 

data Castle Source #

Constructors

Kingside 
Queenside 

Instances

Instances details
Eq Castle Source # 
Instance details

Defined in Game.Chess.Internal

Methods

(==) :: Castle -> Castle -> Bool #

(/=) :: Castle -> Castle -> Bool #

Ord Castle Source # 
Instance details

Defined in Game.Chess.Internal

Show Castle Source # 
Instance details

Defined in Game.Chess.Internal

Ix Castle Source # 
Instance details

Defined in Game.Chess.Internal

data Position Source #

Instances

Instances details
Eq Position Source # 
Instance details

Defined in Game.Chess.Internal

Ord Position Source # 
Instance details

Defined in Game.Chess.Internal

Show Position Source # 
Instance details

Defined in Game.Chess.Internal

IsString Position Source # 
Instance details

Defined in Game.Chess.Internal

Generic Position Source # 
Instance details

Defined in Game.Chess.Internal

Associated Types

type Rep Position :: Type -> Type #

Methods

from :: Position -> Rep Position x #

to :: Rep Position x -> Position #

Binary Position Source # 
Instance details

Defined in Game.Chess.Internal

Methods

put :: Position -> Put #

get :: Get Position #

putList :: [Position] -> Put #

NFData Position Source # 
Instance details

Defined in Game.Chess.Internal

Methods

rnf :: Position -> () #

Hashable Position Source # 
Instance details

Defined in Game.Chess.Internal

Methods

hashWithSalt :: Int -> Position -> Int #

hash :: Position -> Int #

Lift Position Source # 
Instance details

Defined in Game.Chess.Internal

type Rep Position Source # 
Instance details

Defined in Game.Chess.Internal

startpos :: Position Source #

The starting position as given by the FEN string "rnbqkbnrpppppppp8888PPPPPPPP/RNBQKBNR w KQkq - 0 1".

color :: Position -> Color Source #

active color

moveNumber :: Position -> Int Source #

number of the full move

inCheck :: Color -> Position -> Bool Source #

Returns True if Color is in check in the given position.

Converting from/to Forsyth-Edwards-Notation

fromFEN :: String -> Maybe Position Source #

Construct a position from Forsyth-Edwards-Notation.

toFEN :: Position -> String Source #

Convert a position to Forsyth-Edwards-Notation.

Chess moves

data Ply Source #

Instances

Instances details
Eq Ply Source # 
Instance details

Defined in Game.Chess.Internal

Methods

(==) :: Ply -> Ply -> Bool #

(/=) :: Ply -> Ply -> Bool #

Ord Ply Source # 
Instance details

Defined in Game.Chess.Internal

Methods

compare :: Ply -> Ply -> Ordering #

(<) :: Ply -> Ply -> Bool #

(<=) :: Ply -> Ply -> Bool #

(>) :: Ply -> Ply -> Bool #

(>=) :: Ply -> Ply -> Bool #

max :: Ply -> Ply -> Ply #

min :: Ply -> Ply -> Ply #

Show Ply Source # 
Instance details

Defined in Game.Chess.Internal

Methods

showsPrec :: Int -> Ply -> ShowS #

show :: Ply -> String #

showList :: [Ply] -> ShowS #

Storable Ply Source # 
Instance details

Defined in Game.Chess.Internal

Methods

sizeOf :: Ply -> Int #

alignment :: Ply -> Int #

peekElemOff :: Ptr Ply -> Int -> IO Ply #

pokeElemOff :: Ptr Ply -> Int -> Ply -> IO () #

peekByteOff :: Ptr b -> Int -> IO Ply #

pokeByteOff :: Ptr b -> Int -> Ply -> IO () #

peek :: Ptr Ply -> IO Ply #

poke :: Ptr Ply -> Ply -> IO () #

Binary Ply Source # 
Instance details

Defined in Game.Chess.Internal

Methods

put :: Ply -> Put #

get :: Get Ply #

putList :: [Ply] -> Put #

Hashable Ply Source # 
Instance details

Defined in Game.Chess.Internal

Methods

hashWithSalt :: Int -> Ply -> Int #

hash :: Ply -> Int #

Unbox Ply Source # 
Instance details

Defined in Game.Chess.Internal

Lift Ply Source # 
Instance details

Defined in Game.Chess.Internal

Methods

lift :: Ply -> Q Exp #

liftTyped :: Ply -> Q (TExp Ply) #

Vector Vector Ply Source # 
Instance details

Defined in Game.Chess.Internal

MVector MVector Ply Source # 
Instance details

Defined in Game.Chess.Internal

newtype Vector Ply Source # 
Instance details

Defined in Game.Chess.Internal

newtype MVector s Ply Source # 
Instance details

Defined in Game.Chess.Internal

newtype MVector s Ply = MV_Ply (MVector s Word16)

Convertion

fromUCI :: Position -> String -> Maybe Ply Source #

Parse a move in the format used by the Universal Chess Interface protocol.

toUCI :: Ply -> String Source #

Convert a move to the format used by the Universal Chess Interface protocol.

Move generation

legalPlies :: Position -> [Ply] Source #

Generate a list of possible moves for the given position.

Executing moves

doPly :: HasCallStack => Position -> Ply -> Position Source #

Apply a move to the given position.

This function checks if the move is actually legal and throws and error if it isn't. See unsafeDoPly for a version that omits the legality check.

unsafeDoPly :: Position -> Ply -> Position Source #

An unsafe version of doPly. Only use this if you are sure the given move can be applied to the position. This is useful if the move has been generated by the legalPlies function.