module Rattletrap.Type.Frame where

import qualified Data.Map as Map
import qualified Rattletrap.BitGet as BitGet
import qualified Rattletrap.BitPut as BitPut
import qualified Rattletrap.Schema as Schema
import qualified Rattletrap.Type.ClassAttributeMap as ClassAttributeMap
import qualified Rattletrap.Type.CompressedWord as CompressedWord
import qualified Rattletrap.Type.F32 as F32
import qualified Rattletrap.Type.List as List
import qualified Rattletrap.Type.Replication as Replication
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

data Frame = Frame
  { Frame -> F32
time :: F32.F32
  -- ^ Time in seconds since the beginning of the match.
  , Frame -> F32
delta :: F32.F32
  -- ^ Time in seconds since the last frame. Usually about 0.03 since there
  -- are 30 frames per second.
  , Frame -> List Replication
replications :: List.List Replication.Replication
  }
  deriving (Frame -> Frame -> Bool
(Frame -> Frame -> Bool) -> (Frame -> Frame -> Bool) -> Eq Frame
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Frame -> Frame -> Bool
$c/= :: Frame -> Frame -> Bool
== :: Frame -> Frame -> Bool
$c== :: Frame -> Frame -> Bool
Eq, Int -> Frame -> ShowS
[Frame] -> ShowS
Frame -> String
(Int -> Frame -> ShowS)
-> (Frame -> String) -> ([Frame] -> ShowS) -> Show Frame
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Frame] -> ShowS
$cshowList :: [Frame] -> ShowS
show :: Frame -> String
$cshow :: Frame -> String
showsPrec :: Int -> Frame -> ShowS
$cshowsPrec :: Int -> Frame -> ShowS
Show)

instance Json.FromJSON Frame where
  parseJSON :: Value -> Parser Frame
parseJSON = String -> (Object -> Parser Frame) -> Value -> Parser Frame
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Json.withObject String
"Frame" ((Object -> Parser Frame) -> Value -> Parser Frame)
-> (Object -> Parser Frame) -> Value -> Parser Frame
forall a b. (a -> b) -> a -> b
$ \Object
object -> do
    F32
time <- Object -> String -> Parser F32
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"time"
    F32
delta <- Object -> String -> Parser F32
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"delta"
    List Replication
replications <- Object -> String -> Parser (List Replication)
forall value. FromJSON value => Object -> String -> Parser value
Json.required Object
object String
"replications"
    Frame -> Parser Frame
forall (f :: * -> *) a. Applicative f => a -> f a
pure Frame :: F32 -> F32 -> List Replication -> Frame
Frame { F32
time :: F32
time :: F32
time, F32
delta :: F32
delta :: F32
delta, List Replication
replications :: List Replication
replications :: List Replication
replications }

instance Json.ToJSON Frame where
  toJSON :: Frame -> Value
toJSON Frame
x = [Pair] -> Value
Json.object
    [ String -> F32 -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"time" (F32 -> Pair) -> F32 -> Pair
forall a b. (a -> b) -> a -> b
$ Frame -> F32
time Frame
x
    , String -> F32 -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"delta" (F32 -> Pair) -> F32 -> Pair
forall a b. (a -> b) -> a -> b
$ Frame -> F32
delta Frame
x
    , String -> List Replication -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"replications" (List Replication -> Pair) -> List Replication -> Pair
forall a b. (a -> b) -> a -> b
$ Frame -> List Replication
replications Frame
x
    ]

schema :: Schema.Schema
schema :: Schema
schema = String -> Value -> Schema
Schema.named String
"frame" (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
"time" (Value -> Pair) -> Value -> Pair
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
F32.schema, Bool
True)
  , (String -> Value -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"delta" (Value -> Pair) -> Value -> Pair
forall a b. (a -> b) -> a -> b
$ Schema -> Value
Schema.ref Schema
F32.schema, Bool
True)
  , ( String -> Value -> Pair
forall value pair.
(ToJSON value, KeyValue pair) =>
String -> value -> pair
Json.pair String
"replications" (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
List.schema Schema
Replication.schema
    , Bool
True
    )
  ]

