Skip to content

Commit

Permalink
Merge pull request #93 from tfausak/gh-91-patch-1.50
Browse files Browse the repository at this point in the history
Handle replays from patch 1.50
  • Loading branch information
tfausak authored Sep 3, 2018
2 parents da98dd9 + 485b605 commit 03228fe
Show file tree
Hide file tree
Showing 19 changed files with 149 additions and 48 deletions.
5 changes: 4 additions & 1 deletion library/Rattletrap/Data.hs
Original file line number Diff line number Diff line change
Expand Up @@ -127,8 +127,8 @@ rawObjectClasses =
, ("Archetypes.GameEvent.GameEvent_HockeyPrivate", "TAGame.GameEvent_SoccarPrivate_TA")
, ("Archetypes.GameEvent.GameEvent_HockeySplitscreen", "TAGame.GameEvent_SoccarSplitscreen_TA")
, ("Archetypes.GameEvent.GameEvent_Items", "TAGame.GameEvent_Soccar_TA")
, ("Archetypes.GameEvent.GameEvent_Season:CarArchetype", "TAGame.Car_TA")
, ("Archetypes.GameEvent.GameEvent_Season", "TAGame.GameEvent_Season_TA")
, ("Archetypes.GameEvent.GameEvent_Season:CarArchetype", "TAGame.Car_TA")
, ("Archetypes.GameEvent.GameEvent_Soccar", "TAGame.GameEvent_Soccar_TA")
, ("Archetypes.GameEvent.GameEvent_SoccarLan", "TAGame.GameEvent_Soccar_TA")
, ("Archetypes.GameEvent.GameEvent_SoccarPrivate", "TAGame.GameEvent_SoccarPrivate_TA")
Expand Down Expand Up @@ -276,6 +276,7 @@ rawAttributeTypes =
, ("TAGame.PRI_TA:ClientLoadoutOnline", AttributeTypeLoadoutOnline)
, ("TAGame.PRI_TA:ClientLoadouts", AttributeTypeLoadouts)
, ("TAGame.PRI_TA:ClientLoadoutsOnline", AttributeTypeLoadoutsOnline)
, ("TAGame.PRI_TA:ClubID", AttributeTypeInt64)
, ("TAGame.PRI_TA:MatchAssists", AttributeTypeInt)
, ("TAGame.PRI_TA:MatchBreakoutDamage", AttributeTypeInt)
, ("TAGame.PRI_TA:MatchGoals", AttributeTypeInt)
Expand All @@ -292,6 +293,7 @@ rawAttributeTypes =
, ("TAGame.PRI_TA:ReplicatedGameEvent", AttributeTypeFlaggedInt)
, ("TAGame.PRI_TA:ReplicatedWorstNetQualityBeyondLatency", AttributeTypeByte)
, ("TAGame.PRI_TA:SecondaryTitle", AttributeTypeTitle)
, ("TAGame.PRI_TA:SpectatorShortcut", AttributeTypeInt)
, ("TAGame.PRI_TA:SteeringSensitivity", AttributeTypeFloat)
, ("TAGame.PRI_TA:TimeTillItem", AttributeTypeInt)
, ("TAGame.PRI_TA:Title", AttributeTypeInt)
Expand All @@ -309,6 +311,7 @@ rawAttributeTypes =
, ("TAGame.SpecialPickup_Targeted_TA:Targeted", AttributeTypeFlaggedInt)
, ("TAGame.Team_Soccar_TA:GameScore", AttributeTypeInt)
, ("TAGame.Team_TA:ClubColors", AttributeTypeClubColors)
, ("TAGame.Team_TA:ClubID", AttributeTypeInt64)
, ("TAGame.Team_TA:CustomTeamName", AttributeTypeString)
, ("TAGame.Team_TA:GameEvent", AttributeTypeFlaggedInt)
, ("TAGame.Team_TA:LogoData", AttributeTypeFlaggedInt)
Expand Down
10 changes: 6 additions & 4 deletions library/Rattletrap/Decode/AttributeValue.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ import Rattletrap.Decode.ExtendedExplosionAttribute
import Rattletrap.Decode.FlaggedIntAttribute
import Rattletrap.Decode.FloatAttribute
import Rattletrap.Decode.GameModeAttribute
import Rattletrap.Decode.Int64Attribute
import Rattletrap.Decode.IntAttribute
import Rattletrap.Decode.LoadoutAttribute
import Rattletrap.Decode.LoadoutOnlineAttribute
Expand Down Expand Up @@ -70,14 +71,15 @@ decodeAttributeValueBits version objectMap name = do
AttributeTypeEnum -> AttributeValueEnum <$> decodeEnumAttributeBits
AttributeTypeExplosion ->
AttributeValueExplosion <$> decodeExplosionAttributeBits version
AttributeTypeExtendedExplosion ->
AttributeValueExtendedExplosion <$> decodeExtendedExplosionAttributeBits version
AttributeTypeExtendedExplosion -> AttributeValueExtendedExplosion
<$> decodeExtendedExplosionAttributeBits version
AttributeTypeFlaggedInt ->
AttributeValueFlaggedInt <$> decodeFlaggedIntAttributeBits
AttributeTypeFloat -> AttributeValueFloat <$> decodeFloatAttributeBits
AttributeTypeGameMode ->
AttributeValueGameMode <$> decodeGameModeAttributeBits version
AttributeTypeInt -> AttributeValueInt <$> decodeIntAttributeBits
AttributeTypeInt64 -> AttributeValueInt64 <$> decodeInt64AttributeBits
AttributeTypeLoadout ->
AttributeValueLoadout <$> decodeLoadoutAttributeBits
AttributeTypeLoadoutOnline ->
Expand All @@ -103,8 +105,8 @@ decodeAttributeValueBits version objectMap name = do
AttributeTypeQWord -> AttributeValueQWord <$> decodeQWordAttributeBits
AttributeTypeReservation ->
AttributeValueReservation <$> decodeReservationAttributeBits version
AttributeTypeRigidBodyState ->
AttributeValueRigidBodyState <$> decodeRigidBodyStateAttributeBits version
AttributeTypeRigidBodyState -> AttributeValueRigidBodyState
<$> decodeRigidBodyStateAttributeBits version
AttributeTypeStatEvent ->
AttributeValueStatEvent <$> decodeStatEventAttributeBits
AttributeTypeString -> AttributeValueString <$> decodeStringAttributeBits
Expand Down
1 change: 1 addition & 0 deletions library/Rattletrap/Decode/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ module Rattletrap.Decode.Common
, Binary.getLazyByteString
, Binary.getInt8
, Binary.getInt32le
, Binary.getInt64le
, Binary.getWord8
, Binary.getWord32le
, Binary.getWord64le
Expand Down
10 changes: 10 additions & 0 deletions library/Rattletrap/Decode/Int64Attribute.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
module Rattletrap.Decode.Int64Attribute
( decodeInt64AttributeBits
) where

