module Rattletrap.Type.Attribute.Loadout where
import qualified Rattletrap.BitGet as BitGet
import qualified Rattletrap.BitPut as BitPut
import qualified Rattletrap.Schema as Schema
import qualified Rattletrap.Type.U32 as U32
import qualified Rattletrap.Type.U8 as U8
import qualified Rattletrap.Utility.Json as Json
import qualified Rattletrap.Utility.Monad as Monad
data Loadout = Loadout
{ Loadout -> U8
version :: U8.U8,
Loadout -> U32
body :: U32.U32,
Loadout -> U32
decal :: U32.U32,
Loadout -> U32
wheels :: U32.U32,
Loadout -> U32
rocketTrail :: U32.U32,
Loadout -> U32
antenna :: U32.U32,
Loadout -> U32
topper :: U32.U32,
Loadout -> U32
unknown1 :: U32.U32,
Loadout -> Maybe U32
unknown2 :: Maybe U32.U32,
Loadout -> Maybe U32
engineAudio :: Maybe U32.U32,
Loadout -> Maybe U32
trail :: Maybe U32.U32,
Loadout -> Maybe U32
goalExplosion :: Maybe U32.U32,
Loadout -> Maybe U32
banner :: Maybe U32.U32,
Loadout -> Maybe U32
unknown3 :: Maybe U32.U32,
Loadout -> Maybe U32
unknown4 :: Maybe U32.U32,
Loadout -> Maybe U32
unknown5 :: Maybe U32.U32,
Loadout -> Maybe U32
unknown6 :: Maybe U32.U32
}
deriving (Loadout -> Loadout -> Bool
(Loadout -> Loadout -> Bool)
-> (Loadout -> Loadout -> Bool) -> Eq Loadout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Loadout -> Loadout -> Bool
== :: Loadout -> Loadout -> Bool
$c/= :: Loadout -> Loadout -> Bool
/= :: Loadout -> Loadout -> Bool
Eq, Int -> Loadout -> ShowS
[Loadout] -> ShowS
Loadout -> String
(Int -> Loadout -> ShowS)
-> (Loadout -> String) -> ([Loadout] -> ShowS) -> Show Loadout
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Loadout -> ShowS
showsPrec :: Int -> Loadout -> ShowS
$cshow :: Loadout -> String
show :: Loadout -> String
$cshowList :: [Loadout] -> ShowS
showList :: [Loadout] -> ShowS
Show)
instance Json.FromJSON Loadout where
parseJSON :: Value -> Parser Loadout
parseJSON = String -> (Object -> Parser Loadout) -> Value -> Parser Loadout
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Json.withObject String
"Loadout" ((Object -> Parser Loadout) -> Value -> Parser Loadout)
-> (Object -> Parser Loadout) -> Value -> Parser Loadout
forall a b. (a -> b) -> a -> b
$ \Object
object -> do
version <- Object -> String -> Parser U8
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"version"
body <- Json.required object "body"
decal <- Json.required object "decal"
wheels <- Json.required object "wheels"
rocketTrail <- Json.required object "rocket_trail"
antenna <- Json.required object "antenna"
topper <- Json.required object "topper"
unknown1 <- Json.required object "unknown1"
unknown2 <- Json.optional object "unknown2"
engineAudio <- Json.optional object "engine_audio"
trail <- Json.optional object "trail"
goalExplosion <- Json.optional object "goal_explosion"
banner <- Json.optional object "banner"
unknown3 <- Json.optional object "unknown3"
unknown4 <- Json.optional object "unknown4"
unknown5 <- Json.optional object "unknown5"
unknown6 <- Json.optional object "unknown6"
pure
Loadout
{ version,
body,
decal,
wheels,
rocketTrail,
antenna,
topper,
unknown1,
unknown2,
engineAudio,
trail,
goalExplosion,
banner,
unknown3,
unknown4,
unknown5,
unknown6
}
instance Json.ToJSON Loadout where
toJSON :: Loadout -> Value
toJSON Loadout
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
"version" (U8 -> (Key, Value)) -> U8 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> U8
version Loadout
x,
String -> U32 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"body" (U32 -> (Key, Value)) -> U32 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> U32
body Loadout
x,
String -> U32 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"decal" (U32 -> (Key, Value)) -> U32 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> U32
decal Loadout
x,
String -> U32 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"wheels" (U32 -> (Key, Value)) -> U32 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> U32
wheels Loadout
x,
String -> U32 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"rocket_trail" (U32 -> (Key, Value)) -> U32 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> U32
rocketTrail Loadout
x,
String -> U32 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"antenna" (U32 -> (Key, Value)) -> U32 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> U32
antenna Loadout
x,
String -> U32 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"topper" (U32 -> (Key, Value)) -> U32 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> U32
topper Loadout
x,
String -> U32 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"unknown1" (U32 -> (Key, Value)) -> U32 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> U32
unknown1 Loadout
x,
String -> Maybe U32 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"unknown2" (Maybe U32 -> (Key, Value)) -> Maybe U32 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> Maybe U32
unknown2 Loadout
x,
String -> Maybe U32 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"engine_audio" (Maybe U32 -> (Key, Value)) -> Maybe U32 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> Maybe U32
engineAudio Loadout
x,
String -> Maybe U32 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"trail" (Maybe U32 -> (Key, Value)) -> Maybe U32 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> Maybe U32
trail Loadout
x,
String -> Maybe U32 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"goal_explosion" (Maybe U32 -> (Key, Value)) -> Maybe U32 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> Maybe U32
goalExplosion Loadout
x,
String -> Maybe U32 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"banner" (Maybe U32 -> (Key, Value)) -> Maybe U32 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> Maybe U32
banner Loadout
x,
String -> Maybe U32 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"unknown3" (Maybe U32 -> (Key, Value)) -> Maybe U32 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> Maybe U32
unknown3 Loadout
x,
String -> Maybe U32 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"unknown4" (Maybe U32 -> (Key, Value)) -> Maybe U32 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> Maybe U32
unknown4 Loadout
x,
String -> Maybe U32 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"unknown5" (Maybe U32 -> (Key, Value)) -> Maybe U32 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> Maybe U32
unknown5 Loadout
x,
String -> Maybe U32 -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"unknown6" (Maybe U32 -> (Key, Value)) -> Maybe U32 -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Loadout -> Maybe U32
unknown6 Loadout
x
]
schema :: Schema.Schema
schema :: Schema
schema =
String -> Value -> Schema
Schema.named String
"attribute-loadout" (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
"version" (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
"body" (Value -> (Key, Value)) -> Value -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U32.schema, Bool
True),
(String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"decal" (Value -> (Key, Value)) -> Value -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U32.schema, Bool
True),
(String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"wheels" (Value -> (Key, Value)) -> Value -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U32.schema, Bool
True),
(String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"rocket_trail" (Value -> (Key, Value)) -> Value -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U32.schema, Bool
True),
(String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"antenna" (Value -> (Key, Value)) -> Value -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U32.schema, Bool
True),
(String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"topper" (Value -> (Key, Value)) -> Value -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U32.schema, Bool
True),
(String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"unknown1" (Value -> (Key, Value)) -> Value -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U32.schema, Bool
True),
(String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"unknown2" (Value -> (Key, Value))
-> (Schema -> Value) -> Schema -> (Key, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Schema -> Value
Schema.json (Schema -> (Key, Value)) -> Schema -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Schema
Schema.maybe Schema
U32.schema, Bool
False),
(String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"engine_audio" (Value -> (Key, Value))
-> (Schema -> Value) -> Schema -> (Key, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Schema -> Value
Schema.json (Schema -> (Key, Value)) -> Schema -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Schema
Schema.maybe Schema
U32.schema, Bool
False),
(String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"trail" (Value -> (Key, Value))
-> (Schema -> Value) -> Schema -> (Key, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Schema -> Value
Schema.json (Schema -> (Key, Value)) -> Schema -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Schema
Schema.maybe Schema
U32.schema, Bool
False),
(String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"goal_explosion" (Value -> (Key, Value))
-> (Schema -> Value) -> Schema -> (Key, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Schema -> Value
Schema.json (Schema -> (Key, Value)) -> Schema -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Schema
Schema.maybe Schema
U32.schema, Bool
False),
(String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"banner" (Value -> (Key, Value))
-> (Schema -> Value) -> Schema -> (Key, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Schema -> Value
Schema.json (Schema -> (Key, Value)) -> Schema -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Schema
Schema.maybe Schema
U32.schema, Bool
False),
(String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"unknown3" (Value -> (Key, Value))
-> (Schema -> Value) -> Schema -> (Key, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Schema -> Value
Schema.json (Schema -> (Key, Value)) -> Schema -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Schema
Schema.maybe Schema
U32.schema, Bool
False),
(String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"unknown4" (Value -> (Key, Value))
-> (Schema -> Value) -> Schema -> (Key, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Schema -> Value
Schema.json (Schema -> (Key, Value)) -> Schema -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Schema
Schema.maybe Schema
U32.schema, Bool
False),
(String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"unknown5" (Value -> (Key, Value))
-> (Schema -> Value) -> Schema -> (Key, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Schema -> Value
Schema.json (Schema -> (Key, Value)) -> Schema -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Schema
Schema.maybe Schema
U32.schema, Bool
False),
(String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"unknown6" (Value -> (Key, Value))
-> (Schema -> Value) -> Schema -> (Key, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Schema -> Value
Schema.json (Schema -> (Key, Value)) -> Schema -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Schema
Schema.maybe Schema
U32.schema, Bool
False)
]
bitPut :: Loadout -> BitPut.BitPut
bitPut :: Loadout -> BitPut
bitPut Loadout
loadoutAttribute =
U8 -> BitPut
U8.bitPut (Loadout -> U8
version Loadout
loadoutAttribute)
BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> U32 -> BitPut
U32.bitPut (Loadout -> U32
body Loadout
loadoutAttribute)
BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> U32 -> BitPut
U32.bitPut (Loadout -> U32
decal Loadout
loadoutAttribute)
BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> U32 -> BitPut
U32.bitPut (Loadout -> U32
wheels Loadout
loadoutAttribute)
BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> U32 -> BitPut
U32.bitPut (Loadout -> U32
rocketTrail Loadout
loadoutAttribute)
BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> U32 -> BitPut
U32.bitPut (Loadout -> U32
antenna Loadout
loadoutAttribute)
BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> U32 -> BitPut
U32.bitPut (Loadout -> U32
topper Loadout
loadoutAttribute)
BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> U32 -> BitPut
U32.bitPut (Loadout -> U32
unknown1 Loadout
loadoutAttribute)
BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> (U32 -> BitPut) -> Maybe U32 -> BitPut
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap U32 -> BitPut
U32.bitPut (Loadout -> Maybe U32
unknown2 Loadout
loadoutAttribute)
BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> (U32 -> BitPut) -> Maybe U32 -> BitPut
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap U32 -> BitPut
U32.bitPut (Loadout -> Maybe U32
engineAudio Loadout
loadoutAttribute)
BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> (U32 -> BitPut) -> Maybe U32 -> BitPut
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap U32 -> BitPut
U32.bitPut (Loadout -> Maybe U32
trail Loadout
loadoutAttribute)
BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> (U32 -> BitPut) -> Maybe U32 -> BitPut
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap U32 -> BitPut
U32.bitPut (Loadout -> Maybe U32
goalExplosion Loadout
loadoutAttribute)
BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> (U32 -> BitPut) -> Maybe U32 -> BitPut
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap U32 -> BitPut
U32.bitPut (Loadout -> Maybe U32
banner Loadout
loadoutAttribute)
BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> (U32 -> BitPut) -> Maybe U32 -> BitPut
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap U32 -> BitPut
U32.bitPut (Loadout -> Maybe U32
unknown3 Loadout
loadoutAttribute)
BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> (U32 -> BitPut) -> Maybe U32 -> BitPut
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap U32 -> BitPut
U32.bitPut (Loadout -> Maybe U32
unknown4 Loadout
loadoutAttribute)
BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> (U32 -> BitPut) -> Maybe U32 -> BitPut
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap U32 -> BitPut
U32.bitPut (Loadout -> Maybe U32
unknown5 Loadout
loadoutAttribute)
BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> (U32 -> BitPut) -> Maybe U32 -> BitPut
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap U32 -> BitPut
U32.bitPut (Loadout -> Maybe U32
unknown6 Loadout
loadoutAttribute)
bitGet :: BitGet.BitGet Loadout
bitGet :: BitGet Loadout
bitGet = String -> BitGet Loadout -> BitGet Loadout
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"Loadout" (BitGet Loadout -> BitGet Loadout)
-> BitGet Loadout -> BitGet Loadout
forall a b. (a -> b) -> a -> b
$ do
version <- String -> BitGet U8 -> BitGet U8
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"version" BitGet U8
U8.bitGet
body <- BitGet.label "body" U32.bitGet
decal <- BitGet.label "decal" U32.bitGet
wheels <- BitGet.label "wheels" U32.bitGet
rocketTrail <- BitGet.label "rocketTrail" U32.bitGet
antenna <- BitGet.label "antenna" U32.bitGet
topper <- BitGet.label "topper" U32.bitGet
unknown1 <- BitGet.label "unknown1" U32.bitGet
unknown2 <-
BitGet.label "unknown2" $
Monad.whenMaybe (U8.toWord8 version >= 11) U32.bitGet
engineAudio <-
BitGet.label "engineAudio" $
Monad.whenMaybe (U8.toWord8 version >= 16) U32.bitGet
trail <-
BitGet.label "trail" $
Monad.whenMaybe (U8.toWord8 version >= 16) U32.bitGet
goalExplosion <-
BitGet.label "goalExplosion" $
Monad.whenMaybe (U8.toWord8 version >= 16) U32.bitGet
banner <-
BitGet.label "banner" $
Monad.whenMaybe (U8.toWord8 version >= 17) U32.bitGet
unknown3 <-
BitGet.label "unknown3" $
Monad.whenMaybe (U8.toWord8 version >= 19) U32.bitGet
unknown4 <-
BitGet.label "unknown4" $
Monad.whenMaybe (U8.toWord8 version >= 22) U32.bitGet
unknown5 <-
BitGet.label "unknown5" $
Monad.whenMaybe (U8.toWord8 version >= 22) U32.bitGet
unknown6 <-
BitGet.label "unknown6" $
Monad.whenMaybe (U8.toWord8 version >= 22) U32.bitGet
pure
Loadout
{ version,
body,
decal,
wheels,
rocketTrail,
antenna,
topper,
unknown1,
unknown2,
engineAudio,
trail,
goalExplosion,
banner,
unknown3,
unknown4,
unknown5,
unknown6
}