unicode-tricks-0.11.0.0: Functions to work with unicode blocks more convenient.
Maintainerhapytexeu+gh@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Data.Char.Chess

Description

One can make use of a block 2600 and block 1fa00 of Unicode characters to render chess characters. One can render chess characters as netral, white, or black pieces, for such pieces one can render these rotated by 0, 90, 180 and 270 degrees. Knights can be rendered on 45, 135, 225 and 315 degrees as well. Furthermore unicode allows to render an equihopper, and special variants like a knight-queen, knight-rook, and knight-bishop.

The module contains pattern synonyms for names that are often given to the pieces.

Synopsis

Data structures to represent the possible chess pieces.

data ChessColor Source #

The color of a chess piece, this can for most pieces be Black, White, or Neutral.

Constructors

White

White color.

Black

Black color.

Neutral

Neutral chess pieces, sometimes depicted half white and half black.

Instances

Instances details
Bounded ChessColor Source # 
Instance details

Defined in Data.Char.Chess

Enum ChessColor Source # 
Instance details

Defined in Data.Char.Chess

Eq ChessColor Source # 
Instance details

Defined in Data.Char.Chess

Data ChessColor Source # 
Instance details

Defined in Data.Char.Chess

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChessColor -> c ChessColor #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChessColor #

toConstr :: ChessColor -> Constr #

dataTypeOf :: ChessColor -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ChessColor) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChessColor) #

gmapT :: (forall b. Data b => b -> b) -> ChessColor -> ChessColor #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChessColor -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChessColor -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChessColor -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChessColor -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChessColor -> m ChessColor #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChessColor -> m ChessColor #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChessColor -> m ChessColor #

Ord ChessColor Source # 
Instance details

Defined in Data.Char.Chess

Read ChessColor Source # 
Instance details

Defined in Data.Char.Chess

Show ChessColor Source # 
Instance details

Defined in Data.Char.Chess

Generic ChessColor Source # 
Instance details

Defined in Data.Char.Chess

Associated Types

type Rep ChessColor :: Type -> Type #

Arbitrary ChessColor Source # 
Instance details

Defined in Data.Char.Chess

NFData ChessColor Source # 
Instance details

Defined in Data.Char.Chess

Methods

rnf :: ChessColor -> () #

Hashable ChessColor Source # 
Instance details

Defined in Data.Char.Chess

type Rep ChessColor Source # 
Instance details

Defined in Data.Char.Chess

type Rep ChessColor = D1 ('MetaData "ChessColor" "Data.Char.Chess" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) (C1 ('MetaCons "White" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Black" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Neutral" 'PrefixI 'False) (U1 :: Type -> Type)))

data ChessColorBinary Source #

A data type that defined binary colors (BWhite, and BBlack), this is used for special chess pieces like a knight queen, knight rook, and knight bishop that only have no neutral color in unicode.

Constructors

BWhite

White color.

BBlack

Black color.

Instances

Instances details
Bounded ChessColorBinary Source # 
Instance details

Defined in Data.Char.Chess

Enum ChessColorBinary Source # 
Instance details

Defined in Data.Char.Chess

Eq ChessColorBinary Source # 
Instance details

Defined in Data.Char.Chess

Data ChessColorBinary Source # 
Instance details

Defined in Data.Char.Chess

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChessColorBinary -> c ChessColorBinary #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChessColorBinary #

toConstr :: ChessColorBinary -> Constr #

dataTypeOf :: ChessColorBinary -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ChessColorBinary) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChessColorBinary) #

gmapT :: (forall b. Data b => b -> b) -> ChessColorBinary -> ChessColorBinary #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChessColorBinary -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChessColorBinary -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChessColorBinary -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChessColorBinary -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChessColorBinary -> m ChessColorBinary #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChessColorBinary -> m ChessColorBinary #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChessColorBinary -> m ChessColorBinary #

Ord ChessColorBinary Source # 
Instance details

Defined in Data.Char.Chess