import Rattletrap.Decode.Common
import Rattletrap.Decode.Int64le
import Rattletrap.Type.Int64Attribute

decodeInt64AttributeBits :: DecodeBits Int64Attribute
decodeInt64AttributeBits = Int64Attribute <$> decodeInt64leBits
13 changes: 13 additions & 0 deletions library/Rattletrap/Decode/Int64le.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
module Rattletrap.Decode.Int64le
( decodeInt64le
, decodeInt64leBits
) where

import Rattletrap.Decode.Common
import Rattletrap.Type.Int64le

decodeInt64le :: Decode Int64le
decodeInt64le = Int64le <$> getInt64le

decodeInt64leBits :: DecodeBits Int64le
decodeInt64leBits = toBits decodeInt64le 8
47 changes: 26 additions & 21 deletions library/Rattletrap/Decode/ProductAttribute.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,8 @@ import Rattletrap.Decode.Common
import Rattletrap.Decode.CompressedWord
import Rattletrap.Decode.Word32le
import Rattletrap.Decode.Word8le
import Rattletrap.Decode.Str
import Rattletrap.Type.Common
import Rattletrap.Type.CompressedWord
import Rattletrap.Type.ProductAttribute
import Rattletrap.Type.Str
import Rattletrap.Type.Word32le
Expand All @@ -31,27 +31,32 @@ decodeProductAttributeBits
decodeProductAttributeBits version objectMap = do
flag <- getBool
objectId <- decodeWord32leBits
let objectName = Map.lookup objectId objectMap
value <- case objectName of
Just name -> case fromStr name of
"TAGame.ProductAttribute_Painted_TA" -> Just <$> decodePainted version
"TAGame.ProductAttribute_UserColor_TA" -> decodeColor
_ ->
fail
( "unknown object name "
<> show objectName
<> " for ID "
<> show objectId
)
let maybeObjectName = Map.lookup objectId objectMap
value <- case fromStr <$> maybeObjectName of
Just "TAGame.ProductAttribute_Painted_TA" -> decodePainted version
Just "TAGame.ProductAttribute_TitleID_TA" -> decodeTitle
Just "TAGame.ProductAttribute_UserColor_TA" -> decodeColor version
Just objectName ->
fail
("unknown object name "
<> show objectName
<> " for ID "
<> show objectId
)
Nothing -> fail ("missing object name for ID " <> show objectId)
pure (ProductAttribute flag objectId objectName value)
pure (ProductAttribute flag objectId maybeObjectName value)

