module Rattletrap.Type.Attribute.PlayerHistoryKey where

import qualified Data.Word as Word
import qualified Rattletrap.BitGet as BitGet
import qualified Rattletrap.BitPut as BitPut
import qualified Rattletrap.Schema as Schema
import qualified Rattletrap.Utility.Json as Json

newtype PlayerHistoryKey = PlayerHistoryKey
  { PlayerHistoryKey -> Word16
unknown :: Word.Word16
  }
  deriving (PlayerHistoryKey -> PlayerHistoryKey -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PlayerHistoryKey -> PlayerHistoryKey -> Bool
$c/= :: PlayerHistoryKey -> PlayerHistoryKey -> Bool
== :: PlayerHistoryKey -> PlayerHistoryKey -> Bool
$c== :: PlayerHistoryKey -> PlayerHistoryKey -> Bool
Eq, Int -> PlayerHistoryKey -> ShowS
[PlayerHistoryKey] -> ShowS
PlayerHistoryKey -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PlayerHistoryKey] -> ShowS
$cshowList :: [PlayerHistoryKey] -> ShowS
show :: PlayerHistoryKey -> String
$cshow :: PlayerHistoryKey -> String
showsPrec :: Int -> PlayerHistoryKey -> ShowS
$cshowsPrec :: Int -> PlayerHistoryKey -> ShowS
Show)

instance Json.FromJSON PlayerHistoryKey where
  parseJSON :: Value -> Parser PlayerHistoryKey
parseJSON = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word16 -> PlayerHistoryKey
PlayerHistoryKey forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromJSON a => Value -> Parser a
Json.parseJSON

instance Json.ToJSON PlayerHistoryKey where
  toJSON :: PlayerHistoryKey -> Value
toJSON = forall a. ToJSON a => a -> Value
Json.toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlayerHistoryKey -> Word16
unknown

schema :: Schema.Schema
schema :: Schema
schema =
  String -> Value -> Schema
Schema.named String
"attribute-player-history-key" forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
Schema.number

bitPut :: PlayerHistoryKey -> BitPut.BitPut
bitPut :: PlayerHistoryKey -> BitPut
bitPut = forall a. Bits a => Int -> a -> BitPut
BitPut.bits Int
14 forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlayerHistoryKey -> Word16
unknown

bitGet :: BitGet.BitGet PlayerHistoryKey
bitGet :: BitGet PlayerHistoryKey
bitGet = forall a. String -> BitGet a -> BitGet a
BitGet.label String
"PlayerHistoryKey" forall a b. (a -> b) -> a -> b
$ do
  Word16
unknown <- forall a. String -> BitGet a -> BitGet a
BitGet.label String
"unknown" forall a b. (a -> b) -> a -> b
$ forall a. Bits a => Int -> BitGet a
BitGet.bits Int
14
  forall (f :: * -> *) a. Applicative f => a -> f a
pure PlayerHistoryKey {Word16
unknown :: Word16
unknown :: Word16
unknown}