{-# LANGUAGE PatternSynonyms, Safe #-}
module Data.Char.Chess (
ChessColor(White, Black, Neutral)
, ChessColorBinary(BWhite, BBlack)
, ChessPieceType(King, Queen, Rook, Bishop, Knight, Pawn, Equihopper)
, ChessHybridType(KnightQueen, KnightRook, KnightBishop)
, ChessPiece(Chess90, Chess45Knight, ChessHybrid)
, Rotate45(R45, R135, R225, R315)
, chessPiece
, pattern Grasshopper, pattern Nightrider, pattern Amazon, pattern Terror, pattern OmnipotentQueen
, pattern Superqueen, pattern Chancellor, pattern Marshall, pattern Empress, pattern Cardinal
, pattern Princess
) where
import Data.Bits((.|.))
import Data.Char(chr)
import Data.Char.Core(
Rotate90(R0, R180)
)
import Test.QuickCheck.Arbitrary(Arbitrary(arbitrary), arbitraryBoundedEnum)
import Test.QuickCheck.Gen(oneof)
data ChessColorBinary
= BWhite
| BBlack
deriving (Bounded, Enum, Eq, Ord, Read, Show)
data ChessColor
= White
| Black
| Neutral
deriving (Bounded, Enum, Eq, Ord, Read, Show)
data ChessPieceType
= King
| Queen
| Rook
| Bishop
| Knight
| Pawn
| Equihopper
deriving (Bounded, Enum, Eq, Ord, Read, Show)
data Rotate45
= R45
| R135
| R225
| R315
deriving (Bounded, Enum, Eq, Ord, Read, Show)
data ChessHybridType
= KnightQueen
| KnightRook
| KnightBishop
deriving (Bounded, Enum, Eq, Ord, Read, Show)
data ChessPiece
= Chess90 ChessColor ChessPieceType Rotate90
| Chess45Knight ChessColor Rotate45
| ChessHybrid ChessHybridType ChessColorBinary
deriving (Eq, Ord, Read, Show)
instance Arbitrary ChessColorBinary where
arbitrary = arbitraryBoundedEnum
instance Arbitrary ChessColor where
arbitrary = arbitraryBoundedEnum
instance Arbitrary ChessPieceType where
arbitrary = arbitraryBoundedEnum
instance Arbitrary ChessHybridType where
arbitrary = arbitraryBoundedEnum
instance Arbitrary Rotate45 where
arbitrary = arbitraryBoundedEnum
instance Arbitrary ChessPiece where
arbitrary = oneof [Chess90 <$> arbitrary <*> arbitrary <*> arbitrary, Chess45Knight <$> arbitrary <*> arbitrary, ChessHybrid <$> arbitrary <*> arbitrary]
pattern Grasshopper :: ChessColor -> ChessPiece
pattern Grasshopper c = Chess90 c Queen R180
pattern Nightrider :: ChessColor -> ChessPiece
pattern Nightrider c = Chess90 c Knight R180
pattern Amazon :: ChessColorBinary -> ChessPiece
pattern Amazon c = ChessHybrid KnightQueen c
pattern Terror :: ChessColorBinary -> ChessPiece
pattern Terror c = ChessHybrid KnightQueen c
pattern OmnipotentQueen :: ChessColorBinary -> ChessPiece
pattern OmnipotentQueen c = ChessHybrid KnightQueen c
pattern Superqueen :: ChessColorBinary -> ChessPiece
pattern Superqueen c = ChessHybrid KnightQueen c
pattern Chancellor :: ChessColorBinary -> ChessPiece
pattern Chancellor c = ChessHybrid KnightRook c
pattern Marshall :: ChessColorBinary -> ChessPiece
pattern Marshall c = ChessHybrid KnightRook c
pattern Empress :: ChessColorBinary -> ChessPiece
pattern Empress c = ChessHybrid KnightRook c
pattern Cardinal :: ChessColorBinary -> ChessPiece
pattern Cardinal c = ChessHybrid KnightBishop c
pattern Princess :: ChessColorBinary -> ChessPiece
pattern Princess c = ChessHybrid KnightBishop c
_chessValue :: ChessPieceType -> ChessColor -> Int
_chessValue t c = 6 * fromEnum c + fromEnum t
chessPiece
:: ChessPiece
-> Char
chessPiece (Chess90 c Equihopper r) = chr (3 * mod (fromEnum r) 2 + fromEnum c + 0x1fa48)
chessPiece (Chess90 Neutral t R0) = chr (0x1fa00 .|. fromEnum t)
chessPiece (Chess90 c t R0) = chr (_chessValue t c + 0x2654)
chessPiece (Chess90 c t r) = chr (0x15 * fromEnum r + _chessValue t c + 0x1f9f4)
chessPiece (Chess45Knight c r) = chr (0x15 * fromEnum r + fromEnum c + 0x1fa06)
chessPiece (ChessHybrid t c) = chr (3 * fromEnum c + fromEnum t + 0x1fa4e)