module Rattletrap.Type.Attribute.Boost where import qualified Rattletrap.BitGet as BitGet import qualified Rattletrap.BitPut as BitPut import qualified Rattletrap.Schema as Schema import qualified Rattletrap.Type.U8 as U8 import qualified Rattletrap.Utility.Json as Json data Boost = Boost { Boost -> U8 grantCount :: U8.U8, Boost -> U8 boostAmount :: U8.U8, Boost -> U8 unused1 :: U8.U8, Boost -> U8 unused2 :: U8.U8 } deriving (Boost -> Boost -> Bool (Boost -> Boost -> Bool) -> (Boost -> Boost -> Bool) -> Eq Boost forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: Boost -> Boost -> Bool == :: Boost -> Boost -> Bool $c/= :: Boost -> Boost -> Bool /= :: Boost -> Boost -> Bool Eq, Int -> Boost -> ShowS [Boost] -> ShowS Boost -> String (Int -> Boost -> ShowS) -> (Boost -> String) -> ([Boost] -> ShowS) -> Show Boost forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> Boost -> ShowS showsPrec :: Int -> Boost -> ShowS $cshow :: Boost -> String show :: Boost -> String $cshowList :: [Boost] -> ShowS showList :: [Boost] -> ShowS Show) instance Json.FromJSON Boost where parseJSON :: Value -> Parser Boost parseJSON = String -> (Object -> Parser Boost) -> Value -> Parser Boost forall a. String -> (Object -> Parser a) -> Value -> Parser a Json.withObject String "Boost" ((Object -> Parser Boost) -> Value -> Parser Boost) -> (Object -> Parser Boost) -> Value -> Parser Boost forall a b. (a -> b) -> a -> b $ \Object object -> do U8 grantCount <- Object -> String -> Parser U8 forall value. FromJSON value => Object -> String -> Parser value Json.required Object object String "grantCount" U8 boostAmount <- Object -> String -> Parser U8 forall value. FromJSON value => Object -> String -> Parser value Json.required Object object String "boostAmount" U8 unused1 <- Object -> String -> Parser U8 forall value. FromJSON value => Object -> String -> Parser value Json.required Object object String "unused1" U8 unused2 <- Object -> String -> Parser U8 forall value. FromJSON value => Object -> String -> Parser value Json.required Object object String "unused2" Boost -> Parser Boost forall a. a -> Parser a forall (f :: * -> *) a. Applicative f => a -> f a pure Boost {U8 grantCount :: U8 grantCount :: U8 grantCount, U8 boostAmount :: U8 boostAmount :: U8 boostAmount, U8 unused1 :: U8 unused1 :: U8 unused1, U8 unused2 :: U8 unused2 :: U8 unused2} instance Json.ToJSON Boost where toJSON :: Boost -> Value toJSON Boost x = [(Key, Value)] -> Value Json.object [ String -> U8 -> (Key, Value) forall value e p. (ToJSON value, KeyValue e p) => String -> value -> p Json.pair String "grantCount" (U8 -> (Key, Value)) -> U8 -> (Key, Value) forall a b. (a -> b) -> a -> b $ Boost -> U8 grantCount Boost x, String -> U8 -> (Key, Value) forall value e p. (ToJSON value, KeyValue e p) => String -> value -> p Json.pair String "boostAmount" (U8 -> (Key, Value)) -> U8 -> (Key, Value) forall a b. (a -> b) -> a -> b $ Boost -> U8 boostAmount Boost x, String -> U8 -> (Key, Value) forall value e p. (ToJSON value, KeyValue e p) => String -> value -> p Json.pair String "unused1" (U8 -> (Key, Value)) -> U8 -> (Key, Value) forall a b. (a -> b) -> a -> b $ Boost -> U8 unused1 Boost x, String -> U8 -> (Key, Value) forall value e p. (ToJSON value, KeyValue e p) => String -> value -> p Json.pair String "unused2" (U8 -> (Key, Value)) -> U8 -> (Key, Value) forall a b. (a -> b) -> a -> b $ Boost -> U8 unused2 Boost x ] schema :: Schema.Schema schema :: Schema schema = String -> Value -> Schema Schema.named String "boost" (Value -> Schema) -> Value -> Schema forall a b. (a -> b) -> a -> b $ [((Key, Value), Bool)] -> Value Schema.object [ (String -> Value -> (Key, Value) forall value e p. (ToJSON value, KeyValue e p) => String -> value -> p Json.pair String "grantCount" (Value -> (Key, Value)) -> Value -> (Key, Value) forall a b. (a -> b) -> a -> b $ Schema -> Value Schema.ref Schema U8.schema, Bool True), (String -> Value -> (Key, Value) forall value e p. (ToJSON value, KeyValue e p) => String -> value -> p Json.pair String "boostAmount" (Value -> (Key, Value)) -> Value -> (Key, Value) forall a b. (a -> b) -> a -> b $ Schema -> Value Schema.ref Schema U8.schema, Bool True), (String -> Value -> (Key, Value) forall value e p. (ToJSON value, KeyValue e p) => String -> value -> p Json.pair String "unused1" (Value -> (Key, Value)) -> Value -> (Key, Value) forall a b. (a -> b) -> a -> b $ Schema -> Value Schema.ref Schema U8.schema, Bool True), (String -> Value -> (Key, Value) forall value e p. (ToJSON value, KeyValue e p) => String -> value -> p Json.pair String "unused2" (Value -> (Key, Value)) -> Value -> (Key, Value) forall a b. (a -> b) -> a -> b $ Schema -> Value Schema.ref Schema U8.schema, Bool True) ] bitPut :: Boost -> BitPut.BitPut bitPut :: Boost -> BitPut bitPut Boost appliedDamageAttribute = U8 -> BitPut U8.bitPut (Boost -> U8 grantCount Boost appliedDamageAttribute) BitPut -> BitPut -> BitPut forall a. Semigroup a => a -> a -> a <> U8 -> BitPut U8.bitPut (Boost -> U8 boostAmount Boost appliedDamageAttribute) BitPut -> BitPut -> BitPut forall a. Semigroup a => a -> a -> a <> U8 -> BitPut U8.bitPut (Boost -> U8 unused1 Boost appliedDamageAttribute) BitPut -> BitPut -> BitPut forall a. Semigroup a => a -> a -> a <> U8 -> BitPut U8.bitPut (Boost -> U8 unused2 Boost appliedDamageAttribute) bitGet :: BitGet.BitGet Boost bitGet :: BitGet Boost bitGet = String -> BitGet Boost -> BitGet Boost forall a. String -> BitGet a -> BitGet a BitGet.label String "Boost" (BitGet Boost -> BitGet Boost) -> BitGet Boost -> BitGet Boost forall a b. (a -> b) -> a -> b $ do U8 grantCount <- String -> BitGet U8 -> BitGet U8 forall a. String -> BitGet a -> BitGet a BitGet.label String "grantCount" BitGet U8 U8.bitGet U8 boostAmount <- String -> BitGet U8 -> BitGet U8 forall a. String -> BitGet a -> BitGet a BitGet.label String "boostAmount" BitGet U8 U8.bitGet U8 unused1 <- String -> BitGet U8 -> BitGet U8 forall a. String -> BitGet a -> BitGet a BitGet.label String "unused1" BitGet U8 U8.bitGet U8 unused2 <- String -> BitGet U8 -> BitGet U8 forall a. String -> BitGet a -> BitGet a BitGet.label String "unused2" BitGet U8 U8.bitGet Boost -> BitGet Boost forall a. a -> Get BitString Identity a forall (f :: * -> *) a. Applicative f => a -> f a pure Boost {U8 grantCount :: U8 grantCount :: U8 grantCount, U8 boostAmount :: U8 boostAmount :: U8 boostAmount, U8 unused1 :: U8 unused1 :: U8 unused1, U8 unused2 :: U8 unused2 :: U8 unused2}