{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE TypeApplications #-}
module Data.Char.Emoji.NoEvilMonkey
( NoEvilMonkey (SeeNoEvilMonkey, HearNoEvilMonkey, SpeakNoEvilMonkey),
)
where
import Control.DeepSeq (NFData)
import Data.Char.Core (UnicodeCharacter (fromUnicodeChar, fromUnicodeChar', isInCharRange, toUnicodeChar), UnicodeText (isInTextRange), generateIsInTextRange', mapFromEnum, mapToEnum, mapToEnumSafe)
import Data.Data (Data)
import Data.Hashable (Hashable)
import GHC.Generics (Generic)
import Test.QuickCheck.Arbitrary (Arbitrary (arbitrary), arbitraryBoundedEnum)
_noEvilMonkeyOffset :: Int
_noEvilMonkeyOffset :: Int
_noEvilMonkeyOffset = Int
0x1f648
data NoEvilMonkey
=
SeeNoEvilMonkey
|
HearNoEvilMonkey
|
SpeakNoEvilMonkey
deriving (NoEvilMonkey
NoEvilMonkey -> NoEvilMonkey -> Bounded NoEvilMonkey
forall a. a -> a -> Bounded a
$cminBound :: NoEvilMonkey
minBound :: NoEvilMonkey
$cmaxBound :: NoEvilMonkey
maxBound :: NoEvilMonkey
Bounded, Typeable NoEvilMonkey
Typeable NoEvilMonkey
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NoEvilMonkey -> c NoEvilMonkey)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NoEvilMonkey)
-> (NoEvilMonkey -> Constr)
-> (NoEvilMonkey -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NoEvilMonkey))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NoEvilMonkey))
-> ((forall b. Data b => b -> b) -> NoEvilMonkey -> NoEvilMonkey)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NoEvilMonkey -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NoEvilMonkey -> r)
-> (forall u. (forall d. Data d => d -> u) -> NoEvilMonkey -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> NoEvilMonkey -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NoEvilMonkey -> m NoEvilMonkey)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NoEvilMonkey -> m NoEvilMonkey)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NoEvilMonkey -> m NoEvilMonkey)
-> Data NoEvilMonkey
NoEvilMonkey -> Constr
NoEvilMonkey -> DataType
(forall b. Data b => b -> b) -> NoEvilMonkey -> NoEvilMonkey
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) -> NoEvilMonkey -> u
forall u. (forall d. Data d => d -> u) -> NoEvilMonkey -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NoEvilMonkey -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NoEvilMonkey -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NoEvilMonkey -> m NoEvilMonkey
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NoEvilMonkey -> m NoEvilMonkey
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NoEvilMonkey
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NoEvilMonkey -> c NoEvilMonkey
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NoEvilMonkey)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NoEvilMonkey)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NoEvilMonkey -> c NoEvilMonkey
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NoEvilMonkey -> c NoEvilMonkey
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NoEvilMonkey
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NoEvilMonkey
$ctoConstr :: NoEvilMonkey -> Constr
toConstr :: NoEvilMonkey -> Constr
$cdataTypeOf :: NoEvilMonkey -> DataType
dataTypeOf :: NoEvilMonkey -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NoEvilMonkey)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c NoEvilMonkey)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NoEvilMonkey)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NoEvilMonkey)
$cgmapT :: (forall b. Data b => b -> b) -> NoEvilMonkey -> NoEvilMonkey
gmapT :: (forall b. Data b => b -> b) -> NoEvilMonkey -> NoEvilMonkey
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NoEvilMonkey -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> NoEvilMonkey -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NoEvilMonkey -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> NoEvilMonkey -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> NoEvilMonkey -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> NoEvilMonkey -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NoEvilMonkey -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> NoEvilMonkey -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NoEvilMonkey -> m NoEvilMonkey
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> NoEvilMonkey -> m NoEvilMonkey
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NoEvilMonkey -> m NoEvilMonkey
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NoEvilMonkey -> m NoEvilMonkey
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NoEvilMonkey -> m NoEvilMonkey
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> NoEvilMonkey -> m NoEvilMonkey
Data, Int -> NoEvilMonkey
NoEvilMonkey -> Int
NoEvilMonkey -> [NoEvilMonkey]
NoEvilMonkey -> NoEvilMonkey
NoEvilMonkey -> NoEvilMonkey -> [NoEvilMonkey]
NoEvilMonkey -> NoEvilMonkey -> NoEvilMonkey -> [NoEvilMonkey]
(NoEvilMonkey -> NoEvilMonkey)
-> (NoEvilMonkey -> NoEvilMonkey)
-> (Int -> NoEvilMonkey)
-> (NoEvilMonkey -> Int)
-> (NoEvilMonkey -> [NoEvilMonkey])
-> (NoEvilMonkey -> NoEvilMonkey -> [NoEvilMonkey])
-> (NoEvilMonkey -> NoEvilMonkey -> [NoEvilMonkey])
-> (NoEvilMonkey -> NoEvilMonkey -> NoEvilMonkey -> [NoEvilMonkey])
-> Enum NoEvilMonkey
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 :: NoEvilMonkey -> NoEvilMonkey
succ :: NoEvilMonkey -> NoEvilMonkey
$cpred :: NoEvilMonkey -> NoEvilMonkey
pred :: NoEvilMonkey -> NoEvilMonkey
$ctoEnum :: Int -> NoEvilMonkey
toEnum :: Int -> NoEvilMonkey
$cfromEnum :: NoEvilMonkey -> Int
fromEnum :: NoEvilMonkey -> Int
$cenumFrom :: NoEvilMonkey -> [NoEvilMonkey]
enumFrom :: NoEvilMonkey -> [NoEvilMonkey]
$cenumFromThen :: NoEvilMonkey -> NoEvilMonkey -> [NoEvilMonkey]
enumFromThen :: NoEvilMonkey -> NoEvilMonkey -> [NoEvilMonkey]
$cenumFromTo :: NoEvilMonkey -> NoEvilMonkey -> [NoEvilMonkey]
enumFromTo :: NoEvilMonkey -> NoEvilMonkey -> [NoEvilMonkey]
$cenumFromThenTo :: NoEvilMonkey -> NoEvilMonkey -> NoEvilMonkey -> [NoEvilMonkey]
enumFromThenTo :: NoEvilMonkey -> NoEvilMonkey -> NoEvilMonkey -> [NoEvilMonkey]
Enum, NoEvilMonkey -> NoEvilMonkey -> Bool
(NoEvilMonkey -> NoEvilMonkey -> Bool)
-> (NoEvilMonkey -> NoEvilMonkey -> Bool) -> Eq NoEvilMonkey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NoEvilMonkey -> NoEvilMonkey -> Bool
== :: NoEvilMonkey -> NoEvilMonkey -> Bool
$c/= :: NoEvilMonkey -> NoEvilMonkey -> Bool
/= :: NoEvilMonkey -> NoEvilMonkey -> Bool
Eq, (forall x. NoEvilMonkey -> Rep NoEvilMonkey x)
-> (forall x. Rep NoEvilMonkey x -> NoEvilMonkey)
-> Generic NoEvilMonkey
forall x. Rep NoEvilMonkey x -> NoEvilMonkey
forall x. NoEvilMonkey -> Rep NoEvilMonkey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. NoEvilMonkey -> Rep NoEvilMonkey x
from :: forall x. NoEvilMonkey -> Rep NoEvilMonkey x
$cto :: forall x. Rep NoEvilMonkey x -> NoEvilMonkey
to :: forall x. Rep NoEvilMonkey x -> NoEvilMonkey
Generic, Eq NoEvilMonkey
Eq NoEvilMonkey
-> (NoEvilMonkey -> NoEvilMonkey -> Ordering)
-> (NoEvilMonkey -> NoEvilMonkey -> Bool)
-> (NoEvilMonkey -> NoEvilMonkey -> Bool)
-> (NoEvilMonkey -> NoEvilMonkey -> Bool)
-> (NoEvilMonkey -> NoEvilMonkey -> Bool)
-> (NoEvilMonkey -> NoEvilMonkey -> NoEvilMonkey)
-> (NoEvilMonkey -> NoEvilMonkey -> NoEvilMonkey)
-> Ord NoEvilMonkey
NoEvilMonkey -> NoEvilMonkey -> Bool
NoEvilMonkey -> NoEvilMonkey -> Ordering
NoEvilMonkey -> NoEvilMonkey -> NoEvilMonkey
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 :: NoEvilMonkey -> NoEvilMonkey -> Ordering
compare :: NoEvilMonkey -> NoEvilMonkey -> Ordering
$c< :: NoEvilMonkey -> NoEvilMonkey -> Bool
< :: NoEvilMonkey -> NoEvilMonkey -> Bool
$c<= :: NoEvilMonkey -> NoEvilMonkey -> Bool
<= :: NoEvilMonkey -> NoEvilMonkey -> Bool
$c> :: NoEvilMonkey -> NoEvilMonkey -> Bool
> :: NoEvilMonkey -> NoEvilMonkey -> Bool
$c>= :: NoEvilMonkey -> NoEvilMonkey -> Bool
>= :: NoEvilMonkey -> NoEvilMonkey -> Bool
$cmax :: NoEvilMonkey -> NoEvilMonkey -> NoEvilMonkey
max :: NoEvilMonkey -> NoEvilMonkey -> NoEvilMonkey
$cmin :: NoEvilMonkey -> NoEvilMonkey -> NoEvilMonkey
min :: NoEvilMonkey -> NoEvilMonkey -> NoEvilMonkey
Ord, ReadPrec [NoEvilMonkey]
ReadPrec NoEvilMonkey
Int -> ReadS NoEvilMonkey
ReadS [NoEvilMonkey]
(Int -> ReadS NoEvilMonkey)
-> ReadS [NoEvilMonkey]
-> ReadPrec NoEvilMonkey
-> ReadPrec [NoEvilMonkey]
-> Read NoEvilMonkey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NoEvilMonkey
readsPrec :: Int -> ReadS NoEvilMonkey
$creadList :: ReadS [NoEvilMonkey]
readList :: ReadS [NoEvilMonkey]
$creadPrec :: ReadPrec NoEvilMonkey
readPrec :: ReadPrec NoEvilMonkey
$creadListPrec :: ReadPrec [NoEvilMonkey]
readListPrec :: ReadPrec [NoEvilMonkey]
Read, Int -> NoEvilMonkey -> ShowS
[NoEvilMonkey] -> ShowS
NoEvilMonkey -> String
(Int -> NoEvilMonkey -> ShowS)
-> (NoEvilMonkey -> String)
-> ([NoEvilMonkey] -> ShowS)
-> Show NoEvilMonkey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NoEvilMonkey -> ShowS
showsPrec :: Int -> NoEvilMonkey -> ShowS
$cshow :: NoEvilMonkey -> String
show :: NoEvilMonkey -> String
$cshowList :: [NoEvilMonkey] -> ShowS
showList :: [NoEvilMonkey] -> ShowS
Show)
instance Hashable NoEvilMonkey
instance NFData NoEvilMonkey
instance Arbitrary NoEvilMonkey where
arbitrary :: Gen NoEvilMonkey
arbitrary = Gen NoEvilMonkey
forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum
instance UnicodeCharacter NoEvilMonkey where
toUnicodeChar :: NoEvilMonkey -> Char
toUnicodeChar = Int -> NoEvilMonkey -> Char
forall a. Enum a => Int -> a -> Char
mapFromEnum Int
_noEvilMonkeyOffset
fromUnicodeChar :: Char -> Maybe NoEvilMonkey
fromUnicodeChar = Int -> Char -> Maybe NoEvilMonkey
forall a. (Bounded a, Enum a) => Int -> Char -> Maybe a
mapToEnumSafe Int
_noEvilMonkeyOffset
fromUnicodeChar' :: Char -> NoEvilMonkey
fromUnicodeChar' = Int -> Char -> NoEvilMonkey
forall a. Enum a => Int -> Char -> a
mapToEnum Int
_noEvilMonkeyOffset
isInCharRange :: Char -> Bool
isInCharRange Char
c = Char
'\x1f648' Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
c Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\x1f64a'
instance UnicodeText NoEvilMonkey where
isInTextRange :: Text -> Bool
isInTextRange = forall a. UnicodeCharacter a => Text -> Bool
generateIsInTextRange' @NoEvilMonkey