module Rattletrap.Type.Section where

import qualified Rattletrap.ByteGet as ByteGet
import qualified Rattletrap.BytePut as BytePut
import qualified Rattletrap.Schema as Schema
import qualified Rattletrap.Type.U32 as U32
import qualified Rattletrap.Utility.Crc as Crc
import qualified Rattletrap.Utility.Json as Json

import qualified Control.Monad as Monad
import qualified Data.ByteString as ByteString
import qualified Data.Text as Text

-- | A section is a large piece of a 'Rattletrap.Replay.Replay'. It has a
-- 32-bit size (in bytes), a 32-bit CRC (see "Rattletrap.Utility.Crc"), and then a
-- bunch of data (the body). This interface is provided so that you don't have
-- to think about the size and CRC.
data Section a = Section
  { Section a -> U32
size :: U32.U32
  -- ^ read only
  , Section a -> U32
crc :: U32.U32
  -- ^ read only
  , Section a -> a
body :: a
  -- ^ The actual content in the section.
  }
  deriving (Section a -> Section a -> Bool
(Section a -> Section a -> Bool)
-> (Section a -> Section a -> Bool) -> Eq (Section a)
forall a. Eq a => Section a -> Section a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Section a -> Section a -> Bool
$c/= :: forall a. Eq a => Section a -> Section a -> Bool
== :: Section a -> Section a -> Bool
$c== :: forall a. Eq a => Section a -> Section a -> Bool
Eq, Int -> Section a -> ShowS
[Section a] -> ShowS
Section a -> String
(Int -> Section a -> ShowS)
-> (Section a -> String)
-> ([Section a] -> ShowS)
-> Show (Section a)
forall a. Show a => Int -> Section a -> ShowS
forall a. Show a => [Section a] -> ShowS
forall a. Show a => Section a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Section a] -> ShowS
$cshowList :: forall a. Show a => [Section a] -> ShowS
show :: Section a -> String
$cshow :: forall a. Show a => Section a -> String
showsPrec :: Int -> Section a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Section a -> ShowS
Show)

instance Json.FromJSON a => Json.FromJSON (Section a) where
  parseJSON :: Value -> Parser (Section a)
parseJSON = String
-> (Object -> Parser (Section a)) -> Value -> Parser (Section a)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Json.withObject String
"Section" ((Object -> Parser (Section a)) -> Value -> Parser (Section a))
-> (Object -> Parser (Section a)) -> Value -> Parser (Section a)
forall a b. (a -> b) -> a -> b
$ \Object
object -> do
    U32
size <- Object -> String -> Parser U32
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"size"
    U32
crc <- Object -> String -> Parser U32
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"crc"
    a
body <- Object -> String -> Parser a
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"body"
    Section a -> Parser (Section a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Section :: forall a. U32 -> U32 -> a -> Section a
Section { U32
size :: U32
size :: U32
size, U32
crc :: U32
crc :: U32
crc, a
body :: a
body :: a
body }

instance Json.ToJSON a => Json.ToJSON (Section a) where
  toJSON :: Section a -> Value
toJSON Section a
x = [Pair] -> Value
Json.object
    [ String -> U32 -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"size" (U32 -> Pair) -> U32 -> Pair
forall a b. (a -> b) -> a -> b
$ Section a -> U32
forall a. Section a -> U32
size Section a
x
    , String -> U32 -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"crc" (U32 -> Pair) -> U32 -> Pair
forall a b. (a -> b) -> a -> b
$ Section a -> U32
forall a. Section a -> U32
crc Section a
x
    , String -> a -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"body" (a -> Pair) -> a -> Pair
forall a b. (a -> b) -> a -> b
$ Section a -> a
forall a. Section a -> a
body Section a
x
    ]

schema :: Schema.Schema -> Schema.Schema
schema :: Schema -> Schema
schema Schema
s =
  String -> Value -> Schema
Schema.named (String
"section-" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
Text.unpack (Schema -> Text
Schema.name Schema
s)) (Value -> Schema) -> Value -> Schema
forall a b. (a -> b) -> a -> b
$ [(Pair, Bool)] -> Value
Schema.object
    [ (String -> Value -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"size" (Value -> Pair) -> Value -> Pair
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U32.schema, Bool
True)
    , (String -> Value -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"crc" (Value -> Pair) -> Value -> Pair
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U32.schema, Bool
True)
    , (String -> Value -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"body" (Value -> Pair) -> Value -> Pair
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
s, Bool
True)
    ]

create :: (a -> BytePut.BytePut) -> a -> Section a
create :: (a -> BytePut) -> a -> Section a
create a -> BytePut
encode a
body_ =
  let bytes :: ByteString
bytes = BytePut -> ByteString
BytePut.toByteString (BytePut -> ByteString) -> BytePut -> ByteString
forall a b. (a -> b) -> a -> b
$ a -> BytePut
encode a
body_
  in
    Section :: forall a. U32 -> U32 -> a -> Section a
Section
      { size :: U32
size = Word32 -> U32
U32.fromWord32 (Word32 -> U32) -> (Int -> Word32) -> Int -> U32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> U32) -> Int -> U32
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
ByteString.length ByteString
bytes
      , crc :: U32
crc = Word32 -> U32
U32.fromWord32 (Word32 -> U32) -> Word32 -> U32
forall a b. (a -> b) -> a -> b
$ ByteString -> Word32
Crc.compute ByteString
bytes
      , body :: a
body = a
body_
      }

