rattletrap-9.0.7: Parse and generate Rocket League replays.

Safe HaskellNone
LanguageHaskell2010

Rattletrap

Synopsis

Documentation

main :: IO () Source #

encodeReplayJson :: Replay -> ByteString Source #

Encodes a replay as JSON.

encodeReplayFile :: Bool -> Replay -> ByteString Source #

Encodes a raw replay.

data AppliedDamageAttribute Source #

Instances
Eq AppliedDamageAttribute Source # 
Instance details

Defined in Rattletrap.Type.AppliedDamageAttribute

Ord AppliedDamageAttribute Source # 
Instance details

Defined in Rattletrap.Type.AppliedDamageAttribute

Show AppliedDamageAttribute Source # 
Instance details

Defined in Rattletrap.Type.AppliedDamageAttribute

ToJSON AppliedDamageAttribute Source # 
Instance details

Defined in Rattletrap.Type.AppliedDamageAttribute

FromJSON AppliedDamageAttribute Source # 
Instance details

Defined in Rattletrap.Type.AppliedDamageAttribute

data Attribute Source #

Constructors

Attribute 

Fields

data AttributeMapping Source #

data AttributeType Source #

data AttributeValue Source #

Constructors

AttributeValueAppliedDamage AppliedDamageAttribute 
AttributeValueBoolean BooleanAttribute 
AttributeValueByte ByteAttribute 
AttributeValueCamSettings CamSettingsAttribute 
AttributeValueClubColors ClubColorsAttribute 
AttributeValueDamageState DamageStateAttribute 
AttributeValueDemolish DemolishAttribute 
AttributeValueEnum EnumAttribute 
AttributeValueExplosion ExplosionAttribute 
AttributeValueExtendedExplosion ExtendedExplosionAttribute 
AttributeValueFlaggedInt FlaggedIntAttribute 
AttributeValueFlaggedByte FlaggedByteAttribute 
AttributeValueFloat FloatAttribute 
AttributeValueGameMode GameModeAttribute 
AttributeValueInt IntAttribute 
AttributeValueInt64 Int64Attribute 
AttributeValueLoadout LoadoutAttribute 
AttributeValueLoadoutOnline LoadoutOnlineAttribute 
AttributeValueLoadouts LoadoutsAttribute 
AttributeValueLoadoutsOnline LoadoutsOnlineAttribute 
AttributeValueLocation LocationAttribute 
AttributeValueMusicStinger MusicStingerAttribute 
AttributeValuePartyLeader PartyLeaderAttribute 
AttributeValuePickup PickupAttribute 
AttributeValuePickupNew PickupAttributeNew 
AttributeValuePlayerHistoryKey PlayerHistoryKeyAttribute 
AttributeValuePrivateMatchSettings PrivateMatchSettingsAttribute 
AttributeValueQWord QWordAttribute 
AttributeValueReservation ReservationAttribute 
AttributeValueRigidBodyState RigidBodyStateAttribute 
AttributeValueStatEvent StatEventAttribute 
AttributeValueString StringAttribute 
AttributeValueTeamPaint TeamPaintAttribute 
AttributeValueTitle TitleAttribute 
AttributeValueUniqueId UniqueIdAttribute 
AttributeValueWeldedInfo WeldedInfoAttribute 

newtype BooleanAttribute Source #

data Cache Source #

Instances
Eq Cache Source # 
Instance details

Defined in Rattletrap.Type.Cache

Methods

(==) :: Cache -> Cache -> Bool #

(/=) :: Cache -> Cache -> Bool #

Ord Cache Source # 
Instance details

Defined in Rattletrap.Type.Cache

Methods

compare :: Cache -> Cache -> Ordering #

(<) :: Cache -> Cache -> Bool #

(<=) :: Cache -> Cache -> Bool #

(>) :: Cache -> Cache -> Bool #

(>=) :: Cache -> Cache -> Bool #

max :: Cache -> Cache -> Cache #

min :: Cache -> Cache -> Cache #

Show Cache Source # 
Instance details

Defined in Rattletrap.Type.Cache

Methods

showsPrec :: Int -> Cache -> ShowS #

show :: Cache -> String #

showList :: [Cache] -> ShowS #

ToJSON Cache Source # 
Instance details

Defined in Rattletrap.Type.Cache

