module Rattletrap.Type.Attribute.FlaggedByte where

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

data FlaggedByte = FlaggedByte
  { FlaggedByte -> Bool
flag :: Bool,
    FlaggedByte -> U8
byte :: U8.U8
  }
  deriving (FlaggedByte -> FlaggedByte -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FlaggedByte -> FlaggedByte -> Bool
$c/= :: FlaggedByte -> FlaggedByte -> Bool
== :: FlaggedByte -> FlaggedByte -> Bool
$c== :: FlaggedByte -> FlaggedByte -> Bool
Eq, Int -> FlaggedByte -> ShowS
[FlaggedByte] -> ShowS
FlaggedByte -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FlaggedByte] -> ShowS
$cshowList :: [FlaggedByte] -> ShowS
show :: FlaggedByte -> String
$cshow :: FlaggedByte -> String
showsPrec :: Int -> FlaggedByte -> ShowS
$cshowsPrec :: Int -> FlaggedByte -> ShowS
Show)

instance Json.FromJSON FlaggedByte where
  parseJSON :: Value -> Parser FlaggedByte
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
Json.withObject String
"FlaggedByte" forall a b. (a -> b) -> a -> b
$ \Object
object -> do
    Bool
flag <- forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"flag"
    U8
byte <- forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"byte"
    forall (f :: * -> *) a. Applicative f => a -> f a
pure FlaggedByte {Bool
flag :: Bool
flag :: Bool
flag, U8
byte :: U8
byte :: U8
byte}

instance Json.ToJSON FlaggedByte where
  toJSON :: FlaggedByte -> Value
toJSON FlaggedByte
x =
    [(Key, Value)] -> Value
Json.object [forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"flag" forall a b. (a -> b) -> a -> b
$ FlaggedByte -> Bool
flag FlaggedByte
x, forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"byte" forall a b. (a -> b) -> a -> b
$ FlaggedByte -> U8
byte FlaggedByte
x]

schema :: Schema.Schema
schema :: Schema
schema =
  String -> Value -> Schema
Schema.named String
"attribute-flagged-byte" forall a b. (a -> b) -> a -> b
$
    [((Key, Value), Bool)] -> Value
Schema.object
      [ (forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"flag" forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
Schema.boolean, Bool
True),
        (forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"byte" forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U8.schema, Bool
True)
      ]

bitPut :: FlaggedByte -> BitPut.BitPut
bitPut :: FlaggedByte -> BitPut
bitPut FlaggedByte
flaggedByteAttribute =
  Bool -> BitPut
BitPut.bool (FlaggedByte -> Bool
flag FlaggedByte
flaggedByteAttribute)
    forall a. Semigroup a => a -> a -> a
<> U8 -> BitPut
U8.bitPut (FlaggedByte -> U8
byte FlaggedByte
flaggedByteAttribute)

bitGet :: BitGet.BitGet FlaggedByte
bitGet :: BitGet FlaggedByte
bitGet = forall a. String -> BitGet a -> BitGet a
BitGet.label String
"FlaggedByte" forall a b. (a -> b) -> a -> b
$ do
  Bool
flag <- forall a. String -> BitGet a -> BitGet a
BitGet.label String
"flag" BitGet Bool
BitGet.bool
  U8
byte <- forall a. String -> BitGet a -> BitGet a
BitGet.label String
"byte" BitGet U8
U8.bitGet
  forall (f :: * -> *) a. Applicative f => a -> f a
pure FlaggedByte {Bool
flag :: Bool
flag :: Bool
flag, U8
byte :: U8
byte :: U8
byte}