module Rattletrap.Type.Header where

import qualified Rattletrap.ByteGet as ByteGet
import qualified Rattletrap.BytePut as BytePut
import qualified Rattletrap.Schema as Schema
import qualified Rattletrap.Type.Dictionary as Dictionary
import qualified Rattletrap.Type.Property as Property
import qualified Rattletrap.Type.Str as Str
import qualified Rattletrap.Type.U32 as U32
import qualified Rattletrap.Utility.Json as Json
import Rattletrap.Utility.Monad

-- | Contains high-level metadata about a 'Rattletrap.Replay.Replay'.
data Header = Header
  { Header -> U32
engineVersion :: U32.U32
  -- ^ The "major" ("engine") version number.
  , Header -> U32
licenseeVersion :: U32.U32
  -- ^ The "minor" ("licensee") version number.
  , Header -> Maybe U32
patchVersion :: Maybe U32.U32
  -- ^ The "patch" ("net") version number.
  , Header -> Str
label :: Str.Str
  -- ^ Always @TAGame.Replay_Soccar_TA@.
  , Header -> Dictionary Property
properties :: Dictionary.Dictionary Property.Property
  -- ^ These properties determine how a replay will look in the list of
  -- replays in-game. One element is required for the replay to show up:
  --
  -- - MapName: This is a 'Rattletrap.PropertyValue.NameProperty' with a
  --   case-insensitive map identifier, like @Stadium_P@.
  --
  -- There are many other properties that affect how the replay looks in the
  -- list of replays.
  --
  -- - Date: A 'Rattletrap.PropertyValue.StrProperty' with the format
  --   @YYYY-mm-dd:HH-MM@. Dates are not validated, but the month must be
  --   between 1 and 12 to show up. The hour is shown modulo 12 with AM or PM.
  -- - MatchType: A 'Rattletrap.PropertyValue.NameProperty'. If this is not
  --   one of the expected values, nothing will be shown next to the replay's
  --   map. The expected values are: @Online@, @Offline@, @Private@, and
  --   @Season@.
  -- - NumFrames: This 'Rattletrap.PropertyValue.IntProperty' is used to
  --   calculate the length of the match. There are 30 frames per second,
  --   a typical 5-minute match has about 9,000 frames.
  -- - PrimaryPlayerTeam: This is an 'Rattletrap.PropertyValue.IntProperty'.
  --   It is either 0 (blue) or 1 (orange). Any other value is ignored. If
  --   this would be 0, you don't have to set it at all.
  -- - ReplayName: An optional 'Rattletrap.PropertyValue.StrProperty' with a
  --   user-supplied name for the replay.
  -- - Team0Score: The blue team's score as an
  --   'Rattletrap.PropertyValue.IntProperty'. Can be omitted if the score is
  --   0.
  -- - Team1Score: The orange team's score as an
  --   'Rattletrap.PropertyValue.IntProperty'. Can also be omitted if the
  --   score is 0.
  -- - TeamSize: An 'Rattletrap.PropertyValue.IntProperty' with the number of
  --   players per team. This value is not validated, so you can put absurd
  --   values like 99. To get an "unfair" team size like 1v4, you must set the
  --   bUnfairBots 'Rattletrap.PropertyValue.BoolProperty' to @True@.
  }
  deriving (Header -> Header -> Bool
(Header -> Header -> Bool)
-> (Header -> Header -> Bool) -> Eq Header
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Header -> Header -> Bool
$c/= :: Header -> Header -> Bool
== :: Header -> Header -> Bool
$c== :: Header -> Header -> Bool
Eq, Int -> Header -> ShowS
[Header] -> ShowS
Header -> String
(Int -> Header -> ShowS)
-> (Header -> String) -> ([Header] -> ShowS) -> Show Header
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Header] -> ShowS
$cshowList :: [Header] -> ShowS
show :: Header -> String
$cshow :: Header -> String
showsPrec :: Int -> Header -> ShowS
$cshowsPrec :: Int -> Header -> ShowS
Show)

instance Json.FromJSON Header where
  parseJSON :: Value -> Parser Header
parseJSON = String -> (Object -> Parser Header) -> Value -> Parser Header
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Json.withObject String
"Header" ((Object -> Parser Header) -> Value -> Parser Header)
-> (Object -> Parser Header) -> Value -> Parser Header
forall a b. (a -> b) -> a -> b
$ \Object
object -> do
    U32
engineVersion <- Object -> String -> Parser U32
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"engine_version"
    U32
licenseeVersion <- Object -> String -> Parser U32
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"licensee_version"
    Maybe U32
patchVersion <- Object -> String -> Parser (Maybe U32)
forall value.
FromJSON value =>
Object -> String -> Parser (Maybe value)
Json.optional Object
object String
"patch_version"
    Str
label <- Object -> String -> Parser Str
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"label"
    Dictionary Property
properties <- Object -> String -> Parser (Dictionary Property)
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"properties"
    Header -> Parser Header
forall (f :: * -> *) a. Applicative f => a -> f a
pure Header :: U32 -> U32 -> Maybe U32 -> Str -> Dictionary Property -> Header
Header
      { U32
engineVersion :: U32
engineVersion :: U32
engineVersion
      , U32
licenseeVersion :: U32
licenseeVersion :: U32
licenseeVersion
      , Maybe U32
patchVersion :: Maybe U32
patchVersion :: Maybe U32
patchVersion
      , Str
label :: Str
label :: Str
label
      , Dictionary Property
properties :: Dictionary Property
properties :: Dictionary Property
properties
      }