FromJSON Cache Source # 
Instance details

Defined in Rattletrap.Type.Cache

data CamSettingsAttribute Source #

Instances
Eq CamSettingsAttribute Source # 
Instance details

Defined in Rattletrap.Type.CamSettingsAttribute

Ord CamSettingsAttribute Source # 
Instance details

Defined in Rattletrap.Type.CamSettingsAttribute

Show CamSettingsAttribute Source # 
Instance details

Defined in Rattletrap.Type.CamSettingsAttribute

ToJSON CamSettingsAttribute Source # 
Instance details

Defined in Rattletrap.Type.CamSettingsAttribute

FromJSON CamSettingsAttribute Source # 
Instance details

Defined in Rattletrap.Type.CamSettingsAttribute

data ClassAttributeMap Source #

This data structure holds all the information about classes, objects, and attributes in the replay. The class hierarchy is not fixed; it is encoded in the Content. Similarly, the attributes that belong to each class are not fixed either. Converting the raw data into a usable structure is tedious; see makeClassAttributeMap.

Constructors

ClassAttributeMap 

Fields

data ClubColorsAttribute Source #

Instances
Eq ClubColorsAttribute Source # 
Instance details

Defined in Rattletrap.Type.ClubColorsAttribute

Ord ClubColorsAttribute Source # 
Instance details

Defined in Rattletrap.Type.ClubColorsAttribute

Show ClubColorsAttribute Source # 
Instance details

Defined in Rattletrap.Type.ClubColorsAttribute

ToJSON ClubColorsAttribute Source # 
Instance details

Defined in Rattletrap.Type.ClubColorsAttribute

FromJSON ClubColorsAttribute Source # 
Instance details

Defined in Rattletrap.Type.ClubColorsAttribute

data CompressedWord Source #

Although there's no guarantee that these values will not overflow, it's exceptionally unlikely. Most CompressedWords are very small.

data CompressedWordVector Source #

Instances
Eq CompressedWordVector Source # 
Instance details

Defined in Rattletrap.Type.CompressedWordVector

Ord CompressedWordVector Source # 
Instance details

Defined in Rattletrap.Type.CompressedWordVector

Show CompressedWordVector Source # 
Instance details

Defined in Rattletrap.Type.CompressedWordVector

ToJSON CompressedWordVector Source # 
Instance details

Defined in Rattletrap.Type.CompressedWordVector

FromJSON CompressedWordVector Source # 
Instance details

Defined in Rattletrap.Type.CompressedWordVector

data Content Source #

Contains low-level game data about a Replay.

Constructors

Content 

Fields

data DamageStateAttribute Source #

Instances
Eq DamageStateAttribute Source # 
Instance details

Defined in Rattletrap.Type.DamageStateAttribute

Ord DamageStateAttribute Source # 
Instance details

Defined in Rattletrap.Type.DamageStateAttribute

Show DamageStateAttribute Source # 
Instance details

Defined in Rattletrap.Type.DamageStateAttribute

ToJSON DamageStateAttribute Source # 
Instance details

Defined in Rattletrap.Type.DamageStateAttribute

FromJSON DamageStateAttribute Source # 
Instance details

Defined in Rattletrap.Type.DamageStateAttribute

data DemolishAttribute Source #

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
Eq DestroyedReplication Source # 
Instance details

Defined in Rattletrap.Type.DestroyedReplication

Ord DestroyedReplication Source # 
Instance details

Defined in Rattletrap.Type.DestroyedReplication

Show DestroyedReplication Source # 
Instance details

Defined in Rattletrap.Type.DestroyedReplication

ToJSON DestroyedReplication Source # 
Instance details

Defined in Rattletrap.Type.DestroyedReplication

FromJSON DestroyedReplication Source # 
Instance details

Defined in Rattletrap.Type.DestroyedReplication

data Dictionary a Source #

Instances
Eq a => Eq (Dictionary a) Source # 
Instance details

Defined in Rattletrap.Type.Dictionary

Methods

(==) :: Dictionary a -> Dictionary a -> Bool #

(/=) :: Dictionary a -> Dictionary a -> Bool #

Ord a => Ord (Dictionary a) Source # 
Instance details

Defined in Rattletrap.Type.Dictionary

Show a => Show (Dictionary a) Source # 
Instance details

