module Rattletrap.Type.Replication where 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.List as RList import qualified Rattletrap.Type.ReplicationValue as ReplicationValue 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 Replication = Replication { Replication -> CompressedWord actorId :: CompressedWord.CompressedWord, Replication -> ReplicationValue value :: ReplicationValue.ReplicationValue } deriving (Replication -> Replication -> Bool (Replication -> Replication -> Bool) -> (Replication -> Replication -> Bool) -> Eq Replication forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: Replication -> Replication -> Bool == :: Replication -> Replication -> Bool $c/= :: Replication -> Replication -> Bool /= :: Replication -> Replication -> Bool Eq, Int -> Replication -> ShowS [Replication] -> ShowS Replication -> String (Int -> Replication -> ShowS) -> (Replication -> String) -> ([Replication] -> ShowS) -> Show Replication forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> Replication -> ShowS showsPrec :: Int -> Replication -> ShowS $cshow :: Replication -> String show :: Replication -> String $cshowList :: [Replication] -> ShowS showList :: [Replication] -> ShowS Show) instance Json.FromJSON Replication where parseJSON :: Value -> Parser Replication parseJSON = String -> (Object -> Parser Replication) -> Value -> Parser Replication forall a. String -> (Object -> Parser a) -> Value -> Parser a Json.withObject String "Replication" ((Object -> Parser Replication) -> Value -> Parser Replication) -> (Object -> Parser Replication) -> Value -> Parser Replication forall a b. (a -> b) -> a -> b $ \Object object -> do actorId <- Object -> String -> Parser CompressedWord forall value. FromJSON value => Object -> String -> Parser value Json.required Object object String "actor_id" value <- Json.required object "value" pure Replication {actorId, value} instance Json.ToJSON Replication where toJSON :: Replication -> Value toJSON Replication x = [(Key, Value)] -> Value Json.object [String -> CompressedWord -> (Key, Value) forall value e p. (ToJSON value, KeyValue e p) => String -> value -> p Json.pair String "actor_id" (CompressedWord -> (Key, Value)) -> CompressedWord -> (Key, Value) forall a b. (a -> b) -> a -> b $ Replication -> CompressedWord actorId Replication x, String -> ReplicationValue -> (Key, Value) forall value e p. (ToJSON value, KeyValue e p) => String -> value -> p Json.pair String "value" (ReplicationValue -> (Key, Value)) -> ReplicationValue -> (Key, Value) forall a b. (a -> b) -> a -> b $ Replication -> ReplicationValue value Replication x] schema :: Schema.Schema schema :: Schema schema = String -> Value -> Schema Schema.named String "replication" (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 "actor_id" (Value -> (Key, Value)) -> Value -> (Key, Value) forall a b. (a -> b) -> a -> b $ Schema -> Value Schema.ref Schema CompressedWord.schema, Bool True), (String -> Value -> (Key, Value) forall value e p. (ToJSON value, KeyValue e p) => String -> value -> p Json.pair String "value" (Value -> (Key, Value)) -> Value -> (Key, Value) forall a b. (a -> b) -> a -> b $ Schema -> Value Schema.ref Schema ReplicationValue.schema, Bool True) ] putReplications :: RList.List Replication -> BitPut.BitPut putReplications :: List Replication -> BitPut putReplications List Replication xs = (Replication -> BitPut) -> [Replication] -> BitPut forall m a. Monoid m => (a -> m) -> [a] -> m forall (t :: * -> *) m a. (Foldable t, Monoid m) => (a -> m) -> t a -> m foldMap (\Replication x -> Bool -> BitPut BitPut.bool Bool True BitPut -> BitPut -> BitPut forall a. Semigroup a => a -> a -> a <> Replication -> BitPut bitPut Replication x) (List Replication -> [Replication] forall a. List a -> [a] RList.toList List Replication xs) BitPut -> BitPut -> BitPut forall a. Semigroup a => a -> a -> a <> Bool -> BitPut BitPut.bool Bool False bitPut :: Replication -> BitPut.BitPut bitPut :: Replication -> BitPut bitPut Replication replication = CompressedWord -> BitPut CompressedWord.bitPut (Replication -> CompressedWord actorId Replication replication) BitPut -> BitPut -> BitPut forall a. Semigroup a => a -> a -> a <> ReplicationValue -> BitPut ReplicationValue.bitPut (Replication -> ReplicationValue value Replication replication) decodeReplicationsBits :: Maybe Str.Str -> Version.Version -> Maybe Str.Str -> Word -> ClassAttributeMap.ClassAttributeMap -> Map.Map CompressedWord.CompressedWord U32.U32 -> BitGet.BitGet ( Map.Map CompressedWord.CompressedWord U32.U32, RList.List Replication ) decodeReplicationsBits :: Maybe Str -> Version -> Maybe Str -> Word -> ClassAttributeMap -> Map CompressedWord U32 -> BitGet (Map CompressedWord U32, List Replication) decodeReplicationsBits Maybe Str matchType Version version Maybe Str buildVersion Word limit ClassAttributeMap classes Map CompressedWord U32 actorMap = Maybe Str -> Version -> Maybe Str -> Word -> ClassAttributeMap -> Map CompressedWord U32 -> Int -> [Replication] -> BitGet (Map CompressedWord U32, List Replication) decodeReplicationsBitsWith Maybe Str matchType Version version Maybe Str buildVersion Word limit ClassAttributeMap classes Map CompressedWord U32 actorMap Int 0 [] decodeReplicationsBitsWith :: Maybe Str.Str -> Version.Version -> Maybe Str.Str -> Word -> ClassAttributeMap.ClassAttributeMap -> Map.Map CompressedWord.CompressedWord U32.U32 -> Int -> [Replication] -> BitGet.BitGet ( Map.Map CompressedWord.CompressedWord U32.U32, RList.List Replication ) decodeReplicationsBitsWith :: Maybe Str -> Version -> Maybe Str -> Word -> ClassAttributeMap -> Map CompressedWord U32 -> Int -> [Replication] -> BitGet (Map CompressedWord U32, List Replication) decodeReplicationsBitsWith Maybe Str matchType Version version Maybe Str buildVersion Word limit ClassAttributeMap classes Map CompressedWord U32 actorMap Int index [Replication] replications = do hasReplication <- BitGet Bool BitGet.bool if hasReplication then do (newActorMap, replication) <- BitGet.label ("element (" <> show index <> ")") $ bitGet matchType version buildVersion limit classes actorMap decodeReplicationsBitsWith matchType version buildVersion limit classes newActorMap (index + 1) $ replication : replications else pure (actorMap, RList.fromList $ reverse replications) bitGet :: Maybe Str.Str -> Version.Version -> Maybe Str.Str -> Word -> ClassAttributeMap.ClassAttributeMap -> Map.Map CompressedWord.CompressedWord U32.U32 -> BitGet.BitGet ( Map.Map CompressedWord.CompressedWord U32.U32, Replication ) bitGet :: Maybe Str -> Version -> Maybe Str -> Word -> ClassAttributeMap -> Map CompressedWord U32 -> BitGet (Map CompressedWord U32, Replication) bitGet Maybe Str matchType Version version Maybe Str buildVersion Word limit ClassAttributeMap classes Map CompressedWord U32 actorMap = String -> BitGet (Map CompressedWord U32, Replication) -> BitGet (Map CompressedWord U32, Replication) forall a. String -> BitGet a -> BitGet a BitGet.label String "Replication" (BitGet (Map CompressedWord U32, Replication) -> BitGet (Map CompressedWord U32, Replication)) -> BitGet (Map CompressedWord U32, Replication) -> BitGet (Map CompressedWord U32, Replication) forall a b. (a -> b) -> a -> b $ do actorId <- String -> BitGet CompressedWord -> BitGet CompressedWord forall a. String -> BitGet a -> BitGet a BitGet.label String "actorId" (BitGet CompressedWord -> BitGet CompressedWord) -> BitGet CompressedWord -> BitGet CompressedWord forall a b. (a -> b) -> a -> b $ Word -> BitGet CompressedWord CompressedWord.bitGet Word limit (newActorMap, value) <- BitGet.label "value" $ ReplicationValue.bitGet matchType version buildVersion classes actorId actorMap pure (newActorMap, Replication {actorId, value})