decodePainted :: (Int, Int, Int) -> DecodeBits (Either CompressedWord Word32)
decodePainted :: (Int, Int, Int) -> DecodeBits ProductAttributeValue
decodePainted version = if version >= (868, 18, 0)
then Right <$> getWord32be 31
else Left <$> decodeCompressedWordBits 13
then ProductAttributeValuePaintedNew <$> getWord32be 31
else ProductAttributeValuePaintedOld <$> decodeCompressedWordBits 13

decodeColor :: DecodeBits (Maybe (Either CompressedWord Word32))
decodeColor = do
hasValue <- getBool
decodeWhen hasValue (Right <$> getWord32be 31)
decodeColor :: (Int, Int, Int) -> DecodeBits ProductAttributeValue
decodeColor version = if version >= (868, 23, 8)
then ProductAttributeValueUserColorNew <$> decodeWord32leBits
else do
hasValue <- getBool
ProductAttributeValueUserColorOld <$> decodeWhen hasValue (getWord32be 31)

decodeTitle :: DecodeBits ProductAttributeValue
decodeTitle = ProductAttributeValueTitleId <$> decodeStrBits
2 changes: 2 additions & 0 deletions library/Rattletrap/Encode/AttributeValue.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ import Rattletrap.Encode.ExtendedExplosionAttribute
import Rattletrap.Encode.FlaggedIntAttribute
import Rattletrap.Encode.FloatAttribute
import Rattletrap.Encode.GameModeAttribute
import Rattletrap.Encode.Int64Attribute
import Rattletrap.Encode.IntAttribute
import Rattletrap.Encode.LoadoutAttribute
import Rattletrap.Encode.LoadoutOnlineAttribute
Expand Down Expand Up @@ -55,6 +56,7 @@ putAttributeValue value = case value of
AttributeValueFloat x -> putFloatAttribute x
AttributeValueGameMode x -> putGameModeAttribute x
AttributeValueInt x -> putIntAttribute x
AttributeValueInt64 x -> putInt64Attribute x
AttributeValueLoadout x -> putLoadoutAttribute x
AttributeValueLoadoutOnline x -> putLoadoutOnlineAttribute x
AttributeValueLoadouts x -> putLoadoutsAttribute x
Expand Down
12 changes: 12 additions & 0 deletions library/Rattletrap/Encode/Int64Attribute.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
module Rattletrap.Encode.Int64Attribute
( putInt64Attribute
) where

