-- brittany --columns 120
module Rattletrap.Data where

import qualified Data.Bifunctor as Bifunctor
import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified Data.Text as Text
import qualified Rattletrap.Type.AttributeType as AttributeType

parentClasses :: Map.Map Text.Text Text.Text
parentClasses :: Map Text Text
parentClasses =
  forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
      (forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
Bifunctor.bimap String -> Text
Text.pack String -> Text
Text.pack)
      [ (String
"Engine.Actor", String
"Core.Object"),
        (String
"Engine.GameReplicationInfo", String
"Engine.ReplicationInfo"),
        (String
"Engine.Info", String
"Engine.Actor"),
        (String
"Engine.Pawn", String
"Engine.Actor"),
        (String
"Engine.PlayerReplicationInfo", String
"Engine.ReplicationInfo"),
        (String
"Engine.ReplicationInfo", String
"Engine.Info"),
        (String
"Engine.TeamInfo", String
"Engine.ReplicationInfo"),
        (String
"ProjectX.GRI_X", String
"Engine.GameReplicationInfo"),
        (String
"ProjectX.Pawn_X", String
"Engine.Pawn"),
        (String
"ProjectX.PRI_X", String
"Engine.PlayerReplicationInfo"),
        (String
"TAGame.Ball_God_TA", String
"TAGame.Ball_TA"),
        (String
"TAGame.Ball_Haunted_TA", String
"TAGame.Ball_TA"),
        (String
"TAGame.Ball_TA", String
"TAGame.RBActor_TA"),
        (String
"TAGame.CameraSettingsActor_TA", String
"Engine.ReplicationInfo"),
        (String
"TAGame.Car_Season_TA", String
"TAGame.PRI_TA"),
        (String
"TAGame.Car_TA", String
"TAGame.Vehicle_TA"),
        (String
"TAGame.CarComponent_Boost_TA", String
"TAGame.CarComponent_TA"),
        (String
"TAGame.CarComponent_Dodge_TA", String
"TAGame.CarComponent_TA"),
        (String
"TAGame.CarComponent_DoubleJump_TA", String
"TAGame.CarComponent_TA"),
        (String
"TAGame.CarComponent_FlipCar_TA", String
"TAGame.CarComponent_TA"),
        (String
"TAGame.CarComponent_Jump_TA", String
"TAGame.CarComponent_TA"),
        (String
"TAGame.CarComponent_TA", String
"Engine.ReplicationInfo"),
        (String
"TAGame.CrowdActor_TA", String
"Engine.ReplicationInfo"),
        (String
"TAGame.CrowdManager_TA", String
"Engine.ReplicationInfo"),
        (String
"TAGame.GameEvent_Football_TA", String
"TAGame.GameEvent_Soccar_TA"),
        (String
"TAGame.GameEvent_GodBall_TA", String
"TAGame.GameEvent_Soccar_TA"),
        (String
"TAGame.GameEvent_Season_TA", String
"TAGame.GameEvent_Soccar_TA"),
        (String
"TAGame.GameEvent_Soccar_TA", String
"TAGame.GameEvent_Team_TA"),
        (String
"TAGame.GameEvent_SoccarPrivate_TA", String
"TAGame.GameEvent_Soccar_TA"),
        (String
"TAGame.GameEvent_SoccarSplitscreen_TA", String
"TAGame.GameEvent_SoccarPrivate_TA"),
        (String
"TAGame.GameEvent_TA", String
"Engine.ReplicationInfo"),
        (String
"TAGame.GameEvent_Team_TA", String
"TAGame.GameEvent_TA"),
        (String
"TAGame.GRI_TA", String
"ProjectX.GRI_X"),
        (String
"TAGame.HauntedBallTrapTrigger_TA", String
"Engine.Actor"),
        (String
"TAGame.InMapScoreboard_TA", String
"Engine.Actor"),
        (String
"TAGame.PRI_TA", String
"ProjectX.PRI_X"),
        (String
"TAGame.RBActor_TA", String
"ProjectX.Pawn_X"),
        (String
"TAGame.SpecialPickup_BallCarSpring_TA", String
"TAGame.SpecialPickup_Spring_TA"),
        (String
"TAGame.SpecialPickup_BallFreeze_TA", String
"TAGame.SpecialPickup_Targeted_TA"),
        (String
"TAGame.SpecialPickup_BallGravity_TA", String
"TAGame.SpecialPickup_TA"),
        (String
"TAGame.SpecialPickup_BallLasso_TA", String
"TAGame.SpecialPickup_GrapplingHook_TA"),
        (String
"TAGame.SpecialPickup_BallVelcro_TA", String
"TAGame.SpecialPickup_TA"),
        (String
"TAGame.SpecialPickup_Batarang_TA", String
"TAGame.SpecialPickup_BallLasso_TA"),
        (String
"TAGame.SpecialPickup_BoostOverride_TA", String
"TAGame.SpecialPickup_Targeted_TA"),
        (String
"TAGame.SpecialPickup_Football_TA", String
"TAGame.SpecialPickup_TA"),
        (String
"TAGame.SpecialPickup_GrapplingHook_TA", String
"TAGame.SpecialPickup_Targeted_TA"),
        (String
"TAGame.SpecialPickup_HauntedBallBeam_TA", String
"TAGame.SpecialPickup_TA"),
        (String
"TAGame.SpecialPickup_HitForce_TA", String
"TAGame.SpecialPickup_TA"),
        (String
"TAGame.SpecialPickup_Rugby_TA", String
"TAGame.SpecialPickup_TA"),
        (String
"TAGame.SpecialPickup_Spring_TA", String
"TAGame.SpecialPickup_Targeted_TA"),
        (String
"TAGame.SpecialPickup_Swapper_TA", String
"TAGame.SpecialPickup_Targeted_TA"),
        (String
"TAGame.SpecialPickup_TA", String
"TAGame.CarComponent_TA"),
        (String
"TAGame.SpecialPickup_Targeted_TA", String
"TAGame.SpecialPickup_TA"),
        (String
"TAGame.SpecialPickup_Tornado_TA", String
"TAGame.SpecialPickup_TA"),
        (String
"TAGame.Team_Soccar_TA", String
"TAGame.Team_TA"),
        (String
"TAGame.Team_TA", String
"Engine.TeamInfo"),
        (String
"TAGame.Vehicle_TA", String
"TAGame.RBActor_TA"),
        (String
"TAGame.VehiclePickup_Boost_TA", String
"TAGame.VehiclePickup_TA"),
        (String
"TAGame.VehiclePickup_TA", String
"Engine.ReplicationInfo")
      ]

