module Rattletrap.Type.Property.Struct where

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

data Struct a = Struct
  { forall a. Struct a -> Str
name :: Str.Str,
    forall a. Struct a -> Dictionary a
fields :: Dictionary.Dictionary a
  }
  deriving (Struct a -> Struct a -> Bool
(Struct a -> Struct a -> Bool)
-> (Struct a -> Struct a -> Bool) -> Eq (Struct a)
forall a. Eq a => Struct a -> Struct a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Struct a -> Struct a -> Bool
== :: Struct a -> Struct a -> Bool
$c/= :: forall a. Eq a => Struct a -> Struct a -> Bool
/= :: Struct a -> Struct a -> Bool
Eq, Int -> Struct a -> ShowS
[Struct a] -> ShowS
Struct a -> String
(Int -> Struct a -> ShowS)
-> (Struct a -> String) -> ([Struct a] -> ShowS) -> Show (Struct a)
forall a. Show a => Int -> Struct a -> ShowS
forall a. Show a => [Struct a] -> ShowS
forall a. Show a => Struct a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Struct a -> ShowS
showsPrec :: Int -> Struct a -> ShowS
$cshow :: forall a. Show a => Struct a -> String
show :: Struct a -> String
$cshowList :: forall a. Show a => [Struct a] -> ShowS
showList :: [Struct a] -> ShowS
Show)

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

instance (Json.ToJSON a) => Json.ToJSON (Struct a) where
  toJSON :: Struct a -> Value
toJSON Struct a
x =
    [(Key, Value)] -> Value
Json.object
      [ String -> Str -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"name" (Str -> (Key, Value)) -> Str -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Struct a -> Str
forall a. Struct a -> Str
name Struct a
x,
        String -> Dictionary a -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"fields" (Dictionary a -> (Key, Value)) -> Dictionary a -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Struct a -> Dictionary a
forall a. Struct a -> Dictionary a
fields Struct a
x
      ]

schema :: Schema.Schema -> Schema.Schema
schema :: Schema -> Schema
schema Schema
s =
  String -> Value -> Schema
Schema.named String
"property-struct" (Value -> Schema) -> Value -> Schema
forall a b. (a -> b) -> a -> b
$
    [((Key, Value), Bool)] -> Value
Schema.object
      [ (String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"name" (Value -> (Key, Value)) -> Value -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
Str.schema, Bool
True),
        (String -> Value -> (Key, Value)
forall value e p.
(ToJSON value, KeyValue e p) =>
String -> value -> p
Json.pair String
"fields" (Value -> (Key, Value)) -> Value -> (Key, Value)
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref (Schema -> Schema
Dictionary.schema Schema
s), Bool
True)
      ]

bytePut :: (a -> BytePut.BytePut) -> Struct a -> BytePut.BytePut
bytePut :: forall a. (a -> BytePut) -> Struct a -> BytePut
bytePut a -> BytePut
p Struct a
x =
  Str -> BytePut
Str.bytePut (Struct a -> Str
forall a. Struct a -> Str
name Struct a
x)
    BytePut -> BytePut -> BytePut
forall a. Semigroup a => a -> a -> a
<> (a -> BytePut) -> Dictionary a -> BytePut
forall a. (a -> BytePut) -> Dictionary a -> BytePut
Dictionary.bytePut a -> BytePut
p (Struct a -> Dictionary a
forall a. Struct a -> Dictionary a
fields Struct a
x)

byteGet :: ByteGet.ByteGet a -> ByteGet.ByteGet (Struct a)
byteGet :: forall a. ByteGet a -> ByteGet (Struct a)
byteGet ByteGet a
g = String -> ByteGet (Struct a) -> ByteGet (Struct a)
forall a. String -> ByteGet a -> ByteGet a
ByteGet.label String
"Struct" (ByteGet (Struct a) -> ByteGet (Struct a))
-> ByteGet (Struct a) -> ByteGet (Struct a)
forall a b. (a -> b) -> a -> b
$ do
  Str
name <- String -> ByteGet Str -> ByteGet Str
forall a. String -> ByteGet a -> ByteGet a
ByteGet.label String
"name" ByteGet Str
Str.byteGet
  Dictionary a
fields <- String -> ByteGet (Dictionary a) -> ByteGet (Dictionary a)
forall a. String -> ByteGet a -> ByteGet a
ByteGet.label String
"fields" (ByteGet (Dictionary a) -> ByteGet (Dictionary a))
-> ByteGet (Dictionary a) -> ByteGet (Dictionary a)
forall a b. (a -> b) -> a -> b
$ ByteGet a -> ByteGet (Dictionary a)
forall a. ByteGet a -> ByteGet (Dictionary a)
Dictionary.byteGet ByteGet a
g
  Struct a -> ByteGet (Struct a)
forall a. a -> Get ByteString Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Struct {Str
name :: Str
name :: Str
name, Dictionary a
fields :: Dictionary a
fields :: Dictionary a
fields}