module Rattletrap.Type.Attribute.Int64 where

import qualified Rattletrap.BitGet as BitGet
import qualified Rattletrap.BitPut as BitPut
import qualified Rattletrap.Schema as Schema
import qualified Rattletrap.Type.I64 as I64
import qualified Rattletrap.Utility.Json as Json

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

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

instance Json.ToJSON Int64 where
  toJSON :: Int64 -> Value
toJSON = forall a. ToJSON a => a -> Value
Json.toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> I64
value

schema :: Schema.Schema
schema :: Schema
schema = String -> Value -> Schema
Schema.named String
"attribute-int64" forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
I64.schema

putInt64Attribute :: Int64 -> BitPut.BitPut
putInt64Attribute :: Int64 -> BitPut
putInt64Attribute Int64
int64Attribute = I64 -> BitPut
I64.bitPut (Int64 -> I64
value Int64
int64Attribute)

bitGet :: BitGet.BitGet Int64
bitGet :: BitGet Int64
bitGet = forall a. String -> BitGet a -> BitGet a
BitGet.label String
"Int64" forall a b. (a -> b) -> a -> b
$ do
  I64
value <- forall a. String -> BitGet a -> BitGet a
BitGet.label String
"value" BitGet I64
I64.bitGet
  forall (f :: * -> *) a. Applicative f => a -> f a
pure Int64 {I64
value :: I64
value :: I64
value}