-- | This module provides helper functions for converting replays to and from
-- both their binary format and JSON.
module Rattletrap.Utility.Helper
  ( decodeReplayFile
  , encodeReplayJson
  , decodeReplayJson
  , encodeReplayFile
  ) where

import qualified Rattletrap.ByteGet as ByteGet
import qualified Rattletrap.BytePut as BytePut
import qualified Rattletrap.Type.Content as Content
import qualified Rattletrap.Type.Replay as Replay
import qualified Rattletrap.Type.Section as Section

import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Encode.Pretty as Aeson
import qualified Data.ByteString as Bytes
import qualified Data.ByteString.Lazy as LazyBytes

-- | Parses a raw replay.
decodeReplayFile
  :: Bool -> Bool -> Bytes.ByteString -> Either String Replay.Replay
decodeReplayFile :: Bool -> Bool -> ByteString -> Either String Replay
decodeReplayFile Bool
fast = ByteGet Replay -> ByteString -> Either String Replay
forall a. ByteGet a -> ByteString -> Either String a
ByteGet.run (ByteGet Replay -> ByteString -> Either String Replay)
-> (Bool -> ByteGet Replay)
-> Bool
-> ByteString
-> Either String Replay
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Bool -> ByteGet Replay
Replay.byteGet Bool
fast

-- | Encodes a replay as JSON.
encodeReplayJson :: Replay.Replay -> LazyBytes.ByteString
encodeReplayJson :: Replay -> ByteString
encodeReplayJson = Config -> Replay -> ByteString
forall a. ToJSON a => Config -> a -> ByteString
Aeson.encodePretty' Config
Aeson.defConfig
  { confCompare :: Text -> Text -> Ordering
Aeson.confCompare = Text -> Text -> Ordering
forall a. Ord a => a -> a -> Ordering
compare
  , confIndent :: Indent
Aeson.confIndent = Indent
Aeson.Tab
  , confTrailingNewline :: Bool
Aeson.confTrailingNewline = Bool
True
  }

-- | Parses a JSON replay.
decodeReplayJson :: Bytes.ByteString -> Either String Replay.Replay
decodeReplayJson :: ByteString -> Either String Replay
decodeReplayJson = ByteString -> Either String Replay
forall a. FromJSON a => ByteString -> Either String a
Aeson.eitherDecodeStrict'

-- | Encodes a raw replay.
encodeReplayFile :: Bool -> Replay.Replay -> LazyBytes.ByteString
encodeReplayFile :: Bool -> Replay -> ByteString
encodeReplayFile Bool
fast Replay
replay =
  BytePut -> ByteString
BytePut.toLazyByteString (BytePut -> ByteString)
-> (Replay -> BytePut) -> Replay -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Replay -> BytePut
Replay.bytePut (Replay -> ByteString) -> Replay -> ByteString
forall a b. (a -> b) -> a -> b
$ if Bool
fast
    then Replay
replay
      { content :: Section Content
Replay.content = (Content -> BytePut) -> Content -> Section Content
forall a. (a -> BytePut) -> a -> Section a
Section.create Content -> BytePut
Content.bytePut Content
Content.empty
      }
    else Replay
replay