import Rattletrap.Encode.Int64le
import Rattletrap.Type.Int64Attribute

import qualified Data.Binary.Bits.Put as BinaryBits

putInt64Attribute :: Int64Attribute -> BinaryBits.BitPut ()
putInt64Attribute int64Attribute =
putInt64Bits (int64AttributeValue int64Attribute)
20 changes: 20 additions & 0 deletions library/Rattletrap/Encode/Int64le.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
module Rattletrap.Encode.Int64le
( putInt64
, putInt64Bits
) where

import Rattletrap.Type.Int64le
import Rattletrap.Utility.Bytes

import qualified Data.Binary as Binary
import qualified Data.Binary.Bits.Put as BinaryBits
import qualified Data.Binary.Put as Binary
import qualified Data.ByteString.Lazy as LazyBytes

putInt64 :: Int64le -> Binary.Put
putInt64 int64 = Binary.putInt64le (int64leValue int64)

putInt64Bits :: Int64le -> BinaryBits.BitPut ()
putInt64Bits int64 = do
let bytes = Binary.runPut (putInt64 int64)
BinaryBits.putByteString (LazyBytes.toStrict (reverseBytes bytes))
32 changes: 11 additions & 21 deletions library/Rattletrap/Encode/ProductAttribute.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,12 +3,11 @@ module Rattletrap.Encode.ProductAttribute
, putProductAttribute
) where

import Data.Semigroup ((<>))
import Rattletrap.Encode.CompressedWord
import Rattletrap.Encode.Word32le
import Rattletrap.Encode.Word8le
import Rattletrap.Encode.Str
import Rattletrap.Type.ProductAttribute
import Rattletrap.Type.Str
import Rattletrap.Type.Word8le