-- | Given a way to put the 'body', puts a section. This will also put
-- the size and CRC.
bytePut :: (a -> BytePut.BytePut) -> Section a -> BytePut.BytePut
bytePut :: (a -> BytePut) -> Section a -> BytePut
bytePut a -> BytePut
putBody Section a
section =
  let
    rawBody :: ByteString
rawBody = BytePut -> ByteString
BytePut.toByteString (BytePut -> ByteString) -> (a -> BytePut) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> BytePut
putBody (a -> ByteString) -> a -> ByteString
forall a b. (a -> b) -> a -> b
$ Section a -> a
forall a. Section a -> a
body Section a
section
    size_ :: Int
size_ = ByteString -> Int
ByteString.length ByteString
rawBody
    crc_ :: Word32
crc_ = ByteString -> Word32
Crc.compute ByteString
rawBody
  in
    U32 -> BytePut
U32.bytePut (Word32 -> U32
U32.fromWord32 (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size_))
    BytePut -> BytePut -> BytePut
forall a. Semigroup a => a -> a -> a
<> U32 -> BytePut
U32.bytePut (Word32 -> U32
U32.fromWord32 Word32
crc_)
    BytePut -> BytePut -> BytePut
forall a. Semigroup a => a -> a -> a
<> ByteString -> BytePut
BytePut.byteString ByteString
rawBody

byteGet
  :: Bool -> (U32.U32 -> ByteGet.ByteGet a) -> ByteGet.ByteGet (Section a)
byteGet :: Bool -> (U32 -> ByteGet a) -> ByteGet (Section a)
byteGet Bool
skip U32 -> ByteGet a
getBody = do
  U32
size_ <- ByteGet U32
U32.byteGet
  U32
crc_ <- ByteGet U32
U32.byteGet
  ByteString
rawBody <- Int -> ByteGet ByteString
ByteGet.byteString (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (U32 -> Word32
U32.toWord32 U32
size_))
  Bool -> Get ByteString Identity () -> Get ByteString Identity ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
Monad.unless Bool
skip (Get ByteString Identity () -> Get ByteString Identity ())
-> Get ByteString Identity () -> Get ByteString Identity ()
forall a b. (a -> b) -> a -> b
$ do
    let actualCrc :: U32
actualCrc = Word32 -> U32
U32.fromWord32 (ByteString -> Word32
Crc.compute ByteString
rawBody)
    Bool -> Get ByteString Identity () -> Get ByteString Identity ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
Monad.when (U32
actualCrc U32 -> U32 -> Bool
forall a. Eq a => a -> a -> Bool
/= U32
crc_) (String -> Get ByteString Identity ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (U32 -> U32 -> String
crcMessage U32
actualCrc U32
crc_))
  a
body_ <- (String -> ByteGet a)
-> (a -> ByteGet a) -> Either String a -> ByteGet a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> ByteGet a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail a -> ByteGet a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String a -> ByteGet a) -> Either String a -> ByteGet a
forall a b. (a -> b) -> a -> b
$ ByteGet a -> ByteString -> Either String a
forall a. ByteGet a -> ByteString -> Either String a
ByteGet.run (U32 -> ByteGet a
getBody U32
size_) ByteString
rawBody
  Section a -> ByteGet (Section a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (U32 -> U32 -> a -> Section a
forall a. U32 -> U32 -> a -> Section a
Section U32
size_ U32
crc_ a
body_)

crcMessage :: U32.U32 -> U32.U32 -> String
crcMessage :: U32 -> U32 -> String
crcMessage U32
actual U32
expected = [String] -> String
unwords
  [ String
"[RT10] actual CRC"
  , U32 -> String
forall a. Show a => a -> String
show U32
actual
  , String
"does not match expected CRC"
  , U32 -> String
forall a. Show a => a -> String
show U32
expected
  ]