classesWithLocation :: Set.Set Text.Text
classesWithLocation :: Set Text
classesWithLocation =
  forall a. Ord a => [a] -> Set a
Set.fromList forall a b. (a -> b) -> a -> b
$
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
      String -> Text
Text.pack
      [ String
"Archetypes.Ball.Ball_BasketBall_Mutator",
        String
"Archetypes.Ball.Ball_Basketball",
        String
"Archetypes.Ball.Ball_BasketBall",
        String
"Archetypes.Ball.Ball_Breakout",
        String
"Archetypes.Ball.Ball_Default",
        String
"Archetypes.Ball.Ball_Puck",
        String
"Archetypes.Ball.Ball_Trajectory",
        String
"Archetypes.Ball.CubeBall",
        String
"Archetypes.Car.Car_Default",
        String
"Archetypes.GameEvent.GameEvent_Season:CarArchetype",
        String
"Archetypes.SpecialPickups.SpecialPickup_Rugby",
        String
"ProjectX.NetModeReplicator",
        String
"TAGame.Ball_Breakout_TA",
        String
"TAGame.Ball_God_TA",
        String
"TAGame.Ball_Haunted_TA",
        String
"TAGame.Ball_TA",
        String
"TAGame.CameraSettingsActor_TA",
        String
"TAGame.Cannon_TA",
        String
"TAGame.Car_Season_TA",
        String
"TAGame.Car_TA",
        String
"TAGame.CarComponent_Boost_TA",
        String
"TAGame.CarComponent_Dodge_TA",
        String
"TAGame.CarComponent_DoubleJump_TA",
        String
"TAGame.CarComponent_FlipCar_TA",
        String
"TAGame.CarComponent_Jump_TA",
        String
"TAGame.Default__CameraSettingsActor_TA",
        String
"TAGame.Default__PRI_TA",
        String
"TAGame.GameEvent_Football_TA",
        String
"TAGame.GameEvent_GodBall_TA",
        String
"TAGame.GameEvent_Season_TA",
        String
"TAGame.GameEvent_Soccar_TA",
        String
"TAGame.GameEvent_SoccarPrivate_TA",
        String
"TAGame.GameEvent_SoccarSplitscreen_TA",
        String
"TAGame.GameEvent_Tutorial_TA",
        String
"TAGame.GRI_TA",
        String
"TAGame.MaxTimeWarningData_TA",
        String
"TAGame.PickupTimer_TA",
        String
"TAGame.PRI_TA",
        String
"TAGame.RumblePickups_TA",
        String
"TAGame.SpecialPickup_BallCarSpring_TA",
        String
"TAGame.SpecialPickup_BallFreeze_TA",
        String
"TAGame.SpecialPickup_BallGravity_TA",
        String
"TAGame.SpecialPickup_BallLasso_TA",
        String
"TAGame.SpecialPickup_BallVelcro_TA",
        String
"TAGame.SpecialPickup_Batarang_TA",
        String
"TAGame.SpecialPickup_BoostOverride_TA",
        String
"TAGame.SpecialPickup_Football_TA",
        String
"TAGame.SpecialPickup_GrapplingHook_TA",
        String
"TAGame.SpecialPickup_HauntedBallBeam_TA",
        String
"TAGame.SpecialPickup_HitForce_TA",
        String
"TAGame.SpecialPickup_Rugby_TA",
        String
"TAGame.SpecialPickup_Swapper_TA",
        String
"TAGame.SpecialPickup_Tornado_TA",
        String
"TAGame.Team_Soccar_TA",
        String
"TheWorld:PersistentLevel.BreakOutActor_Platform_TA",
        String
"TheWorld:PersistentLevel.CrowdActor_TA",
        String
"TheWorld:PersistentLevel.CrowdManager_TA",
        String
"TheWorld:PersistentLevel.InMapScoreboard_TA",
        String
"TheWorld:PersistentLevel.VehiclePickup_Boost_TA"
      ]

classesWithRotation :: Set.Set Text.Text
classesWithRotation :: Set Text
classesWithRotation =
  forall a. Ord a => [a] -> Set a
Set.fromList forall a b. (a -> b) -> a -> b
$
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
      String -> Text
Text.pack
      [ String
"Archetypes.Ball.Ball_BasketBall_Mutator",
        String
"Archetypes.Ball.Ball_Basketball",
        String
"Archetypes.Ball.Ball_BasketBall",
        String
"Archetypes.Ball.Ball_Breakout",
        String
"Archetypes.Ball.Ball_Default",
        String
"Archetypes.Ball.Ball_Puck",
        String
"Archetypes.Ball.Ball_Trajectory",
        String
"Archetypes.Ball.CubeBall",
        String
"Archetypes.Car.Car_Default",
        String
"Archetypes.GameEvent.GameEvent_Season:CarArchetype",
        String
"Archetypes.SpecialPickups.SpecialPickup_Rugby",
        String
"TAGame.Ball_Breakout_TA",
        String
"TAGame.Ball_God_TA",
        String
"TAGame.Ball_Haunted_TA",
        String
"TAGame.Ball_TA",
        String
"TAGame.Car_Season_TA",
        String
"TAGame.Car_TA"
      ]

