{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE 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 Control.DeepSeq (NFData)
import Data.Bits ((.|.))
import Data.Char (chr)
import Data.Char.Core (Rotate90 (R0, R180))
import Data.Data (Data)
import Data.Hashable (Hashable)
import GHC.Generics (Generic)
import Test.QuickCheck.Arbitrary (Arbitrary (arbitrary), arbitraryBoundedEnum)
import Test.QuickCheck.Gen (oneof)
data ChessColorBinary
=
BWhite
|
BBlack
deriving (ChessColorBinary
ChessColorBinary -> ChessColorBinary -> Bounded ChessColorBinary
forall a. a -> a -> Bounded a
$cminBound :: ChessColorBinary
minBound :: ChessColorBinary
$cmaxBound :: ChessColorBinary
maxBound :: ChessColorBinary
Bounded, Typeable ChessColorBinary
Typeable ChessColorBinary
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessColorBinary -> c ChessColorBinary)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessColorBinary)
-> (ChessColorBinary -> Constr)
-> (ChessColorBinary -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessColorBinary))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChessColorBinary))
-> ((forall b. Data b => b -> b)
-> ChessColorBinary -> ChessColorBinary)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessColorBinary -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ChessColorBinary -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ChessColorBinary -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ChessColorBinary -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ChessColorBinary -> m ChessColorBinary)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessColorBinary -> m ChessColorBinary)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessColorBinary -> m ChessColorBinary)
-> Data ChessColorBinary
ChessColorBinary -> Constr
ChessColorBinary -> DataType
(forall b. Data b => b -> b)
-> ChessColorBinary -> ChessColorBinary
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> ChessColorBinary -> u
forall u. (forall d. Data d => d -> u) -> ChessColorBinary -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessColorBinary -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ChessColorBinary -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ChessColorBinary -> m ChessColorBinary
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessColorBinary -> m ChessColorBinary
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessColorBinary
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessColorBinary -> c ChessColorBinary
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessColorBinary)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChessColorBinary)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessColorBinary -> c ChessColorBinary
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessColorBinary -> c ChessColorBinary
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessColorBinary
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessColorBinary
$ctoConstr :: ChessColorBinary -> Constr
toConstr :: ChessColorBinary -> Constr
$cdataTypeOf :: ChessColorBinary -> DataType
dataTypeOf :: ChessColorBinary -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessColorBinary)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessColorBinary)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChessColorBinary)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChessColorBinary)
$cgmapT :: (forall b. Data b => b -> b)
-> ChessColorBinary -> ChessColorBinary
gmapT :: (forall b. Data b => b -> b)
-> ChessColorBinary -> ChessColorBinary
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessColorBinary -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessColorBinary -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ChessColorBinary -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ChessColorBinary -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ChessColorBinary -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ChessColorBinary -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ChessColorBinary -> m ChessColorBinary
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ChessColorBinary -> m ChessColorBinary
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessColorBinary -> m ChessColorBinary
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessColorBinary -> m ChessColorBinary
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessColorBinary -> m ChessColorBinary
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessColorBinary -> m ChessColorBinary
Data, Int -> ChessColorBinary
ChessColorBinary -> Int
ChessColorBinary -> [ChessColorBinary]
ChessColorBinary -> ChessColorBinary
ChessColorBinary -> ChessColorBinary -> [ChessColorBinary]
ChessColorBinary
-> ChessColorBinary -> ChessColorBinary -> [ChessColorBinary]
(ChessColorBinary -> ChessColorBinary)
-> (ChessColorBinary -> ChessColorBinary)
-> (Int -> ChessColorBinary)
-> (ChessColorBinary -> Int)
-> (ChessColorBinary -> [ChessColorBinary])
-> (ChessColorBinary -> ChessColorBinary -> [ChessColorBinary])
-> (ChessColorBinary -> ChessColorBinary -> [ChessColorBinary])
-> (ChessColorBinary
-> ChessColorBinary -> ChessColorBinary -> [ChessColorBinary])
-> Enum ChessColorBinary
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ChessColorBinary -> ChessColorBinary
succ :: ChessColorBinary -> ChessColorBinary
$cpred :: ChessColorBinary -> ChessColorBinary
pred :: ChessColorBinary -> ChessColorBinary
$ctoEnum :: Int -> ChessColorBinary
toEnum :: Int -> ChessColorBinary
$cfromEnum :: ChessColorBinary -> Int
fromEnum :: ChessColorBinary -> Int
$cenumFrom :: ChessColorBinary -> [ChessColorBinary]
enumFrom :: ChessColorBinary -> [ChessColorBinary]
$cenumFromThen :: ChessColorBinary -> ChessColorBinary -> [ChessColorBinary]
enumFromThen :: ChessColorBinary -> ChessColorBinary -> [ChessColorBinary]
$cenumFromTo :: ChessColorBinary -> ChessColorBinary -> [ChessColorBinary]
enumFromTo :: ChessColorBinary -> ChessColorBinary -> [ChessColorBinary]
$cenumFromThenTo :: ChessColorBinary
-> ChessColorBinary -> ChessColorBinary -> [ChessColorBinary]
enumFromThenTo :: ChessColorBinary
-> ChessColorBinary -> ChessColorBinary -> [ChessColorBinary]
Enum, ChessColorBinary -> ChessColorBinary -> Bool
(ChessColorBinary -> ChessColorBinary -> Bool)
-> (ChessColorBinary -> ChessColorBinary -> Bool)
-> Eq ChessColorBinary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChessColorBinary -> ChessColorBinary -> Bool
== :: ChessColorBinary -> ChessColorBinary -> Bool
$c/= :: ChessColorBinary -> ChessColorBinary -> Bool
/= :: ChessColorBinary -> ChessColorBinary -> Bool
Eq, (forall x. ChessColorBinary -> Rep ChessColorBinary x)
-> (forall x. Rep ChessColorBinary x -> ChessColorBinary)
-> Generic ChessColorBinary
forall x. Rep ChessColorBinary x -> ChessColorBinary
forall x. ChessColorBinary -> Rep ChessColorBinary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ChessColorBinary -> Rep ChessColorBinary x
from :: forall x. ChessColorBinary -> Rep ChessColorBinary x
$cto :: forall x. Rep ChessColorBinary x -> ChessColorBinary
to :: forall x. Rep ChessColorBinary x -> ChessColorBinary
Generic, Eq ChessColorBinary
Eq ChessColorBinary
-> (ChessColorBinary -> ChessColorBinary -> Ordering)
-> (ChessColorBinary -> ChessColorBinary -> Bool)
-> (ChessColorBinary -> ChessColorBinary -> Bool)
-> (ChessColorBinary -> ChessColorBinary -> Bool)
-> (ChessColorBinary -> ChessColorBinary -> Bool)
-> (ChessColorBinary -> ChessColorBinary -> ChessColorBinary)
-> (ChessColorBinary -> ChessColorBinary -> ChessColorBinary)
-> Ord ChessColorBinary
ChessColorBinary -> ChessColorBinary -> Bool
ChessColorBinary -> ChessColorBinary -> Ordering
ChessColorBinary -> ChessColorBinary -> ChessColorBinary
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ChessColorBinary -> ChessColorBinary -> Ordering
compare :: ChessColorBinary -> ChessColorBinary -> Ordering
$c< :: ChessColorBinary -> ChessColorBinary -> Bool
< :: ChessColorBinary -> ChessColorBinary -> Bool
$c<= :: ChessColorBinary -> ChessColorBinary -> Bool
<= :: ChessColorBinary -> ChessColorBinary -> Bool
$c> :: ChessColorBinary -> ChessColorBinary -> Bool
> :: ChessColorBinary -> ChessColorBinary -> Bool
$c>= :: ChessColorBinary -> ChessColorBinary -> Bool
>= :: ChessColorBinary -> ChessColorBinary -> Bool
$cmax :: ChessColorBinary -> ChessColorBinary -> ChessColorBinary
max :: ChessColorBinary -> ChessColorBinary -> ChessColorBinary
$cmin :: ChessColorBinary -> ChessColorBinary -> ChessColorBinary
min :: ChessColorBinary -> ChessColorBinary -> ChessColorBinary
Ord, ReadPrec [ChessColorBinary]
ReadPrec ChessColorBinary
Int -> ReadS ChessColorBinary
ReadS [ChessColorBinary]
(Int -> ReadS ChessColorBinary)
-> ReadS [ChessColorBinary]
-> ReadPrec ChessColorBinary
-> ReadPrec [ChessColorBinary]
-> Read ChessColorBinary
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ChessColorBinary
readsPrec :: Int -> ReadS ChessColorBinary
$creadList :: ReadS [ChessColorBinary]
readList :: ReadS [ChessColorBinary]
$creadPrec :: ReadPrec ChessColorBinary
readPrec :: ReadPrec ChessColorBinary
$creadListPrec :: ReadPrec [ChessColorBinary]
readListPrec :: ReadPrec [ChessColorBinary]
Read, Int -> ChessColorBinary -> ShowS
[ChessColorBinary] -> ShowS
ChessColorBinary -> String
(Int -> ChessColorBinary -> ShowS)
-> (ChessColorBinary -> String)
-> ([ChessColorBinary] -> ShowS)
-> Show ChessColorBinary
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChessColorBinary -> ShowS
showsPrec :: Int -> ChessColorBinary -> ShowS
$cshow :: ChessColorBinary -> String
show :: ChessColorBinary -> String
$cshowList :: [ChessColorBinary] -> ShowS
showList :: [ChessColorBinary] -> ShowS
Show)
instance Hashable ChessColorBinary
instance NFData ChessColorBinary
data ChessColor
=
White
|
Black
|
Neutral
deriving (ChessColor
ChessColor -> ChessColor -> Bounded ChessColor
forall a. a -> a -> Bounded a
$cminBound :: ChessColor
minBound :: ChessColor
$cmaxBound :: ChessColor
maxBound :: ChessColor
Bounded, Typeable ChessColor
Typeable ChessColor
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessColor -> c ChessColor)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessColor)
-> (ChessColor -> Constr)
-> (ChessColor -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessColor))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChessColor))
-> ((forall b. Data b => b -> b) -> ChessColor -> ChessColor)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessColor -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ChessColor -> r)
-> (forall u. (forall d. Data d => d -> u) -> ChessColor -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ChessColor -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ChessColor -> m ChessColor)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ChessColor -> m ChessColor)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ChessColor -> m ChessColor)
-> Data ChessColor
ChessColor -> Constr
ChessColor -> DataType
(forall b. Data b => b -> b) -> ChessColor -> ChessColor
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ChessColor -> u
forall u. (forall d. Data d => d -> u) -> ChessColor -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessColor -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ChessColor -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ChessColor -> m ChessColor
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ChessColor -> m ChessColor
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessColor
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessColor -> c ChessColor
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessColor)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChessColor)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessColor -> c ChessColor
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessColor -> c ChessColor
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessColor
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessColor
$ctoConstr :: ChessColor -> Constr
toConstr :: ChessColor -> Constr
$cdataTypeOf :: ChessColor -> DataType
dataTypeOf :: ChessColor -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessColor)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessColor)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChessColor)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChessColor)
$cgmapT :: (forall b. Data b => b -> b) -> ChessColor -> ChessColor
gmapT :: (forall b. Data b => b -> b) -> ChessColor -> ChessColor
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessColor -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessColor -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ChessColor -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ChessColor -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ChessColor -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ChessColor -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ChessColor -> m ChessColor
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ChessColor -> m ChessColor
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ChessColor -> m ChessColor
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ChessColor -> m ChessColor
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ChessColor -> m ChessColor
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ChessColor -> m ChessColor
Data, Int -> ChessColor
ChessColor -> Int
ChessColor -> [ChessColor]
ChessColor -> ChessColor
ChessColor -> ChessColor -> [ChessColor]
ChessColor -> ChessColor -> ChessColor -> [ChessColor]
(ChessColor -> ChessColor)
-> (ChessColor -> ChessColor)
-> (Int -> ChessColor)
-> (ChessColor -> Int)
-> (ChessColor -> [ChessColor])
-> (ChessColor -> ChessColor -> [ChessColor])
-> (ChessColor -> ChessColor -> [ChessColor])
-> (ChessColor -> ChessColor -> ChessColor -> [ChessColor])
-> Enum ChessColor
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ChessColor -> ChessColor
succ :: ChessColor -> ChessColor
$cpred :: ChessColor -> ChessColor
pred :: ChessColor -> ChessColor
$ctoEnum :: Int -> ChessColor
toEnum :: Int -> ChessColor
$cfromEnum :: ChessColor -> Int
fromEnum :: ChessColor -> Int
$cenumFrom :: ChessColor -> [ChessColor]
enumFrom :: ChessColor -> [ChessColor]
$cenumFromThen :: ChessColor -> ChessColor -> [ChessColor]
enumFromThen :: ChessColor -> ChessColor -> [ChessColor]
$cenumFromTo :: ChessColor -> ChessColor -> [ChessColor]
enumFromTo :: ChessColor -> ChessColor -> [ChessColor]
$cenumFromThenTo :: ChessColor -> ChessColor -> ChessColor -> [ChessColor]
enumFromThenTo :: ChessColor -> ChessColor -> ChessColor -> [ChessColor]
Enum, ChessColor -> ChessColor -> Bool
(ChessColor -> ChessColor -> Bool)
-> (ChessColor -> ChessColor -> Bool) -> Eq ChessColor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChessColor -> ChessColor -> Bool
== :: ChessColor -> ChessColor -> Bool
$c/= :: ChessColor -> ChessColor -> Bool
/= :: ChessColor -> ChessColor -> Bool
Eq, (forall x. ChessColor -> Rep ChessColor x)
-> (forall x. Rep ChessColor x -> ChessColor) -> Generic ChessColor
forall x. Rep ChessColor x -> ChessColor
forall x. ChessColor -> Rep ChessColor x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ChessColor -> Rep ChessColor x
from :: forall x. ChessColor -> Rep ChessColor x
$cto :: forall x. Rep ChessColor x -> ChessColor
to :: forall x. Rep ChessColor x -> ChessColor
Generic, Eq ChessColor
Eq ChessColor
-> (ChessColor -> ChessColor -> Ordering)
-> (ChessColor -> ChessColor -> Bool)
-> (ChessColor -> ChessColor -> Bool)
-> (ChessColor -> ChessColor -> Bool)
-> (ChessColor -> ChessColor -> Bool)
-> (ChessColor -> ChessColor -> ChessColor)
-> (ChessColor -> ChessColor -> ChessColor)
-> Ord ChessColor
ChessColor -> ChessColor -> Bool
ChessColor -> ChessColor -> Ordering
ChessColor -> ChessColor -> ChessColor
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ChessColor -> ChessColor -> Ordering
compare :: ChessColor -> ChessColor -> Ordering
$c< :: ChessColor -> ChessColor -> Bool
< :: ChessColor -> ChessColor -> Bool
$c<= :: ChessColor -> ChessColor -> Bool
<= :: ChessColor -> ChessColor -> Bool
$c> :: ChessColor -> ChessColor -> Bool
> :: ChessColor -> ChessColor -> Bool
$c>= :: ChessColor -> ChessColor -> Bool
>= :: ChessColor -> ChessColor -> Bool
$cmax :: ChessColor -> ChessColor -> ChessColor
max :: ChessColor -> ChessColor -> ChessColor
$cmin :: ChessColor -> ChessColor -> ChessColor
min :: ChessColor -> ChessColor -> ChessColor
Ord, ReadPrec [ChessColor]
ReadPrec ChessColor
Int -> ReadS ChessColor
ReadS [ChessColor]
(Int -> ReadS ChessColor)
-> ReadS [ChessColor]
-> ReadPrec ChessColor
-> ReadPrec [ChessColor]
-> Read ChessColor
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ChessColor
readsPrec :: Int -> ReadS ChessColor
$creadList :: ReadS [ChessColor]
readList :: ReadS [ChessColor]
$creadPrec :: ReadPrec ChessColor
readPrec :: ReadPrec ChessColor
$creadListPrec :: ReadPrec [ChessColor]
readListPrec :: ReadPrec [ChessColor]
Read, Int -> ChessColor -> ShowS
[ChessColor] -> ShowS
ChessColor -> String
(Int -> ChessColor -> ShowS)
-> (ChessColor -> String)
-> ([ChessColor] -> ShowS)
-> Show ChessColor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChessColor -> ShowS
showsPrec :: Int -> ChessColor -> ShowS
$cshow :: ChessColor -> String
show :: ChessColor -> String
$cshowList :: [ChessColor] -> ShowS
showList :: [ChessColor] -> ShowS
Show)
instance Hashable ChessColor
instance NFData ChessColor
data ChessPieceType
=
King
|
Queen
|
Rook
|
Bishop
|
Knight
|
Pawn
|
Equihopper
deriving (ChessPieceType
ChessPieceType -> ChessPieceType -> Bounded ChessPieceType
forall a. a -> a -> Bounded a
$cminBound :: ChessPieceType
minBound :: ChessPieceType
$cmaxBound :: ChessPieceType
maxBound :: ChessPieceType
Bounded, Typeable ChessPieceType
Typeable ChessPieceType
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessPieceType -> c ChessPieceType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessPieceType)
-> (ChessPieceType -> Constr)
-> (ChessPieceType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessPieceType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChessPieceType))
-> ((forall b. Data b => b -> b)
-> ChessPieceType -> ChessPieceType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessPieceType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ChessPieceType -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ChessPieceType -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ChessPieceType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ChessPieceType -> m ChessPieceType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessPieceType -> m ChessPieceType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessPieceType -> m ChessPieceType)
-> Data ChessPieceType
ChessPieceType -> Constr
ChessPieceType -> DataType
(forall b. Data b => b -> b) -> ChessPieceType -> ChessPieceType
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> ChessPieceType -> u
forall u. (forall d. Data d => d -> u) -> ChessPieceType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessPieceType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ChessPieceType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ChessPieceType -> m ChessPieceType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessPieceType -> m ChessPieceType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessPieceType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessPieceType -> c ChessPieceType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessPieceType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChessPieceType)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessPieceType -> c ChessPieceType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessPieceType -> c ChessPieceType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessPieceType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessPieceType
$ctoConstr :: ChessPieceType -> Constr
toConstr :: ChessPieceType -> Constr
$cdataTypeOf :: ChessPieceType -> DataType
dataTypeOf :: ChessPieceType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessPieceType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessPieceType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChessPieceType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChessPieceType)
$cgmapT :: (forall b. Data b => b -> b) -> ChessPieceType -> ChessPieceType
gmapT :: (forall b. Data b => b -> b) -> ChessPieceType -> ChessPieceType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessPieceType -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessPieceType -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ChessPieceType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ChessPieceType -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ChessPieceType -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ChessPieceType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ChessPieceType -> m ChessPieceType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ChessPieceType -> m ChessPieceType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessPieceType -> m ChessPieceType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessPieceType -> m ChessPieceType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessPieceType -> m ChessPieceType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessPieceType -> m ChessPieceType
Data, Int -> ChessPieceType
ChessPieceType -> Int
ChessPieceType -> [ChessPieceType]
ChessPieceType -> ChessPieceType
ChessPieceType -> ChessPieceType -> [ChessPieceType]
ChessPieceType
-> ChessPieceType -> ChessPieceType -> [ChessPieceType]
(ChessPieceType -> ChessPieceType)
-> (ChessPieceType -> ChessPieceType)
-> (Int -> ChessPieceType)
-> (ChessPieceType -> Int)
-> (ChessPieceType -> [ChessPieceType])
-> (ChessPieceType -> ChessPieceType -> [ChessPieceType])
-> (ChessPieceType -> ChessPieceType -> [ChessPieceType])
-> (ChessPieceType
-> ChessPieceType -> ChessPieceType -> [ChessPieceType])
-> Enum ChessPieceType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ChessPieceType -> ChessPieceType
succ :: ChessPieceType -> ChessPieceType
$cpred :: ChessPieceType -> ChessPieceType
pred :: ChessPieceType -> ChessPieceType
$ctoEnum :: Int -> ChessPieceType
toEnum :: Int -> ChessPieceType
$cfromEnum :: ChessPieceType -> Int
fromEnum :: ChessPieceType -> Int
$cenumFrom :: ChessPieceType -> [ChessPieceType]
enumFrom :: ChessPieceType -> [ChessPieceType]
$cenumFromThen :: ChessPieceType -> ChessPieceType -> [ChessPieceType]
enumFromThen :: ChessPieceType -> ChessPieceType -> [ChessPieceType]
$cenumFromTo :: ChessPieceType -> ChessPieceType -> [ChessPieceType]
enumFromTo :: ChessPieceType -> ChessPieceType -> [ChessPieceType]
$cenumFromThenTo :: ChessPieceType
-> ChessPieceType -> ChessPieceType -> [ChessPieceType]
enumFromThenTo :: ChessPieceType
-> ChessPieceType -> ChessPieceType -> [ChessPieceType]
Enum, ChessPieceType -> ChessPieceType -> Bool
(ChessPieceType -> ChessPieceType -> Bool)
-> (ChessPieceType -> ChessPieceType -> Bool) -> Eq ChessPieceType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChessPieceType -> ChessPieceType -> Bool
== :: ChessPieceType -> ChessPieceType -> Bool
$c/= :: ChessPieceType -> ChessPieceType -> Bool
/= :: ChessPieceType -> ChessPieceType -> Bool
Eq, (forall x. ChessPieceType -> Rep ChessPieceType x)
-> (forall x. Rep ChessPieceType x -> ChessPieceType)
-> Generic ChessPieceType
forall x. Rep ChessPieceType x -> ChessPieceType
forall x. ChessPieceType -> Rep ChessPieceType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ChessPieceType -> Rep ChessPieceType x
from :: forall x. ChessPieceType -> Rep ChessPieceType x
$cto :: forall x. Rep ChessPieceType x -> ChessPieceType
to :: forall x. Rep ChessPieceType x -> ChessPieceType
Generic, Eq ChessPieceType
Eq ChessPieceType
-> (ChessPieceType -> ChessPieceType -> Ordering)
-> (ChessPieceType -> ChessPieceType -> Bool)
-> (ChessPieceType -> ChessPieceType -> Bool)
-> (ChessPieceType -> ChessPieceType -> Bool)
-> (ChessPieceType -> ChessPieceType -> Bool)
-> (ChessPieceType -> ChessPieceType -> ChessPieceType)
-> (ChessPieceType -> ChessPieceType -> ChessPieceType)
-> Ord ChessPieceType
ChessPieceType -> ChessPieceType -> Bool
ChessPieceType -> ChessPieceType -> Ordering
ChessPieceType -> ChessPieceType -> ChessPieceType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ChessPieceType -> ChessPieceType -> Ordering
compare :: ChessPieceType -> ChessPieceType -> Ordering
$c< :: ChessPieceType -> ChessPieceType -> Bool
< :: ChessPieceType -> ChessPieceType -> Bool
$c<= :: ChessPieceType -> ChessPieceType -> Bool
<= :: ChessPieceType -> ChessPieceType -> Bool
$c> :: ChessPieceType -> ChessPieceType -> Bool
> :: ChessPieceType -> ChessPieceType -> Bool
$c>= :: ChessPieceType -> ChessPieceType -> Bool
>= :: ChessPieceType -> ChessPieceType -> Bool
$cmax :: ChessPieceType -> ChessPieceType -> ChessPieceType
max :: ChessPieceType -> ChessPieceType -> ChessPieceType
$cmin :: ChessPieceType -> ChessPieceType -> ChessPieceType
min :: ChessPieceType -> ChessPieceType -> ChessPieceType
Ord, ReadPrec [ChessPieceType]
ReadPrec ChessPieceType
Int -> ReadS ChessPieceType
ReadS [ChessPieceType]
(Int -> ReadS ChessPieceType)
-> ReadS [ChessPieceType]
-> ReadPrec ChessPieceType
-> ReadPrec [ChessPieceType]
-> Read ChessPieceType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ChessPieceType
readsPrec :: Int -> ReadS ChessPieceType
$creadList :: ReadS [ChessPieceType]
readList :: ReadS [ChessPieceType]
$creadPrec :: ReadPrec ChessPieceType
readPrec :: ReadPrec ChessPieceType
$creadListPrec :: ReadPrec [ChessPieceType]
readListPrec :: ReadPrec [ChessPieceType]
Read, Int -> ChessPieceType -> ShowS
[ChessPieceType] -> ShowS
ChessPieceType -> String
(Int -> ChessPieceType -> ShowS)
-> (ChessPieceType -> String)
-> ([ChessPieceType] -> ShowS)
-> Show ChessPieceType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChessPieceType -> ShowS
showsPrec :: Int -> ChessPieceType -> ShowS
$cshow :: ChessPieceType -> String
show :: ChessPieceType -> String
$cshowList :: [ChessPieceType] -> ShowS
showList :: [ChessPieceType] -> ShowS
Show)
instance Hashable ChessPieceType
instance NFData ChessPieceType
data Rotate45
=
R45
|
R135
|
R225
|
R315
deriving (Rotate45
Rotate45 -> Rotate45 -> Bounded Rotate45
forall a. a -> a -> Bounded a
$cminBound :: Rotate45
minBound :: Rotate45
$cmaxBound :: Rotate45
maxBound :: Rotate45
Bounded, Typeable Rotate45
Typeable Rotate45
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Rotate45 -> c Rotate45)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Rotate45)
-> (Rotate45 -> Constr)
-> (Rotate45 -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Rotate45))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rotate45))
-> ((forall b. Data b => b -> b) -> Rotate45 -> Rotate45)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Rotate45 -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Rotate45 -> r)
-> (forall u. (forall d. Data d => d -> u) -> Rotate45 -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Rotate45 -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Rotate45 -> m Rotate45)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rotate45 -> m Rotate45)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rotate45 -> m Rotate45)
-> Data Rotate45
Rotate45 -> Constr
Rotate45 -> DataType
(forall b. Data b => b -> b) -> Rotate45 -> Rotate45
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Rotate45 -> u
forall u. (forall d. Data d => d -> u) -> Rotate45 -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Rotate45 -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Rotate45 -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Rotate45 -> m Rotate45
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rotate45 -> m Rotate45
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Rotate45
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Rotate45 -> c Rotate45
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Rotate45)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rotate45)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Rotate45 -> c Rotate45
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Rotate45 -> c Rotate45
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Rotate45
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Rotate45
$ctoConstr :: Rotate45 -> Constr
toConstr :: Rotate45 -> Constr
$cdataTypeOf :: Rotate45 -> DataType
dataTypeOf :: Rotate45 -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Rotate45)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Rotate45)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rotate45)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rotate45)
$cgmapT :: (forall b. Data b => b -> b) -> Rotate45 -> Rotate45
gmapT :: (forall b. Data b => b -> b) -> Rotate45 -> Rotate45
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Rotate45 -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Rotate45 -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Rotate45 -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Rotate45 -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Rotate45 -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Rotate45 -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Rotate45 -> m Rotate45
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Rotate45 -> m Rotate45
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rotate45 -> m Rotate45
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rotate45 -> m Rotate45
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rotate45 -> m Rotate45
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rotate45 -> m Rotate45
Data, Int -> Rotate45
Rotate45 -> Int
Rotate45 -> [Rotate45]
Rotate45 -> Rotate45
Rotate45 -> Rotate45 -> [Rotate45]
Rotate45 -> Rotate45 -> Rotate45 -> [Rotate45]
(Rotate45 -> Rotate45)
-> (Rotate45 -> Rotate45)
-> (Int -> Rotate45)
-> (Rotate45 -> Int)
-> (Rotate45 -> [Rotate45])
-> (Rotate45 -> Rotate45 -> [Rotate45])
-> (Rotate45 -> Rotate45 -> [Rotate45])
-> (Rotate45 -> Rotate45 -> Rotate45 -> [Rotate45])
-> Enum Rotate45
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Rotate45 -> Rotate45
succ :: Rotate45 -> Rotate45
$cpred :: Rotate45 -> Rotate45
pred :: Rotate45 -> Rotate45
$ctoEnum :: Int -> Rotate45
toEnum :: Int -> Rotate45
$cfromEnum :: Rotate45 -> Int
fromEnum :: Rotate45 -> Int
$cenumFrom :: Rotate45 -> [Rotate45]
enumFrom :: Rotate45 -> [Rotate45]
$cenumFromThen :: Rotate45 -> Rotate45 -> [Rotate45]
enumFromThen :: Rotate45 -> Rotate45 -> [Rotate45]
$cenumFromTo :: Rotate45 -> Rotate45 -> [Rotate45]
enumFromTo :: Rotate45 -> Rotate45 -> [Rotate45]
$cenumFromThenTo :: Rotate45 -> Rotate45 -> Rotate45 -> [Rotate45]
enumFromThenTo :: Rotate45 -> Rotate45 -> Rotate45 -> [Rotate45]
Enum, Rotate45 -> Rotate45 -> Bool
(Rotate45 -> Rotate45 -> Bool)
-> (Rotate45 -> Rotate45 -> Bool) -> Eq Rotate45
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Rotate45 -> Rotate45 -> Bool
== :: Rotate45 -> Rotate45 -> Bool
$c/= :: Rotate45 -> Rotate45 -> Bool
/= :: Rotate45 -> Rotate45 -> Bool
Eq, (forall x. Rotate45 -> Rep Rotate45 x)
-> (forall x. Rep Rotate45 x -> Rotate45) -> Generic Rotate45
forall x. Rep Rotate45 x -> Rotate45
forall x. Rotate45 -> Rep Rotate45 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Rotate45 -> Rep Rotate45 x
from :: forall x. Rotate45 -> Rep Rotate45 x
$cto :: forall x. Rep Rotate45 x -> Rotate45
to :: forall x. Rep Rotate45 x -> Rotate45
Generic, Eq Rotate45
Eq Rotate45
-> (Rotate45 -> Rotate45 -> Ordering)
-> (Rotate45 -> Rotate45 -> Bool)
-> (Rotate45 -> Rotate45 -> Bool)
-> (Rotate45 -> Rotate45 -> Bool)
-> (Rotate45 -> Rotate45 -> Bool)
-> (Rotate45 -> Rotate45 -> Rotate45)
-> (Rotate45 -> Rotate45 -> Rotate45)
-> Ord Rotate45
Rotate45 -> Rotate45 -> Bool
Rotate45 -> Rotate45 -> Ordering
Rotate45 -> Rotate45 -> Rotate45
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Rotate45 -> Rotate45 -> Ordering
compare :: Rotate45 -> Rotate45 -> Ordering
$c< :: Rotate45 -> Rotate45 -> Bool
< :: Rotate45 -> Rotate45 -> Bool
$c<= :: Rotate45 -> Rotate45 -> Bool
<= :: Rotate45 -> Rotate45 -> Bool
$c> :: Rotate45 -> Rotate45 -> Bool
> :: Rotate45 -> Rotate45 -> Bool
$c>= :: Rotate45 -> Rotate45 -> Bool
>= :: Rotate45 -> Rotate45 -> Bool
$cmax :: Rotate45 -> Rotate45 -> Rotate45
max :: Rotate45 -> Rotate45 -> Rotate45
$cmin :: Rotate45 -> Rotate45 -> Rotate45
min :: Rotate45 -> Rotate45 -> Rotate45
Ord, ReadPrec [Rotate45]
ReadPrec Rotate45
Int -> ReadS Rotate45
ReadS [Rotate45]
(Int -> ReadS Rotate45)
-> ReadS [Rotate45]
-> ReadPrec Rotate45
-> ReadPrec [Rotate45]
-> Read Rotate45
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Rotate45
readsPrec :: Int -> ReadS Rotate45
$creadList :: ReadS [Rotate45]
readList :: ReadS [Rotate45]
$creadPrec :: ReadPrec Rotate45
readPrec :: ReadPrec Rotate45
$creadListPrec :: ReadPrec [Rotate45]
readListPrec :: ReadPrec [Rotate45]
Read, Int -> Rotate45 -> ShowS
[Rotate45] -> ShowS
Rotate45 -> String
(Int -> Rotate45 -> ShowS)
-> (Rotate45 -> String) -> ([Rotate45] -> ShowS) -> Show Rotate45
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Rotate45 -> ShowS
showsPrec :: Int -> Rotate45 -> ShowS
$cshow :: Rotate45 -> String
show :: Rotate45 -> String
$cshowList :: [Rotate45] -> ShowS
showList :: [Rotate45] -> ShowS
Show)
instance Hashable Rotate45
instance NFData Rotate45
data ChessHybridType
=
KnightQueen
|
KnightRook
|
KnightBishop
deriving (ChessHybridType
ChessHybridType -> ChessHybridType -> Bounded ChessHybridType
forall a. a -> a -> Bounded a
$cminBound :: ChessHybridType
minBound :: ChessHybridType
$cmaxBound :: ChessHybridType
maxBound :: ChessHybridType
Bounded, Typeable ChessHybridType
Typeable ChessHybridType
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessHybridType -> c ChessHybridType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessHybridType)
-> (ChessHybridType -> Constr)
-> (ChessHybridType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessHybridType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChessHybridType))
-> ((forall b. Data b => b -> b)
-> ChessHybridType -> ChessHybridType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessHybridType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ChessHybridType -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ChessHybridType -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ChessHybridType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ChessHybridType -> m ChessHybridType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessHybridType -> m ChessHybridType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessHybridType -> m ChessHybridType)
-> Data ChessHybridType
ChessHybridType -> Constr
ChessHybridType -> DataType
(forall b. Data b => b -> b) -> ChessHybridType -> ChessHybridType
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> ChessHybridType -> u
forall u. (forall d. Data d => d -> u) -> ChessHybridType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessHybridType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ChessHybridType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ChessHybridType -> m ChessHybridType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessHybridType -> m ChessHybridType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessHybridType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessHybridType -> c ChessHybridType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessHybridType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChessHybridType)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessHybridType -> c ChessHybridType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessHybridType -> c ChessHybridType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessHybridType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessHybridType
$ctoConstr :: ChessHybridType -> Constr
toConstr :: ChessHybridType -> Constr
$cdataTypeOf :: ChessHybridType -> DataType
dataTypeOf :: ChessHybridType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessHybridType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessHybridType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChessHybridType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChessHybridType)
$cgmapT :: (forall b. Data b => b -> b) -> ChessHybridType -> ChessHybridType
gmapT :: (forall b. Data b => b -> b) -> ChessHybridType -> ChessHybridType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessHybridType -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessHybridType -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ChessHybridType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ChessHybridType -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ChessHybridType -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ChessHybridType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ChessHybridType -> m ChessHybridType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ChessHybridType -> m ChessHybridType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessHybridType -> m ChessHybridType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessHybridType -> m ChessHybridType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessHybridType -> m ChessHybridType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ChessHybridType -> m ChessHybridType
Data, Int -> ChessHybridType
ChessHybridType -> Int
ChessHybridType -> [ChessHybridType]
ChessHybridType -> ChessHybridType
ChessHybridType -> ChessHybridType -> [ChessHybridType]
ChessHybridType
-> ChessHybridType -> ChessHybridType -> [ChessHybridType]
(ChessHybridType -> ChessHybridType)
-> (ChessHybridType -> ChessHybridType)
-> (Int -> ChessHybridType)
-> (ChessHybridType -> Int)
-> (ChessHybridType -> [ChessHybridType])
-> (ChessHybridType -> ChessHybridType -> [ChessHybridType])
-> (ChessHybridType -> ChessHybridType -> [ChessHybridType])
-> (ChessHybridType
-> ChessHybridType -> ChessHybridType -> [ChessHybridType])
-> Enum ChessHybridType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ChessHybridType -> ChessHybridType
succ :: ChessHybridType -> ChessHybridType
$cpred :: ChessHybridType -> ChessHybridType
pred :: ChessHybridType -> ChessHybridType
$ctoEnum :: Int -> ChessHybridType
toEnum :: Int -> ChessHybridType
$cfromEnum :: ChessHybridType -> Int
fromEnum :: ChessHybridType -> Int
$cenumFrom :: ChessHybridType -> [ChessHybridType]
enumFrom :: ChessHybridType -> [ChessHybridType]
$cenumFromThen :: ChessHybridType -> ChessHybridType -> [ChessHybridType]
enumFromThen :: ChessHybridType -> ChessHybridType -> [ChessHybridType]
$cenumFromTo :: ChessHybridType -> ChessHybridType -> [ChessHybridType]
enumFromTo :: ChessHybridType -> ChessHybridType -> [ChessHybridType]
$cenumFromThenTo :: ChessHybridType
-> ChessHybridType -> ChessHybridType -> [ChessHybridType]
enumFromThenTo :: ChessHybridType
-> ChessHybridType -> ChessHybridType -> [ChessHybridType]
Enum, ChessHybridType -> ChessHybridType -> Bool
(ChessHybridType -> ChessHybridType -> Bool)
-> (ChessHybridType -> ChessHybridType -> Bool)
-> Eq ChessHybridType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChessHybridType -> ChessHybridType -> Bool
== :: ChessHybridType -> ChessHybridType -> Bool
$c/= :: ChessHybridType -> ChessHybridType -> Bool
/= :: ChessHybridType -> ChessHybridType -> Bool
Eq, (forall x. ChessHybridType -> Rep ChessHybridType x)
-> (forall x. Rep ChessHybridType x -> ChessHybridType)
-> Generic ChessHybridType
forall x. Rep ChessHybridType x -> ChessHybridType
forall x. ChessHybridType -> Rep ChessHybridType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ChessHybridType -> Rep ChessHybridType x
from :: forall x. ChessHybridType -> Rep ChessHybridType x
$cto :: forall x. Rep ChessHybridType x -> ChessHybridType
to :: forall x. Rep ChessHybridType x -> ChessHybridType
Generic, Eq ChessHybridType
Eq ChessHybridType
-> (ChessHybridType -> ChessHybridType -> Ordering)
-> (ChessHybridType -> ChessHybridType -> Bool)
-> (ChessHybridType -> ChessHybridType -> Bool)
-> (ChessHybridType -> ChessHybridType -> Bool)
-> (ChessHybridType -> ChessHybridType -> Bool)
-> (ChessHybridType -> ChessHybridType -> ChessHybridType)
-> (ChessHybridType -> ChessHybridType -> ChessHybridType)
-> Ord ChessHybridType
ChessHybridType -> ChessHybridType -> Bool
ChessHybridType -> ChessHybridType -> Ordering
ChessHybridType -> ChessHybridType -> ChessHybridType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ChessHybridType -> ChessHybridType -> Ordering
compare :: ChessHybridType -> ChessHybridType -> Ordering
$c< :: ChessHybridType -> ChessHybridType -> Bool
< :: ChessHybridType -> ChessHybridType -> Bool
$c<= :: ChessHybridType -> ChessHybridType -> Bool
<= :: ChessHybridType -> ChessHybridType -> Bool
$c> :: ChessHybridType -> ChessHybridType -> Bool
> :: ChessHybridType -> ChessHybridType -> Bool
$c>= :: ChessHybridType -> ChessHybridType -> Bool
>= :: ChessHybridType -> ChessHybridType -> Bool
$cmax :: ChessHybridType -> ChessHybridType -> ChessHybridType
max :: ChessHybridType -> ChessHybridType -> ChessHybridType
$cmin :: ChessHybridType -> ChessHybridType -> ChessHybridType
min :: ChessHybridType -> ChessHybridType -> ChessHybridType
Ord, ReadPrec [ChessHybridType]
ReadPrec ChessHybridType
Int -> ReadS ChessHybridType
ReadS [ChessHybridType]
(Int -> ReadS ChessHybridType)
-> ReadS [ChessHybridType]
-> ReadPrec ChessHybridType
-> ReadPrec [ChessHybridType]
-> Read ChessHybridType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ChessHybridType
readsPrec :: Int -> ReadS ChessHybridType
$creadList :: ReadS [ChessHybridType]
readList :: ReadS [ChessHybridType]
$creadPrec :: ReadPrec ChessHybridType
readPrec :: ReadPrec ChessHybridType
$creadListPrec :: ReadPrec [ChessHybridType]
readListPrec :: ReadPrec [ChessHybridType]
Read, Int -> ChessHybridType -> ShowS
[ChessHybridType] -> ShowS
ChessHybridType -> String
(Int -> ChessHybridType -> ShowS)
-> (ChessHybridType -> String)
-> ([ChessHybridType] -> ShowS)
-> Show ChessHybridType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChessHybridType -> ShowS
showsPrec :: Int -> ChessHybridType -> ShowS
$cshow :: ChessHybridType -> String
show :: ChessHybridType -> String
$cshowList :: [ChessHybridType] -> ShowS
showList :: [ChessHybridType] -> ShowS
Show)
instance Hashable ChessHybridType
instance NFData ChessHybridType
data ChessPiece
=
Chess90 ChessColor ChessPieceType Rotate90
|
Chess45Knight ChessColor Rotate45
|
ChessHybrid ChessHybridType ChessColorBinary
deriving (Typeable ChessPiece
Typeable ChessPiece
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessPiece -> c ChessPiece)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessPiece)
-> (ChessPiece -> Constr)
-> (ChessPiece -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessPiece))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ChessPiece))
-> ((forall b. Data b => b -> b) -> ChessPiece -> ChessPiece)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessPiece -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ChessPiece -> r)
-> (forall u. (forall d. Data d => d -> u) -> ChessPiece -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ChessPiece -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ChessPiece -> m ChessPiece)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ChessPiece -> m ChessPiece)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ChessPiece -> m ChessPiece)
-> Data ChessPiece
ChessPiece -> Constr
ChessPiece -> DataType
(forall b. Data b => b -> b) -> ChessPiece -> ChessPiece
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ChessPiece -> u
forall u. (forall d. Data d => d -> u) -> ChessPiece -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessPiece -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ChessPiece -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ChessPiece -> m ChessPiece
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ChessPiece -> m ChessPiece
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessPiece
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessPiece -> c ChessPiece
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessPiece)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChessPiece)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessPiece -> c ChessPiece
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ChessPiece -> c ChessPiece
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessPiece
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ChessPiece
$ctoConstr :: ChessPiece -> Constr
toConstr :: ChessPiece -> Constr
$cdataTypeOf :: ChessPiece -> DataType
dataTypeOf :: ChessPiece -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessPiece)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ChessPiece)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChessPiece)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChessPiece)
$cgmapT :: (forall b. Data b => b -> b) -> ChessPiece -> ChessPiece
gmapT :: (forall b. Data b => b -> b) -> ChessPiece -> ChessPiece
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessPiece -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ChessPiece -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ChessPiece -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ChessPiece -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ChessPiece -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ChessPiece -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ChessPiece -> m ChessPiece
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ChessPiece -> m ChessPiece
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ChessPiece -> m ChessPiece
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ChessPiece -> m ChessPiece
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ChessPiece -> m ChessPiece
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ChessPiece -> m ChessPiece
Data, ChessPiece -> ChessPiece -> Bool
(ChessPiece -> ChessPiece -> Bool)
-> (ChessPiece -> ChessPiece -> Bool) -> Eq ChessPiece
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChessPiece -> ChessPiece -> Bool
== :: ChessPiece -> ChessPiece -> Bool
$c/= :: ChessPiece -> ChessPiece -> Bool
/= :: ChessPiece -> ChessPiece -> Bool
Eq, (forall x. ChessPiece -> Rep ChessPiece x)
-> (forall x. Rep ChessPiece x -> ChessPiece) -> Generic ChessPiece
forall x. Rep ChessPiece x -> ChessPiece
forall x. ChessPiece -> Rep ChessPiece x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ChessPiece -> Rep ChessPiece x
from :: forall x. ChessPiece -> Rep ChessPiece x
$cto :: forall x. Rep ChessPiece x -> ChessPiece
to :: forall x. Rep ChessPiece x -> ChessPiece
Generic, Eq ChessPiece
Eq ChessPiece
-> (ChessPiece -> ChessPiece -> Ordering)
-> (ChessPiece -> ChessPiece -> Bool)
-> (ChessPiece -> ChessPiece -> Bool)
-> (ChessPiece -> ChessPiece -> Bool)
-> (ChessPiece -> ChessPiece -> Bool)
-> (ChessPiece -> ChessPiece -> ChessPiece)
-> (ChessPiece -> ChessPiece -> ChessPiece)
-> Ord ChessPiece
ChessPiece -> ChessPiece -> Bool
ChessPiece -> ChessPiece -> Ordering
ChessPiece -> ChessPiece -> ChessPiece
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ChessPiece -> ChessPiece -> Ordering
compare :: ChessPiece -> ChessPiece -> Ordering
$c< :: ChessPiece -> ChessPiece -> Bool
< :: ChessPiece -> ChessPiece -> Bool
$c<= :: ChessPiece -> ChessPiece -> Bool
<= :: ChessPiece -> ChessPiece -> Bool
$c> :: ChessPiece -> ChessPiece -> Bool
> :: ChessPiece -> ChessPiece -> Bool
$c>= :: ChessPiece -> ChessPiece -> Bool
>= :: ChessPiece -> ChessPiece -> Bool
$cmax :: ChessPiece -> ChessPiece -> ChessPiece
max :: ChessPiece -> ChessPiece -> ChessPiece
$cmin :: ChessPiece -> ChessPiece -> ChessPiece
min :: ChessPiece -> ChessPiece -> ChessPiece
Ord, ReadPrec [ChessPiece]
ReadPrec ChessPiece
Int -> ReadS ChessPiece
ReadS [ChessPiece]
(Int -> ReadS ChessPiece)
-> ReadS [ChessPiece]
-> ReadPrec ChessPiece
-> ReadPrec [ChessPiece]
-> Read ChessPiece
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ChessPiece
readsPrec :: Int -> ReadS ChessPiece
$creadList :: ReadS [ChessPiece]
readList :: ReadS [ChessPiece]
$creadPrec :: ReadPrec ChessPiece
readPrec :: ReadPrec ChessPiece
$creadListPrec :: ReadPrec [ChessPiece]
readListPrec :: ReadPrec [ChessPiece]
Read, Int -> ChessPiece -> ShowS
[ChessPiece] -> ShowS
ChessPiece -> String
(Int -> ChessPiece -> ShowS)
-> (ChessPiece -> String)
-> ([ChessPiece] -> ShowS)
-> Show ChessPiece
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChessPiece -> ShowS
showsPrec :: Int -> ChessPiece -> ShowS
$cshow :: ChessPiece -> String
show :: ChessPiece -> String
$cshowList :: [ChessPiece] -> ShowS
showList :: [ChessPiece] -> ShowS
Show)
instance Hashable ChessPiece
instance NFData ChessPiece
instance Arbitrary ChessColorBinary where
arbitrary :: Gen ChessColorBinary
arbitrary = Gen ChessColorBinary
forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum
instance Arbitrary ChessColor where
arbitrary :: Gen ChessColor
arbitrary = Gen ChessColor
forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum
instance Arbitrary ChessPieceType where
arbitrary :: Gen ChessPieceType
arbitrary = Gen ChessPieceType
forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum
instance Arbitrary ChessHybridType where
arbitrary :: Gen ChessHybridType
arbitrary = Gen ChessHybridType
forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum
instance Arbitrary Rotate45 where
arbitrary :: Gen Rotate45
arbitrary = Gen Rotate45
forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum
instance Arbitrary ChessPiece where
arbitrary :: Gen ChessPiece
arbitrary = [Gen ChessPiece] -> Gen ChessPiece
forall a. [Gen a] -> Gen a
oneof [ChessColor -> ChessPieceType -> Rotate90 -> ChessPiece
Chess90 (ChessColor -> ChessPieceType -> Rotate90 -> ChessPiece)
-> Gen ChessColor -> Gen (ChessPieceType -> Rotate90 -> ChessPiece)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen ChessColor
forall a. Arbitrary a => Gen a
arbitrary Gen (ChessPieceType -> Rotate90 -> ChessPiece)
-> Gen ChessPieceType -> Gen (Rotate90 -> ChessPiece)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen ChessPieceType
forall a. Arbitrary a => Gen a
arbitrary Gen (Rotate90 -> ChessPiece) -> Gen Rotate90 -> Gen ChessPiece
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Rotate90
forall a. Arbitrary a => Gen a
arbitrary, ChessColor -> Rotate45 -> ChessPiece
Chess45Knight (ChessColor -> Rotate45 -> ChessPiece)
-> Gen ChessColor -> Gen (Rotate45 -> ChessPiece)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen ChessColor
forall a. Arbitrary a => Gen a
arbitrary Gen (Rotate45 -> ChessPiece) -> Gen Rotate45 -> Gen ChessPiece
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Rotate45
forall a. Arbitrary a => Gen a
arbitrary, ChessHybridType -> ChessColorBinary -> ChessPiece
ChessHybrid (ChessHybridType -> ChessColorBinary -> ChessPiece)
-> Gen ChessHybridType -> Gen (ChessColorBinary -> ChessPiece)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen ChessHybridType
forall a. Arbitrary a => Gen a
arbitrary Gen (ChessColorBinary -> ChessPiece)
-> Gen ChessColorBinary -> Gen ChessPiece
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen ChessColorBinary
forall a. Arbitrary a => Gen a
arbitrary]
pattern Grasshopper :: ChessColor -> ChessPiece
pattern $mGrasshopper :: forall {r}. ChessPiece -> (ChessColor -> r) -> ((# #) -> r) -> r
$bGrasshopper :: ChessColor -> ChessPiece
Grasshopper c = Chess90 c Queen R180
pattern Nightrider :: ChessColor -> ChessPiece
pattern $mNightrider :: forall {r}. ChessPiece -> (ChessColor -> r) -> ((# #) -> r) -> r
$bNightrider :: ChessColor -> ChessPiece
Nightrider c = Chess90 c Knight R180
pattern Amazon :: ChessColorBinary -> ChessPiece
pattern $mAmazon :: forall {r}.
ChessPiece -> (ChessColorBinary -> r) -> ((# #) -> r) -> r
$bAmazon :: ChessColorBinary -> ChessPiece
Amazon c = ChessHybrid KnightQueen c
pattern Terror :: ChessColorBinary -> ChessPiece
pattern $mTerror :: forall {r}.
ChessPiece -> (ChessColorBinary -> r) -> ((# #) -> r) -> r
$bTerror :: ChessColorBinary -> ChessPiece
Terror c = ChessHybrid KnightQueen c
pattern OmnipotentQueen :: ChessColorBinary -> ChessPiece
pattern $mOmnipotentQueen :: forall {r}.
ChessPiece -> (ChessColorBinary -> r) -> ((# #) -> r) -> r
$bOmnipotentQueen :: ChessColorBinary -> ChessPiece
OmnipotentQueen c = ChessHybrid KnightQueen c
pattern Superqueen :: ChessColorBinary -> ChessPiece
pattern $mSuperqueen :: forall {r}.
ChessPiece -> (ChessColorBinary -> r) -> ((# #) -> r) -> r
$bSuperqueen :: ChessColorBinary -> ChessPiece
Superqueen c = ChessHybrid KnightQueen c
pattern Chancellor :: ChessColorBinary -> ChessPiece
pattern $mChancellor :: forall {r}.
ChessPiece -> (ChessColorBinary -> r) -> ((# #) -> r) -> r
$bChancellor :: ChessColorBinary -> ChessPiece
Chancellor c = ChessHybrid KnightRook c
pattern Marshall :: ChessColorBinary -> ChessPiece
pattern $mMarshall :: forall {r}.
ChessPiece -> (ChessColorBinary -> r) -> ((# #) -> r) -> r
$bMarshall :: ChessColorBinary -> ChessPiece
Marshall c = ChessHybrid KnightRook c
pattern Empress :: ChessColorBinary -> ChessPiece
pattern $mEmpress :: forall {r}.
ChessPiece -> (ChessColorBinary -> r) -> ((# #) -> r) -> r
$bEmpress :: ChessColorBinary -> ChessPiece
Empress c = ChessHybrid KnightRook c
pattern Cardinal :: ChessColorBinary -> ChessPiece
pattern $mCardinal :: forall {r}.
ChessPiece -> (ChessColorBinary -> r) -> ((# #) -> r) -> r
$bCardinal :: ChessColorBinary -> ChessPiece
Cardinal c = ChessHybrid KnightBishop c
pattern Princess :: ChessColorBinary -> ChessPiece
pattern $mPrincess :: forall {r}.
ChessPiece -> (ChessColorBinary -> r) -> ((# #) -> r) -> r
$bPrincess :: ChessColorBinary -> ChessPiece
Princess c = ChessHybrid KnightBishop c
_chessValue :: ChessPieceType -> ChessColor -> Int
_chessValue :: ChessPieceType -> ChessColor -> Int
_chessValue ChessPieceType
t ChessColor
c = Int
6 Int -> Int -> Int
forall a. Num a => a -> a -> a
* ChessColor -> Int
forall a. Enum a => a -> Int
fromEnum ChessColor
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ChessPieceType -> Int
forall a. Enum a => a -> Int
fromEnum ChessPieceType
t
chessPiece ::
ChessPiece ->
Char
chessPiece :: ChessPiece -> Char
chessPiece (Chess90 ChessColor
c ChessPieceType
Equihopper Rotate90
r) = Int -> Char
chr (Int
3 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int -> Int -> Int
forall a. Integral a => a -> a -> a
mod (Rotate90 -> Int
forall a. Enum a => a -> Int
fromEnum Rotate90
r) Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ChessColor -> Int
forall a. Enum a => a -> Int
fromEnum ChessColor
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
0x1fa48)
chessPiece (Chess90 ChessColor
Neutral ChessPieceType
t Rotate90
R0) = Int -> Char
chr (Int
0x1fa00 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.|. ChessPieceType -> Int
forall a. Enum a => a -> Int
fromEnum ChessPieceType
t)
chessPiece (Chess90 ChessColor
c ChessPieceType
t Rotate90
R0) = Int -> Char
chr (ChessPieceType -> ChessColor -> Int
_chessValue ChessPieceType
t ChessColor
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
0x2654)
chessPiece (Chess90 ChessColor
c ChessPieceType
t Rotate90
r) = Int -> Char
chr (Int
0x15 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Rotate90 -> Int
forall a. Enum a => a -> Int
fromEnum Rotate90
r Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ChessPieceType -> ChessColor -> Int
_chessValue ChessPieceType
t ChessColor
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
0x1f9f4)
chessPiece (Chess45Knight ChessColor
c Rotate45
r) = Int -> Char
chr (Int
0x15 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Rotate45 -> Int
forall a. Enum a => a -> Int
fromEnum Rotate45
r Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ChessColor -> Int
forall a. Enum a => a -> Int
fromEnum ChessColor
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
0x1fa06)
chessPiece (ChessHybrid ChessHybridType
t ChessColorBinary
c) = Int -> Char
chr (Int
3 Int -> Int -> Int
forall a. Num a => a -> a -> a
* ChessColorBinary -> Int
forall a. Enum a => a -> Int
fromEnum ChessColorBinary
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ChessHybridType -> Int
forall a. Enum a => a -> Int
fromEnum ChessHybridType
t Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
0x1fa4e)