{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE Safe #-}
module Data.Char.Emoji.BloodType
(
BloodType (O, B, A, AB),
pattern DropOfBlood,
)
where
import Control.DeepSeq (NFData)
import Data.Bits (Bits (bit, bitSize, bitSizeMaybe, complement, isSigned, popCount, rotate, shift, testBit, xor, (.&.), (.|.)))
import Data.Char.Core (UnicodeText (fromUnicodeText, isInTextRange, toUnicodeText))
import Data.Char.Emoji.Core (pattern EmojiSuffix)
import Data.Data (Data)
import Data.Function (on)
import Data.Hashable (Hashable)
import Data.Text (unpack)
import GHC.Generics (Generic)
import Test.QuickCheck.Arbitrary (Arbitrary (arbitrary), arbitraryBoundedEnum)
pattern DropOfBlood :: Char
pattern $mDropOfBlood :: forall {r}. Char -> ((# #) -> r) -> ((# #) -> r) -> r
$bDropOfBlood :: Char
DropOfBlood = '\x1fa78'
data BloodType
=
O
|
B
|
A
|
AB
deriving (BloodType
BloodType -> BloodType -> Bounded BloodType
forall a. a -> a -> Bounded a
$cminBound :: BloodType
minBound :: BloodType
$cmaxBound :: BloodType
maxBound :: BloodType
Bounded, Typeable BloodType
Typeable BloodType
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BloodType -> c BloodType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BloodType)
-> (BloodType -> Constr)
-> (BloodType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BloodType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BloodType))
-> ((forall b. Data b => b -> b) -> BloodType -> BloodType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BloodType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BloodType -> r)
-> (forall u. (forall d. Data d => d -> u) -> BloodType -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> BloodType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BloodType -> m BloodType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BloodType -> m BloodType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BloodType -> m BloodType)
-> Data BloodType
BloodType -> Constr
BloodType -> DataType
(forall b. Data b => b -> b) -> BloodType -> BloodType
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) -> BloodType -> u
forall u. (forall d. Data d => d -> u) -> BloodType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BloodType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BloodType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BloodType -> m BloodType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BloodType -> m BloodType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BloodType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BloodType -> c BloodType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BloodType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BloodType)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BloodType -> c BloodType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BloodType -> c BloodType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BloodType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BloodType
$ctoConstr :: BloodType -> Constr
toConstr :: BloodType -> Constr
$cdataTypeOf :: BloodType -> DataType
dataTypeOf :: BloodType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BloodType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BloodType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BloodType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BloodType)
$cgmapT :: (forall b. Data b => b -> b) -> BloodType -> BloodType
gmapT :: (forall b. Data b => b -> b) -> BloodType -> BloodType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BloodType -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BloodType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BloodType -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BloodType -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> BloodType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> BloodType -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> BloodType -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> BloodType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BloodType -> m BloodType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BloodType -> m BloodType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BloodType -> m BloodType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BloodType -> m BloodType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BloodType -> m BloodType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BloodType -> m BloodType
Data, Int -> BloodType
BloodType -> Int
BloodType -> [BloodType]
BloodType -> BloodType
BloodType -> BloodType -> [BloodType]
BloodType -> BloodType -> BloodType -> [BloodType]
(BloodType -> BloodType)
-> (BloodType -> BloodType)
-> (Int -> BloodType)
-> (BloodType -> Int)
-> (BloodType -> [BloodType])
-> (BloodType -> BloodType -> [BloodType])
-> (BloodType -> BloodType -> [BloodType])
-> (BloodType -> BloodType -> BloodType -> [BloodType])
-> Enum BloodType
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 :: BloodType -> BloodType
succ :: BloodType -> BloodType
$cpred :: BloodType -> BloodType
pred :: BloodType -> BloodType
$ctoEnum :: Int -> BloodType
toEnum :: Int -> BloodType
$cfromEnum :: BloodType -> Int
fromEnum :: BloodType -> Int
$cenumFrom :: BloodType -> [BloodType]
enumFrom :: BloodType -> [BloodType]
$cenumFromThen :: BloodType -> BloodType -> [BloodType]
enumFromThen :: BloodType -> BloodType -> [BloodType]
$cenumFromTo :: BloodType -> BloodType -> [BloodType]
enumFromTo :: BloodType -> BloodType -> [BloodType]
$cenumFromThenTo :: BloodType -> BloodType -> BloodType -> [BloodType]
enumFromThenTo :: BloodType -> BloodType -> BloodType -> [BloodType]
Enum, BloodType -> BloodType -> Bool
(BloodType -> BloodType -> Bool)
-> (BloodType -> BloodType -> Bool) -> Eq BloodType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BloodType -> BloodType -> Bool
== :: BloodType -> BloodType -> Bool
$c/= :: BloodType -> BloodType -> Bool
/= :: BloodType -> BloodType -> Bool
Eq, (forall x. BloodType -> Rep BloodType x)
-> (forall x. Rep BloodType x -> BloodType) -> Generic BloodType
forall x. Rep BloodType x -> BloodType
forall x. BloodType -> Rep BloodType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BloodType -> Rep BloodType x
from :: forall x. BloodType -> Rep BloodType x
$cto :: forall x. Rep BloodType x -> BloodType
to :: forall x. Rep BloodType x -> BloodType
Generic, Eq BloodType
Eq BloodType
-> (BloodType -> BloodType -> Ordering)
-> (BloodType -> BloodType -> Bool)
-> (BloodType -> BloodType -> Bool)
-> (BloodType -> BloodType -> Bool)
-> (BloodType -> BloodType -> Bool)
-> (BloodType -> BloodType -> BloodType)
-> (BloodType -> BloodType -> BloodType)
-> Ord BloodType
BloodType -> BloodType -> Bool
BloodType -> BloodType -> Ordering
BloodType -> BloodType -> BloodType
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 :: BloodType -> BloodType -> Ordering
compare :: BloodType -> BloodType -> Ordering
$c< :: BloodType -> BloodType -> Bool
< :: BloodType -> BloodType -> Bool
$c<= :: BloodType -> BloodType -> Bool
<= :: BloodType -> BloodType -> Bool
$c> :: BloodType -> BloodType -> Bool
> :: BloodType -> BloodType -> Bool
$c>= :: BloodType -> BloodType -> Bool
>= :: BloodType -> BloodType -> Bool
$cmax :: BloodType -> BloodType -> BloodType
max :: BloodType -> BloodType -> BloodType
$cmin :: BloodType -> BloodType -> BloodType
min :: BloodType -> BloodType -> BloodType
Ord, ReadPrec [BloodType]
ReadPrec BloodType
Int -> ReadS BloodType
ReadS [BloodType]
(Int -> ReadS BloodType)
-> ReadS [BloodType]
-> ReadPrec BloodType
-> ReadPrec [BloodType]
-> Read BloodType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BloodType
readsPrec :: Int -> ReadS BloodType
$creadList :: ReadS [BloodType]
readList :: ReadS [BloodType]
$creadPrec :: ReadPrec BloodType
readPrec :: ReadPrec BloodType
$creadListPrec :: ReadPrec [BloodType]
readListPrec :: ReadPrec [BloodType]
Read, Int -> BloodType -> ShowS
[BloodType] -> ShowS
BloodType -> [Char]
(Int -> BloodType -> ShowS)
-> (BloodType -> [Char])
-> ([BloodType] -> ShowS)
-> Show BloodType
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BloodType -> ShowS
showsPrec :: Int -> BloodType -> ShowS
$cshow :: BloodType -> [Char]
show :: BloodType -> [Char]
$cshowList :: [BloodType] -> ShowS
showList :: [BloodType] -> ShowS
Show)
instance Arbitrary BloodType where
arbitrary :: Gen BloodType
arbitrary = Gen BloodType
forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum
_overEnumMask :: Enum a => Int -> (Int -> Int) -> a -> a
_overEnumMask :: forall a. Enum a => Int -> (Int -> Int) -> a -> a
_overEnumMask Int
m Int -> Int
f = Int -> a
forall a. Enum a => Int -> a
toEnum (Int -> a) -> (a -> Int) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int
m Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&.) (Int -> Int) -> (a -> Int) -> a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int
f (Int -> Int) -> (a -> Int) -> a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Int
forall a. Enum a => a -> Int
fromEnum
_overEnum2 :: Enum a => (Int -> Int -> Int) -> a -> a -> a
_overEnum2 :: forall a. Enum a => (Int -> Int -> Int) -> a -> a -> a
_overEnum2 Int -> Int -> Int
f a
x a
y = Int -> a
forall a. Enum a => Int -> a
toEnum ((Int -> Int -> Int) -> (a -> Int) -> a -> a -> Int
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on Int -> Int -> Int
f a -> Int
forall a. Enum a => a -> Int
fromEnum a
x a
y)
_overEnumMask2 :: Enum a => Int -> (Int -> Int -> Int) -> a -> a -> a
_overEnumMask2 :: forall a. Enum a => Int -> (Int -> Int -> Int) -> a -> a -> a
_overEnumMask2 Int
m Int -> Int -> Int
f a
x a
y = Int -> a
forall a. Enum a => Int -> a
toEnum (Int
m Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. (Int -> Int -> Int) -> (a -> Int) -> a -> a -> Int
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on Int -> Int -> Int
f a -> Int
forall a. Enum a => a -> Int
fromEnum a
x a
y)
instance Bits BloodType where
.&. :: BloodType -> BloodType -> BloodType
(.&.) = (Int -> Int -> Int) -> BloodType -> BloodType -> BloodType
forall a. Enum a => (Int -> Int -> Int) -> a -> a -> a
_overEnum2 Int -> Int -> Int
forall a. Bits a => a -> a -> a
(.&.)
.|. :: BloodType -> BloodType -> BloodType
(.|.) = (Int -> Int -> Int) -> BloodType -> BloodType -> BloodType
forall a. Enum a => (Int -> Int -> Int) -> a -> a -> a
_overEnum2 Int -> Int -> Int
forall a. Bits a => a -> a -> a
(.|.)
xor :: BloodType -> BloodType -> BloodType
xor = Int -> (Int -> Int -> Int) -> BloodType -> BloodType -> BloodType
forall a. Enum a => Int -> (Int -> Int -> Int) -> a -> a -> a
_overEnumMask2 Int
0x03 Int -> Int -> Int
forall a. Bits a => a -> a -> a
xor
complement :: BloodType -> BloodType
complement BloodType
O = BloodType
AB
complement BloodType
A = BloodType
B
complement BloodType
B = BloodType
A
complement BloodType
AB = BloodType
O
shift :: BloodType -> Int -> BloodType
shift BloodType
abo Int
n = Int -> (Int -> Int) -> BloodType -> BloodType
forall a. Enum a => Int -> (Int -> Int) -> a -> a
_overEnumMask Int
0x03 (Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shift` Int
n) BloodType
abo
rotate :: BloodType -> Int -> BloodType
rotate = (Int -> BloodType -> BloodType) -> BloodType -> Int -> BloodType
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Int -> BloodType -> BloodType
forall {a}. (Eq a, Num a) => a -> BloodType -> BloodType
go (Int -> BloodType -> BloodType)
-> (Int -> Int) -> Int -> BloodType -> BloodType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int
0x01 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&.))
where
go :: a -> BloodType -> BloodType
go a
1 BloodType
A = BloodType
B
go a
1 BloodType
B = BloodType
B
go a
_ BloodType
x = BloodType
x
bitSize :: BloodType -> Int
bitSize = Int -> BloodType -> Int
forall a b. a -> b -> a
const Int
2
bitSizeMaybe :: BloodType -> Maybe Int
bitSizeMaybe = Maybe Int -> BloodType -> Maybe Int
forall a b. a -> b -> a
const (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
2)
isSigned :: BloodType -> Bool
isSigned = Bool -> BloodType -> Bool
forall a b. a -> b -> a
const Bool
False
testBit :: BloodType -> Int -> Bool
testBit = Int -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit (Int -> Int -> Bool)
-> (BloodType -> Int) -> BloodType -> Int -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BloodType -> Int
forall a. Enum a => a -> Int
fromEnum
bit :: Int -> BloodType
bit Int
0 = BloodType
B
bit Int
1 = BloodType
A
bit Int
_ = BloodType
O
popCount :: BloodType -> Int
popCount BloodType
O = Int
0
popCount BloodType
A = Int
1
popCount BloodType
B = Int
1
popCount BloodType
AB = Int
2
instance Hashable BloodType
instance NFData BloodType
instance UnicodeText BloodType where
toUnicodeText :: BloodType -> Text
toUnicodeText BloodType
AB = Text
"\x1f18e"
toUnicodeText BloodType
A = Text
"\x1f170\xfe0f"
toUnicodeText BloodType
B = Text
"\x1f171\xfe0f"
toUnicodeText BloodType
O = Text
"\x1f17e\xfe0f"
fromUnicodeText :: Text -> Maybe BloodType
fromUnicodeText Text
"\x1f18e" = BloodType -> Maybe BloodType
forall a. a -> Maybe a
Just BloodType
AB
fromUnicodeText Text
t
| [Char
c, Char
EmojiSuffix] <- Text -> [Char]
unpack Text
t = Char -> Maybe BloodType
go Char
c
| Bool
otherwise = Maybe BloodType
forall a. Maybe a
Nothing
where
go :: Char -> Maybe BloodType
go Char
'\x1f170' = BloodType -> Maybe BloodType
forall a. a -> Maybe a
Just BloodType
A
go Char
'\x1f171' = BloodType -> Maybe BloodType
forall a. a -> Maybe a
Just BloodType
B
go Char
'\x1f17e' = BloodType -> Maybe BloodType
forall a. a -> Maybe a
Just BloodType
O
go Char
_ = Maybe BloodType
forall a. Maybe a
Nothing
isInTextRange :: Text -> Bool
isInTextRange Text
"\x1f170\xfe0f" = Bool
True
isInTextRange Text
"\x1f171\xfe0f" = Bool
True
isInTextRange Text
"\x1f17e\xfe0f" = Bool
True
isInTextRange Text
"\x1f18e" = Bool
True
isInTextRange Text
_ = Bool
False