putFrames :: List.List Frame -> BitPut.BitPut
putFrames :: List Frame -> BitPut
putFrames = (Frame -> BitPut) -> [Frame] -> BitPut
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Frame -> BitPut
bitPut ([Frame] -> BitPut)
-> (List Frame -> [Frame]) -> List Frame -> BitPut
forall b c a. (b -> c) -> (a -> b) -> a -> c
. List Frame -> [Frame]
forall a. List a -> [a]
List.toList

bitPut :: Frame -> BitPut.BitPut
bitPut :: Frame -> BitPut
bitPut Frame
frame =
  F32 -> BitPut
F32.bitPut (Frame -> F32
time Frame
frame)
    BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> F32 -> BitPut
F32.bitPut (Frame -> F32
delta Frame
frame)
    BitPut -> BitPut -> BitPut
forall a. Semigroup a => a -> a -> a
<> List Replication -> BitPut
Replication.putReplications (Frame -> List Replication
replications Frame
frame)

decodeFramesBits
  :: Maybe Str.Str
  -> Version.Version
  -> Int
  -> Word
  -> ClassAttributeMap.ClassAttributeMap
  -> BitGet.BitGet (List.List Frame)
decodeFramesBits :: Maybe Str
-> Version
-> Int
-> Word
-> ClassAttributeMap
-> BitGet (List Frame)
decodeFramesBits Maybe Str
matchType Version
version Int
count Word
limit ClassAttributeMap
classes =
  ((Map CompressedWord U32, List Frame) -> List Frame)
-> Get BitString Identity (Map CompressedWord U32, List Frame)
-> BitGet (List Frame)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Map CompressedWord U32, List Frame) -> List Frame
forall a b. (a, b) -> b
snd (Get BitString Identity (Map CompressedWord U32, List Frame)
 -> BitGet (List Frame))
-> Get BitString Identity (Map CompressedWord U32, List Frame)
-> BitGet (List Frame)
forall a b. (a -> b) -> a -> b
$ Maybe Str
-> Version
-> Int
-> Word
-> ClassAttributeMap
-> Map CompressedWord U32
-> Int
-> [Frame]
-> Get BitString Identity (Map CompressedWord U32, List Frame)
decodeFramesBitsWith
    Maybe Str
matchType
    Version
version
    Int
count
    Word
limit
    ClassAttributeMap
classes
    Map CompressedWord U32
forall k a. Map k a
Map.empty
    Int
0
    []

decodeFramesBitsWith
  :: Maybe Str.Str
  -> Version.Version
  -> Int
  -> Word
  -> ClassAttributeMap.ClassAttributeMap
  -> Map.Map CompressedWord.CompressedWord U32.U32
  -> Int
  -> [Frame]
  -> BitGet.BitGet
       ( Map.Map CompressedWord.CompressedWord U32.U32
       , List.List Frame
       )
decodeFramesBitsWith :: Maybe Str
-> Version
-> Int
-> Word
-> ClassAttributeMap
-> Map CompressedWord U32
-> Int
-> [Frame]
-> Get BitString Identity (Map CompressedWord U32, List Frame)
decodeFramesBitsWith Maybe Str
matchType Version
version Int
count Word
limit ClassAttributeMap
classes Map CompressedWord U32
actorMap Int
index [Frame]
frames
  = if Int
index Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
count
    then (Map CompressedWord U32, List Frame)
-> Get BitString Identity (Map CompressedWord U32, List Frame)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Map CompressedWord U32
actorMap, [Frame] -> List Frame
forall a. [a] -> List a
List.fromList ([Frame] -> List Frame) -> [Frame] -> List Frame
forall a b. (a -> b) -> a -> b
$ [Frame] -> [Frame]
forall a. [a] -> [a]
reverse [Frame]
frames)
    else do
      (Map CompressedWord U32
newActorMap, Frame
frame) <-
        String
