module Rattletrap.Utility.Helper where
import qualified Rattletrap.ByteGet as ByteGet
import qualified Rattletrap.BytePut as BytePut
import qualified Rattletrap.Exception.InvalidJson as InvalidJson
import qualified Rattletrap.Type.Content as Content
import qualified Rattletrap.Type.Replay as Replay
import qualified Rattletrap.Type.Section as Section
import qualified Rattletrap.Utility.Json as Json
import qualified Control.Exception as Exception
import qualified Data.Bifunctor as Bifunctor
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Lazy as LazyByteString
decodeReplayFile
:: Bool
-> Bool
-> ByteString.ByteString
-> Either ([String], Exception.SomeException) Replay.Replay
decodeReplayFile :: Bool
-> Bool -> ByteString -> Either ([String], SomeException) Replay
decodeReplayFile Bool
fast = forall a.
ByteGet a -> ByteString -> Either ([String], SomeException) a
ByteGet.run forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Bool -> ByteGet Replay
Replay.byteGet Bool
fast
encodeReplayJson :: Replay.Replay -> LazyByteString.ByteString
encodeReplayJson :: Replay -> ByteString
encodeReplayJson = forall a. ToJSON a => a -> ByteString
Json.encodePretty
decodeReplayJson
:: ByteString.ByteString
-> Either ([String], Exception.SomeException) Replay.Replay
decodeReplayJson :: ByteString -> Either ([String], SomeException) Replay
decodeReplayJson =
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
Bifunctor.first ((,) [] forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e. Exception e => e -> SomeException
Exception.toException forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> InvalidJson
InvalidJson.InvalidJson)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromJSON a => ByteString -> Either String a
Json.decode
encodeReplayFile :: Bool -> Replay.Replay -> LazyByteString.ByteString
encodeReplayFile :: Bool -> Replay -> ByteString
encodeReplayFile Bool
fast Replay
replay =
BytePut -> ByteString
BytePut.toLazyByteString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Replay -> BytePut
Replay.bytePut forall a b. (a -> b) -> a -> b
$ if Bool
fast
then Replay
replay
{ content :: Section Content
Replay.content = forall a. (a -> BytePut) -> a -> Section a
Section.create Content -> BytePut
Content.bytePut Content
Content.empty
}
else Replay
replay