Defined in Rattletrap.Type.Dictionary

ToJSON a => ToJSON (Dictionary a) Source # 
Instance details

Defined in Rattletrap.Type.Dictionary

FromJSON a => FromJSON (Dictionary a) Source # 
Instance details

Defined in Rattletrap.Type.Dictionary

data ExplosionAttribute Source #

Instances
Eq ExplosionAttribute Source # 
Instance details

Defined in Rattletrap.Type.ExplosionAttribute

Ord ExplosionAttribute Source # 
Instance details

Defined in Rattletrap.Type.ExplosionAttribute

Show ExplosionAttribute Source # 
Instance details

Defined in Rattletrap.Type.ExplosionAttribute

ToJSON ExplosionAttribute Source # 
Instance details

Defined in Rattletrap.Type.ExplosionAttribute

FromJSON ExplosionAttribute Source # 
Instance details

Defined in Rattletrap.Type.ExplosionAttribute

data ExtendedExplosionAttribute Source #

Instances
Eq ExtendedExplosionAttribute Source # 
Instance details

Defined in Rattletrap.Type.ExtendedExplosionAttribute

Ord ExtendedExplosionAttribute Source # 
Instance details

Defined in Rattletrap.Type.ExtendedExplosionAttribute

Show ExtendedExplosionAttribute Source # 
Instance details

Defined in Rattletrap.Type.ExtendedExplosionAttribute

ToJSON ExtendedExplosionAttribute Source # 
Instance details

Defined in Rattletrap.Type.ExtendedExplosionAttribute

FromJSON ExtendedExplosionAttribute Source # 
Instance details

Defined in Rattletrap.Type.ExtendedExplosionAttribute

data FlaggedIntAttribute Source #

Instances
Eq FlaggedIntAttribute Source # 
Instance details

Defined in Rattletrap.Type.FlaggedIntAttribute

Ord FlaggedIntAttribute Source # 
Instance details

Defined in Rattletrap.Type.FlaggedIntAttribute

Show FlaggedIntAttribute Source # 
Instance details

Defined in Rattletrap.Type.FlaggedIntAttribute

ToJSON FlaggedIntAttribute Source # 
Instance details

Defined in Rattletrap.Type.FlaggedIntAttribute

FromJSON FlaggedIntAttribute Source # 
Instance details

Defined in Rattletrap.Type.FlaggedIntAttribute

data Frame Source #

Constructors

Frame 

Fields

Instances
Eq Frame Source # 
Instance details

Defined in Rattletrap.Type.Frame

Methods

(==) :: Frame -> Frame -> Bool #

(/=) :: Frame -> Frame -> Bool #

Ord Frame Source # 
Instance details

Defined in Rattletrap.Type.Frame

Methods

compare :: Frame -> Frame -> Ordering #

(<) :: Frame -> Frame -> Bool #

(<=) :: Frame -> Frame -> Bool #

(>) :: Frame -> Frame -> Bool #

(>=) :: Frame -> Frame -> Bool #

max :: Frame -> Frame -> Frame #

min :: Frame -> Frame -> Frame #

Show Frame Source # 
Instance details

Defined in Rattletrap.Type.Frame

Methods

showsPrec :: Int -> Frame -> ShowS #

show :: Frame -> String #

showList :: [Frame] -> ShowS #

ToJSON Frame Source # 
Instance details

Defined in Rattletrap.Type.Frame

FromJSON Frame Source # 
Instance details

Defined in Rattletrap.Type.Frame

data GameModeAttribute Source #

Constructors

GameModeAttribute 

Fields

  • gameModeAttributeNumBits :: Int

    This field is guaranteed to be small. In other words, it won't overflow. It's stored as a regular Int rather than something more precise like an Int8 because it just gets passed to functions that expect Ints. There's no reason to do a bunch of conversions.

  • gameModeAttributeWord :: Word8
     

data Header Source #

Contains high-level metadata about a Replay.

Constructors

Header 

