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,
    -- | Now known as "rocket boost".
    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,
     :: 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
    U8
version <- Object -> String -> Parser U8
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"version"
    U32
body <- Object -> String -> Parser U32
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"body"
    U32
decal <- Object -> String -> Parser U32
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"decal"
    U32
wheels <- Object -> String -> Parser U32
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"wheels"
    U32
rocketTrail <- Object -> String -> Parser U32
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"rocket_trail"
    U32
antenna <- Object -> String -> Parser U32
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"antenna"
    U32
topper <- Object -> String -> Parser U32
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"topper"
    U32
unknown1 <- Object -> String -> Parser U32
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"unknown1"
    Maybe U32
unknown2 <- Object -> String -> Parser (Maybe U32)
forall value.
FromJSON value =>
Object -> String -> Parser (Maybe value)
Json.optional Object
object String
"unknown2"
    Maybe U32
engineAudio <- Object -> String -> Parser (Maybe U32)
forall value.
FromJSON value =>
Object -> String -> Parser (Maybe value)
Json.optional Object
object String
"engine_audio"
    Maybe U32
trail <- Object -> String -> Parser (Maybe U32)
forall value.
FromJSON value =>
Object -> String -> Parser (Maybe value)
Json.optional Object
object String
"trail"
    Maybe U32
goalExplosion <- Object -> String -> Parser (Maybe U32)
forall value.
FromJSON value =>
Object -> String -> Parser (Maybe value)
Json.optional Object
object String
"goal_explosion"
    Maybe U32
banner <- Object -> String -> Parser (Maybe U32)
forall value.
FromJSON value =>
Object -> String -> Parser (Maybe value)
Json.optional Object
object String
"banner"
    Maybe U32
unknown3 <- Object -> String -> Parser (Maybe U32)
forall value.
FromJSON value =>
Object -> String -> Parser (Maybe value)
Json.optional Object
object String
"unknown3"
    Maybe U32
unknown4 <- Object -> String -> Parser (Maybe U32)
forall value.
FromJSON value =>
Object -> String -> Parser (Maybe value)
Json.optional Object
object String
"unknown4"
    Maybe U32
unknown5 <- Object -> String -> Parser (Maybe U32)
forall value.
FromJSON value =>
Object -> String -> Parser (Maybe value)
Json.optional Object
object String
"unknown5"
    Maybe U32