objectClasses :: Map.Map Text.Text Text.Text
objectClasses :: Map Text Text
objectClasses =
  forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
      (forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
Bifunctor.bimap String -> Text
Text.pack String -> Text
Text.pack)
      [ (String
"Archetypes.Ball.Ball_Anniversary", String
"TAGame.Ball_TA"),
        (String
"Archetypes.Ball.Ball_BasketBall_Mutator", String
"TAGame.Ball_TA"),
        (String
"Archetypes.Ball.Ball_Basketball", String
"TAGame.Ball_TA"),
        (String
"Archetypes.Ball.Ball_BasketBall", String
"TAGame.Ball_TA"),
        (String
"Archetypes.Ball.Ball_Beachball", String
"TAGame.Ball_TA"),
        (String
"Archetypes.Ball.Ball_Breakout", String
"TAGame.Ball_Breakout_TA"),
        (String
"Archetypes.Ball.Ball_Default", String
"TAGame.Ball_TA"),
        (String
"Archetypes.Ball.Ball_Football", String
"TAGame.Ball_TA"),
        (String
"Archetypes.Ball.Ball_God", String
"TAGame.Ball_God_TA"),
        (String
"Archetypes.Ball.Ball_Haunted", String
"TAGame.Ball_Haunted_TA"),
        (String
"Archetypes.Ball.Ball_Puck", String
"TAGame.Ball_TA"),
        (String
"Archetypes.Ball.Ball_Training", String
"TAGame.Ball_TA"),
        (String
"Archetypes.Ball.Ball_Trajectory", String
"TAGame.Ball_TA"),
        (String
"Archetypes.Ball.CubeBall", String
"TAGame.Ball_TA"),
        (String
"Archetypes.Car.Car_Default", String
"TAGame.Car_TA"),
        (String
"Archetypes.Car.Car_PostGameLobby", String
"TAGame.Car_TA"),
        (String
"Archetypes.CarComponents.CarComponent_Boost", String
"TAGame.CarComponent_Boost_TA"),
        (String
"Archetypes.CarComponents.CarComponent_Dodge", String
"TAGame.CarComponent_Dodge_TA"),
        (String
"Archetypes.CarComponents.CarComponent_DoubleJump", String
"TAGame.CarComponent_DoubleJump_TA"),
        (String
"Archetypes.CarComponents.CarComponent_FlipCar", String
"TAGame.CarComponent_FlipCar_TA"),
        (String
"Archetypes.CarComponents.CarComponent_Jump", String
"TAGame.CarComponent_Jump_TA"),
        (String
"Archetypes.GameEvent.GameEvent_Basketball", String
"TAGame.GameEvent_Soccar_TA"),
        (String
"Archetypes.GameEvent.GameEvent_BasketballPrivate", String
"TAGame.GameEvent_SoccarPrivate_TA"),
        (String
"Archetypes.GameEvent.GameEvent_BasketballSplitscreen", String
"TAGame.GameEvent_SoccarSplitscreen_TA"),
        (String
"Archetypes.GameEvent.GameEvent_Breakout", String
"TAGame.GameEvent_Soccar_TA"),
        (String
"Archetypes.GameEvent.GameEvent_Hockey", String
"TAGame.GameEvent_Soccar_TA"),
        (String
"Archetypes.GameEvent.GameEvent_HockeyPrivate", String
"TAGame.GameEvent_SoccarPrivate_TA"),
        (String
"Archetypes.GameEvent.GameEvent_HockeySplitscreen", String
"TAGame.GameEvent_SoccarSplitscreen_TA"),
        (String
"Archetypes.GameEvent.GameEvent_Items", String
"TAGame.GameEvent_Soccar_TA"),
        (String
"Archetypes.GameEvent.GameEvent_Season:CarArchetype", String
"TAGame.Car_TA"),
        (String
"Archetypes.GameEvent.GameEvent_Season", String
"TAGame.GameEvent_Season_TA"),
        (String
"Archetypes.GameEvent.GameEvent_Soccar", String
"TAGame.GameEvent_Soccar_TA"),
        (String
"Archetypes.GameEvent.GameEvent_SoccarLan", String
"TAGame.GameEvent_Soccar_TA"),
        (String
"Archetypes.GameEvent.GameEvent_SoccarPrivate", String
"TAGame.GameEvent_SoccarPrivate_TA"),
        (String
"Archetypes.GameEvent.GameEvent_SoccarSplitscreen", String
"TAGame.GameEvent_SoccarSplitscreen_TA"),
        (String
"Archetypes.SpecialPickups.SpecialPickup_BallFreeze", String
"TAGame.SpecialPickup_BallFreeze_TA"),
        (String
"Archetypes.SpecialPickups.SpecialPickup_BallGrapplingHook", String
"TAGame.SpecialPickup_GrapplingHook_TA"),
        (String
"Archetypes.SpecialPickups.SpecialPickup_BallLasso", String
"TAGame.SpecialPickup_BallLasso_TA"),
        (String
"Archetypes.SpecialPickups.SpecialPickup_BallSpring", String
"TAGame.SpecialPickup_BallCarSpring_TA"),
        (String
"Archetypes.SpecialPickups.SpecialPickup_BallVelcro", String
"TAGame.SpecialPickup_BallVelcro_TA"),
        (String
"Archetypes.SpecialPickups.SpecialPickup_Batarang", String
"TAGame.SpecialPickup_Batarang_TA"),
        (String
"Archetypes.SpecialPickups.SpecialPickup_BoostOverride", String
"TAGame.SpecialPickup_BoostOverride_TA"),
        (String
"Archetypes.SpecialPickups.SpecialPickup_CarSpring", String
"TAGame.SpecialPickup_BallCarSpring_TA"),
        (String
"Archetypes.SpecialPickups.SpecialPickup_Football", String
"TAGame.SpecialPickup_Football_TA"),
        (String
"Archetypes.SpecialPickups.SpecialPickup_GravityWell", String
"TAGame.SpecialPickup_BallGravity_TA"),
        (String
"Archetypes.SpecialPickups.SpecialPickup_HauntedBallBeam", String
"TAGame.SpecialPickup_HauntedBallBeam_TA"),
        (String
"Archetypes.SpecialPickups.SpecialPickup_Rugby", String
"TAGame.SpecialPickup_Rugby_TA"),
        (String
"Archetypes.SpecialPickups.SpecialPickup_StrongHit", String
"TAGame.SpecialPickup_HitForce_TA"),
        (String
"Archetypes.SpecialPickups.SpecialPickup_Swapper", String
"TAGame.SpecialPickup_Swapper_TA"),
        (String
"Archetypes.SpecialPickups.SpecialPickup_Tornado", String
"TAGame.SpecialPickup_Tornado_TA"),
        (String
"Archetypes.Teams.Team0", String
"TAGame.Team_Soccar_TA"),
        (String
"Archetypes.Teams.Team1", String
"TAGame.Team_Soccar_TA"),
        (String
"Archetypes.Tutorial.Cannon", String
"TAGame.Cannon_TA"),
        (String
"GameInfo_Basketball.GameInfo.GameInfo_Basketball:GameReplicationInfoArchetype", String
"TAGame.GRI_TA"),
        (String
"GameInfo_Breakout.GameInfo.GameInfo_Breakout:GameReplicationInfoArchetype", String
"TAGame.GRI_TA"),
        (String
"GameInfo_FootBall.GameInfo.GameInfo_FootBall:Archetype", String
"TAGame.GameEvent_Football_TA"),
        (String
"GameInfo_FootBall.GameInfo.GameInfo_FootBall:GameReplicationInfoArchetype", String
"TAGame.GRI_TA"),
        (String
"gameinfo_godball.GameInfo.gameinfo_godball:Archetype", String
"TAGame.GameEvent_GodBall_TA"),
        (String
"GameInfo_GodBall.GameInfo.GameInfo_GodBall:Archetype", String
"TAGame.GameEvent_GodBall_TA"),
        (String
"gameinfo_godball.GameInfo.gameinfo_godball:GameReplicationInfoArchetype", String
"TAGame.GRI_TA"),
        (String
"GameInfo_GodBall.GameInfo.GameInfo_GodBall:GameReplicationInfoArchetype", String
"TAGame.GRI_TA"),
        (String
"Gameinfo_Hockey.GameInfo.Gameinfo_Hockey:GameReplicationInfoArchetype", String
"TAGame.GRI_TA"),
        (String
"GameInfo_Items.GameInfo.GameInfo_Items:GameReplicationInfoArchetype", String
"TAGame.GRI_TA"),
        (String
"GameInfo_Season.GameInfo.GameInfo_Season:GameReplicationInfoArchetype", String
"TAGame.GRI_TA"),
        (String
"GameInfo_Soccar.GameInfo.GameInfo_Soccar:GameReplicationInfoArchetype", String
"TAGame.GRI_TA"),
        (String
"GameInfo_Tutorial.GameEvent.GameEvent_Tutorial_Aerial", String
"TAGame.GameEvent_Tutorial_TA"),
        (String
"GameInfo_Tutorial.GameInfo.GameInfo_Tutorial:GameReplicationInfoArchetype", String
"TAGame.GRI_TA"),
        (String
"Haunted_TrainStation_P.TheWorld:PersistentLevel.HauntedBallTrapTrigger_TA_0", String
"TAGame.HauntedBallTrapTrigger_TA"),
        (String
"Haunted_TrainStation_P.TheWorld:PersistentLevel.HauntedBallTrapTrigger_TA_1", String
"TAGame.HauntedBallTrapTrigger_TA"),
        (String
"ProjectX.Default__NetModeReplicator_X", String
"ProjectX.NetModeReplicator"),
        (String
"TAGame.Default__CameraSettingsActor_TA", String
"TAGame.CameraSettingsActor_TA"),
        (String
"TAGame.Default__MaxTimeWarningData_TA", String
"TAGame.MaxTimeWarningData_TA"),
        (String
"TAGame.Default__PickupTimer_TA", String
"TAGame.PickupTimer_TA"),
        (String
"TAGame.Default__PRI_TA", String
"TAGame.PRI_TA"),
        (String
"TAGame.Default__RumblePickups_TA", String
"TAGame.RumblePickups_TA"),
        (String
"TheWorld:PersistentLevel.BreakOutActor_Platform_TA", String
"TAGame.BreakOutActor_Platform_TA"),
        (String
"TheWorld:PersistentLevel.CrowdActor_TA", String
"TAGame.CrowdActor_TA"),
        (String
"TheWorld:PersistentLevel.CrowdManager_TA", String
"TAGame.CrowdManager_TA"),
        (String
"TheWorld:PersistentLevel.InMapScoreboard_TA", String
"TAGame.InMapScoreboard_TA"),
        (String
"TheWorld:PersistentLevel.VehiclePickup_Boost_TA", String
"TAGame.VehiclePickup_Boost_TA")
      ]