instance Json.ToJSON Header where
  toJSON :: Header -> Value
toJSON Header
x = [Pair] -> Value
Json.object
    [ String -> U32 -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"engine_version" (U32 -> Pair) -> U32 -> Pair
forall a b. (a -> b) -> a -> b
$ Header -> U32
engineVersion Header
x
    , String -> U32 -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"licensee_version" (U32 -> Pair) -> U32 -> Pair
forall a b. (a -> b) -> a -> b
$ Header -> U32
licenseeVersion Header
x
    , String -> Maybe U32 -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"patch_version" (Maybe U32 -> Pair) -> Maybe U32 -> Pair
forall a b. (a -> b) -> a -> b
$ Header -> Maybe U32
patchVersion Header
x
    , String -> Str -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"label" (Str -> Pair) -> Str -> Pair
forall a b. (a -> b) -> a -> b
$ Header -> Str
label Header
x
    , String -> Dictionary Property -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"properties" (Dictionary Property -> Pair) -> Dictionary Property -> Pair
forall a b. (a -> b) -> a -> b
$ Header -> Dictionary Property
properties Header
x
    ]

schema :: Schema.Schema
schema :: Schema
schema = String -> Value -> Schema
Schema.named String
"header" (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
"engine_version" (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
"licensee_version" (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
"patch_version" (Value -> Pair) -> (Schema -> Value) -> Schema -> Pair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Schema -> Value
Schema.json (Schema -> Pair) -> Schema -> Pair
forall a b. (a -> b) -> a -> b
$ Schema -> Schema
Schema.maybe Schema
U32.schema, Bool
False)
  , (String -> Value -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"label" (Value -> Pair) -> Value -> Pair
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
Str.schema, Bool
True)
  , ( String -> Value -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"properties" (Value -> Pair) -> (Schema -> Value) -> Schema -> Pair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Schema -> Value
Schema.json (Schema -> Pair) -> Schema -> Pair
forall a b. (a -> b) -> a -> b
$ Schema -> Schema
Dictionary.schema Schema
Property.schema
    , Bool
True
    )
  ]

bytePut :: Header -> BytePut.BytePut
bytePut :: Header -> BytePut
bytePut Header
x =
  U32 -> BytePut
U32.bytePut (Header -> U32
engineVersion Header
x)
    BytePut -> BytePut -> BytePut
forall a. Semigroup a => a -> a -> a
<> U32 -> BytePut
U32.bytePut (Header -> U32
licenseeVersion Header
x)
    BytePut -> BytePut -> BytePut
forall a. Semigroup a => a -> a -> a
<> (U32 -> BytePut) -> Maybe U32 -> BytePut
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap U32 -> BytePut
U32.bytePut (Header -> Maybe U32
patchVersion Header
x)
    BytePut -> BytePut -> BytePut
forall a. Semigroup a => a -> a -> a
<> Str -> BytePut
Str.bytePut (Header -> Str
label Header
x)
    BytePut -> BytePut -> BytePut
forall a. Semigroup a => a -> a -> a
<> (Property -> BytePut) -> Dictionary Property -> BytePut
forall a. (a -> BytePut) -> Dictionary a -> BytePut
Dictionary.bytePut Property -> BytePut
Property.bytePut (Header -> Dictionary Property
properties Header
x)

byteGet :: ByteGet.ByteGet Header
byteGet :: ByteGet Header
byteGet = do
  (U32
major, U32
minor) <- (,) (U32 -> U32 -> (U32, U32))
-> Get ByteString Identity U32
-> Get ByteString Identity (U32 -> (U32, U32))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get ByteString Identity U32
U32.byteGet Get ByteString Identity (U32 -> (U32, U32))
-> Get ByteString Identity U32
-> Get ByteString Identity (U32, U32)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get ByteString Identity U32
U32.byteGet
  U32 -> U32 -> Maybe U32 -> Str -> Dictionary Property -> Header
Header U32
major U32
minor
    (Maybe U32 -> Str -> Dictionary Property -> Header)
-> Get ByteString Identity (Maybe U32)
-> Get ByteString Identity (Str -> Dictionary Property -> Header)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool
-> Get ByteString Identity U32
-> Get ByteString Identity (Maybe U32)
forall (m :: * -> *) a. Applicative m => Bool -> m a -> m (Maybe a)
whenMaybe
          (U32 -> Word32
U32.toWord32 U32
major Word32 -> Word32 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word32
868 Bool -> Bool -> Bool
&& U32 -> Word32
U32.toWord32 U32
minor Word32 -> Word32 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word32
18)
          Get ByteString Identity U32
U32.byteGet
    Get ByteString Identity (Str -> Dictionary Property -> Header)
-> Get ByteString Identity Str
-> Get ByteString Identity (Dictionary Property -> Header)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get ByteString Identity Str
Str.byteGet
    Get ByteString Identity (Dictionary Property -> Header)
-> Get ByteString Identity (Dictionary Property) -> ByteGet Header
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ByteGet Property -> Get ByteString Identity (Dictionary Property)
forall a. ByteGet a -> ByteGet (Dictionary a)
Dictionary.byteGet ByteGet Property
Property.byteGet