import qualified Data.Binary.Bits.Put as BinaryBits
Expand All @@ -22,22 +21,13 @@ putProductAttribute :: ProductAttribute -> BinaryBits.BitPut ()
putProductAttribute attribute = do
BinaryBits.putBool (productAttributeUnknown attribute)
putWord32Bits (productAttributeObjectId attribute)
case productAttributeObjectName attribute of
Just name -> case fromStr name of
"TAGame.ProductAttribute_Painted_TA" ->
case productAttributeValue attribute of
Nothing -> pure ()
Just (Left x) -> putCompressedWord x
Just (Right x) -> BinaryBits.putWord32be 31 x
"TAGame.ProductAttribute_UserColor_TA" ->
case productAttributeValue attribute of
Nothing -> BinaryBits.putBool False
Just value -> do
BinaryBits.putBool True
case value of
Left x -> putCompressedWord x
Right x -> BinaryBits.putWord32be 31 x
_ ->
fail ("unknown object name for product attribute " <> show attribute)
Nothing ->
fail ("missing object name for product attribute " <> show attribute)
case productAttributeValue attribute of
ProductAttributeValuePaintedOld x -> putCompressedWord x
ProductAttributeValuePaintedNew x -> BinaryBits.putWord32be 31 x
ProductAttributeValueUserColorOld x -> case x of
Nothing -> BinaryBits.putBool False
Just y -> do
BinaryBits.putBool True
BinaryBits.putWord32be 31 y
ProductAttributeValueUserColorNew x -> putWord32Bits x
ProductAttributeValueTitleId x -> putTextBits x
1 change: 1 addition & 0 deletions library/Rattletrap/Type/AttributeType.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@ data AttributeType
| AttributeTypeFloat
| AttributeTypeGameMode
| AttributeTypeInt
| AttributeTypeInt64
| AttributeTypeLoadout
| AttributeTypeLoadoutOnline
| AttributeTypeLoadouts
Expand Down
2 changes: 2 additions & 0 deletions library/Rattletrap/Type/AttributeValue.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ import Rattletrap.Type.ExtendedExplosionAttribute
import Rattletrap.Type.FlaggedIntAttribute
import Rattletrap.Type.FloatAttribute
import Rattletrap.Type.GameModeAttribute
import Rattletrap.Type.Int64Attribute
import Rattletrap.Type.IntAttribute
import Rattletrap.Type.LoadoutAttribute
import Rattletrap.Type.LoadoutOnlineAttribute
Expand Down Expand Up @@ -54,6 +55,7 @@ data AttributeValue
| AttributeValueFloat FloatAttribute
| AttributeValueGameMode GameModeAttribute
| AttributeValueInt IntAttribute
| AttributeValueInt64 Int64Attribute
| AttributeValueLoadout LoadoutAttribute
| AttributeValueLoadoutOnline LoadoutOnlineAttribute
| AttributeValueLoadouts LoadoutsAttribute
Expand Down
14 changes: 14 additions & 0 deletions library/Rattletrap/Type/Int64Attribute.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
{-# LANGUAGE TemplateHaskell #-}

module Rattletrap.Type.Int64Attribute
( Int64Attribute(..)
) where

import Rattletrap.Type.Common
import Rattletrap.Type.Int64le

newtype Int64Attribute = Int64Attribute
{ int64AttributeValue :: Int64le
} deriving (Eq, Ord, Show)

$(deriveJson ''Int64Attribute)
13 changes: 13 additions & 0 deletions library/Rattletrap/Type/Int64le.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
{-# LANGUAGE TemplateHaskell #-}

module Rattletrap.Type.Int64le
( Int64le(..)
) where

import Rattletrap.Type.Common

newtype Int64le = Int64le
{ int64leValue :: Int64
} deriving (Eq, Ord, Show)

$(deriveJson ''Int64le)
13 changes: 12 additions & 1 deletion library/Rattletrap/Type/ProductAttribute.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,19 +2,30 @@

module Rattletrap.Type.ProductAttribute
( ProductAttribute(..)
, ProductAttributeValue(..)
) where

import Rattletrap.Type.Common
import Rattletrap.Type.CompressedWord
import Rattletrap.Type.Str
import Rattletrap.Type.Word32le

data ProductAttributeValue
= ProductAttributeValuePaintedOld CompressedWord
| ProductAttributeValuePaintedNew Word32
| ProductAttributeValueUserColorOld (Maybe Word32)
| ProductAttributeValueUserColorNew Word32le
| ProductAttributeValueTitleId Str
deriving (Eq, Ord, Show)

$(deriveJson ''ProductAttributeValue)

data ProductAttribute = ProductAttribute
{ productAttributeUnknown :: Bool
, productAttributeObjectId :: Word32le
, productAttributeObjectName :: Maybe Str
-- ^ read-only
, productAttributeValue :: Maybe (Either CompressedWord Word32)
, productAttributeValue :: ProductAttributeValue
} deriving (Eq, Ord, Show)

$(deriveJson ''ProductAttribute)
Empty file modified replays/92a6.replay
100755 → 100644
Empty file.
Binary file added replays/a676.replay
Binary file not shown.
Binary file added replays/aa70.replay
Binary file not shown.
2 changes: 2 additions & 0 deletions tests/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -104,8 +104,10 @@ replays =
, ("a52f", "some more mutators")
, ("a558", "extended explosion data")
, ("a671", "a waiting player")
, ("a676", "new user color")
, ("a7f0", "a ready attribute")
, ("a9df", "salty shores patch 1.45")
, ("aa70", "patch 1.50 - TitleID attribute")
, ("afb1", "patch 1.37")
, ("b9f9", "a party leader")
, ("c14f", "some mutators")
Expand Down

0 comments on commit 03228fe

Please sign in to comment.