module M.TODO
( Slot,
BossBarAction,
CommandNode,
ParticleData,
TextComponent,
MapIcon,
MerchantOffer,
)
where
import Control.DeepSeq
import Data.Data
import Data.Hashable
import GHC.Generics
import Language.Haskell.TH.Syntax (Lift)
import M.Pack
import Text.Printf
newtype ErrorOnPackUnpack a = ErrorOnPackUnpack a
deriving newtype (ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool
(ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool)
-> (ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool)
-> Eq (ErrorOnPackUnpack a)
forall a.
Eq a =>
ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a.
Eq a =>
ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool
== :: ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool
$c/= :: forall a.
Eq a =>
ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool
/= :: ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool
Eq, Eq (ErrorOnPackUnpack a)
Eq (ErrorOnPackUnpack a) =>
(ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Ordering)
-> (ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool)
-> (ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool)
-> (ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool)
-> (ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool)
-> (ErrorOnPackUnpack a
-> ErrorOnPackUnpack a -> ErrorOnPackUnpack a)
-> (ErrorOnPackUnpack a
-> ErrorOnPackUnpack a -> ErrorOnPackUnpack a)
-> Ord (ErrorOnPackUnpack a)
ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool
ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Ordering
ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> ErrorOnPackUnpack a
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
forall a. Ord a => Eq (ErrorOnPackUnpack a)
forall a.
Ord a =>
ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool
forall a.
Ord a =>
ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Ordering
forall a.
Ord a =>
ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> ErrorOnPackUnpack a
$ccompare :: forall a.
Ord a =>
ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Ordering
compare :: ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Ordering
$c< :: forall a.
Ord a =>
ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool
< :: ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool
$c<= :: forall a.
Ord a =>
ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool
<= :: ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool
$c> :: forall a.
Ord a =>
ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool
> :: ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool
$c>= :: forall a.
Ord a =>
ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool
>= :: ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> Bool
$cmax :: forall a.
Ord a =>
ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> ErrorOnPackUnpack a
max :: ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> ErrorOnPackUnpack a
$cmin :: forall a.
Ord a =>
ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> ErrorOnPackUnpack a
min :: ErrorOnPackUnpack a -> ErrorOnPackUnpack a -> ErrorOnPackUnpack a
Ord, Int -> ErrorOnPackUnpack a -> ShowS
[ErrorOnPackUnpack a] -> ShowS
ErrorOnPackUnpack a -> String
(Int -> ErrorOnPackUnpack a -> ShowS)
-> (ErrorOnPackUnpack a -> String)
-> ([ErrorOnPackUnpack a] -> ShowS)
-> Show (ErrorOnPackUnpack a)
forall a. Show a => Int -> ErrorOnPackUnpack a -> ShowS
forall a. Show a => [ErrorOnPackUnpack a] -> ShowS
forall a. Show a => ErrorOnPackUnpack a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> ErrorOnPackUnpack a -> ShowS
showsPrec :: Int -> ErrorOnPackUnpack a -> ShowS
$cshow :: forall a. Show a => ErrorOnPackUnpack a -> String
show :: ErrorOnPackUnpack a -> String
$cshowList :: forall a. Show a => [ErrorOnPackUnpack a] -> ShowS
showList :: [ErrorOnPackUnpack a] -> ShowS
Show, ReadPrec [ErrorOnPackUnpack a]
ReadPrec (ErrorOnPackUnpack a)
Int -> ReadS (ErrorOnPackUnpack a)
ReadS [ErrorOnPackUnpack a]
(Int -> ReadS (ErrorOnPackUnpack a))
-> ReadS [ErrorOnPackUnpack a]
-> ReadPrec (ErrorOnPackUnpack a)
-> ReadPrec [ErrorOnPackUnpack a]
-> Read (ErrorOnPackUnpack a)
forall a. Read a => ReadPrec [ErrorOnPackUnpack a]
forall a. Read a => ReadPrec (ErrorOnPackUnpack a)
forall a. Read a => Int -> ReadS (ErrorOnPackUnpack a)
forall a. Read a => ReadS [ErrorOnPackUnpack a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall a. Read a => Int -> ReadS (ErrorOnPackUnpack a)
readsPrec :: Int -> ReadS (ErrorOnPackUnpack a)
$creadList :: forall a. Read a => ReadS [ErrorOnPackUnpack a]
readList :: ReadS [ErrorOnPackUnpack a]
$creadPrec :: forall a. Read a => ReadPrec (ErrorOnPackUnpack a)
readPrec :: ReadPrec (ErrorOnPackUnpack a)
$creadListPrec :: forall a. Read a => ReadPrec [ErrorOnPackUnpack a]
readListPrec :: ReadPrec [ErrorOnPackUnpack a]
Read)
deriving stock ((forall x. ErrorOnPackUnpack a -> Rep (ErrorOnPackUnpack a) x)
-> (forall x. Rep (ErrorOnPackUnpack a) x -> ErrorOnPackUnpack a)
-> Generic (ErrorOnPackUnpack a)
forall x. Rep (ErrorOnPackUnpack a) x -> ErrorOnPackUnpack a
forall x. ErrorOnPackUnpack a -> Rep (ErrorOnPackUnpack a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (ErrorOnPackUnpack a) x -> ErrorOnPackUnpack a
forall a x. ErrorOnPackUnpack a -> Rep (ErrorOnPackUnpack a) x
$cfrom :: forall a x. ErrorOnPackUnpack a -> Rep (ErrorOnPackUnpack a) x
from :: forall x. ErrorOnPackUnpack a -> Rep (ErrorOnPackUnpack a) x
$cto :: forall a x. Rep (ErrorOnPackUnpack a) x -> ErrorOnPackUnpack a
to :: forall x. Rep (ErrorOnPackUnpack a) x -> ErrorOnPackUnpack a
Generic, Typeable, Typeable (ErrorOnPackUnpack a)
Typeable (ErrorOnPackUnpack a) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ErrorOnPackUnpack a
-> c (ErrorOnPackUnpack a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ErrorOnPackUnpack a))
-> (ErrorOnPackUnpack a -> Constr)
-> (ErrorOnPackUnpack a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (ErrorOnPackUnpack a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ErrorOnPackUnpack a)))
-> ((forall b. Data b => b -> b)
-> ErrorOnPackUnpack a -> ErrorOnPackUnpack a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorOnPackUnpack a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorOnPackUnpack a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ErrorOnPackUnpack a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ErrorOnPackUnpack a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ErrorOnPackUnpack a -> m (ErrorOnPackUnpack a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ErrorOnPackUnpack a -> m (ErrorOnPackUnpack a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ErrorOnPackUnpack a -> m (ErrorOnPackUnpack a))
-> Data (ErrorOnPackUnpack a)
ErrorOnPackUnpack a -> Constr
ErrorOnPackUnpack a -> DataType
(forall b. Data b => b -> b)
-> ErrorOnPackUnpack a -> ErrorOnPackUnpack a
forall a. Data a => Typeable (ErrorOnPackUnpack a)
forall a. Data a => ErrorOnPackUnpack a -> Constr
forall a. Data a => ErrorOnPackUnpack a -> DataType
forall a.
Data a =>
(forall b. Data b => b -> b)
-> ErrorOnPackUnpack a -> ErrorOnPackUnpack a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> ErrorOnPackUnpack a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> ErrorOnPackUnpack a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorOnPackUnpack a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorOnPackUnpack a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> ErrorOnPackUnpack a -> m (ErrorOnPackUnpack a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> ErrorOnPackUnpack a -> m (ErrorOnPackUnpack a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ErrorOnPackUnpack a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ErrorOnPackUnpack a
-> c (ErrorOnPackUnpack a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (ErrorOnPackUnpack a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ErrorOnPackUnpack a))
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) -> ErrorOnPackUnpack a -> u
forall u.
(forall d. Data d => d -> u) -> ErrorOnPackUnpack a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorOnPackUnpack a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorOnPackUnpack a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ErrorOnPackUnpack a -> m (ErrorOnPackUnpack a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ErrorOnPackUnpack a -> m (ErrorOnPackUnpack a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ErrorOnPackUnpack a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ErrorOnPackUnpack a
-> c (ErrorOnPackUnpack a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (ErrorOnPackUnpack a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ErrorOnPackUnpack a))
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ErrorOnPackUnpack a
-> c (ErrorOnPackUnpack a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ErrorOnPackUnpack a
-> c (ErrorOnPackUnpack a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ErrorOnPackUnpack a)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ErrorOnPackUnpack a)
$ctoConstr :: forall a. Data a => ErrorOnPackUnpack a -> Constr
toConstr :: ErrorOnPackUnpack a -> Constr
$cdataTypeOf :: forall a. Data a => ErrorOnPackUnpack a -> DataType
dataTypeOf :: ErrorOnPackUnpack a -> DataType
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (ErrorOnPackUnpack a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (ErrorOnPackUnpack a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ErrorOnPackUnpack a))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ErrorOnPackUnpack a))
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> ErrorOnPackUnpack a -> ErrorOnPackUnpack a
gmapT :: (forall b. Data b => b -> b)
-> ErrorOnPackUnpack a -> ErrorOnPackUnpack a
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorOnPackUnpack a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorOnPackUnpack a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorOnPackUnpack a -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ErrorOnPackUnpack a -> r
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> ErrorOnPackUnpack a -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> ErrorOnPackUnpack a -> [u]
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> ErrorOnPackUnpack a -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ErrorOnPackUnpack a -> u
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> ErrorOnPackUnpack a -> m (ErrorOnPackUnpack a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ErrorOnPackUnpack a -> m (ErrorOnPackUnpack a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> ErrorOnPackUnpack a -> m (ErrorOnPackUnpack a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ErrorOnPackUnpack a -> m (ErrorOnPackUnpack a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> ErrorOnPackUnpack a -> m (ErrorOnPackUnpack a)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ErrorOnPackUnpack a -> m (ErrorOnPackUnpack a)
Data, (forall (m :: * -> *). Quote m => ErrorOnPackUnpack a -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
ErrorOnPackUnpack a -> Code m (ErrorOnPackUnpack a))
-> Lift (ErrorOnPackUnpack a)
forall a (m :: * -> *).
(Lift a, Quote m) =>
ErrorOnPackUnpack a -> m Exp
forall a (m :: * -> *).
(Lift a, Quote m) =>
ErrorOnPackUnpack a -> Code m (ErrorOnPackUnpack a)
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => ErrorOnPackUnpack a -> m Exp
forall (m :: * -> *).
Quote m =>
ErrorOnPackUnpack a -> Code m (ErrorOnPackUnpack a)
$clift :: forall a (m :: * -> *).
(Lift a, Quote m) =>
ErrorOnPackUnpack a -> m Exp
lift :: forall (m :: * -> *). Quote m => ErrorOnPackUnpack a -> m Exp
$cliftTyped :: forall a (m :: * -> *).
(Lift a, Quote m) =>
ErrorOnPackUnpack a -> Code m (ErrorOnPackUnpack a)
liftTyped :: forall (m :: * -> *).
Quote m =>
ErrorOnPackUnpack a -> Code m (ErrorOnPackUnpack a)
Lift)
deriving anyclass (ErrorOnPackUnpack a -> ()
(ErrorOnPackUnpack a -> ()) -> NFData (ErrorOnPackUnpack a)
forall a. NFData a => ErrorOnPackUnpack a -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall a. NFData a => ErrorOnPackUnpack a -> ()
rnf :: ErrorOnPackUnpack a -> ()
NFData, Eq (ErrorOnPackUnpack a)
Eq (ErrorOnPackUnpack a) =>
(Int -> ErrorOnPackUnpack a -> Int)
-> (ErrorOnPackUnpack a -> Int) -> Hashable (ErrorOnPackUnpack a)
Int -> ErrorOnPackUnpack a -> Int
ErrorOnPackUnpack a -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
forall a. Hashable a => Eq (ErrorOnPackUnpack a)
forall a. Hashable a => Int -> ErrorOnPackUnpack a -> Int
forall a. Hashable a => ErrorOnPackUnpack a -> Int
$chashWithSalt :: forall a. Hashable a => Int -> ErrorOnPackUnpack a -> Int
hashWithSalt :: Int -> ErrorOnPackUnpack a -> Int
$chash :: forall a. Hashable a => ErrorOnPackUnpack a -> Int
hash :: ErrorOnPackUnpack a -> Int
Hashable)
instance (Typeable a) => Pack (ErrorOnPackUnpack a) where
pack :: ErrorOnPackUnpack a -> Builder
pack ErrorOnPackUnpack a
_ =
String -> Builder
forall a. HasCallStack => String -> a
error (String -> Builder) -> String -> Builder
forall a b. (a -> b) -> a -> b
$
String -> ShowS
forall r. PrintfType r => String -> r
printf
String
"pack: not implemented for type %s"
(TypeRep -> String
forall a. Show a => a -> String
show (TypeRep -> String) -> TypeRep -> String
forall a b. (a -> b) -> a -> b
$ Proxy a -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a))
{-# INLINE pack #-}
instance (Typeable a) => Unpack (ErrorOnPackUnpack a) where
unpack :: forall (st :: ZeroBitType) r. Parser st r (ErrorOnPackUnpack a)
unpack =
String -> Parser st r (ErrorOnPackUnpack a)
forall a. HasCallStack => String -> a
error (String -> Parser st r (ErrorOnPackUnpack a))
-> String -> Parser st r (ErrorOnPackUnpack a)
forall a b. (a -> b) -> a -> b
$
String -> ShowS
forall r. PrintfType r => String -> r
printf
String
"unpack: not implemented for type %s"
(TypeRep -> String
forall a. Show a => a -> String
show (TypeRep -> String) -> TypeRep -> String
forall a b. (a -> b) -> a -> b
$ Proxy a -> TypeRep
forall {k} (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @a))
{-# INLINE unpack #-}
data BossBarAction
deriving stock (BossBarAction -> BossBarAction -> Bool
(BossBarAction -> BossBarAction -> Bool)
-> (BossBarAction -> BossBarAction -> Bool) -> Eq BossBarAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BossBarAction -> BossBarAction -> Bool
== :: BossBarAction -> BossBarAction -> Bool
$c/= :: BossBarAction -> BossBarAction -> Bool
/= :: BossBarAction -> BossBarAction -> Bool
Eq, Eq BossBarAction
Eq BossBarAction =>
(BossBarAction -> BossBarAction -> Ordering)
-> (BossBarAction -> BossBarAction -> Bool)
-> (BossBarAction -> BossBarAction -> Bool)
-> (BossBarAction -> BossBarAction -> Bool)
-> (BossBarAction -> BossBarAction -> Bool)
-> (BossBarAction -> BossBarAction -> BossBarAction)
-> (BossBarAction -> BossBarAction -> BossBarAction)
-> Ord BossBarAction
BossBarAction -> BossBarAction -> Bool
BossBarAction -> BossBarAction -> Ordering
BossBarAction -> BossBarAction -> BossBarAction
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 :: BossBarAction -> BossBarAction -> Ordering
compare :: BossBarAction -> BossBarAction -> Ordering
$c< :: BossBarAction -> BossBarAction -> Bool
< :: BossBarAction -> BossBarAction -> Bool
$c<= :: BossBarAction -> BossBarAction -> Bool
<= :: BossBarAction -> BossBarAction -> Bool
$c> :: BossBarAction -> BossBarAction -> Bool
> :: BossBarAction -> BossBarAction -> Bool
$c>= :: BossBarAction -> BossBarAction -> Bool
>= :: BossBarAction -> BossBarAction -> Bool
$cmax :: BossBarAction -> BossBarAction -> BossBarAction
max :: BossBarAction -> BossBarAction -> BossBarAction
$cmin :: BossBarAction -> BossBarAction -> BossBarAction
min :: BossBarAction -> BossBarAction -> BossBarAction
Ord, Int -> BossBarAction -> ShowS
[BossBarAction] -> ShowS
BossBarAction -> String
(Int -> BossBarAction -> ShowS)
-> (BossBarAction -> String)
-> ([BossBarAction] -> ShowS)
-> Show BossBarAction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BossBarAction -> ShowS
showsPrec :: Int -> BossBarAction -> ShowS
$cshow :: BossBarAction -> String
show :: BossBarAction -> String
$cshowList :: [BossBarAction] -> ShowS
showList :: [BossBarAction] -> ShowS
Show, ReadPrec [BossBarAction]
ReadPrec BossBarAction
Int -> ReadS BossBarAction
ReadS [BossBarAction]
(Int -> ReadS BossBarAction)
-> ReadS [BossBarAction]
-> ReadPrec BossBarAction
-> ReadPrec [BossBarAction]
-> Read BossBarAction
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BossBarAction
readsPrec :: Int -> ReadS BossBarAction
$creadList :: ReadS [BossBarAction]
readList :: ReadS [BossBarAction]
$creadPrec :: ReadPrec BossBarAction
readPrec :: ReadPrec BossBarAction
$creadListPrec :: ReadPrec [BossBarAction]
readListPrec :: ReadPrec [BossBarAction]
Read, (forall x. BossBarAction -> Rep BossBarAction x)
-> (forall x. Rep BossBarAction x -> BossBarAction)
-> Generic BossBarAction
forall x. Rep BossBarAction x -> BossBarAction
forall x. BossBarAction -> Rep BossBarAction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BossBarAction -> Rep BossBarAction x
from :: forall x. BossBarAction -> Rep BossBarAction x
$cto :: forall x. Rep BossBarAction x -> BossBarAction
to :: forall x. Rep BossBarAction x -> BossBarAction
Generic, Typeable, Typeable BossBarAction
Typeable BossBarAction =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BossBarAction -> c BossBarAction)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BossBarAction)
-> (BossBarAction -> Constr)
-> (BossBarAction -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BossBarAction))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c BossBarAction))
-> ((forall b. Data b => b -> b) -> BossBarAction -> BossBarAction)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BossBarAction -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BossBarAction -> r)
-> (forall u. (forall d. Data d => d -> u) -> BossBarAction -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> BossBarAction -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BossBarAction -> m BossBarAction)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BossBarAction -> m BossBarAction)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BossBarAction -> m BossBarAction)
-> Data BossBarAction
BossBarAction -> Constr
BossBarAction -> DataType
(forall b. Data b => b -> b) -> BossBarAction -> BossBarAction
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) -> BossBarAction -> u
forall u. (forall d. Data d => d -> u) -> BossBarAction -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BossBarAction -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BossBarAction -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BossBarAction -> m BossBarAction
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BossBarAction -> m BossBarAction
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BossBarAction
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BossBarAction -> c BossBarAction
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BossBarAction)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c BossBarAction)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BossBarAction -> c BossBarAction
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BossBarAction -> c BossBarAction
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BossBarAction
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BossBarAction
$ctoConstr :: BossBarAction -> Constr
toConstr :: BossBarAction -> Constr
$cdataTypeOf :: BossBarAction -> DataType
dataTypeOf :: BossBarAction -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BossBarAction)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BossBarAction)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c BossBarAction)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c BossBarAction)
$cgmapT :: (forall b. Data b => b -> b) -> BossBarAction -> BossBarAction
gmapT :: (forall b. Data b => b -> b) -> BossBarAction -> BossBarAction
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BossBarAction -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BossBarAction -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BossBarAction -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BossBarAction -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> BossBarAction -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> BossBarAction -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> BossBarAction -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> BossBarAction -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BossBarAction -> m BossBarAction
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BossBarAction -> m BossBarAction
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BossBarAction -> m BossBarAction
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BossBarAction -> m BossBarAction
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BossBarAction -> m BossBarAction
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BossBarAction -> m BossBarAction
Data)
deriving anyclass (BossBarAction -> ()
(BossBarAction -> ()) -> NFData BossBarAction
forall a. (a -> ()) -> NFData a
$crnf :: BossBarAction -> ()
rnf :: BossBarAction -> ()
NFData, Eq BossBarAction
Eq BossBarAction =>
(Int -> BossBarAction -> Int)
-> (BossBarAction -> Int) -> Hashable BossBarAction
Int -> BossBarAction -> Int
BossBarAction -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> BossBarAction -> Int
hashWithSalt :: Int -> BossBarAction -> Int
$chash :: BossBarAction -> Int
hash :: BossBarAction -> Int
Hashable)
deriving (BossBarAction -> Builder
(BossBarAction -> Builder) -> Pack BossBarAction
forall a. (a -> Builder) -> Pack a
$cpack :: BossBarAction -> Builder
pack :: BossBarAction -> Builder
Pack, (forall (st :: ZeroBitType) r. Parser st r BossBarAction)
-> Unpack BossBarAction
forall (st :: ZeroBitType) r. Parser st r BossBarAction
forall a. (forall (st :: ZeroBitType) r. Parser st r a) -> Unpack a
$cunpack :: forall (st :: ZeroBitType) r. Parser st r BossBarAction
unpack :: forall (st :: ZeroBitType) r. Parser st r BossBarAction
Unpack) via ErrorOnPackUnpack BossBarAction
data CommandNode
deriving stock (CommandNode -> CommandNode -> Bool
(CommandNode -> CommandNode -> Bool)
-> (CommandNode -> CommandNode -> Bool) -> Eq CommandNode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CommandNode -> CommandNode -> Bool
== :: CommandNode -> CommandNode -> Bool
$c/= :: CommandNode -> CommandNode -> Bool
/= :: CommandNode -> CommandNode -> Bool
Eq, Eq CommandNode
Eq CommandNode =>
(CommandNode -> CommandNode -> Ordering)
-> (CommandNode -> CommandNode -> Bool)
-> (CommandNode -> CommandNode -> Bool)
-> (CommandNode -> CommandNode -> Bool)
-> (CommandNode -> CommandNode -> Bool)
-> (CommandNode -> CommandNode -> CommandNode)
-> (CommandNode -> CommandNode -> CommandNode)
-> Ord CommandNode
CommandNode -> CommandNode -> Bool
CommandNode -> CommandNode -> Ordering
CommandNode -> CommandNode -> CommandNode
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 :: CommandNode -> CommandNode -> Ordering
compare :: CommandNode -> CommandNode -> Ordering
$c< :: CommandNode -> CommandNode -> Bool
< :: CommandNode -> CommandNode -> Bool
$c<= :: CommandNode -> CommandNode -> Bool
<= :: CommandNode -> CommandNode -> Bool
$c> :: CommandNode -> CommandNode -> Bool
> :: CommandNode -> CommandNode -> Bool
$c>= :: CommandNode -> CommandNode -> Bool
>= :: CommandNode -> CommandNode -> Bool
$cmax :: CommandNode -> CommandNode -> CommandNode
max :: CommandNode -> CommandNode -> CommandNode
$cmin :: CommandNode -> CommandNode -> CommandNode
min :: CommandNode -> CommandNode -> CommandNode
Ord, Int -> CommandNode -> ShowS
[CommandNode] -> ShowS
CommandNode -> String
(Int -> CommandNode -> ShowS)
-> (CommandNode -> String)
-> ([CommandNode] -> ShowS)
-> Show CommandNode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CommandNode -> ShowS
showsPrec :: Int -> CommandNode -> ShowS
$cshow :: CommandNode -> String
show :: CommandNode -> String
$cshowList :: [CommandNode] -> ShowS
showList :: [CommandNode] -> ShowS
Show, ReadPrec [CommandNode]
ReadPrec CommandNode
Int -> ReadS CommandNode
ReadS [CommandNode]
(Int -> ReadS CommandNode)
-> ReadS [CommandNode]
-> ReadPrec CommandNode
-> ReadPrec [CommandNode]
-> Read CommandNode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CommandNode
readsPrec :: Int -> ReadS CommandNode
$creadList :: ReadS [CommandNode]
readList :: ReadS [CommandNode]
$creadPrec :: ReadPrec CommandNode
readPrec :: ReadPrec CommandNode
$creadListPrec :: ReadPrec [CommandNode]
readListPrec :: ReadPrec [CommandNode]
Read, (forall x. CommandNode -> Rep CommandNode x)
-> (forall x. Rep CommandNode x -> CommandNode)
-> Generic CommandNode
forall x. Rep CommandNode x -> CommandNode
forall x. CommandNode -> Rep CommandNode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CommandNode -> Rep CommandNode x
from :: forall x. CommandNode -> Rep CommandNode x
$cto :: forall x. Rep CommandNode x -> CommandNode
to :: forall x. Rep CommandNode x -> CommandNode
Generic, Typeable, Typeable CommandNode
Typeable CommandNode =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CommandNode -> c CommandNode)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CommandNode)
-> (CommandNode -> Constr)
-> (CommandNode -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CommandNode))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CommandNode))
-> ((forall b. Data b => b -> b) -> CommandNode -> CommandNode)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CommandNode -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CommandNode -> r)
-> (forall u. (forall d. Data d => d -> u) -> CommandNode -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> CommandNode -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CommandNode -> m CommandNode)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CommandNode -> m CommandNode)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CommandNode -> m CommandNode)
-> Data CommandNode
CommandNode -> Constr
CommandNode -> DataType
(forall b. Data b => b -> b) -> CommandNode -> CommandNode
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) -> CommandNode -> u
forall u. (forall d. Data d => d -> u) -> CommandNode -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CommandNode -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CommandNode -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CommandNode -> m CommandNode
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CommandNode -> m CommandNode
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CommandNode
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CommandNode -> c CommandNode
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CommandNode)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CommandNode)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CommandNode -> c CommandNode
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CommandNode -> c CommandNode
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CommandNode
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CommandNode
$ctoConstr :: CommandNode -> Constr
toConstr :: CommandNode -> Constr
$cdataTypeOf :: CommandNode -> DataType
dataTypeOf :: CommandNode -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CommandNode)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CommandNode)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CommandNode)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CommandNode)
$cgmapT :: (forall b. Data b => b -> b) -> CommandNode -> CommandNode
gmapT :: (forall b. Data b => b -> b) -> CommandNode -> CommandNode
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CommandNode -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CommandNode -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CommandNode -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CommandNode -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> CommandNode -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> CommandNode -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CommandNode -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CommandNode -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CommandNode -> m CommandNode
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CommandNode -> m CommandNode
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CommandNode -> m CommandNode
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CommandNode -> m CommandNode
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CommandNode -> m CommandNode
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CommandNode -> m CommandNode
Data)
deriving anyclass (CommandNode -> ()
(CommandNode -> ()) -> NFData CommandNode
forall a. (a -> ()) -> NFData a
$crnf :: CommandNode -> ()
rnf :: CommandNode -> ()
NFData, Eq CommandNode
Eq CommandNode =>
(Int -> CommandNode -> Int)
-> (CommandNode -> Int) -> Hashable CommandNode
Int -> CommandNode -> Int
CommandNode -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> CommandNode -> Int
hashWithSalt :: Int -> CommandNode -> Int
$chash :: CommandNode -> Int
hash :: CommandNode -> Int
Hashable)
deriving (CommandNode -> Builder
(CommandNode -> Builder) -> Pack CommandNode
forall a. (a -> Builder) -> Pack a
$cpack :: CommandNode -> Builder
pack :: CommandNode -> Builder
Pack, (forall (st :: ZeroBitType) r. Parser st r CommandNode)
-> Unpack CommandNode
forall (st :: ZeroBitType) r. Parser st r CommandNode
forall a. (forall (st :: ZeroBitType) r. Parser st r a) -> Unpack a
$cunpack :: forall (st :: ZeroBitType) r. Parser st r CommandNode
unpack :: forall (st :: ZeroBitType) r. Parser st r CommandNode
Unpack) via ErrorOnPackUnpack CommandNode
data Slot
deriving stock (Slot -> Slot -> Bool
(Slot -> Slot -> Bool) -> (Slot -> Slot -> Bool) -> Eq Slot
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Slot -> Slot -> Bool
== :: Slot -> Slot -> Bool
$c/= :: Slot -> Slot -> Bool
/= :: Slot -> Slot -> Bool
Eq, Eq Slot
Eq Slot =>
(Slot -> Slot -> Ordering)
-> (Slot -> Slot -> Bool)
-> (Slot -> Slot -> Bool)
-> (Slot -> Slot -> Bool)
-> (Slot -> Slot -> Bool)
-> (Slot -> Slot -> Slot)
-> (Slot -> Slot -> Slot)
-> Ord Slot
Slot -> Slot -> Bool
Slot -> Slot -> Ordering
Slot -> Slot -> Slot
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 :: Slot -> Slot -> Ordering
compare :: Slot -> Slot -> Ordering
$c< :: Slot -> Slot -> Bool
< :: Slot -> Slot -> Bool
$c<= :: Slot -> Slot -> Bool
<= :: Slot -> Slot -> Bool
$c> :: Slot -> Slot -> Bool
> :: Slot -> Slot -> Bool
$c>= :: Slot -> Slot -> Bool
>= :: Slot -> Slot -> Bool
$cmax :: Slot -> Slot -> Slot
max :: Slot -> Slot -> Slot
$cmin :: Slot -> Slot -> Slot
min :: Slot -> Slot -> Slot
Ord, Int -> Slot -> ShowS
[Slot] -> ShowS
Slot -> String
(Int -> Slot -> ShowS)
-> (Slot -> String) -> ([Slot] -> ShowS) -> Show Slot
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Slot -> ShowS
showsPrec :: Int -> Slot -> ShowS
$cshow :: Slot -> String
show :: Slot -> String
$cshowList :: [Slot] -> ShowS
showList :: [Slot] -> ShowS
Show, ReadPrec [Slot]
ReadPrec Slot
Int -> ReadS Slot
ReadS [Slot]
(Int -> ReadS Slot)
-> ReadS [Slot] -> ReadPrec Slot -> ReadPrec [Slot] -> Read Slot
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Slot
readsPrec :: Int -> ReadS Slot
$creadList :: ReadS [Slot]
readList :: ReadS [Slot]
$creadPrec :: ReadPrec Slot
readPrec :: ReadPrec Slot
$creadListPrec :: ReadPrec [Slot]
readListPrec :: ReadPrec [Slot]
Read, (forall x. Slot -> Rep Slot x)
-> (forall x. Rep Slot x -> Slot) -> Generic Slot
forall x. Rep Slot x -> Slot
forall x. Slot -> Rep Slot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Slot -> Rep Slot x
from :: forall x. Slot -> Rep Slot x
$cto :: forall x. Rep Slot x -> Slot
to :: forall x. Rep Slot x -> Slot
Generic, Typeable, Typeable Slot
Typeable Slot =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Slot -> c Slot)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Slot)
-> (Slot -> Constr)
-> (Slot -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Slot))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Slot))
-> ((forall b. Data b => b -> b) -> Slot -> Slot)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r)
-> (forall u. (forall d. Data d => d -> u) -> Slot -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Slot -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot)
-> Data Slot
Slot -> Constr
Slot -> DataType
(forall b. Data b => b -> b) -> Slot -> Slot
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) -> Slot -> u
forall u. (forall d. Data d => d -> u) -> Slot -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Slot
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Slot -> c Slot
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Slot)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Slot)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Slot -> c Slot
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Slot -> c Slot
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Slot
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Slot
$ctoConstr :: Slot -> Constr
toConstr :: Slot -> Constr
$cdataTypeOf :: Slot -> DataType
dataTypeOf :: Slot -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Slot)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Slot)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Slot)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Slot)
$cgmapT :: (forall b. Data b => b -> b) -> Slot -> Slot
gmapT :: (forall b. Data b => b -> b) -> Slot -> Slot
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Slot -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Slot -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Slot -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Slot -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Slot -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Slot -> m Slot
Data)
deriving anyclass (Slot -> ()
(Slot -> ()) -> NFData Slot
forall a. (a -> ()) -> NFData a
$crnf :: Slot -> ()
rnf :: Slot -> ()
NFData, Eq Slot
Eq Slot => (Int -> Slot -> Int) -> (Slot -> Int) -> Hashable Slot
Int -> Slot -> Int
Slot -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Slot -> Int
hashWithSalt :: Int -> Slot -> Int
$chash :: Slot -> Int
hash :: Slot -> Int
Hashable)
deriving (Slot -> Builder
(Slot -> Builder) -> Pack Slot
forall a. (a -> Builder) -> Pack a
$cpack :: Slot -> Builder
pack :: Slot -> Builder
Pack, (forall (st :: ZeroBitType) r. Parser st r Slot) -> Unpack Slot
forall (st :: ZeroBitType) r. Parser st r Slot
forall a. (forall (st :: ZeroBitType) r. Parser st r a) -> Unpack a
$cunpack :: forall (st :: ZeroBitType) r. Parser st r Slot
unpack :: forall (st :: ZeroBitType) r. Parser st r Slot
Unpack) via ErrorOnPackUnpack Slot
data ParticleData
deriving stock (ParticleData -> ParticleData -> Bool
(ParticleData -> ParticleData -> Bool)
-> (ParticleData -> ParticleData -> Bool) -> Eq ParticleData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ParticleData -> ParticleData -> Bool
== :: ParticleData -> ParticleData -> Bool
$c/= :: ParticleData -> ParticleData -> Bool
/= :: ParticleData -> ParticleData -> Bool
Eq, Eq ParticleData
Eq ParticleData =>
(ParticleData -> ParticleData -> Ordering)
-> (ParticleData -> ParticleData -> Bool)
-> (ParticleData -> ParticleData -> Bool)
-> (ParticleData -> ParticleData -> Bool)
-> (ParticleData -> ParticleData -> Bool)
-> (ParticleData -> ParticleData -> ParticleData)
-> (ParticleData -> ParticleData -> ParticleData)
-> Ord ParticleData
ParticleData -> ParticleData -> Bool
ParticleData -> ParticleData -> Ordering
ParticleData -> ParticleData -> ParticleData
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 :: ParticleData -> ParticleData -> Ordering
compare :: ParticleData -> ParticleData -> Ordering
$c< :: ParticleData -> ParticleData -> Bool
< :: ParticleData -> ParticleData -> Bool
$c<= :: ParticleData -> ParticleData -> Bool
<= :: ParticleData -> ParticleData -> Bool
$c> :: ParticleData -> ParticleData -> Bool
> :: ParticleData -> ParticleData -> Bool
$c>= :: ParticleData -> ParticleData -> Bool
>= :: ParticleData -> ParticleData -> Bool
$cmax :: ParticleData -> ParticleData -> ParticleData
max :: ParticleData -> ParticleData -> ParticleData
$cmin :: ParticleData -> ParticleData -> ParticleData
min :: ParticleData -> ParticleData -> ParticleData
Ord, Int -> ParticleData -> ShowS
[ParticleData] -> ShowS
ParticleData -> String
(Int -> ParticleData -> ShowS)
-> (ParticleData -> String)
-> ([ParticleData] -> ShowS)
-> Show ParticleData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ParticleData -> ShowS
showsPrec :: Int -> ParticleData -> ShowS
$cshow :: ParticleData -> String
show :: ParticleData -> String
$cshowList :: [ParticleData] -> ShowS
showList :: [ParticleData] -> ShowS
Show, ReadPrec [ParticleData]
ReadPrec ParticleData
Int -> ReadS ParticleData
ReadS [ParticleData]
(Int -> ReadS ParticleData)
-> ReadS [ParticleData]
-> ReadPrec ParticleData
-> ReadPrec [ParticleData]
-> Read ParticleData
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ParticleData
readsPrec :: Int -> ReadS ParticleData
$creadList :: ReadS [ParticleData]
readList :: ReadS [ParticleData]
$creadPrec :: ReadPrec ParticleData
readPrec :: ReadPrec ParticleData
$creadListPrec :: ReadPrec [ParticleData]
readListPrec :: ReadPrec [ParticleData]
Read, (forall x. ParticleData -> Rep ParticleData x)
-> (forall x. Rep ParticleData x -> ParticleData)
-> Generic ParticleData
forall x. Rep ParticleData x -> ParticleData
forall x. ParticleData -> Rep ParticleData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ParticleData -> Rep ParticleData x
from :: forall x. ParticleData -> Rep ParticleData x
$cto :: forall x. Rep ParticleData x -> ParticleData
to :: forall x. Rep ParticleData x -> ParticleData
Generic, Typeable, Typeable ParticleData
Typeable ParticleData =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParticleData -> c ParticleData)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParticleData)
-> (ParticleData -> Constr)
-> (ParticleData -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParticleData))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParticleData))
-> ((forall b. Data b => b -> b) -> ParticleData -> ParticleData)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParticleData -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParticleData -> r)
-> (forall u. (forall d. Data d => d -> u) -> ParticleData -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ParticleData -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ParticleData -> m ParticleData)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParticleData -> m ParticleData)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParticleData -> m ParticleData)
-> Data ParticleData
ParticleData -> Constr
ParticleData -> DataType
(forall b. Data b => b -> b) -> ParticleData -> ParticleData
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) -> ParticleData -> u
forall u. (forall d. Data d => d -> u) -> ParticleData -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParticleData -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParticleData -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ParticleData -> m ParticleData
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParticleData -> m ParticleData
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParticleData
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParticleData -> c ParticleData
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParticleData)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParticleData)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParticleData -> c ParticleData
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ParticleData -> c ParticleData
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParticleData
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ParticleData
$ctoConstr :: ParticleData -> Constr
toConstr :: ParticleData -> Constr
$cdataTypeOf :: ParticleData -> DataType
dataTypeOf :: ParticleData -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParticleData)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ParticleData)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParticleData)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ParticleData)
$cgmapT :: (forall b. Data b => b -> b) -> ParticleData -> ParticleData
gmapT :: (forall b. Data b => b -> b) -> ParticleData -> ParticleData
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParticleData -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ParticleData -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParticleData -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ParticleData -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ParticleData -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ParticleData -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ParticleData -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ParticleData -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ParticleData -> m ParticleData
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ParticleData -> m ParticleData
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParticleData -> m ParticleData
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParticleData -> m ParticleData
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParticleData -> m ParticleData
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ParticleData -> m ParticleData
Data)
deriving anyclass (ParticleData -> ()
(ParticleData -> ()) -> NFData ParticleData
forall a. (a -> ()) -> NFData a
$crnf :: ParticleData -> ()
rnf :: ParticleData -> ()
NFData, Eq ParticleData
Eq ParticleData =>
(Int -> ParticleData -> Int)
-> (ParticleData -> Int) -> Hashable ParticleData
Int -> ParticleData -> Int
ParticleData -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> ParticleData -> Int
hashWithSalt :: Int -> ParticleData -> Int
$chash :: ParticleData -> Int
hash :: ParticleData -> Int
Hashable)
deriving (ParticleData -> Builder
(ParticleData -> Builder) -> Pack ParticleData
forall a. (a -> Builder) -> Pack a
$cpack :: ParticleData -> Builder
pack :: ParticleData -> Builder
Pack, (forall (st :: ZeroBitType) r. Parser st r ParticleData)
-> Unpack ParticleData
forall (st :: ZeroBitType) r. Parser st r ParticleData
forall a. (forall (st :: ZeroBitType) r. Parser st r a) -> Unpack a
$cunpack :: forall (st :: ZeroBitType) r. Parser st r ParticleData
unpack :: forall (st :: ZeroBitType) r. Parser st r ParticleData
Unpack) via ErrorOnPackUnpack ParticleData
data TextComponent
deriving stock (TextComponent -> TextComponent -> Bool
(TextComponent -> TextComponent -> Bool)
-> (TextComponent -> TextComponent -> Bool) -> Eq TextComponent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TextComponent -> TextComponent -> Bool
== :: TextComponent -> TextComponent -> Bool
$c/= :: TextComponent -> TextComponent -> Bool
/= :: TextComponent -> TextComponent -> Bool
Eq, Eq TextComponent
Eq TextComponent =>
(TextComponent -> TextComponent -> Ordering)
-> (TextComponent -> TextComponent -> Bool)
-> (TextComponent -> TextComponent -> Bool)
-> (TextComponent -> TextComponent -> Bool)
-> (TextComponent -> TextComponent -> Bool)
-> (TextComponent -> TextComponent -> TextComponent)
-> (TextComponent -> TextComponent -> TextComponent)
-> Ord TextComponent
TextComponent -> TextComponent -> Bool
TextComponent -> TextComponent -> Ordering
TextComponent -> TextComponent -> TextComponent
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 :: TextComponent -> TextComponent -> Ordering
compare :: TextComponent -> TextComponent -> Ordering
$c< :: TextComponent -> TextComponent -> Bool
< :: TextComponent -> TextComponent -> Bool
$c<= :: TextComponent -> TextComponent -> Bool
<= :: TextComponent -> TextComponent -> Bool
$c> :: TextComponent -> TextComponent -> Bool
> :: TextComponent -> TextComponent -> Bool
$c>= :: TextComponent -> TextComponent -> Bool
>= :: TextComponent -> TextComponent -> Bool
$cmax :: TextComponent -> TextComponent -> TextComponent
max :: TextComponent -> TextComponent -> TextComponent
$cmin :: TextComponent -> TextComponent -> TextComponent
min :: TextComponent -> TextComponent -> TextComponent
Ord, Int -> TextComponent -> ShowS
[TextComponent] -> ShowS
TextComponent -> String
(Int -> TextComponent -> ShowS)
-> (TextComponent -> String)
-> ([TextComponent] -> ShowS)
-> Show TextComponent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TextComponent -> ShowS
showsPrec :: Int -> TextComponent -> ShowS
$cshow :: TextComponent -> String
show :: TextComponent -> String
$cshowList :: [TextComponent] -> ShowS
showList :: [TextComponent] -> ShowS
Show, ReadPrec [TextComponent]
ReadPrec TextComponent
Int -> ReadS TextComponent
ReadS [TextComponent]
(Int -> ReadS TextComponent)
-> ReadS [TextComponent]
-> ReadPrec TextComponent
-> ReadPrec [TextComponent]
-> Read TextComponent
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TextComponent
readsPrec :: Int -> ReadS TextComponent
$creadList :: ReadS [TextComponent]
readList :: ReadS [TextComponent]
$creadPrec :: ReadPrec TextComponent
readPrec :: ReadPrec TextComponent
$creadListPrec :: ReadPrec [TextComponent]
readListPrec :: ReadPrec [TextComponent]
Read, (forall x. TextComponent -> Rep TextComponent x)
-> (forall x. Rep TextComponent x -> TextComponent)
-> Generic TextComponent
forall x. Rep TextComponent x -> TextComponent
forall x. TextComponent -> Rep TextComponent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TextComponent -> Rep TextComponent x
from :: forall x. TextComponent -> Rep TextComponent x
$cto :: forall x. Rep TextComponent x -> TextComponent
to :: forall x. Rep TextComponent x -> TextComponent
Generic, Typeable, Typeable TextComponent
Typeable TextComponent =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextComponent -> c TextComponent)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextComponent)
-> (TextComponent -> Constr)
-> (TextComponent -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextComponent))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TextComponent))
-> ((forall b. Data b => b -> b) -> TextComponent -> TextComponent)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextComponent -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextComponent -> r)
-> (forall u. (forall d. Data d => d -> u) -> TextComponent -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TextComponent -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TextComponent -> m TextComponent)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TextComponent -> m TextComponent)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TextComponent -> m TextComponent)
-> Data TextComponent
TextComponent -> Constr
TextComponent -> DataType
(forall b. Data b => b -> b) -> TextComponent -> TextComponent
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) -> TextComponent -> u
forall u. (forall d. Data d => d -> u) -> TextComponent -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextComponent -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextComponent -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TextComponent -> m TextComponent
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TextComponent -> m TextComponent
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextComponent
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextComponent -> c TextComponent
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextComponent)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TextComponent)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextComponent -> c TextComponent
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TextComponent -> c TextComponent
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextComponent
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TextComponent
$ctoConstr :: TextComponent -> Constr
toConstr :: TextComponent -> Constr
$cdataTypeOf :: TextComponent -> DataType
dataTypeOf :: TextComponent -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextComponent)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TextComponent)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TextComponent)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TextComponent)
$cgmapT :: (forall b. Data b => b -> b) -> TextComponent -> TextComponent
gmapT :: (forall b. Data b => b -> b) -> TextComponent -> TextComponent
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextComponent -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TextComponent -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextComponent -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TextComponent -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TextComponent -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TextComponent -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TextComponent -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TextComponent -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TextComponent -> m TextComponent
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TextComponent -> m TextComponent
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TextComponent -> m TextComponent
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TextComponent -> m TextComponent
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TextComponent -> m TextComponent
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TextComponent -> m TextComponent
Data)
deriving anyclass (TextComponent -> ()
(TextComponent -> ()) -> NFData TextComponent
forall a. (a -> ()) -> NFData a
$crnf :: TextComponent -> ()
rnf :: TextComponent -> ()
NFData, Eq TextComponent
Eq TextComponent =>
(Int -> TextComponent -> Int)
-> (TextComponent -> Int) -> Hashable TextComponent
Int -> TextComponent -> Int
TextComponent -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> TextComponent -> Int
hashWithSalt :: Int -> TextComponent -> Int
$chash :: TextComponent -> Int
hash :: TextComponent -> Int
Hashable)
deriving (TextComponent -> Builder
(TextComponent -> Builder) -> Pack TextComponent
forall a. (a -> Builder) -> Pack a
$cpack :: TextComponent -> Builder
pack :: TextComponent -> Builder
Pack, (forall (st :: ZeroBitType) r. Parser st r TextComponent)
-> Unpack TextComponent
forall (st :: ZeroBitType) r. Parser st r TextComponent
forall a. (forall (st :: ZeroBitType) r. Parser st r a) -> Unpack a
$cunpack :: forall (st :: ZeroBitType) r. Parser st r TextComponent
unpack :: forall (st :: ZeroBitType) r. Parser st r TextComponent
Unpack) via ErrorOnPackUnpack TextComponent
data MapIcon
deriving stock (MapIcon -> MapIcon -> Bool
(MapIcon -> MapIcon -> Bool)
-> (MapIcon -> MapIcon -> Bool) -> Eq MapIcon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MapIcon -> MapIcon -> Bool
== :: MapIcon -> MapIcon -> Bool
$c/= :: MapIcon -> MapIcon -> Bool
/= :: MapIcon -> MapIcon -> Bool
Eq, Eq MapIcon
Eq MapIcon =>
(MapIcon -> MapIcon -> Ordering)
-> (MapIcon -> MapIcon -> Bool)
-> (MapIcon -> MapIcon -> Bool)
-> (MapIcon -> MapIcon -> Bool)
-> (MapIcon -> MapIcon -> Bool)
-> (MapIcon -> MapIcon -> MapIcon)
-> (MapIcon -> MapIcon -> MapIcon)
-> Ord MapIcon
MapIcon -> MapIcon -> Bool
MapIcon -> MapIcon -> Ordering
MapIcon -> MapIcon -> MapIcon
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 :: MapIcon -> MapIcon -> Ordering
compare :: MapIcon -> MapIcon -> Ordering
$c< :: MapIcon -> MapIcon -> Bool
< :: MapIcon -> MapIcon -> Bool
$c<= :: MapIcon -> MapIcon -> Bool
<= :: MapIcon -> MapIcon -> Bool
$c> :: MapIcon -> MapIcon -> Bool
> :: MapIcon -> MapIcon -> Bool
$c>= :: MapIcon -> MapIcon -> Bool
>= :: MapIcon -> MapIcon -> Bool
$cmax :: MapIcon -> MapIcon -> MapIcon
max :: MapIcon -> MapIcon -> MapIcon
$cmin :: MapIcon -> MapIcon -> MapIcon
min :: MapIcon -> MapIcon -> MapIcon
Ord, Int -> MapIcon -> ShowS
[MapIcon] -> ShowS
MapIcon -> String
(Int -> MapIcon -> ShowS)
-> (MapIcon -> String) -> ([MapIcon] -> ShowS) -> Show MapIcon
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MapIcon -> ShowS
showsPrec :: Int -> MapIcon -> ShowS
$cshow :: MapIcon -> String
show :: MapIcon -> String
$cshowList :: [MapIcon] -> ShowS
showList :: [MapIcon] -> ShowS
Show, ReadPrec [MapIcon]
ReadPrec MapIcon
Int -> ReadS MapIcon
ReadS [MapIcon]
(Int -> ReadS MapIcon)
-> ReadS [MapIcon]
-> ReadPrec MapIcon
-> ReadPrec [MapIcon]
-> Read MapIcon
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MapIcon
readsPrec :: Int -> ReadS MapIcon
$creadList :: ReadS [MapIcon]
readList :: ReadS [MapIcon]
$creadPrec :: ReadPrec MapIcon
readPrec :: ReadPrec MapIcon
$creadListPrec :: ReadPrec [MapIcon]
readListPrec :: ReadPrec [MapIcon]
Read, (forall x. MapIcon -> Rep MapIcon x)
-> (forall x. Rep MapIcon x -> MapIcon) -> Generic MapIcon
forall x. Rep MapIcon x -> MapIcon
forall x. MapIcon -> Rep MapIcon x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MapIcon -> Rep MapIcon x
from :: forall x. MapIcon -> Rep MapIcon x
$cto :: forall x. Rep MapIcon x -> MapIcon
to :: forall x. Rep MapIcon x -> MapIcon
Generic, Typeable, Typeable MapIcon
Typeable MapIcon =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MapIcon -> c MapIcon)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MapIcon)
-> (MapIcon -> Constr)
-> (MapIcon -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MapIcon))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MapIcon))
-> ((forall b. Data b => b -> b) -> MapIcon -> MapIcon)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MapIcon -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MapIcon -> r)
-> (forall u. (forall d. Data d => d -> u) -> MapIcon -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> MapIcon -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MapIcon -> m MapIcon)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MapIcon -> m MapIcon)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MapIcon -> m MapIcon)
-> Data MapIcon
MapIcon -> Constr
MapIcon -> DataType
(forall b. Data b => b -> b) -> MapIcon -> MapIcon
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) -> MapIcon -> u
forall u. (forall d. Data d => d -> u) -> MapIcon -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MapIcon -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MapIcon -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MapIcon -> m MapIcon
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MapIcon -> m MapIcon
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MapIcon
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MapIcon -> c MapIcon
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MapIcon)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MapIcon)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MapIcon -> c MapIcon
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MapIcon -> c MapIcon
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MapIcon
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MapIcon
$ctoConstr :: MapIcon -> Constr
toConstr :: MapIcon -> Constr
$cdataTypeOf :: MapIcon -> DataType
dataTypeOf :: MapIcon -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MapIcon)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MapIcon)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MapIcon)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MapIcon)
$cgmapT :: (forall b. Data b => b -> b) -> MapIcon -> MapIcon
gmapT :: (forall b. Data b => b -> b) -> MapIcon -> MapIcon
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MapIcon -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MapIcon -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MapIcon -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MapIcon -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MapIcon -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> MapIcon -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MapIcon -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MapIcon -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MapIcon -> m MapIcon
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MapIcon -> m MapIcon
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MapIcon -> m MapIcon
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MapIcon -> m MapIcon
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MapIcon -> m MapIcon
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MapIcon -> m MapIcon
Data)
deriving anyclass (MapIcon -> ()
(MapIcon -> ()) -> NFData MapIcon
forall a. (a -> ()) -> NFData a
$crnf :: MapIcon -> ()
rnf :: MapIcon -> ()
NFData, Eq MapIcon
Eq MapIcon =>
(Int -> MapIcon -> Int) -> (MapIcon -> Int) -> Hashable MapIcon
Int -> MapIcon -> Int
MapIcon -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> MapIcon -> Int
hashWithSalt :: Int -> MapIcon -> Int
$chash :: MapIcon -> Int
hash :: MapIcon -> Int
Hashable)
deriving (MapIcon -> Builder
(MapIcon -> Builder) -> Pack MapIcon
forall a. (a -> Builder) -> Pack a
$cpack :: MapIcon -> Builder
pack :: MapIcon -> Builder
Pack, (forall (st :: ZeroBitType) r. Parser st r MapIcon)
-> Unpack MapIcon
forall (st :: ZeroBitType) r. Parser st r MapIcon
forall a. (forall (st :: ZeroBitType) r. Parser st r a) -> Unpack a
$cunpack :: forall (st :: ZeroBitType) r. Parser st r MapIcon
unpack :: forall (st :: ZeroBitType) r. Parser st r MapIcon
Unpack) via ErrorOnPackUnpack MapIcon
data MerchantOffer
deriving stock (MerchantOffer -> MerchantOffer -> Bool
(MerchantOffer -> MerchantOffer -> Bool)
-> (MerchantOffer -> MerchantOffer -> Bool) -> Eq MerchantOffer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MerchantOffer -> MerchantOffer -> Bool
== :: MerchantOffer -> MerchantOffer -> Bool
$c/= :: MerchantOffer -> MerchantOffer -> Bool
/= :: MerchantOffer -> MerchantOffer -> Bool
Eq, Eq MerchantOffer
Eq MerchantOffer =>
(MerchantOffer -> MerchantOffer -> Ordering)
-> (MerchantOffer -> MerchantOffer -> Bool)
-> (MerchantOffer -> MerchantOffer -> Bool)
-> (MerchantOffer -> MerchantOffer -> Bool)
-> (MerchantOffer -> MerchantOffer -> Bool)
-> (MerchantOffer -> MerchantOffer -> MerchantOffer)
-> (MerchantOffer -> MerchantOffer -> MerchantOffer)
-> Ord MerchantOffer
MerchantOffer -> MerchantOffer -> Bool
MerchantOffer -> MerchantOffer -> Ordering
MerchantOffer -> MerchantOffer -> MerchantOffer
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 :: MerchantOffer -> MerchantOffer -> Ordering
compare :: MerchantOffer -> MerchantOffer -> Ordering
$c< :: MerchantOffer -> MerchantOffer -> Bool
< :: MerchantOffer -> MerchantOffer -> Bool
$c<= :: MerchantOffer -> MerchantOffer -> Bool
<= :: MerchantOffer -> MerchantOffer -> Bool
$c> :: MerchantOffer -> MerchantOffer -> Bool
> :: MerchantOffer -> MerchantOffer -> Bool
$c>= :: MerchantOffer -> MerchantOffer -> Bool
>= :: MerchantOffer -> MerchantOffer -> Bool
$cmax :: MerchantOffer -> MerchantOffer -> MerchantOffer
max :: MerchantOffer -> MerchantOffer -> MerchantOffer
$cmin :: MerchantOffer -> MerchantOffer -> MerchantOffer
min :: MerchantOffer -> MerchantOffer -> MerchantOffer
Ord, Int -> MerchantOffer -> ShowS
[MerchantOffer] -> ShowS
MerchantOffer -> String
(Int -> MerchantOffer -> ShowS)
-> (MerchantOffer -> String)
-> ([MerchantOffer] -> ShowS)
-> Show MerchantOffer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MerchantOffer -> ShowS
showsPrec :: Int -> MerchantOffer -> ShowS
$cshow :: MerchantOffer -> String
show :: MerchantOffer -> String
$cshowList :: [MerchantOffer] -> ShowS
showList :: [MerchantOffer] -> ShowS
Show, ReadPrec [MerchantOffer]
ReadPrec MerchantOffer
Int -> ReadS MerchantOffer
ReadS [MerchantOffer]
(Int -> ReadS MerchantOffer)
-> ReadS [MerchantOffer]
-> ReadPrec MerchantOffer
-> ReadPrec [MerchantOffer]
-> Read MerchantOffer
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MerchantOffer
readsPrec :: Int -> ReadS MerchantOffer
$creadList :: ReadS [MerchantOffer]
readList :: ReadS [MerchantOffer]
$creadPrec :: ReadPrec MerchantOffer
readPrec :: ReadPrec MerchantOffer
$creadListPrec :: ReadPrec [MerchantOffer]
readListPrec :: ReadPrec [MerchantOffer]
Read, (forall x. MerchantOffer -> Rep MerchantOffer x)
-> (forall x. Rep MerchantOffer x -> MerchantOffer)
-> Generic MerchantOffer
forall x. Rep MerchantOffer x -> MerchantOffer
forall x. MerchantOffer -> Rep MerchantOffer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MerchantOffer -> Rep MerchantOffer x
from :: forall x. MerchantOffer -> Rep MerchantOffer x
$cto :: forall x. Rep MerchantOffer x -> MerchantOffer
to :: forall x. Rep MerchantOffer x -> MerchantOffer
Generic, Typeable, Typeable MerchantOffer
Typeable MerchantOffer =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MerchantOffer -> c MerchantOffer)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MerchantOffer)
-> (MerchantOffer -> Constr)
-> (MerchantOffer -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MerchantOffer))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MerchantOffer))
-> ((forall b. Data b => b -> b) -> MerchantOffer -> MerchantOffer)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MerchantOffer -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MerchantOffer -> r)
-> (forall u. (forall d. Data d => d -> u) -> MerchantOffer -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> MerchantOffer -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MerchantOffer -> m MerchantOffer)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MerchantOffer -> m MerchantOffer)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MerchantOffer -> m MerchantOffer)
-> Data MerchantOffer
MerchantOffer -> Constr
MerchantOffer -> DataType
(forall b. Data b => b -> b) -> MerchantOffer -> MerchantOffer
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) -> MerchantOffer -> u
forall u. (forall d. Data d => d -> u) -> MerchantOffer -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MerchantOffer -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MerchantOffer -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MerchantOffer -> m MerchantOffer
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MerchantOffer -> m MerchantOffer
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MerchantOffer
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MerchantOffer -> c MerchantOffer
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MerchantOffer)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MerchantOffer)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MerchantOffer -> c MerchantOffer
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MerchantOffer -> c MerchantOffer
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MerchantOffer
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MerchantOffer
$ctoConstr :: MerchantOffer -> Constr
toConstr :: MerchantOffer -> Constr
$cdataTypeOf :: MerchantOffer -> DataType
dataTypeOf :: MerchantOffer -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MerchantOffer)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MerchantOffer)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MerchantOffer)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MerchantOffer)
$cgmapT :: (forall b. Data b => b -> b) -> MerchantOffer -> MerchantOffer
gmapT :: (forall b. Data b => b -> b) -> MerchantOffer -> MerchantOffer
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MerchantOffer -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MerchantOffer -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MerchantOffer -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MerchantOffer -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MerchantOffer -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> MerchantOffer -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MerchantOffer -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MerchantOffer -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MerchantOffer -> m MerchantOffer
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MerchantOffer -> m MerchantOffer
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MerchantOffer -> m MerchantOffer
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MerchantOffer -> m MerchantOffer
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MerchantOffer -> m MerchantOffer
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MerchantOffer -> m MerchantOffer
Data)
deriving anyclass (MerchantOffer -> ()
(MerchantOffer -> ()) -> NFData MerchantOffer
forall a. (a -> ()) -> NFData a
$crnf :: MerchantOffer -> ()
rnf :: MerchantOffer -> ()
NFData, Eq MerchantOffer
Eq MerchantOffer =>
(Int -> MerchantOffer -> Int)
-> (MerchantOffer -> Int) -> Hashable MerchantOffer
Int -> MerchantOffer -> Int
MerchantOffer -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> MerchantOffer -> Int
hashWithSalt :: Int -> MerchantOffer -> Int
$chash :: MerchantOffer -> Int
hash :: MerchantOffer -> Int
Hashable)
deriving (MerchantOffer -> Builder
(MerchantOffer -> Builder) -> Pack MerchantOffer
forall a. (a -> Builder) -> Pack a
$cpack :: MerchantOffer -> Builder
pack :: MerchantOffer -> Builder
Pack, (forall (st :: ZeroBitType) r. Parser st r MerchantOffer)
-> Unpack MerchantOffer
forall (st :: ZeroBitType) r. Parser st r MerchantOffer
forall a. (forall (st :: ZeroBitType) r. Parser st r a) -> Unpack a
$cunpack :: forall (st :: ZeroBitType) r. Parser st r MerchantOffer
unpack :: forall (st :: ZeroBitType) r. Parser st r MerchantOffer
Unpack) via ErrorOnPackUnpack MerchantOffer