-> BitGet (Map CompressedWord U32, Frame)
-> BitGet (Map CompressedWord U32, Frame)
forall a. String -> BitGet a -> BitGet a
BitGet.label (String
"element (" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show Int
index String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")")
          (BitGet (Map CompressedWord U32, Frame)
 -> BitGet (Map CompressedWord U32, Frame))
-> BitGet (Map CompressedWord U32, Frame)
-> BitGet (Map CompressedWord U32, Frame)
forall a b. (a -> b) -> a -> b
$ Maybe Str
-> Version
-> Word
-> ClassAttributeMap
-> Map CompressedWord U32
-> BitGet (Map CompressedWord U32, Frame)
bitGet Maybe Str
matchType Version
version Word
limit ClassAttributeMap
classes Map CompressedWord U32
actorMap
      Maybe Str
-> Version
-> Int
-> Word
-> ClassAttributeMap
-> Map CompressedWord U32
-> Int
-> [Frame]
-> Get BitString Identity (Map CompressedWord U32, List Frame)
decodeFramesBitsWith
          Maybe Str
matchType
          Version
version
          Int
count
          Word
limit
          ClassAttributeMap
classes
          Map CompressedWord U32
newActorMap
          (Int
index Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
        ([Frame]
 -> Get BitString Identity (Map CompressedWord U32, List Frame))
-> [Frame]
-> Get BitString Identity (Map CompressedWord U32, List Frame)
forall a b. (a -> b) -> a -> b
$ Frame
frame
        Frame -> [Frame] -> [Frame]
forall a. a -> [a] -> [a]
: [Frame]
frames

bitGet
  :: Maybe Str.Str
  -> Version.Version
  -> Word
  -> ClassAttributeMap.ClassAttributeMap
  -> Map.Map CompressedWord.CompressedWord U32.U32
  -> BitGet.BitGet
       (Map.Map CompressedWord.CompressedWord U32.U32, Frame)
bitGet :: Maybe Str
-> Version
-> Word
-> ClassAttributeMap
-> Map CompressedWord U32
-> BitGet (Map CompressedWord U32, Frame)
bitGet Maybe Str
matchType Version
version Word
limit ClassAttributeMap
classes Map CompressedWord U32
actorMap = String
-> BitGet (Map CompressedWord U32, Frame)
-> BitGet (Map CompressedWord U32, Frame)
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"Frame" (BitGet (Map CompressedWord U32, Frame)
 -> BitGet (Map CompressedWord U32, Frame))
-> BitGet (Map CompressedWord U32, Frame)
-> BitGet (Map CompressedWord U32, Frame)
forall a b. (a -> b) -> a -> b
$ do
  F32
time <- String -> BitGet F32 -> BitGet F32
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"time" BitGet F32
F32.bitGet
  F32
delta <- String -> BitGet F32 -> BitGet F32
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"delta" BitGet F32
F32.bitGet
  (Map CompressedWord U32
newActorMap, List Replication
replications) <-
    String
-> BitGet (Map CompressedWord U32, List Replication)
-> BitGet (Map CompressedWord U32, List Replication)
forall a. String -> BitGet a -> BitGet a
BitGet.label String
"replications" (BitGet (Map CompressedWord U32, List Replication)
 -> BitGet (Map CompressedWord U32, List Replication))
-> BitGet (Map CompressedWord U32, List Replication)
-> BitGet (Map CompressedWord U32, List Replication)
forall a b. (a -> b) -> a -> b
$ Maybe Str
-> Version
-> Word
-> ClassAttributeMap
-> Map CompressedWord U32
-> BitGet (Map CompressedWord U32, List Replication)
Replication.decodeReplicationsBits
      Maybe Str
matchType
      Version
version
      Word
limit
      ClassAttributeMap
classes
      Map CompressedWord U32
actorMap
  (Map CompressedWord U32, Frame)
-> BitGet (Map CompressedWord U32, Frame)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Map CompressedWord U32
newActorMap, Frame :: F32 -> F32 -> List Replication -> Frame
Frame { F32
time :: F32
time :: F32
time, F32
delta :: F32
delta :: F32
delta, List Replication
replications :: List Replication
replications :: List Replication
replications })