module Rattletrap.Type.ReplicationValue where

import qualified Data.Foldable as Foldable
import qualified Data.Map as Map
import qualified Rattletrap.BitGet as BitGet
import qualified Rattletrap.BitPut as BitPut
import qualified Rattletrap.Schema as Schema
import qualified Rattletrap.Type.ClassAttributeMap as ClassAttributeMap
import qualified Rattletrap.Type.CompressedWord as CompressedWord
import qualified Rattletrap.Type.Replication.Destroyed as Destroyed
import qualified Rattletrap.Type.Replication.Spawned as Spawned
import qualified Rattletrap.Type.Replication.Updated as Updated
import qualified Rattletrap.Type.Str as Str
import qualified Rattletrap.Type.U32 as U32
import qualified Rattletrap.Type.Version as Version
import qualified Rattletrap.Utility.Json as Json

data ReplicationValue
  = -- | Creates a new actor.
    Spawned Spawned.Spawned
  | -- | Updates an existing actor.
    Updated Updated.Updated
  | -- | Destroys an existing actor.
    Destroyed Destroyed.Destroyed
  deriving (ReplicationValue -> ReplicationValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReplicationValue -> ReplicationValue -> Bool
$c/= :: ReplicationValue -> ReplicationValue -> Bool
== :: ReplicationValue -> ReplicationValue -> Bool
$c== :: ReplicationValue -> ReplicationValue -> Bool
Eq, Int -> ReplicationValue -> ShowS
[ReplicationValue] -> ShowS
ReplicationValue -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReplicationValue] -> ShowS
$cshowList :: [ReplicationValue] -> ShowS
show :: ReplicationValue -> String
$cshow :: ReplicationValue -> String
showsPrec :: Int -> ReplicationValue -> ShowS
$cshowsPrec :: Int -> ReplicationValue -> ShowS
Show)

instance Json.FromJSON ReplicationValue where
  parseJSON :: Value -> Parser ReplicationValue
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
Json.withObject String
"ReplicationValue" forall a b. (a -> b) -> a -> b
$ \Object
object ->
    forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
Foldable.asum
      [ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Spawned -> ReplicationValue
Spawned forall a b. (a -> b) -> a -> b
$ forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"spawned",
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Updated -> ReplicationValue
Updated forall a b. (a -> b) -> a -> b
$ forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"updated",
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Destroyed -> ReplicationValue
Destroyed forall a b. (a -> b) -> a -> b
$ forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"destroyed"
      ]

instance Json.ToJSON ReplicationValue where
  toJSON :: ReplicationValue -> Value
toJSON ReplicationValue
x = case ReplicationValue
x of
    Spawned Spawned
y -> [(Key, Value)] -> Value
Json.object [forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"spawned" Spawned
y]
    Updated Updated
y -> [(Key, Value)] -> Value
Json.object [forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"updated" Updated
y]
    Destroyed Destroyed
y -> [(Key, Value)] -> Value
Json.object [forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"destroyed" Destroyed
y]

schema :: Schema.Schema
schema :: Schema
schema =
  String -> Value -> Schema
Schema.named String
"replicationValue" forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Value] -> Value
Schema.oneOf forall a b. (a -> b) -> a -> b
$
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
      (\(String
k, Schema
v) -> [((Key, Value), Bool)] -> Value
Schema.object [(forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
k forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
v, Bool
True)])
      [ (String
"spawned", Schema
Spawned.schema),
        (String
"updated", Schema
Updated.schema),
        (String
"destroyed", Schema
Destroyed.schema)
      ]

bitPut :: ReplicationValue -> BitPut.BitPut
bitPut :: ReplicationValue -> BitPut
bitPut ReplicationValue
value = case ReplicationValue
value of
  Spawned Spawned
x -> Bool -> BitPut
BitPut.bool Bool
True forall a. Semigroup a => a -> a -> a
<> Bool -> BitPut
BitPut.bool Bool
True forall a. Semigroup a => a -> a -> a
<> Spawned -> BitPut
Spawned.bitPut Spawned
x
  Updated Updated
x -> Bool -> BitPut
BitPut.bool Bool
True forall a. Semigroup a => a -> a -> a
<> Bool -> BitPut
BitPut.bool Bool
False forall a. Semigroup a => a -> a -> a
<> Updated -> BitPut
Updated.bitPut Updated
x
  Destroyed Destroyed
x -> Bool -> BitPut
BitPut.bool Bool
False forall a. Semigroup a => a -> a -> a
<> Destroyed -> BitPut
Destroyed.bitPut Destroyed
x

bitGet ::
  Maybe Str.Str ->
  Version.Version ->
  Maybe Str.Str ->
  ClassAttributeMap.ClassAttributeMap ->
  CompressedWord.CompressedWord ->
  Map.Map CompressedWord.CompressedWord U32.U32 ->
  BitGet.BitGet
    ( Map.Map CompressedWord.CompressedWord U32.U32,
      ReplicationValue
    )
bitGet :: Maybe Str
-> Version
-> Maybe Str
-> ClassAttributeMap
-> CompressedWord
-> Map CompressedWord U32
-> BitGet (Map CompressedWord U32, ReplicationValue)
bitGet Maybe Str
matchType Version
version Maybe Str
buildVersion ClassAttributeMap
classAttributeMap CompressedWord
actorId Map CompressedWord U32
actorMap =
  forall a. String -> BitGet a -> BitGet a
BitGet.label String
"ReplicationValue" forall a b. (a -> b) -> a -> b
$ do
    Bool
isOpen <- BitGet Bool
BitGet.bool
    if Bool
isOpen
      then do
        Bool
isNew <- BitGet Bool
BitGet.bool
        if Bool
isNew
          then do
            (Map CompressedWord U32
newActorMap, Spawned
spawned) <-
              Maybe Str
-> Version
-> ClassAttributeMap
-> CompressedWord
-> Map CompressedWord U32
-> BitGet (Map CompressedWord U32, Spawned)
Spawned.bitGet
                Maybe Str
matchType
                Version
version
                ClassAttributeMap
classAttributeMap
                CompressedWord
actorId
                Map CompressedWord U32
actorMap
            forall (f :: * -> *) a. Applicative f => a -> f a
pure (Map CompressedWord U32
newActorMap, Spawned -> ReplicationValue
Spawned Spawned
spawned)
          else do
            Updated
updated <-
              Version
-> Maybe Str
-> ClassAttributeMap
-> Map CompressedWord U32
-> CompressedWord
-> BitGet Updated
Updated.bitGet
                Version
version
                Maybe Str
buildVersion
                ClassAttributeMap
classAttributeMap
                Map CompressedWord U32
actorMap
                CompressedWord
actorId
            forall (f :: * -> *) a. Applicative f => a -> f a
pure (Map CompressedWord U32
actorMap, Updated -> ReplicationValue
Updated Updated
updated)
      else do
        Destroyed
destroyed <- BitGet Destroyed
Destroyed.bitGet
        forall (f :: * -> *) a. Applicative f => a -> f a
pure (Map CompressedWord U32
actorMap, Destroyed -> ReplicationValue
Destroyed Destroyed
destroyed)