Read ChessColorBinary Source # 
Instance details

Defined in Data.Char.Chess

Show ChessColorBinary Source # 
Instance details

Defined in Data.Char.Chess

Generic ChessColorBinary Source # 
Instance details

Defined in Data.Char.Chess

Associated Types

type Rep ChessColorBinary :: Type -> Type #

Arbitrary ChessColorBinary Source # 
Instance details

Defined in Data.Char.Chess

NFData ChessColorBinary Source # 
Instance details

Defined in Data.Char.Chess

Methods

rnf :: ChessColorBinary -> () #

Hashable ChessColorBinary Source # 
Instance details

Defined in Data.Char.Chess

type Rep ChessColorBinary Source # 
Instance details

Defined in Data.Char.Chess

type Rep ChessColorBinary = D1 ('MetaData "ChessColorBinary" "Data.Char.Chess" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) (C1 ('MetaCons "BWhite" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BBlack" 'PrefixI 'False) (U1 :: Type -> Type))

data ChessPieceType Source #

The type of chess pieces. Unicode includes an Equihopper as piece as well.

Constructors

King

The king chess piece.

Queen

The queen chess piece.

Rook

The rook chess piece.

Bishop

The bishop chess piece.

Knight

The knight chess piece.

Pawn

The pawn chess piece.

Equihopper

The equihopper chess piece.

Instances

Instances details
Bounded ChessPieceType Source # 
Instance details

Defined in Data.Char.Chess

Enum ChessPieceType Source # 
Instance details

Defined in Data.Char.Chess

Eq ChessPieceType Source # 
Instance details

Defined in Data.Char.Chess

Data ChessPieceType Source # 
Instance details

Defined in Data.Char.Chess

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChessPieceType -> c ChessPieceType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChessPieceType #

toConstr :: ChessPieceType -> Constr #

dataTypeOf :: ChessPieceType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ChessPieceType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChessPieceType) #

gmapT :: (forall b. Data b => b -> b) -> ChessPieceType -> ChessPieceType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChessPieceType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChessPieceType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChessPieceType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChessPieceType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChessPieceType -> m ChessPieceType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChessPieceType -> m ChessPieceType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChessPieceType -> m ChessPieceType #

Ord ChessPieceType Source # 
Instance details

Defined in Data.Char.Chess

Read ChessPieceType Source # 
Instance details

Defined in Data.Char.Chess

Show ChessPieceType Source # 
Instance details

Defined in Data.Char.Chess

Generic ChessPieceType Source # 
Instance details

Defined in Data.Char.Chess

Associated Types

type Rep ChessPieceType :: Type -> Type #

Arbitrary ChessPieceType Source # 
Instance details

Defined in Data.Char.Chess

NFData ChessPieceType Source # 
Instance details

Defined in Data.Char.Chess

Methods

rnf :: ChessPieceType -> () #

Hashable ChessPieceType Source # 
Instance details

Defined in Data.Char.Chess

type Rep ChessPieceType Source # 
Instance details

Defined in Data.Char.Chess

type Rep ChessPieceType = D1 ('MetaData "ChessPieceType" "Data.Char.Chess" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) ((C1 ('MetaCons "King" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Queen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Rook" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Bishop" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Knight" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Pawn" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Equihopper" 'PrefixI 'False) (U1 :: Type -> Type))))

data ChessHybridType Source #

Hybrid chess pieces like the knight-queen, knight-rook and knight-bishop.

Constructors

KnightQueen

The knight-queen chess piece.

KnightRook

The knight-rook chess piece.

KnightBishop

The knight-bishop chess piece.

Instances

Instances details
Bounded ChessHybridType Source # 
Instance details

Defined in Data.Char.Chess

Enum ChessHybridType Source # 
Instance details

Defined in Data.Char.Chess

Eq ChessHybridType Source # 
Instance details

Defined in Data.Char.Chess

Data ChessHybridType Source # 
Instance details

Defined in Data.Char.Chess

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChessHybridType -> c ChessHybridType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChessHybridType #

toConstr :: ChessHybridType -> Constr #

dataTypeOf :: ChessHybridType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ChessHybridType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChessHybridType) #

