Safe Haskell | None |
---|---|
Language | Haskell2010 |
Rattletrap
Synopsis
- decodeReplayFile :: ByteString -> Either String Replay
- encodeReplayJson :: Replay -> ByteString
- decodeReplayJson :: ByteString -> Either String Replay
- encodeReplayFile :: Replay -> ByteString
- data Replay = Replay {}
- data Section a = Section {
- sectionSize :: Word32le
- sectionCrc :: Word32le
- sectionBody :: a
- data Header = Header {}
- newtype Word32le = Word32le {}
- newtype Str = Str {}
- data Dictionary a
- = DictionaryElement Str a (Dictionary a)
- | DictionaryEnd Str
- data Property = Property {}
- newtype Word64le = Word64le {}
- data PropertyValue a
- newtype List a = List {
- listValue :: [a]
- newtype Word8le = Word8le {}
- newtype Float32le = Float32le {}
- newtype Int32le = Int32le {}
- data Content = Content {
- contentLevels :: List Str
- contentKeyFrames :: List KeyFrame
- contentStreamSize :: Word32le
- contentFrames :: [Frame]
- contentMessages :: List Message
- contentMarks :: List Mark
- contentPackages :: List Str
- contentObjects :: List Str
- contentNames :: List Str
- contentClassMappings :: List ClassMapping
- contentCaches :: List Cache
- contentUnknown :: Maybe Word32le
- data KeyFrame = KeyFrame {}
- data Frame = Frame {}
- data Replication = Replication {}
- data CompressedWord = CompressedWord {}
- data ReplicationValue
- data SpawnedReplication = SpawnedReplication {}
- data Initialization = Initialization {}
- data Vector = Vector {
- vectorSize :: CompressedWord
- vectorBias :: Word
- vectorX :: Int
- vectorY :: Int
- vectorZ :: Int
- data Int8Vector = Int8Vector {}
- newtype Int8le = Int8le {
- int8leValue :: Int8
- newtype UpdatedReplication = UpdatedReplication {}
- data Attribute = Attribute {}
- data AttributeValue
- = AttributeValueAppliedDamage AppliedDamageAttribute
- | AttributeValueBoolean BooleanAttribute
- | AttributeValueByte ByteAttribute
- | AttributeValueCamSettings CamSettingsAttribute
- | AttributeValueClubColors ClubColorsAttribute
- | AttributeValueDamageState DamageStateAttribute
- | AttributeValueDemolish DemolishAttribute
- | AttributeValueEnum EnumAttribute
- | AttributeValueExplosion ExplosionAttribute
- | AttributeValueExtendedExplosion ExtendedExplosionAttribute
- | AttributeValueFlaggedInt FlaggedIntAttribute
- | AttributeValueFloat FloatAttribute
- | AttributeValueGameMode GameModeAttribute
- | AttributeValueInt IntAttribute
- | AttributeValueInt64 Int64Attribute
- | AttributeValueLoadout LoadoutAttribute
- | AttributeValueLoadoutOnline LoadoutOnlineAttribute
- | AttributeValueLoadouts LoadoutsAttribute
- | AttributeValueLoadoutsOnline LoadoutsOnlineAttribute
- | AttributeValueLocation LocationAttribute
- | AttributeValueMusicStinger MusicStingerAttribute
- | AttributeValuePartyLeader PartyLeaderAttribute
- | AttributeValuePickup PickupAttribute
- | AttributeValuePlayerHistoryKey PlayerHistoryKeyAttribute
- | AttributeValuePrivateMatchSettings PrivateMatchSettingsAttribute
- | AttributeValueQWord QWordAttribute
- | AttributeValueReservation ReservationAttribute
- | AttributeValueRigidBodyState RigidBodyStateAttribute
- | AttributeValueStatEvent StatEventAttribute
- | AttributeValueString StringAttribute
- | AttributeValueTeamPaint TeamPaintAttribute
- | AttributeValueTitle TitleAttribute
- | AttributeValueUniqueId UniqueIdAttribute
- | AttributeValueWeldedInfo WeldedInfoAttribute
- data AppliedDamageAttribute = AppliedDamageAttribute {}
- newtype BooleanAttribute = BooleanAttribute {}
- newtype ByteAttribute = ByteAttribute {}
- data CamSettingsAttribute = CamSettingsAttribute {}
- data ClubColorsAttribute = ClubColorsAttribute {}
- data DamageStateAttribute = DamageStateAttribute {}
- data DemolishAttribute = DemolishAttribute {}
- newtype EnumAttribute = EnumAttribute {}
- data ExplosionAttribute = ExplosionAttribute {}
- data ExtendedExplosionAttribute = ExtendedExplosionAttribute {}
- data FlaggedIntAttribute = FlaggedIntAttribute {}
- newtype FloatAttribute = FloatAttribute {}
- data GameModeAttribute = GameModeAttribute {}
- newtype IntAttribute = IntAttribute {}
- data LoadoutAttribute = LoadoutAttribute {
- loadoutAttributeVersion :: Word8le
- loadoutAttributeBody :: Word32le
- loadoutAttributeDecal :: Word32le
- loadoutAttributeWheels :: Word32le
- loadoutAttributeRocketTrail :: Word32le
- loadoutAttributeAntenna :: Word32le
- loadoutAttributeTopper :: Word32le
- loadoutAttributeUnknown1 :: Word32le
- loadoutAttributeUnknown2 :: Maybe Word32le
- loadoutAttributeEngineAudio :: Maybe Word32le
- loadoutAttributeTrail :: Maybe Word32le
- loadoutAttributeGoalExplosion :: Maybe Word32le
- loadoutAttributeBanner :: Maybe Word32le
- loadoutAttributeUnknown3 :: Maybe Word32le
- loadoutAttributeUnknown4 :: Maybe Word32le
- loadoutAttributeUnknown5 :: Maybe Word32le
- loadoutAttributeUnknown6 :: Maybe Word32le
- newtype LoadoutOnlineAttribute = LoadoutOnlineAttribute {}
- data ProductAttribute = ProductAttribute {}
- data LoadoutsAttribute = LoadoutsAttribute {}
- data LoadoutsOnlineAttribute = LoadoutsOnlineAttribute {}
- newtype LocationAttribute = LocationAttribute {}
- data MusicStingerAttribute = MusicStingerAttribute {}
- data PartyLeaderAttribute = PartyLeaderAttribute {}
- data RemoteId
- data PickupAttribute = PickupAttribute {}
- data PrivateMatchSettingsAttribute = PrivateMatchSettingsAttribute {}
- newtype QWordAttribute = QWordAttribute {}
- data ReservationAttribute = ReservationAttribute {}
- data UniqueIdAttribute = UniqueIdAttribute {}
- data RigidBodyStateAttribute = RigidBodyStateAttribute {}
- data CompressedWordVector = CompressedWordVector {}
- newtype StringAttribute = StringAttribute {}
- data TeamPaintAttribute = TeamPaintAttribute {}
- data WeldedInfoAttribute = WeldedInfoAttribute {}
- data DestroyedReplication = DestroyedReplication
- data Message = Message {}
- data Mark = Mark {}
- data ClassMapping = ClassMapping {}
- data Cache = Cache {}
- data AttributeMapping = AttributeMapping {}
Documentation
decodeReplayFile :: ByteString -> Either String Replay Source #
Parses a raw replay.
encodeReplayJson :: Replay -> ByteString Source #
Encodes a replay as JSON.
decodeReplayJson :: ByteString -> Either String Replay Source #
Parses a JSON replay.
encodeReplayFile :: Replay -> ByteString Source #
Encodes a raw replay.
A Rocket League replay.
Constructors
Replay | |
Fields
|
A section is a large piece of a 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.
Constructors
Section | |
Fields
|
Instances
Eq a => Eq (Section a) Source # | |
Ord a => Ord (Section a) Source # | |
Show a => Show (Section a) Source # | |
ToJSON a => ToJSON (Section a) Source # | |
Defined in Rattletrap.Type.Section | |
FromJSON a => FromJSON (Section a) Source # | |
Contains high-level metadata about a Replay
.
Constructors
Header | |
Fields
|
Constructors
Word32le | |
Fields |
data Dictionary a Source #
Constructors
DictionaryElement Str a (Dictionary a) | |
DictionaryEnd Str |
Instances
Constructors
Property | |
Fields
|
Constructors
Word64le | |
Fields |
data PropertyValue a Source #
Constructors
PropertyValueArray (List (Dictionary a)) | Yes, a list of dictionaries. No, it doesn't make sense. These usually only have one element. |
PropertyValueBool Word8le | |
PropertyValueByte Str (Maybe Str) | This is a strange name for essentially a key-value pair. |
PropertyValueFloat Float32le | |
PropertyValueInt Int32le | |
PropertyValueName Str | It's unclear how exactly this is different than a |
PropertyValueQWord Word64le | |
PropertyValueStr Str |
Instances
Constructors
Word8le | |
Fields |
Constructors
Float32le | |
Fields |
Instances
Eq Float32le Source # | |
Ord Float32le Source # | |
Show Float32le Source # | |
ToJSON Float32le Source # | |
Defined in Rattletrap.Type.Float32le | |
FromJSON Float32le Source # | |
Constructors
Int32le | |
Fields |
Contains low-level game data about a Replay
.
Constructors
Content | |
Fields
|
Constructors
KeyFrame | |
Fields
|
Constructors
Frame | |
Fields
|
data Replication Source #
Constructors
Replication | |
Instances
Eq Replication Source # | |
Defined in Rattletrap.Type.Replication | |
Ord Replication Source # | |
Defined in Rattletrap.Type.Replication Methods compare :: Replication -> Replication -> Ordering # (<) :: Replication -> Replication -> Bool # (<=) :: Replication -> Replication -> Bool # (>) :: Replication -> Replication -> Bool # (>=) :: Replication -> Replication -> Bool # max :: Replication -> Replication -> Replication # min :: Replication -> Replication -> Replication # | |
Show Replication Source # | |
Defined in Rattletrap.Type.Replication Methods showsPrec :: Int -> Replication -> ShowS # show :: Replication -> String # showList :: [Replication] -> ShowS # | |
ToJSON Replication Source # | |
Defined in Rattletrap.Type.Replication Methods toJSON :: Replication -> Value # toEncoding :: Replication -> Encoding # toJSONList :: [Replication] -> Value # toEncodingList :: [Replication] -> Encoding # | |
FromJSON Replication Source # | |
Defined in Rattletrap.Type.Replication |
data CompressedWord Source #
Constructors
CompressedWord | |
Fields |
Instances
data ReplicationValue Source #
Constructors
ReplicationValueSpawned SpawnedReplication | Creates a new actor. |
ReplicationValueUpdated UpdatedReplication | Updates an existing actor. |
ReplicationValueDestroyed DestroyedReplication | Destroys an existing actor. |
Instances
data SpawnedReplication Source #
Constructors
SpawnedReplication | |
Fields
|
Instances
data Initialization Source #
Constructors
Initialization | |
Fields
|
Instances
Constructors
Vector | |
Fields
|
data Int8Vector Source #
Constructors
Int8Vector | |
Fields
|
Instances
Eq Int8Vector Source # | |
Defined in Rattletrap.Type.Int8Vector | |
Ord Int8Vector Source # | |
Defined in Rattletrap.Type.Int8Vector Methods compare :: Int8Vector -> Int8Vector -> Ordering # (<) :: Int8Vector -> Int8Vector -> Bool # (<=) :: Int8Vector -> Int8Vector -> Bool # (>) :: Int8Vector -> Int8Vector -> Bool # (>=) :: Int8Vector -> Int8Vector -> Bool # max :: Int8Vector -> Int8Vector -> Int8Vector # min :: Int8Vector -> Int8Vector -> Int8Vector # | |
Show Int8Vector Source # | |
Defined in Rattletrap.Type.Int8Vector Methods showsPrec :: Int -> Int8Vector -> ShowS # show :: Int8Vector -> String # showList :: [Int8Vector] -> ShowS # | |
ToJSON Int8Vector Source # | |
Defined in Rattletrap.Type.Int8Vector Methods toJSON :: Int8Vector -> Value # toEncoding :: Int8Vector -> Encoding # toJSONList :: [Int8Vector] -> Value # toEncodingList :: [Int8Vector] -> Encoding # | |
FromJSON Int8Vector Source # | |
Defined in Rattletrap.Type.Int8Vector |
Constructors
Int8le | |
Fields
|
newtype UpdatedReplication Source #
Constructors
UpdatedReplication | |
Fields |
Instances
Constructors
Attribute | |
Fields
|
Instances
Eq Attribute Source # | |
Ord Attribute Source # | |
Show Attribute Source # | |
ToJSON Attribute Source # | |
Defined in Rattletrap.Type.Attribute | |
FromJSON Attribute Source # | |
data AttributeValue Source #
Constructors
Instances
data AppliedDamageAttribute Source #
Constructors
AppliedDamageAttribute | |
Instances
newtype BooleanAttribute Source #
Constructors
BooleanAttribute | |
Fields |
Instances
newtype ByteAttribute Source #
Constructors
ByteAttribute | |
Fields |
Instances
data CamSettingsAttribute Source #
Constructors
Instances
data ClubColorsAttribute Source #
Constructors
ClubColorsAttribute | |
Instances
data DamageStateAttribute Source #
Constructors
DamageStateAttribute | |
Instances
data DemolishAttribute Source #
Constructors
DemolishAttribute | |
Instances
newtype EnumAttribute Source #
Constructors
EnumAttribute | |
Fields |
Instances
data ExplosionAttribute Source #
Constructors
ExplosionAttribute | |
Instances
data ExtendedExplosionAttribute Source #
Constructors
ExtendedExplosionAttribute | |
Instances
data FlaggedIntAttribute Source #
Constructors
FlaggedIntAttribute | |
Fields |
Instances
newtype FloatAttribute Source #
Constructors
FloatAttribute | |
Fields |
Instances
data GameModeAttribute Source #
Constructors
GameModeAttribute | |
Fields |
Instances
newtype IntAttribute Source #
Constructors
IntAttribute | |
Fields |
Instances
Eq IntAttribute Source # | |
Defined in Rattletrap.Type.IntAttribute | |
Ord IntAttribute Source # | |
Defined in Rattletrap.Type.IntAttribute Methods compare :: IntAttribute -> IntAttribute -> Ordering # (<) :: IntAttribute -> IntAttribute -> Bool # (<=) :: IntAttribute -> IntAttribute -> Bool # (>) :: IntAttribute -> IntAttribute -> Bool # (>=) :: IntAttribute -> IntAttribute -> Bool # max :: IntAttribute -> IntAttribute -> IntAttribute # min :: IntAttribute -> IntAttribute -> IntAttribute # | |
Show IntAttribute Source # | |
Defined in Rattletrap.Type.IntAttribute Methods showsPrec :: Int -> IntAttribute -> ShowS # show :: IntAttribute -> String # showList :: [IntAttribute] -> ShowS # | |
ToJSON IntAttribute Source # | |
Defined in Rattletrap.Type.IntAttribute Methods toJSON :: IntAttribute -> Value # toEncoding :: IntAttribute -> Encoding # toJSONList :: [IntAttribute] -> Value # toEncodingList :: [IntAttribute] -> Encoding # | |
FromJSON IntAttribute Source # | |
Defined in Rattletrap.Type.IntAttribute |
data LoadoutAttribute Source #
Constructors
Instances
newtype LoadoutOnlineAttribute Source #
Constructors
LoadoutOnlineAttribute | |
Fields |
Instances
data ProductAttribute Source #
Constructors
ProductAttribute | |
Fields |
Instances
data LoadoutsAttribute Source #
Constructors
LoadoutsAttribute | |
Instances
data LoadoutsOnlineAttribute Source #
Constructors
LoadoutsOnlineAttribute | |
Instances
newtype LocationAttribute Source #
Constructors
LocationAttribute | |
Fields |
Instances
data MusicStingerAttribute Source #
Constructors
MusicStingerAttribute | |
Instances
data PartyLeaderAttribute Source #
Constructors
PartyLeaderAttribute | |
Fields |
Instances
Constructors
RemoteIdPlayStation Text [Word8] | |
RemoteIdPsyNet Bitstream | |
RemoteIdSplitscreen Word32 | |
RemoteIdSteam Word64le | |
RemoteIdSwitch Bitstream | |
RemoteIdXbox Word64le |
data PickupAttribute Source #
Constructors
PickupAttribute | |
Instances
data PrivateMatchSettingsAttribute Source #
Constructors
PrivateMatchSettingsAttribute | |
Instances
newtype QWordAttribute Source #
Constructors
QWordAttribute | |
Fields |
Instances
data ReservationAttribute Source #
Constructors
ReservationAttribute | |
Instances
data UniqueIdAttribute Source #
Constructors
UniqueIdAttribute | |
Instances
data RigidBodyStateAttribute Source #
Constructors
RigidBodyStateAttribute | |
Instances
data CompressedWordVector Source #
Constructors
CompressedWordVector | |
Instances
newtype StringAttribute Source #
Constructors
StringAttribute | |
Fields |
Instances
data TeamPaintAttribute Source #
Constructors
TeamPaintAttribute | |
Instances
data WeldedInfoAttribute Source #
Constructors
WeldedInfoAttribute | |
Instances
data DestroyedReplication Source #
Destroyed replications don't actually contain any extra information. All
you need to know is the actor's ID, which is given by the
Replication
.
Constructors
DestroyedReplication |
Instances
Constructors
Message | |
Fields
|
Constructors
Mark | |
data ClassMapping Source #
Constructors
ClassMapping | |
Fields |
Instances
Eq ClassMapping Source # | |
Defined in Rattletrap.Type.ClassMapping | |
Ord ClassMapping Source # | |
Defined in Rattletrap.Type.ClassMapping Methods compare :: ClassMapping -> ClassMapping -> Ordering # (<) :: ClassMapping -> ClassMapping -> Bool # (<=) :: ClassMapping -> ClassMapping -> Bool # (>) :: ClassMapping -> ClassMapping -> Bool # (>=) :: ClassMapping -> ClassMapping -> Bool # max :: ClassMapping -> ClassMapping -> ClassMapping # min :: ClassMapping -> ClassMapping -> ClassMapping # | |
Show ClassMapping Source # | |
Defined in Rattletrap.Type.ClassMapping Methods showsPrec :: Int -> ClassMapping -> ShowS # show :: ClassMapping -> String # showList :: [ClassMapping] -> ShowS # | |
ToJSON ClassMapping Source # | |
Defined in Rattletrap.Type.ClassMapping Methods toJSON :: ClassMapping -> Value # toEncoding :: ClassMapping -> Encoding # toJSONList :: [ClassMapping] -> Value # toEncodingList :: [ClassMapping] -> Encoding # | |
FromJSON ClassMapping Source # | |
Defined in Rattletrap.Type.ClassMapping |
Constructors
Cache | |
data AttributeMapping Source #
Constructors
AttributeMapping | |