unknown6 <- Object -> String -> Parser (Maybe U32)
forall value.
FromJSON value =>
Object -> String -> Parser (Maybe value)
Json.optional Object
object String
"unknown6"
    Loadout -> Parser Loadout
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
      Loadout
        { U8
version :: U8
version :: U8
version,
          U32
body :: U32
body :: U32
body,
          U32
decal :: U32
decal :: U32
decal,
          U32
wheels :: U32
wheels :: U32
wheels,
          U32
rocketTrail :: U32
rocketTrail :: U32
rocketTrail,
          U32
antenna :: U32
antenna :: U32
antenna,
          U32
topper :: U32
topper :: U32
topper,
          U32
unknown1 :: U32
unknown1 :: U32
unknown1,
          Maybe U32
unknown2 :: Maybe U32
unknown2 :: Maybe U32
unknown2,
          Maybe U32
engineAudio :: Maybe U32
engineAudio :: Maybe U32
engineAudio,
          Maybe U32
trail :: Maybe U32
trail :: Maybe U32
trail,
          Maybe U32
goalExplosion :: Maybe U32
goalExplosion :: Maybe U32
goalExplosion,
          Maybe U32
banner :: Maybe U32
banner :: Maybe U32
banner,
          Maybe U32
unknown3 :: Maybe U32
unknown3 :: Maybe U32
unknown3,
          Maybe U32
unknown4 :: Maybe U32
unknown4 :: Maybe U32
unknown4,
          Maybe U32
unknown5 :: Maybe U32
unknown5 :: Maybe U32
unknown5,
          Maybe U32
unknown6 :: Maybe U32
unknown6 :: Maybe U32
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
  U8
version <- String -> BitGet U8 -> BitGet U8
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"version" BitGet U8
U8.bitGet
  U32
body <- String -> BitGet U32 -> BitGet U32
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"body" BitGet U32
U32.bitGet
  U32
decal <- String -> BitGet U32 -> BitGet U32
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"decal" BitGet U32
U32.bitGet
  U32
wheels <- String -> BitGet U32 -> BitGet U32
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"wheels" BitGet U32
U32.bitGet
  U32
rocketTrail <- String -> BitGet U32 -> BitGet U32
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"rocketTrail" BitGet U32
U32.bitGet
  U32
antenna <- String -> BitGet U32 -> BitGet U32
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"antenna" BitGet U32
U32.bitGet
  U32
topper <- String -> BitGet U32 -> BitGet U32
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"topper" BitGet U32
U32.bitGet
  U32
unknown1 <- String -> BitGet U32 -> BitGet U32
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"unknown1" BitGet U32
U32.bitGet
  Maybe U32
unknown2 <-
    String -> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"unknown2" (BitGet (Maybe U32) -> BitGet (Maybe U32))
-> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a b. (a -> b) -> a -> b
$
      Bool -> BitGet U32 -> BitGet (Maybe U32)
forall (m :: * -> *) a. Applicative m => Bool -> m a -> m (Maybe a)
Monad.whenMaybe (U8 -> Word8
U8.toWord8 U8
version Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
11) BitGet U32
U32.bitGet
  Maybe U32
engineAudio <-
    String -> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"engineAudio" (BitGet (Maybe U32) -> BitGet (Maybe U32))
-> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a b. (a -> b) -> a -> b
$
      Bool -> BitGet U32 -> BitGet (Maybe U32)
forall (m :: * -> *) a. Applicative m => Bool -> m a -> m (Maybe a)
Monad.whenMaybe (U8 -> Word8
U8.toWord8 U8
version Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
16) BitGet U32
U32.bitGet
  Maybe U32
trail <-
    String -> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"trail" (BitGet (Maybe U32) -> BitGet (Maybe U32))
-> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a b. (a -> b) -> a -> b
$
      Bool -> BitGet U32 -> BitGet (Maybe U32)
forall (m :: * -> *) a. Applicative m => Bool -> m a -> m (Maybe a)
Monad.whenMaybe (U8 -> Word8
U8.toWord8 U8
version Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
16) BitGet U32
U32.bitGet
  Maybe U32
goalExplosion <-
    String -> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"goalExplosion" (BitGet (Maybe U32) -> BitGet (Maybe U32))
-> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a b. (a -> b) -> a -> b
$
      Bool -> BitGet U32 -> BitGet (Maybe U32)
forall (m :: * -> *) a. Applicative m => Bool -> m a -> m (Maybe a)
Monad.whenMaybe (U8 -> Word8
U8.toWord8 U8
version Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
16) BitGet U32
U32.bitGet
  Maybe U32
banner <-
    String -> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"banner" (BitGet (Maybe U32) -> BitGet (Maybe U32))
-> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a b. (a -> b) -> a -> b
$
      Bool -> BitGet U32 -> BitGet (Maybe U32)
forall (m :: * -> *) a. Applicative m => Bool -> m a -> m (Maybe a)
Monad.whenMaybe (U8 -> Word8
U8.toWord8 U8
version Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
17) BitGet U32
U32.bitGet
  Maybe U32
unknown3 <-
    String -> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"unknown3" (BitGet (Maybe U32) -> BitGet (Maybe U32))
-> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a b. (a -> b) -> a -> b
$
      Bool -> BitGet U32 -> BitGet (Maybe U32)
forall (m :: * -> *) a. Applicative m => Bool -> m a -> m (Maybe a)
Monad.whenMaybe (U8 -> Word8
U8.toWord8 U8
version Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
19) BitGet U32
U32.bitGet
  Maybe U32
unknown4 <-
    String -> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"unknown4" (BitGet (Maybe U32) -> BitGet (Maybe U32))
-> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a b. (a -> b) -> a -> b
$
      Bool -> BitGet U32 -> BitGet (Maybe U32)
forall (m :: * -> *) a. Applicative m => Bool -> m a -> m (Maybe a)
Monad.whenMaybe (U8 -> Word8
U8.toWord8 U8
version Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
22) BitGet U32
U32.bitGet
  Maybe U32
unknown5 <-
    String -> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"unknown5" (BitGet (Maybe U32) -> BitGet (Maybe U32))
-> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a b. (a -> b) -> a -> b
$
      Bool -> BitGet U32 -> BitGet (Maybe U32)
forall (m :: * -> *) a. Applicative m => Bool -> m a -> m (Maybe a)
Monad.whenMaybe (U8 -> Word8
U8.toWord8 U8
version Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
22) BitGet U32
U32.bitGet
  Maybe U32
unknown6 <-
    String -> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"unknown6" (BitGet (Maybe U32) -> BitGet (Maybe U32))
-> BitGet (Maybe U32) -> BitGet (Maybe U32)
forall a b. (a -> b) -> a -> b
$
      Bool -> BitGet U32 -> BitGet (Maybe U32)
forall (m :: * -> *) a. Applicative m => Bool -> m a -> m (Maybe a)
Monad.whenMaybe (U8 -> Word8
U8.toWord8 U8
version Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
22) BitGet U32
U32.bitGet
  Loadout -> BitGet Loadout
forall a. a -> Get BitString Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
    Loadout
      { U8
version :: U8
version :: U8
version,
        U32
body :: U32
body :: U32
body,
        U32
decal :: U32
decal :: U32
decal,
        U32
wheels :: U32
wheels :: U32
wheels,
        U32
rocketTrail :: U32
rocketTrail :: U32
rocketTrail,
        U32
antenna :: U32
antenna :: U32
antenna,
        U32
topper :: U32
topper :: U32
topper,
        U32
unknown1 :: U32
unknown1 :: U32
unknown1,
        Maybe U32
unknown2 :: Maybe U32
unknown2 :: Maybe U32
unknown2,
        Maybe U32
engineAudio :: Maybe U32
engineAudio :: Maybe U32
engineAudio,
        Maybe U32
trail :: Maybe U32
trail :: Maybe U32
trail,
        Maybe U32
goalExplosion :: Maybe U32
goalExplosion :: Maybe U32
goalExplosion,
        Maybe U32
banner :: Maybe U32
banner :: Maybe U32
banner,
        Maybe U32
unknown3 :: Maybe U32
unknown3 :: Maybe U32
unknown3,
        Maybe U32
unknown4 :: Maybe U32
unknown4 :: Maybe U32
unknown4,
        Maybe U32
unknown5 :: Maybe U32
unknown5 :: Maybe U32
unknown5,
        Maybe U32
unknown6 :: Maybe U32
unknown6 :: Maybe U32
unknown6
      }