gmapT :: (forall b. Data b => b -> b) -> ChessHybridType -> ChessHybridType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChessHybridType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChessHybridType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChessHybridType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChessHybridType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChessHybridType -> m ChessHybridType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChessHybridType -> m ChessHybridType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChessHybridType -> m ChessHybridType #

Ord ChessHybridType Source # 
Instance details

Defined in Data.Char.Chess

Read ChessHybridType Source # 
Instance details

Defined in Data.Char.Chess

Show ChessHybridType Source # 
Instance details

Defined in Data.Char.Chess

Generic ChessHybridType Source # 
Instance details

Defined in Data.Char.Chess

Associated Types

type Rep ChessHybridType :: Type -> Type #

Arbitrary ChessHybridType Source # 
Instance details

Defined in Data.Char.Chess

NFData ChessHybridType Source # 
Instance details

Defined in Data.Char.Chess

Methods

rnf :: ChessHybridType -> () #

Hashable ChessHybridType Source # 
Instance details

Defined in Data.Char.Chess

type Rep ChessHybridType Source # 
Instance details

Defined in Data.Char.Chess

type Rep ChessHybridType = D1 ('MetaData "ChessHybridType" "Data.Char.Chess" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) (C1 ('MetaCons "KnightQueen" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KnightRook" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KnightBishop" 'PrefixI 'False) (U1 :: Type -> Type)))

data ChessPiece Source #

Chess pieces that can be represented in Unicode. These are the king, queen, rook, bishop, knight, pawn, and equihopper over 0, 90, 180, and 270 degrees; and the knight over 45, 135, 225, and 315 degrees in Black, White and Neutral. Furthermore one can draw a knight-queen, knight-rook, and knight-bishop pieces can be drawn without rotation and only in BBlack or BWhite.

Constructors

Chess90 ChessColor ChessPieceType Rotate90

Standard pieces drawn in black, white, or neutral and with rotation.

Chess45Knight ChessColor Rotate45

Knights have unicode characters to render these rotated over 45, 135, 225 and 315 degrees.

ChessHybrid ChessHybridType ChessColorBinary

Hybrid chess pieces can only be rendered in BBlack and BWhite.

Instances

Instances details
Eq ChessPiece Source # 
Instance details

Defined in Data.Char.Chess

Data ChessPiece Source # 
Instance details

Defined in Data.Char.Chess

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChessPiece -> c ChessPiece #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChessPiece #

toConstr :: ChessPiece -> Constr #

dataTypeOf :: ChessPiece -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ChessPiece) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChessPiece) #

gmapT :: (forall b. Data b => b -> b) -> ChessPiece -> ChessPiece #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChessPiece -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChessPiece -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChessPiece -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChessPiece -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChessPiece -> m ChessPiece #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChessPiece -> m ChessPiece #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChessPiece -> m ChessPiece #

Ord ChessPiece Source # 
Instance details

Defined in Data.Char.Chess

Read ChessPiece Source # 
Instance details

Defined in Data.Char.Chess

Show ChessPiece Source # 
Instance details

Defined in Data.Char.Chess

Generic ChessPiece Source # 
Instance details

Defined in Data.Char.Chess

Associated Types

type Rep ChessPiece :: Type -> Type #

Arbitrary ChessPiece Source # 
Instance details

Defined in Data.Char.Chess

NFData ChessPiece Source # 
Instance details

Defined in Data.Char.Chess

Methods

rnf :: ChessPiece -> () #

Hashable ChessPiece Source # 
Instance details

Defined in Data.Char.Chess

type Rep ChessPiece Source # 
Instance details

Defined in Data.Char.Chess

data Rotate45 Source #

Extra rotations that can be performed for knight chess pieces.

Constructors

R45