Fields

  • headerEngineVersion :: Word32le

    The "major" ("engine") version number.

  • headerLicenseeVersion :: Word32le

    The "minor" ("licensee") version number.

  • headerPatchVersion :: Maybe Word32le

    The "patch" ("net") version number.

  • headerLabel :: Str

    Always TAGame.Replay_Soccar_TA.

  • headerProperties :: Dictionary 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 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 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 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 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 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 StrProperty with a user-supplied name for the replay.
    • Team0Score: The blue team's score as an IntProperty. Can be omitted if the score is 0.
    • Team1Score: The orange team's score as an IntProperty. Can also be omitted if the score is 0.
    • TeamSize: An 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 BoolProperty to True.
Instances
Eq Header Source # 
Instance details

Defined in Rattletrap.Type.Header

Methods

(==) :: Header -> Header -> Bool #

(/=) :: Header -> Header -> Bool #

Ord Header Source # 
Instance details

Defined in Rattletrap.Type.Header

Show Header Source # 
Instance details

Defined in Rattletrap.Type.Header

ToJSON Header Source # 
Instance details

Defined in Rattletrap.Type.Header

FromJSON Header Source # 
Instance details

Defined in Rattletrap.Type.Header

data Initialization Source #

Constructors

Initialization 

Fields

newtype Int32le Source #

Constructors

Int32le 

Fields

newtype Int64le Source #

Constructors

Int64le 

Fields

newtype Int8le Source #

Constructors

Int8le 

Fields

Instances
Eq Int8le Source # 
Instance details

Defined in Rattletrap.Type.Int8le

Methods

(==) :: Int8le -> Int8le -> Bool #

(/=) :: Int8le -> Int8le -> Bool #

Ord Int8le Source # 
Instance details

Defined in Rattletrap.Type.Int8le

Show Int8le Source # 
Instance details

Defined in Rattletrap.Type.Int8le

ToJSON Int8le Source # 
Instance details

Defined in Rattletrap.Type.Int8le

FromJSON Int8le Source # 
Instance details

Defined in Rattletrap.Type.Int8le

data KeyFrame Source #

Constructors

KeyFrame 

Fields

newtype List a Source #

Constructors

List 

Fields

Instances
Eq a => Eq (List a) Source # 
Instance details

Defined in Rattletrap.Type.List

Methods

(==) :: List a -> List a -> Bool #

(/=) :: List a -> List a -> Bool #

Ord a => Ord (List a) Source # 
Instance details

Defined in Rattletrap.Type.List

Methods

compare :: List a -> List a -> Ordering #

(<) :: List a -> List a -> Bool #

(<=) :: List a -> List a -> Bool #

(>) :: List a -> List a -> Bool #

(>=) :: List a -> List a -> Bool #

max :: List a -> List a -> List a #

min :: List a -> List a -> List a #

Show a => Show (List a) Source # 
Instance details

Defined in Rattletrap.Type.List

Methods

showsPrec :: Int -> List a -> ShowS #

show :: List a -> String #

showList :: [List a] -> ShowS #

ToJSON a => ToJSON (List a) Source # 
Instance details

Defined in Rattletrap.Type.List

FromJSON a => FromJSON (List a) Source # 
Instance details

Defined in Rattletrap.Type.List

data LoadoutAttribute Source #

newtype LoadoutOnlineAttribute Source #

Instances
Eq LoadoutOnlineAttribute Source # 
Instance details

Defined in Rattletrap.Type.LoadoutOnlineAttribute

Ord LoadoutOnlineAttribute Source # 
Instance details

Defined in Rattletrap.Type.LoadoutOnlineAttribute

Show LoadoutOnlineAttribute Source # 
Instance details

Defined in Rattletrap.Type.LoadoutOnlineAttribute

ToJSON LoadoutOnlineAttribute Source # 
Instance details

Defined in Rattletrap.Type.LoadoutOnlineAttribute

FromJSON LoadoutOnlineAttribute Source # 
Instance details

Defined in Rattletrap.Type.LoadoutOnlineAttribute

data LoadoutsAttribute Source #

data LoadoutsOnlineAttribute Source #

Instances
Eq LoadoutsOnlineAttribute Source # 
Instance details

Defined in Rattletrap.Type.LoadoutsOnlineAttribute

Ord LoadoutsOnlineAttribute Source # 
Instance details

Defined in Rattletrap.Type.LoadoutsOnlineAttribute

Show LoadoutsOnlineAttribute Source # 
Instance details

Defined in Rattletrap.Type.LoadoutsOnlineAttribute

ToJSON LoadoutsOnlineAttribute Source # 
Instance details

