module Rattletrap.Decode.AppliedDamageAttribute
  ( decodeAppliedDamageAttributeBits
  )
where

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

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