Rotation over 45 degrees.

R135

Rotation over 135 degrees.

R225

Rotation over 225 degrees.

R315

Rotation over 315 degrees.

Instances

Instances details
Bounded Rotate45 Source # 
Instance details

Defined in Data.Char.Chess

Enum Rotate45 Source # 
Instance details

Defined in Data.Char.Chess

Eq Rotate45 Source # 
Instance details

Defined in Data.Char.Chess

Data Rotate45 Source # 
Instance details

Defined in Data.Char.Chess

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Rotate45 -> c Rotate45 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Rotate45 #

toConstr :: Rotate45 -> Constr #

dataTypeOf :: Rotate45 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Rotate45) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rotate45) #

gmapT :: (forall b. Data b => b -> b) -> Rotate45 -> Rotate45 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rotate45 -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rotate45 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Rotate45 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Rotate45 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Rotate45 -> m Rotate45 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Rotate45 -> m Rotate45 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Rotate45 -> m Rotate45 #

Ord Rotate45 Source # 
Instance details

Defined in Data.Char.Chess

Read Rotate45 Source # 
Instance details

Defined in Data.Char.Chess

Show Rotate45 Source # 
Instance details

Defined in Data.Char.Chess

Generic Rotate45 Source # 
Instance details

Defined in Data.Char.Chess

Associated Types

type Rep Rotate45 :: Type -> Type #

Methods

from :: Rotate45 -> Rep Rotate45 x #

to :: Rep Rotate45 x -> Rotate45 #

Arbitrary Rotate45 Source # 
Instance details

Defined in Data.Char.Chess

NFData Rotate45 Source # 
Instance details

Defined in Data.Char.Chess

Methods

rnf :: Rotate45 -> () #

Hashable Rotate45 Source # 
Instance details

Defined in Data.Char.Chess

Methods

hashWithSalt :: Int -> Rotate45 -> Int #

hash :: Rotate45 -> Int #

type Rep Rotate45 Source # 
Instance details

Defined in Data.Char.Chess

type Rep Rotate45 = D1 ('MetaData "Rotate45" "Data.Char.Chess" "unicode-tricks-0.11.0.0-C7NrNgm5l6sAip6k96QRri" 'False) ((C1 ('MetaCons "R45" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "R135" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "R225" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "R315" 'PrefixI 'False) (U1 :: Type -> Type)))

Convert the chess piece to its unicode equivalent.

chessPiece Source #

Arguments

:: ChessPiece

The given ChessPiece to convert.

-> Char

The unicode character that represents the given ChessPiece.

Convert the given ChessPiece to the corresponding unicode character.

Pattern synonyms of special pieces

pattern Grasshopper :: ChessColor -> ChessPiece Source #

A grasshopper is a queen rotated over 180 degrees.

pattern Nightrider :: ChessColor -> ChessPiece Source #

A Nightrider is a knight rotated over 180 degrees.

pattern Amazon :: ChessColorBinary -> ChessPiece Source #

An amazon is alterative name for a knight-queen.

pattern Terror :: ChessColorBinary -> ChessPiece Source #

A terror is alterative name for a knight-queen.

pattern OmnipotentQueen :: ChessColorBinary -> ChessPiece Source #

An omnipotent queen is alterative name for a knight-queen.

pattern Superqueen :: ChessColorBinary -> ChessPiece Source #

A superqueen is alterative name for a knight-queen.

pattern Chancellor :: ChessColorBinary -> ChessPiece Source #

A chancellor is alterative name for a knight-rook.

pattern Marshall :: ChessColorBinary -> ChessPiece Source #

A marshall is alterative name for a knight-rook.

pattern Empress :: ChessColorBinary -> ChessPiece Source #

An empress is alterative name for a knight-rook.

pattern Cardinal :: ChessColorBinary -> ChessPiece Source #

A cardinal is alterative name for a knight-bishop.

pattern Princess :: ChessColorBinary -> ChessPiece Source #

A princess is alterative name for a knight-bishop.