Defined in Rattletrap.Type.LoadoutsOnlineAttribute

FromJSON LoadoutsOnlineAttribute Source # 
Instance details

Defined in Rattletrap.Type.LoadoutsOnlineAttribute

newtype LocationAttribute Source #

data Mark Source #

Constructors

Mark 

Fields

Instances
Eq Mark Source # 
Instance details

Defined in Rattletrap.Type.Mark

Methods

(==) :: Mark -> Mark -> Bool #

(/=) :: Mark -> Mark -> Bool #

Ord Mark Source # 
Instance details

Defined in Rattletrap.Type.Mark

Methods

compare :: Mark -> Mark -> Ordering #

(<) :: Mark -> Mark -> Bool #

(<=) :: Mark -> Mark -> Bool #

(>) :: Mark -> Mark -> Bool #

(>=) :: Mark -> Mark -> Bool #

max :: Mark -> Mark -> Mark #

min :: Mark -> Mark -> Mark #

Show Mark Source # 
Instance details

Defined in Rattletrap.Type.Mark

Methods

showsPrec :: Int -> Mark -> ShowS #

show :: Mark -> String #

showList :: [Mark] -> ShowS #

ToJSON Mark Source # 
Instance details

Defined in Rattletrap.Type.Mark

FromJSON Mark Source # 
Instance details

Defined in Rattletrap.Type.Mark

data Message Source #

Constructors

Message 

Fields

data MusicStingerAttribute Source #

Instances
Eq MusicStingerAttribute Source # 
Instance details

Defined in Rattletrap.Type.MusicStingerAttribute

Ord MusicStingerAttribute Source # 
Instance details

Defined in Rattletrap.Type.MusicStingerAttribute

Show MusicStingerAttribute Source # 
Instance details

Defined in Rattletrap.Type.MusicStingerAttribute

ToJSON MusicStingerAttribute Source # 
Instance details

Defined in Rattletrap.Type.MusicStingerAttribute

FromJSON MusicStingerAttribute Source # 
Instance details

Defined in Rattletrap.Type.MusicStingerAttribute

data PartyLeaderAttribute Source #

Instances
Eq PartyLeaderAttribute Source # 
Instance details

Defined in Rattletrap.Type.PartyLeaderAttribute

Ord PartyLeaderAttribute Source # 
Instance details

Defined in Rattletrap.Type.PartyLeaderAttribute

Show PartyLeaderAttribute Source # 
Instance details

Defined in Rattletrap.Type.PartyLeaderAttribute

ToJSON PartyLeaderAttribute Source # 
Instance details

Defined in Rattletrap.Type.PartyLeaderAttribute

FromJSON PartyLeaderAttribute Source # 
Instance details

Defined in Rattletrap.Type.PartyLeaderAttribute

data PickupAttribute Source #

newtype PlayerHistoryKeyAttribute Source #

Instances
Eq PlayerHistoryKeyAttribute Source # 
Instance details

Defined in Rattletrap.Type.PlayerHistoryKeyAttribute

Ord PlayerHistoryKeyAttribute Source # 
Instance details

Defined in Rattletrap.Type.PlayerHistoryKeyAttribute

Show PlayerHistoryKeyAttribute Source # 
Instance details

Defined in Rattletrap.Type.PlayerHistoryKeyAttribute

ToJSON PlayerHistoryKeyAttribute Source # 
Instance details

Defined in Rattletrap.Type.PlayerHistoryKeyAttribute

FromJSON PlayerHistoryKeyAttribute Source # 
Instance details

Defined in Rattletrap.Type.PlayerHistoryKeyAttribute

data PrivateMatchSettingsAttribute Source #

Instances
Eq PrivateMatchSettingsAttribute Source # 
Instance details

Defined in Rattletrap.Type.PrivateMatchSettingsAttribute

Ord PrivateMatchSettingsAttribute Source # 
Instance details

Defined in Rattletrap.Type.PrivateMatchSettingsAttribute

Show PrivateMatchSettingsAttribute Source # 
Instance details

Defined in Rattletrap.Type.PrivateMatchSettingsAttribute

ToJSON PrivateMatchSettingsAttribute Source # 
Instance details

Defined in Rattletrap.Type.PrivateMatchSettingsAttribute

