module Rattletrap.Type.Mark where

import qualified Rattletrap.ByteGet as ByteGet
import qualified Rattletrap.BytePut as BytePut
import qualified Rattletrap.Schema as Schema
import qualified Rattletrap.Type.Str as Str
import qualified Rattletrap.Type.U32 as U32
import qualified Rattletrap.Utility.Json as Json

data Mark = Mark
  { -- | Which type of mark this is, like @Team0Goal@.
    Mark -> Str
value :: Str.Str,
    -- | Which frame this mark belongs to, starting from 0.
    Mark -> U32
frame :: U32.U32
  }
  deriving (Mark -> Mark -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Mark -> Mark -> Bool
$c/= :: Mark -> Mark -> Bool
== :: Mark -> Mark -> Bool
$c== :: Mark -> Mark -> Bool
Eq, Int -> Mark -> ShowS
[Mark] -> ShowS
Mark -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Mark] -> ShowS
$cshowList :: [Mark] -> ShowS
show :: Mark -> String
$cshow :: Mark -> String
showsPrec :: Int -> Mark -> ShowS
$cshowsPrec :: Int -> Mark -> ShowS
Show)

instance Json.FromJSON Mark where
  parseJSON :: Value -> Parser Mark
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
Json.withObject String
"Mark" forall a b. (a -> b) -> a -> b
$ \Object
object -> do
    Str
value <- forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"value"
    U32
frame <- forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"frame"
    forall (f :: * -> *) a. Applicative f => a -> f a
pure Mark {Str
value :: Str
value :: Str
value, U32
frame :: U32
frame :: U32
frame}

instance Json.ToJSON Mark where
  toJSON :: Mark -> Value
toJSON Mark
x =
    [(Key, Value)] -> Value
Json.object [forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"value" forall a b. (a -> b) -> a -> b
$ Mark -> Str
value Mark
x, forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"frame" forall a b. (a -> b) -> a -> b
$ Mark -> U32
frame Mark
x]

schema :: Schema.Schema
schema :: Schema
schema =
  String -> Value -> Schema
Schema.named String
"mark" 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
"value" forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
Str.schema, Bool
True),
        (forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"frame" forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U32.schema, Bool
True)
      ]

bytePut :: Mark -> BytePut.BytePut
bytePut :: Mark -> BytePut
bytePut Mark
x = Str -> BytePut
Str.bytePut (Mark -> Str
value Mark
x) forall a. Semigroup a => a -> a -> a
<> U32 -> BytePut
U32.bytePut (Mark -> U32
frame Mark
x)

byteGet :: ByteGet.ByteGet Mark
byteGet :: ByteGet Mark
byteGet = forall a. String -> ByteGet a -> ByteGet a
ByteGet.label String
"Mark" forall a b. (a -> b) -> a -> b
$ do
  Str
value <- forall a. String -> ByteGet a -> ByteGet a
ByteGet.label String
"value" ByteGet Str
Str.byteGet
  U32
frame <- forall a. String -> ByteGet a -> ByteGet a
ByteGet.label String
"frame" ByteGet U32
U32.byteGet
  forall (f :: * -> *) a. Applicative f => a -> f a
pure Mark {Str
value :: Str
value :: Str
value, U32
frame :: U32
frame :: U32
frame}