module Rattletrap.Decode.DamageStateAttribute
  ( decodeDamageStateAttributeBits
  )
where

import Rattletrap.Decode.Common
import Rattletrap.Decode.Int32le
import Rattletrap.Decode.Vector
import Rattletrap.Decode.Word8le
import Rattletrap.Type.DamageStateAttribute

decodeDamageStateAttributeBits
  :: (Int, Int, Int) -> DecodeBits DamageStateAttribute
decodeDamageStateAttributeBits :: (Int, Int, Int) -> DecodeBits DamageStateAttribute
decodeDamageStateAttributeBits (Int, Int, Int)
version =
  Word8le
-> Bool
-> Int32le
-> Vector
-> Bool
-> Bool
-> DamageStateAttribute
DamageStateAttribute
    (Word8le
 -> Bool
 -> Int32le
 -> Vector
 -> Bool
 -> Bool
 -> DamageStateAttribute)
-> BitGet Word8le
-> BitGet
     (Bool -> Int32le -> Vector -> Bool -> Bool -> DamageStateAttribute)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BitGet Word8le
decodeWord8leBits
    BitGet
  (Bool -> Int32le -> Vector -> Bool -> Bool -> DamageStateAttribute)
-> BitGet Bool
-> BitGet
     (Int32le -> Vector -> Bool -> Bool -> DamageStateAttribute)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BitGet Bool
getBool
    BitGet (Int32le -> Vector -> Bool -> Bool -> DamageStateAttribute)
-> BitGet Int32le
-> BitGet (Vector -> Bool -> Bool -> DamageStateAttribute)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BitGet Int32le
decodeInt32leBits
    BitGet (Vector -> Bool -> Bool -> DamageStateAttribute)
-> BitGet Vector -> BitGet (Bool -> Bool -> DamageStateAttribute)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Int, Int, Int) -> BitGet Vector
decodeVectorBits (Int, Int, Int)
version
    BitGet (Bool -> Bool -> DamageStateAttribute)
-> BitGet Bool -> BitGet (Bool -> DamageStateAttribute)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BitGet Bool
getBool
    BitGet (Bool -> DamageStateAttribute)
-> BitGet Bool -> DecodeBits DamageStateAttribute
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BitGet Bool
getBool