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.Type.Version as Version
import qualified Rattletrap.Utility.Json as Json

-- | Contains high-level metadata about a 'Rattletrap.Replay.Replay'.
data Header = Header
  { Header -> Version
version :: Version.Version,
    -- | Always @TAGame.Replay_Soccar_TA@.
    Header -> Str
label :: Str.Str,
    -- | 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@.
    Header -> Dictionary Property
properties :: Dictionary.Dictionary Property.Property
  }
  deriving (Header -> Header -> Bool
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
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 = forall a. String -> (Object -> Parser a) -> Value -> Parser a
Json.withObject String
"Header" forall a b. (a -> b) -> a -> b
$ \Object
object -> do
    U32
major <- forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"engine_version"
    U32
minor <- forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"licensee_version"
    Maybe U32
patch <- forall value.
FromJSON value =>
Object -> String -> Parser (Maybe value)
Json.optional Object
object String
"patch_version"
    Str
label <- forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"label"
    Dictionary Property
properties <- forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"properties"
    forall (f :: * -> *) a. Applicative f => a -> f a
pure
      Header
        { version :: Version
version =
            Version.Version
              { U32
major :: U32
major :: U32
Version.major,
                U32
minor :: U32
minor :: U32
Version.minor,
                Maybe U32
patch :: Maybe U32
patch :: Maybe U32
Version.patch
              },
          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 =
    [(Key, Value)] -> Value
Json.object
      [ forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"engine_version" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> U32
Version.major forall a b. (a -> b) -> a -> b
$ Header -> Version
version Header
x,
        forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"licensee_version" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> U32
Version.minor forall a b. (a -> b) -> a -> b
$ Header -> Version
version Header
x,
        forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"patch_version" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> Maybe U32
Version.patch forall a b. (a -> b) -> a -> b
$ Header -> Version
version Header
x,
        forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"label" forall a b. (a -> b) -> a -> b
$ Header -> Str
label Header
x,
        forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"properties" 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" forall a b. (a -> b) -> a -> b
$
    [((Key, Value), Bool)] -> Value
Schema.object
      [ (forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"engine_version" forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U32.schema, Bool
True),
        (forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"licensee_version" forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
U32.schema, Bool
True),
        (forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"patch_version" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Schema -> Value
Schema.json forall a b. (a -> b) -> a -> b
$ Schema -> Schema
Schema.maybe Schema
U32.schema, Bool
False),
        (forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"label" forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
Str.schema, Bool
True),
        ( forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"properties" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Schema -> Value
Schema.json 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 =
  Version -> BytePut
Version.bytePut (Header -> Version
version Header
x)
    forall a. Semigroup a => a -> a -> a
<> Str -> BytePut
Str.bytePut (Header -> Str
label Header
x)
    forall a. Semigroup a => a -> a -> a
<> 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 = forall a. String -> ByteGet a -> ByteGet a
ByteGet.label String
"Header" forall a b. (a -> b) -> a -> b
$ do
  Version
version <- forall a. String -> ByteGet a -> ByteGet a
ByteGet.label String
"version" ByteGet Version
Version.byteGet
  Str
label <- forall a. String -> ByteGet a -> ByteGet a
ByteGet.label String
"label" ByteGet Str
Str.byteGet
  Dictionary Property
properties <-
    forall a. String -> ByteGet a -> ByteGet a
ByteGet.label String
"properties" forall a b. (a -> b) -> a -> b
$
      forall a. ByteGet a -> ByteGet (Dictionary a)
Dictionary.byteGet ByteGet Property
Property.byteGet
  forall (f :: * -> *) a. Applicative f => a -> f a
pure Header {Version
version :: Version
version :: Version
version, Str
label :: Str
label :: Str
label, Dictionary Property
properties :: Dictionary Property
properties :: Dictionary Property
properties}