FromJSON PrivateMatchSettingsAttribute Source # 
Instance details

Defined in Rattletrap.Type.PrivateMatchSettingsAttribute

data ProductAttribute Source #

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 StrProperty.

PropertyValueQWord Word64le 
PropertyValueStr Str 

data Replay Source #

A Rocket League replay.

Constructors

Replay 

Fields

Instances
Eq Replay Source # 
Instance details

Defined in Rattletrap.Type.Replay

Methods

(==) :: Replay -> Replay -> Bool #

(/=) :: Replay -> Replay -> Bool #

Ord Replay Source # 
Instance details

Defined in Rattletrap.Type.Replay

Show Replay Source # 
Instance details

Defined in Rattletrap.Type.Replay

ToJSON Replay Source # 
Instance details

Defined in Rattletrap.Type.Replay

FromJSON Replay Source # 
Instance details

Defined in Rattletrap.Type.Replay

data ReplicationValue Source #

Constructors

ReplicationValueSpawned SpawnedReplication

Creates a new actor.

ReplicationValueUpdated UpdatedReplication

Updates an existing actor.

ReplicationValueDestroyed DestroyedReplication

Destroys an existing actor.

data ReservationAttribute Source #

Instances
Eq ReservationAttribute Source # 
Instance details

Defined in Rattletrap.Type.ReservationAttribute

Ord ReservationAttribute Source # 
Instance details

Defined in Rattletrap.Type.ReservationAttribute

Show ReservationAttribute Source # 
Instance details

Defined in Rattletrap.Type.ReservationAttribute

ToJSON ReservationAttribute Source # 
Instance details

Defined in Rattletrap.Type.ReservationAttribute

FromJSON ReservationAttribute Source # 
Instance details

Defined in Rattletrap.Type.ReservationAttribute

data RigidBodyStateAttribute Source #

Instances
Eq RigidBodyStateAttribute Source # 
Instance details

Defined in Rattletrap.Type.RigidBodyStateAttribute

Ord RigidBodyStateAttribute Source # 
Instance details

Defined in Rattletrap.Type.RigidBodyStateAttribute

Show RigidBodyStateAttribute Source # 
Instance details

Defined in Rattletrap.Type.RigidBodyStateAttribute

ToJSON RigidBodyStateAttribute Source # 
Instance details

Defined in Rattletrap.Type.RigidBodyStateAttribute

FromJSON RigidBodyStateAttribute Source # 
Instance details

Defined in Rattletrap.Type.RigidBodyStateAttribute

data Section a Source #

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 # 
Instance details

Defined in Rattletrap.Type.Section

Methods

(==) :: Section a -> Section a -> Bool #

(/=) :: Section a -> Section a -> Bool #

Ord a => Ord (Section a) Source # 
Instance details

Defined in Rattletrap.Type.Section

Methods

compare :: Section a -> Section a -> Ordering #

(<) :: Section a -> Section a -> Bool #

(<=) :: Section a -> Section a -> Bool #

(>) :: Section a -> Section a -> Bool #

(>=) :: Section a -> Section a -> Bool #

max :: Section a -> Section a -> Section a #

min :: Section a -> Section a -> Section a #

Show a => Show (Section a) Source # 
Instance details

Defined in Rattletrap.Type.Section

Methods

showsPrec :: Int -> Section a -> ShowS #

show :: Section a -> String #

showList :: [Section a] -> ShowS #

ToJSON a => ToJSON (Section a) Source # 
Instance details

Defined in Rattletrap.Type.Section

FromJSON a => FromJSON (Section a) Source # 
Instance details

Defined in Rattletrap.Type.Section

data SpawnedReplication Source #

Constructors

SpawnedReplication 

Fields

Instances
Eq SpawnedReplication Source # 
Instance details

Defined in Rattletrap.Type.SpawnedReplication

Ord SpawnedReplication Source # 
Instance details

Defined in Rattletrap.Type.SpawnedReplication

Show SpawnedReplication Source # 
Instance details

Defined in Rattletrap.Type.SpawnedReplication

ToJSON SpawnedReplication Source # 
Instance details

Defined in Rattletrap.Type.SpawnedReplication

FromJSON SpawnedReplication Source # 
Instance details

Defined in Rattletrap.Type.SpawnedReplication

data StatEventAttribute Source #

