module M.Misc (TeleportFlags (..), SoundEvent (..)) where
import Control.DeepSeq
import Data.Bits
import Data.Data
import Data.Hashable
import Data.Serde.QQ
import Data.Text (Text)
import GHC.Generics
import Language.Haskell.TH.Syntax (Lift)
import M.Pack
data TeleportFlags = TeleportFlags
{ TeleportFlags -> Bool
tprelx :: Bool,
TeleportFlags -> Bool
tprely :: Bool,
TeleportFlags -> Bool
tprelz :: Bool,
TeleportFlags -> Bool
tprelyaw :: Bool,
TeleportFlags -> Bool
tprelpitch :: Bool,
TeleportFlags -> Bool
tprelvelx :: Bool,
TeleportFlags -> Bool
tprelvely :: Bool,
TeleportFlags -> Bool
tprelvelz :: Bool,
TeleportFlags -> Bool
tprelvelyaw :: Bool,
TeleportFlags -> Bool
tprotvelfirst :: Bool
}
deriving stock (TeleportFlags -> TeleportFlags -> Bool
(TeleportFlags -> TeleportFlags -> Bool)
-> (TeleportFlags -> TeleportFlags -> Bool) -> Eq TeleportFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TeleportFlags -> TeleportFlags -> Bool
== :: TeleportFlags -> TeleportFlags -> Bool
$c/= :: TeleportFlags -> TeleportFlags -> Bool
/= :: TeleportFlags -> TeleportFlags -> Bool
Eq, Eq TeleportFlags
Eq TeleportFlags =>
(TeleportFlags -> TeleportFlags -> Ordering)
-> (TeleportFlags -> TeleportFlags -> Bool)
-> (TeleportFlags -> TeleportFlags -> Bool)
-> (TeleportFlags -> TeleportFlags -> Bool)
-> (TeleportFlags -> TeleportFlags -> Bool)
-> (TeleportFlags -> TeleportFlags -> TeleportFlags)
-> (TeleportFlags -> TeleportFlags -> TeleportFlags)
-> Ord TeleportFlags
TeleportFlags -> TeleportFlags -> Bool
TeleportFlags -> TeleportFlags -> Ordering
TeleportFlags -> TeleportFlags -> TeleportFlags
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 :: TeleportFlags -> TeleportFlags -> Ordering
compare :: TeleportFlags -> TeleportFlags -> Ordering
$c< :: TeleportFlags -> TeleportFlags -> Bool
< :: TeleportFlags -> TeleportFlags -> Bool
$c<= :: TeleportFlags -> TeleportFlags -> Bool
<= :: TeleportFlags -> TeleportFlags -> Bool
$c> :: TeleportFlags -> TeleportFlags -> Bool
> :: TeleportFlags -> TeleportFlags -> Bool
$c>= :: TeleportFlags -> TeleportFlags -> Bool
>= :: TeleportFlags -> TeleportFlags -> Bool
$cmax :: TeleportFlags -> TeleportFlags -> TeleportFlags
max :: TeleportFlags -> TeleportFlags -> TeleportFlags
$cmin :: TeleportFlags -> TeleportFlags -> TeleportFlags
min :: TeleportFlags -> TeleportFlags -> TeleportFlags
Ord, Int -> TeleportFlags -> ShowS
[TeleportFlags] -> ShowS
TeleportFlags -> String
(Int -> TeleportFlags -> ShowS)
-> (TeleportFlags -> String)
-> ([TeleportFlags] -> ShowS)
-> Show TeleportFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TeleportFlags -> ShowS
showsPrec :: Int -> TeleportFlags -> ShowS
$cshow :: TeleportFlags -> String
show :: TeleportFlags -> String
$cshowList :: [TeleportFlags] -> ShowS
showList :: [TeleportFlags] -> ShowS
Show, ReadPrec [TeleportFlags]
ReadPrec TeleportFlags
Int -> ReadS TeleportFlags
ReadS [TeleportFlags]
(Int -> ReadS TeleportFlags)
-> ReadS [TeleportFlags]
-> ReadPrec TeleportFlags
-> ReadPrec [TeleportFlags]
-> Read TeleportFlags
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TeleportFlags
readsPrec :: Int -> ReadS TeleportFlags
$creadList :: ReadS [TeleportFlags]
readList :: ReadS [TeleportFlags]
$creadPrec :: ReadPrec TeleportFlags
readPrec :: ReadPrec TeleportFlags
$creadListPrec :: ReadPrec [TeleportFlags]
readListPrec :: ReadPrec [TeleportFlags]
Read, (forall x. TeleportFlags -> Rep TeleportFlags x)
-> (forall x. Rep TeleportFlags x -> TeleportFlags)
-> Generic TeleportFlags
forall x. Rep TeleportFlags x -> TeleportFlags
forall x. TeleportFlags -> Rep TeleportFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TeleportFlags -> Rep TeleportFlags x
from :: forall x. TeleportFlags -> Rep TeleportFlags x
$cto :: forall x. Rep TeleportFlags x -> TeleportFlags
to :: forall x. Rep TeleportFlags x -> TeleportFlags
Generic, (forall (m :: * -> *). Quote m => TeleportFlags -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
TeleportFlags -> Code m TeleportFlags)
-> Lift TeleportFlags
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => TeleportFlags -> m Exp
forall (m :: * -> *).
Quote m =>
TeleportFlags -> Code m TeleportFlags
$clift :: forall (m :: * -> *). Quote m => TeleportFlags -> m Exp
lift :: forall (m :: * -> *). Quote m => TeleportFlags -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
TeleportFlags -> Code m TeleportFlags
liftTyped :: forall (m :: * -> *).
Quote m =>
TeleportFlags -> Code m TeleportFlags
Lift, Typeable TeleportFlags
Typeable TeleportFlags =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TeleportFlags -> c TeleportFlags)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TeleportFlags)
-> (TeleportFlags -> Constr)
-> (TeleportFlags -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TeleportFlags))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TeleportFlags))
-> ((forall b. Data b => b -> b) -> TeleportFlags -> TeleportFlags)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TeleportFlags -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TeleportFlags -> r)
-> (forall u. (forall d. Data d => d -> u) -> TeleportFlags -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TeleportFlags -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TeleportFlags -> m TeleportFlags)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TeleportFlags -> m TeleportFlags)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TeleportFlags -> m TeleportFlags)
-> Data TeleportFlags
TeleportFlags -> Constr
TeleportFlags -> DataType
(forall b. Data b => b -> b) -> TeleportFlags -> TeleportFlags
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) -> TeleportFlags -> u
forall u. (forall d. Data d => d -> u) -> TeleportFlags -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TeleportFlags -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TeleportFlags -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TeleportFlags -> m TeleportFlags
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TeleportFlags -> m TeleportFlags
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TeleportFlags
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TeleportFlags -> c TeleportFlags
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TeleportFlags)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TeleportFlags)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TeleportFlags -> c TeleportFlags
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TeleportFlags -> c TeleportFlags
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TeleportFlags
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TeleportFlags
$ctoConstr :: TeleportFlags -> Constr
toConstr :: TeleportFlags -> Constr
$cdataTypeOf :: TeleportFlags -> DataType
dataTypeOf :: TeleportFlags -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TeleportFlags)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TeleportFlags)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TeleportFlags)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TeleportFlags)
$cgmapT :: (forall b. Data b => b -> b) -> TeleportFlags -> TeleportFlags
gmapT :: (forall b. Data b => b -> b) -> TeleportFlags -> TeleportFlags
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TeleportFlags -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TeleportFlags -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TeleportFlags -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TeleportFlags -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TeleportFlags -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TeleportFlags -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TeleportFlags -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TeleportFlags -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TeleportFlags -> m TeleportFlags
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TeleportFlags -> m TeleportFlags
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TeleportFlags -> m TeleportFlags
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TeleportFlags -> m TeleportFlags
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TeleportFlags -> m TeleportFlags
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TeleportFlags -> m TeleportFlags
Data, Typeable)
deriving anyclass (Eq TeleportFlags
Eq TeleportFlags =>
(Int -> TeleportFlags -> Int)
-> (TeleportFlags -> Int) -> Hashable TeleportFlags
Int -> TeleportFlags -> Int
TeleportFlags -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> TeleportFlags -> Int
hashWithSalt :: Int -> TeleportFlags -> Int
$chash :: TeleportFlags -> Int
hash :: TeleportFlags -> Int
Hashable, TeleportFlags -> ()
(TeleportFlags -> ()) -> NFData TeleportFlags
forall a. (a -> ()) -> NFData a
$crnf :: TeleportFlags -> ()
rnf :: TeleportFlags -> ()
NFData)
instance (Bits i, Integral i, Pack i, Unpack i) => Bitreppable i TeleportFlags
[serde|
.derive
Show Read Lift Data Typeable
data SoundEvent
soundname :: Text via Identifier
fixedrange :: Maybe Float
|]
runusercoercion
borrowderivepackunpack
properderivepackunpack
[ ''Generic,
''Hashable,
''NFData,
''Eq,
''Ord
]