attributeTypes :: Map.Map Text.Text AttributeType.AttributeType
attributeTypes :: Map Text AttributeType
attributeTypes =
  forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
      (forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
Bifunctor.first String -> Text
Text.pack)
      [ (String
"Engine.Actor:bBlockActors", AttributeType
AttributeType.Boolean),
        (String
"Engine.Actor:bCollideActors", AttributeType
AttributeType.Boolean),
        (String
"Engine.Actor:bHidden", AttributeType
AttributeType.Boolean),
        (String
"Engine.Actor:bTearOff", AttributeType
AttributeType.Boolean),
        (String
"Engine.Actor:DrawScale", AttributeType
AttributeType.Float),
        (String
"Engine.Actor:RemoteRole", AttributeType
AttributeType.Enum),
        (String
"Engine.Actor:Role", AttributeType
AttributeType.Enum),
        (String
"Engine.Actor:Rotation", AttributeType
AttributeType.Rotation),
        (String
"Engine.GameReplicationInfo:bMatchIsOver", AttributeType
AttributeType.Boolean),
        (String
"Engine.GameReplicationInfo:GameClass", AttributeType
AttributeType.FlaggedInt),
        (String
"Engine.GameReplicationInfo:ServerName", AttributeType
AttributeType.String),
        (String
"Engine.Pawn:HealthMax", AttributeType
AttributeType.Int),
        (String
"Engine.Pawn:PlayerReplicationInfo", AttributeType
AttributeType.FlaggedInt),
        (String
"Engine.PlayerReplicationInfo:bBot", AttributeType
AttributeType.Boolean),
        (String
"Engine.PlayerReplicationInfo:bIsSpectator", AttributeType
AttributeType.Boolean),
        (String
"Engine.PlayerReplicationInfo:bReadyToPlay", AttributeType
AttributeType.Boolean),
        (String
"Engine.PlayerReplicationInfo:bTimedOut", AttributeType
AttributeType.Boolean),
        (String
"Engine.PlayerReplicationInfo:bWaitingPlayer", AttributeType
AttributeType.Boolean),
        (String
"Engine.PlayerReplicationInfo:Ping", AttributeType
AttributeType.Byte),
        (String
"Engine.PlayerReplicationInfo:PlayerID", AttributeType
AttributeType.Int),
        (String
"Engine.PlayerReplicationInfo:PlayerName", AttributeType
AttributeType.String),
        (String
"Engine.PlayerReplicationInfo:RemoteUserData", AttributeType
AttributeType.String),
        (String
"Engine.PlayerReplicationInfo:Score", AttributeType
AttributeType.Int),
        (String
"Engine.PlayerReplicationInfo:Team", AttributeType
AttributeType.FlaggedInt),
        (String
"Engine.PlayerReplicationInfo:UniqueId", AttributeType
AttributeType.UniqueId),
        (String
"Engine.ReplicatedActor_ORS:ReplicatedOwner", AttributeType
AttributeType.FlaggedInt),
        (String
"Engine.TeamInfo:Score", AttributeType
AttributeType.Int),
        (String
"ProjectX.GRI_X:bGameStarted", AttributeType
AttributeType.Boolean),
        (String
"ProjectX.GRI_X:GameServerID", AttributeType
AttributeType.GameServer),
        (String
"ProjectX.GRI_X:MatchGuid", AttributeType
AttributeType.String),
        (String
"ProjectX.GRI_X:MatchGUID", AttributeType
AttributeType.String),
        (String
"ProjectX.GRI_X:ReplicatedGameMutatorIndex", AttributeType
AttributeType.Int),
        (String
"ProjectX.GRI_X:ReplicatedGamePlaylist", AttributeType
AttributeType.Int),
        (String
"ProjectX.GRI_X:ReplicatedServerRegion", AttributeType
AttributeType.String),
        (String
"ProjectX.GRI_X:Reservations", AttributeType
AttributeType.Reservation),
        (String
"TAGame.Ball_Breakout_TA:AppliedDamage", AttributeType
AttributeType.AppliedDamage),
        (String
"TAGame.Ball_Breakout_TA:DamageIndex", AttributeType
AttributeType.Int),
        (String
"TAGame.Ball_Breakout_TA:LastTeamTouch", AttributeType
AttributeType.Byte),
        (String
"TAGame.Ball_God_TA:TargetSpeed", AttributeType
AttributeType.Float),
        (String
"TAGame.Ball_Haunted_TA:bIsBallBeamed", AttributeType
AttributeType.Boolean),
        (String
"TAGame.Ball_Haunted_TA:DeactivatedGoalIndex", AttributeType
AttributeType.Byte),
        (String
"TAGame.Ball_Haunted_TA:LastTeamTouch", AttributeType
AttributeType.Byte),
        (String
"TAGame.Ball_Haunted_TA:ReplicatedBeamBrokenValue", AttributeType
AttributeType.Byte),
        (String
"TAGame.Ball_Haunted_TA:TotalActiveBeams", AttributeType
AttributeType.Byte),
        (String
"TAGame.Ball_TA:GameEvent", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.Ball_TA:HitTeamNum", AttributeType
AttributeType.Byte),
        (String
"TAGame.Ball_TA:ReplicatedAddedCarBounceScale", AttributeType
AttributeType.Float),
        (String
"TAGame.Ball_TA:ReplicatedBallMaxLinearSpeedScale", AttributeType
AttributeType.Float),
        (String
"TAGame.Ball_TA:ReplicatedBallScale", AttributeType
AttributeType.Float),
        (String
"TAGame.Ball_TA:ReplicatedExplosionData", AttributeType
AttributeType.Explosion),
        (String
"TAGame.Ball_TA:ReplicatedExplosionDataExtended", AttributeType
AttributeType.ExtendedExplosion),
        (String
"TAGame.Ball_TA:ReplicatedPhysMatOverride", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.Ball_TA:ReplicatedWorldBounceScale", AttributeType
AttributeType.Float),
        (String
"TAGame.BreakOutActor_Platform_TA:DamageState", AttributeType
AttributeType.DamageState),
        (String
"TAGame.CameraSettingsActor_TA:bMouseCameraToggleEnabled", AttributeType
AttributeType.Boolean),
        (String
"TAGame.CameraSettingsActor_TA:bUsingBehindView", AttributeType
AttributeType.Boolean),
        (String
"TAGame.CameraSettingsActor_TA:bUsingSecondaryCamera", AttributeType
AttributeType.Boolean),
        (String
"TAGame.CameraSettingsActor_TA:bUsingSwivel", AttributeType
AttributeType.Boolean),
        (String
"TAGame.CameraSettingsActor_TA:CameraPitch", AttributeType
AttributeType.Byte),
        (String
"TAGame.CameraSettingsActor_TA:CameraYaw", AttributeType
AttributeType.Byte),
        (String
"TAGame.CameraSettingsActor_TA:PRI", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.CameraSettingsActor_TA:ProfileSettings", AttributeType
AttributeType.CamSettings),
        (String
"TAGame.Cannon_TA:FireCount", AttributeType
AttributeType.Byte),
        (String
"TAGame.Cannon_TA:Pitch", AttributeType
AttributeType.Float),
        (String
"TAGame.Car_TA:AddedBallForceMultiplier", AttributeType
AttributeType.Float),
        (String
"TAGame.Car_TA:AddedCarForceMultiplier", AttributeType
AttributeType.Float),
        (String
"TAGame.Car_TA:AttachedPickup", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.Car_TA:ClubColors", AttributeType
AttributeType.ClubColors),
        (String
"TAGame.Car_TA:ReplicatedCarScale", AttributeType
AttributeType.Float),
        (String
"TAGame.Car_TA:ReplicatedDemolish_CustomFX", AttributeType
AttributeType.CustomDemolish),
        (String
"TAGame.Car_TA:ReplicatedDemolish", AttributeType
AttributeType.Demolish),
        (String
"TAGame.Car_TA:ReplicatedDemolishGoalExplosion", AttributeType
AttributeType.CustomDemolish),
        (String
"TAGame.Car_TA:RumblePickups", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.Car_TA:TeamPaint", AttributeType
AttributeType.TeamPaint),
        (String
"TAGame.CarComponent_Boost_TA:bNoBoost", AttributeType
AttributeType.Boolean),
        (String
"TAGame.CarComponent_Boost_TA:BoostModifier", AttributeType
AttributeType.Float),
        (String
"TAGame.CarComponent_Boost_TA:bUnlimitedBoost", AttributeType
AttributeType.Boolean),
        (String
"TAGame.CarComponent_Boost_TA:RechargeDelay", AttributeType
AttributeType.Float),
        (String
"TAGame.CarComponent_Boost_TA:RechargeRate", AttributeType
AttributeType.Float),
        (String
"TAGame.CarComponent_Boost_TA:ReplicatedBoostAmount", AttributeType
AttributeType.Byte),
        (String
"TAGame.CarComponent_Boost_TA:UnlimitedBoostRefCount", AttributeType
AttributeType.Int),
        (String
"TAGame.CarComponent_Dodge_TA:DodgeImpulse", AttributeType
AttributeType.Location),
        (String
"TAGame.CarComponent_Dodge_TA:DodgeTorque", AttributeType
AttributeType.Location),
        (String
"TAGame.CarComponent_DoubleJump_TA:DoubleJumpImpulse", AttributeType
AttributeType.Location),
        (String
"TAGame.CarComponent_FlipCar_TA:bFlipRight", AttributeType
AttributeType.Boolean),
        (String
"TAGame.CarComponent_FlipCar_TA:FlipCarTime", AttributeType
AttributeType.Float),
        (String
"TAGame.CarComponent_TA:ReplicatedActive", AttributeType
AttributeType.Byte),
        (String
"TAGame.CarComponent_TA:ReplicatedActivityTime", AttributeType
AttributeType.Float),
        (String
"TAGame.CarComponent_TA:Vehicle", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.CrowdActor_TA:GameEvent", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.CrowdActor_TA:ModifiedNoise", AttributeType
AttributeType.Float),
        (String
"TAGame.CrowdActor_TA:ReplicatedCountDownNumber", AttributeType
AttributeType.Int),
        (String
"TAGame.CrowdActor_TA:ReplicatedOneShotSound", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.CrowdActor_TA:ReplicatedRoundCountDownNumber", AttributeType
AttributeType.Int),
        (String
"TAGame.CrowdManager_TA:GameEvent", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.CrowdManager_TA:ReplicatedGlobalOneShotSound", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.GameEvent_Soccar_TA:bBallHasBeenHit", AttributeType
AttributeType.Boolean),
        (String
"TAGame.GameEvent_Soccar_TA:bClubMatch", AttributeType
AttributeType.Boolean),
        (String
"TAGame.GameEvent_Soccar_TA:bMatchEnded", AttributeType
AttributeType.Boolean),
        (String
"TAGame.GameEvent_Soccar_TA:bNoContest", AttributeType
AttributeType.Boolean),
        (String
"TAGame.GameEvent_Soccar_TA:bOverTime", AttributeType
AttributeType.Boolean),
        (String
"TAGame.GameEvent_Soccar_TA:bUnlimitedTime", AttributeType
AttributeType.Boolean),
        (String
"TAGame.GameEvent_Soccar_TA:GameTime", AttributeType
AttributeType.Int),
        (String
"TAGame.GameEvent_Soccar_TA:GameWinner", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.GameEvent_Soccar_TA:MatchWinner", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.GameEvent_Soccar_TA:MaxScore", AttributeType
AttributeType.Int),
        (String
"TAGame.GameEvent_Soccar_TA:MVP", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.GameEvent_Soccar_TA:ReplicatedMusicStinger", AttributeType
AttributeType.MusicStinger),
        (String
"TAGame.GameEvent_Soccar_TA:ReplicatedScoredOnTeam", AttributeType
AttributeType.Byte),
        (String
"TAGame.GameEvent_Soccar_TA:ReplicatedServerPerformanceState", AttributeType
AttributeType.Byte),
        (String
"TAGame.GameEvent_Soccar_TA:ReplicatedStatEvent", AttributeType
AttributeType.StatEvent),
        (String
"TAGame.GameEvent_Soccar_TA:RoundNum", AttributeType
AttributeType.Int),
        (String
"TAGame.GameEvent_Soccar_TA:SecondsRemaining", AttributeType
AttributeType.Int),
        (String
"TAGame.GameEvent_Soccar_TA:SeriesLength", AttributeType
AttributeType.Int),
        (String
"TAGame.GameEvent_Soccar_TA:SubRulesArchetype", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.GameEvent_SoccarPrivate_TA:MatchSettings", AttributeType
AttributeType.PrivateMatchSettings),
        (String
"TAGame.GameEvent_TA:bAllowReadyUp", AttributeType
AttributeType.Boolean),
        (String
"TAGame.GameEvent_TA:bCanVoteToForfeit", AttributeType
AttributeType.Boolean),
        (String
"TAGame.GameEvent_TA:bHasLeaveMatchPenalty", AttributeType
AttributeType.Boolean),
        (String
"TAGame.GameEvent_TA:BotSkill", AttributeType
AttributeType.Int),
        (String
"TAGame.GameEvent_TA:GameMode", AttributeType
AttributeType.GameMode),
        (String
"TAGame.GameEvent_TA:MatchTypeClass", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.GameEvent_TA:ReplicatedGameStateTimeRemaining", AttributeType
AttributeType.Int),
        (String
"TAGame.GameEvent_TA:ReplicatedRoundCountDownNumber", AttributeType
AttributeType.Int),
        (String
"TAGame.GameEvent_TA:ReplicatedStateIndex", AttributeType
AttributeType.Byte),
        (String
"TAGame.GameEvent_TA:ReplicatedStateName", AttributeType
AttributeType.Int),
        (String
"TAGame.GameEvent_Team_TA:bForfeit", AttributeType
AttributeType.Boolean),
        (String
"TAGame.GameEvent_Team_TA:MaxTeamSize", AttributeType
AttributeType.Int),
        (String
"TAGame.GRI_TA:NewDedicatedServerIP", AttributeType
AttributeType.String),
        (String
"TAGame.MaxTimeWarningData_TA:EndGameEpochTime", AttributeType
AttributeType.Int64),
        (String
"TAGame.MaxTimeWarningData_TA:EndGameWarningEpochTime", AttributeType
AttributeType.Int64),
        (String
"TAGame.PRI_TA:bIsDistracted", AttributeType
AttributeType.Boolean),
        (String
"TAGame.PRI_TA:bIsInSplitScreen", AttributeType
AttributeType.Boolean),
        (String
"TAGame.PRI_TA:bMatchMVP", AttributeType
AttributeType.Boolean),
        (String
"TAGame.PRI_TA:bOnlineLoadoutSet", AttributeType
AttributeType.Boolean),
        (String
"TAGame.PRI_TA:bOnlineLoadoutsSet", AttributeType
AttributeType.Boolean),
        (String
"TAGame.PRI_TA:BotProductName", AttributeType
AttributeType.Int),
        (String
"TAGame.PRI_TA:bReady", AttributeType
AttributeType.Boolean),
        (String
"TAGame.PRI_TA:bUsingBehindView", AttributeType
AttributeType.Boolean),
        (String
"TAGame.PRI_TA:bUsingItems", AttributeType
AttributeType.Boolean),
        (String
"TAGame.PRI_TA:bUsingSecondaryCamera", AttributeType
AttributeType.Boolean),
        (String
"TAGame.PRI_TA:CameraPitch", AttributeType
AttributeType.Byte),
        (String
"TAGame.PRI_TA:CameraSettings", AttributeType
AttributeType.CamSettings),
        (String
"TAGame.PRI_TA:CameraYaw", AttributeType
AttributeType.Byte),
        (String
"TAGame.PRI_TA:ClientLoadout", AttributeType
AttributeType.Loadout),
        (String
"TAGame.PRI_TA:ClientLoadoutOnline", AttributeType
AttributeType.LoadoutOnline),
        (String
"TAGame.PRI_TA:ClientLoadouts", AttributeType
AttributeType.Loadouts),
        (String
"TAGame.PRI_TA:ClientLoadoutsOnline", AttributeType
AttributeType.LoadoutsOnline),
        (String
"TAGame.PRI_TA:ClubID", AttributeType
AttributeType.Int64),
        (String
"TAGame.PRI_TA:CurrentVoiceRoom", AttributeType
AttributeType.String),
        (String
"TAGame.PRI_TA:MatchAssists", AttributeType
AttributeType.Int),
        (String
"TAGame.PRI_TA:MatchBreakoutDamage", AttributeType
AttributeType.Int),
        (String
"TAGame.PRI_TA:MatchGoals", AttributeType
AttributeType.Int),
        (String
"TAGame.PRI_TA:MatchSaves", AttributeType
AttributeType.Int),
        (String
"TAGame.PRI_TA:MatchScore", AttributeType
AttributeType.Int),
        (String
"TAGame.PRI_TA:MatchShots", AttributeType
AttributeType.Int),
        (String
"TAGame.PRI_TA:MaxTimeTillItem", AttributeType
AttributeType.Int),
        (String
"TAGame.PRI_TA:PartyLeader", AttributeType
AttributeType.PartyLeader),
        (String
"TAGame.PRI_TA:PawnType", AttributeType
AttributeType.Byte),
        (String
"TAGame.PRI_TA:PersistentCamera", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.PRI_TA:PlayerHistoryKey", AttributeType
AttributeType.PlayerHistoryKey),
        (String
"TAGame.PRI_TA:PlayerHistoryValid", AttributeType
AttributeType.Boolean),
        (String
"TAGame.PRI_TA:PrimaryTitle", AttributeType
AttributeType.Title),
        (String
"TAGame.PRI_TA:ReplicatedGameEvent", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.PRI_TA:ReplicatedWorstNetQualityBeyondLatency", AttributeType
AttributeType.Byte),
        (String
"TAGame.PRI_TA:RepStatTitles", AttributeType
AttributeType.RepStatTitle),
        (String
"TAGame.PRI_TA:SecondaryTitle", AttributeType
AttributeType.Title),
        (String
"TAGame.PRI_TA:SkillTier", AttributeType
AttributeType.FlaggedByte),
        (String
"TAGame.PRI_TA:SpectatorShortcut", AttributeType
AttributeType.Int),
        (String
"TAGame.PRI_TA:SteeringSensitivity", AttributeType
AttributeType.Float),
        (String
"TAGame.PRI_TA:TimeTillItem", AttributeType
AttributeType.Int),
        (String
"TAGame.PRI_TA:Title", AttributeType
AttributeType.Int),
        (String
"TAGame.PRI_TA:TotalXP", AttributeType
AttributeType.Int),
        (String
"TAGame.RBActor_TA:bFrozen", AttributeType
AttributeType.Boolean),
        (String
"TAGame.RBActor_TA:bIgnoreSyncing", AttributeType
AttributeType.Boolean),
        (String
"TAGame.RBActor_TA:bReplayActor", AttributeType
AttributeType.Boolean),
        (String
"TAGame.RBActor_TA:ReplicatedRBState", AttributeType
AttributeType.RigidBodyState),
        (String
"TAGame.RBActor_TA:WeldedInfo", AttributeType
AttributeType.WeldedInfo),
        (String
"TAGame.RumblePickups_TA:AttachedPickup", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.RumblePickups_TA:ConcurrentItemCount", AttributeType
AttributeType.Int),
        (String
"TAGame.RumblePickups_TA:PickupInfo", AttributeType
AttributeType.PickupInfo),
        (String
"TAGame.SpecialPickup_BallFreeze_TA:RepOrigSpeed", AttributeType
AttributeType.Float),
        (String
"TAGame.SpecialPickup_BallVelcro_TA:AttachTime", AttributeType
AttributeType.Float),
        (String
"TAGame.SpecialPickup_BallVelcro_TA:bBroken", AttributeType
AttributeType.Boolean),
        (String
"TAGame.SpecialPickup_BallVelcro_TA:bHit", AttributeType
AttributeType.Boolean),
        (String
"TAGame.SpecialPickup_BallVelcro_TA:BreakTime", AttributeType
AttributeType.Float),
        (String
"TAGame.SpecialPickup_Football_TA:WeldedBall", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.SpecialPickup_Rugby_TA:bBallWelded", AttributeType
AttributeType.Boolean),
        (String
"TAGame.SpecialPickup_Targeted_TA:Targeted", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.Team_Soccar_TA:GameScore", AttributeType
AttributeType.Int),
        (String
"TAGame.Team_TA:ClubColors", AttributeType
AttributeType.ClubColors),
        (String
"TAGame.Team_TA:ClubID", AttributeType
AttributeType.Int64),
        (String
"TAGame.Team_TA:CustomTeamName", AttributeType
AttributeType.String),
        (String
"TAGame.Team_TA:Difficulty", AttributeType
AttributeType.Int),
        (String
"TAGame.Team_TA:GameEvent", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.Team_TA:LogoData", AttributeType
AttributeType.FlaggedInt),
        (String
"TAGame.Vehicle_TA:bDriving", AttributeType
AttributeType.Boolean),
        (String
"TAGame.Vehicle_TA:bPodiumMode", AttributeType
AttributeType.Boolean),
        (String
"TAGame.Vehicle_TA:bReplicatedHandbrake", AttributeType
AttributeType.Boolean),
        (String
"TAGame.Vehicle_TA:ReplicatedSteer", AttributeType
AttributeType.Byte),
        (String
"TAGame.Vehicle_TA:ReplicatedThrottle", AttributeType
AttributeType.Byte),
        (String
"TAGame.VehiclePickup_TA:bNoPickup", AttributeType
AttributeType.Boolean),
        (String
"TAGame.VehiclePickup_TA:NewReplicatedPickupData", AttributeType
AttributeType.PickupNew),
        (String
"TAGame.VehiclePickup_TA:ReplicatedPickupData", AttributeType
AttributeType.Pickup)
      ]