Instances
Eq StatEventAttribute Source # 
Instance details

Defined in Rattletrap.Type.StatEventAttribute

Ord StatEventAttribute Source # 
Instance details

Defined in Rattletrap.Type.StatEventAttribute

Show StatEventAttribute Source # 
Instance details

Defined in Rattletrap.Type.StatEventAttribute

ToJSON StatEventAttribute Source # 
Instance details

Defined in Rattletrap.Type.StatEventAttribute

FromJSON StatEventAttribute Source # 
Instance details

Defined in Rattletrap.Type.StatEventAttribute

newtype Str Source #

Constructors

Str 

Fields

Instances
Eq Str Source # 
Instance details

Defined in Rattletrap.Type.Str

Methods

(==) :: Str -> Str -> Bool #

(/=) :: Str -> Str -> Bool #

Ord Str Source # 
Instance details

Defined in Rattletrap.Type.Str

Methods

compare :: Str -> Str -> Ordering #

(<) :: Str -> Str -> Bool #

(<=) :: Str -> Str -> Bool #

(>) :: Str -> Str -> Bool #

(>=) :: Str -> Str -> Bool #

max :: Str -> Str -> Str #

min :: Str -> Str -> Str #

Show Str Source # 
Instance details

Defined in Rattletrap.Type.Str

Methods

showsPrec :: Int -> Str -> ShowS #

show :: Str -> String #

showList :: [Str] -> ShowS #

ToJSON Str Source # 
Instance details

Defined in Rattletrap.Type.Str

FromJSON Str Source # 
Instance details

Defined in Rattletrap.Type.Str

data TeamPaintAttribute Source #

Instances
Eq TeamPaintAttribute Source # 
Instance details

Defined in Rattletrap.Type.TeamPaintAttribute

Ord TeamPaintAttribute Source # 
Instance details

Defined in Rattletrap.Type.TeamPaintAttribute

Show TeamPaintAttribute Source # 
Instance details

Defined in Rattletrap.Type.TeamPaintAttribute

ToJSON TeamPaintAttribute Source # 
Instance details

Defined in Rattletrap.Type.TeamPaintAttribute

FromJSON TeamPaintAttribute Source # 
Instance details

Defined in Rattletrap.Type.TeamPaintAttribute

data TitleAttribute Source #

data UniqueIdAttribute Source #

newtype UpdatedReplication Source #

Instances
Eq UpdatedReplication Source # 
Instance details

Defined in Rattletrap.Type.UpdatedReplication

Ord UpdatedReplication Source # 
Instance details

Defined in Rattletrap.Type.UpdatedReplication

Show UpdatedReplication Source # 
Instance details

Defined in Rattletrap.Type.UpdatedReplication

ToJSON UpdatedReplication Source # 
Instance details

Defined in Rattletrap.Type.UpdatedReplication

FromJSON UpdatedReplication Source # 
Instance details

Defined in Rattletrap.Type.UpdatedReplication

data Vector Source #

Constructors

Vector 

Fields

Instances
Eq Vector Source # 
Instance details

Defined in Rattletrap.Type.Vector

Methods

(==) :: Vector -> Vector -> Bool #

(/=) :: Vector -> Vector -> Bool #

Ord Vector Source # 
Instance details

Defined in Rattletrap.Type.Vector

Show Vector Source # 
Instance details

Defined in Rattletrap.Type.Vector

ToJSON Vector Source # 
Instance details

Defined in Rattletrap.Type.Vector

FromJSON Vector Source # 
Instance details

Defined in Rattletrap.Type.Vector

data WeldedInfoAttribute Source #

Instances
Eq WeldedInfoAttribute Source # 
Instance details

Defined in Rattletrap.Type.WeldedInfoAttribute

Ord WeldedInfoAttribute Source # 
Instance details

Defined in Rattletrap.Type.WeldedInfoAttribute

Show WeldedInfoAttribute Source # 
Instance details

Defined in Rattletrap.Type.WeldedInfoAttribute

ToJSON WeldedInfoAttribute Source # 
Instance details

Defined in Rattletrap.Type.WeldedInfoAttribute

FromJSON WeldedInfoAttribute Source # 
Instance details

Defined in Rattletrap.Type.WeldedInfoAttribute

newtype Word8le Source #

Constructors

Word8le 

Fields