module Rattletrap.Type.ClassMapping 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 ClassMapping = ClassMapping
  { ClassMapping -> Str
name :: Str.Str
  , ClassMapping -> U32
streamId :: U32.U32
  }
  deriving (ClassMapping -> ClassMapping -> Bool
(ClassMapping -> ClassMapping -> Bool)
-> (ClassMapping -> ClassMapping -> Bool) -> Eq ClassMapping
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClassMapping -> ClassMapping -> Bool
$c/= :: ClassMapping -> ClassMapping -> Bool
== :: ClassMapping -> ClassMapping -> Bool
$c== :: ClassMapping -> ClassMapping -> Bool
Eq, Int -> ClassMapping -> ShowS
[ClassMapping] -> ShowS
ClassMapping -> String
(Int -> ClassMapping -> ShowS)
-> (ClassMapping -> String)
-> ([ClassMapping] -> ShowS)
-> Show ClassMapping
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClassMapping] -> ShowS
$cshowList :: [ClassMapping] -> ShowS
show :: ClassMapping -> String
$cshow :: ClassMapping -> String
showsPrec :: Int -> ClassMapping -> ShowS
$cshowsPrec :: Int -> ClassMapping -> ShowS
Show)

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

instance Json.ToJSON ClassMapping where
  toJSON :: ClassMapping -> Value
toJSON ClassMapping
x =
    [Pair] -> Value
Json.object [String -> Str -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"name" (Str -> Pair) -> Str -> Pair
forall a b. (a -> b) -> a -> b
$ ClassMapping -> Str
name ClassMapping
x, String -> U32 -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"stream_id" (U32 -> Pair) -> U32 -> Pair
forall a b. (a -> b) -> a -> b
$ ClassMapping -> U32
streamId ClassMapping
x]

schema :: Schema.Schema
schema :: Schema
schema = String -> Value -> Schema
Schema.named String
"classMapping" (Value -> Schema) -> Value -> Schema
forall a b. (a -> b) -> a -> b
$ [(Pair, Bool)] -> Value
Schema.object
  [ (String -> Value -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"name" (Value -> Pair) -> Value -> Pair
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
Str.schema, Bool
True)
  , (String -> Value -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"stream_id" (Value -> Pair) -> Value -> Pair
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U32.schema, Bool
True)
  ]

bytePut :: ClassMapping -> BytePut.BytePut
bytePut :: ClassMapping -> BytePut
bytePut ClassMapping
x = Str -> BytePut
Str.bytePut (ClassMapping -> Str
name ClassMapping
x) BytePut -> BytePut -> BytePut
forall a. Semigroup a => a -> a -> a
<> U32 -> BytePut
U32.bytePut (ClassMapping -> U32
streamId ClassMapping
x)

byteGet :: ByteGet.ByteGet ClassMapping
byteGet :: ByteGet ClassMapping
byteGet = do
  Str
name <- ByteGet Str
Str.byteGet
  U32
streamId <- ByteGet U32
U32.byteGet
  ClassMapping -> ByteGet ClassMapping
forall (f :: * -> *) a. Applicative f => a -> f a
pure ClassMapping :: Str -> U32 -> ClassMapping
ClassMapping { Str
name :: Str
name :: Str
name, U32
streamId :: U32
streamId :: U32
streamId }