octane-0.14.0: Parse Rocket League replays.

Safe HaskellNone
LanguageHaskell2010

Octane.Type.RemoteId

Synopsis

Documentation

data RemoteId Source #

A player's canonical remote ID. This is the best way to uniquely identify players

Instances

Eq RemoteId Source # 
Show RemoteId Source # 
Generic RemoteId Source # 

Associated Types

type Rep RemoteId :: * -> * #

Methods

from :: RemoteId -> Rep RemoteId x #

to :: Rep RemoteId x -> RemoteId #

ToJSON RemoteId Source #

Encodes the remote ID as an object with Type and Value keys.

>>> Aeson.encode (RemoteSteamId (SteamId 1))
"{\"Value\":1,\"Type\":\"Steam\"}"
NFData RemoteId Source # 

Methods

rnf :: RemoteId -> () #

type Rep RemoteId Source # 

newtype SteamId Source #

Constructors

SteamId 

Instances

Eq SteamId Source # 

Methods

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

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

Show SteamId Source # 
Generic SteamId Source # 

Associated Types

type Rep SteamId :: * -> * #

Methods

from :: SteamId -> Rep SteamId x #

to :: Rep SteamId x -> SteamId #

ToJSON SteamId Source #

Encoded directly as a number.

>>> Aeson.encode (SteamId 1)
"1"
BinaryBit SteamId Source #

Stored as a plain Word64.

>>> Binary.runGet (BinaryBit.runBitGet (BinaryBit.getBits 0)) "\x80\x00\x00\x00\x00\x00\x00\x00" :: SteamId
SteamId {steamIdUnpack = 0x0000000000000001}
>>> Binary.runPut (BinaryBit.runBitPut (BinaryBit.putBits 0 (SteamId 1)))
"\128\NUL\NUL\NUL\NUL\NUL\NUL\NUL"

Methods

putBits :: Int -> SteamId -> BitPut () #

getBits :: Int -> BitGet SteamId #

NFData SteamId Source # 

Methods

rnf :: SteamId -> () #

HasField "unpack" SteamId Word64 Source # 

Methods

getField :: Proxy# Symbol "unpack" -> SteamId -> Word64 #

ModifyField "unpack" SteamId SteamId Word64 Word64 Source # 

Methods

modifyField :: Proxy# Symbol "unpack" -> (Word64 -> Word64) -> SteamId -> SteamId #

setField :: Proxy# Symbol "unpack" -> SteamId -> Word64 -> SteamId #

fieldLens :: Functor f => Proxy# Symbol "unpack" -> (Word64 -> f Word64) -> SteamId -> f SteamId #

ModifyRec "unpack" Word64 cs0 => HasField "unpack" (Rec cs0 SteamId) Word64 Source # 

Methods

getField :: Proxy# Symbol "unpack" -> Rec cs0 SteamId -> Word64 #

ModifyRec "unpack" Word64 cs0 => ModifyField "unpack" (Rec cs0 SteamId) (Rec cs0 SteamId) Word64 Word64 Source # 

Methods

modifyField :: Proxy# Symbol "unpack" -> (Word64 -> Word64) -> Rec cs0 SteamId -> Rec cs0 SteamId #

setField :: Proxy# Symbol "unpack" -> Rec cs0 SteamId -> Word64 -> Rec cs0 SteamId #

fieldLens :: Functor f => Proxy# Symbol "unpack" -> (Word64 -> f Word64) -> Rec cs0 SteamId -> f (Rec cs0 SteamId) #

type Rep SteamId Source # 
type Rep SteamId = D1 (MetaData "SteamId" "Octane.Type.RemoteId" "octane-0.14.0-IznL7Q8DYDX3jshGLPoKHr" True) (C1 (MetaCons "SteamId" PrefixI True) (S1 (MetaSel (Just Symbol "steamIdUnpack") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)))
type FieldType "unpack" SteamId Source # 
type FieldType "unpack" SteamId = Word64
type UpdateType "unpack" SteamId Word64 Source # 

data PlayStationId Source #

Instances

Eq PlayStationId Source # 
Show PlayStationId Source # 
Generic PlayStationId Source # 

Associated Types

type Rep PlayStationId :: * -> * #

ToJSON PlayStationId Source #
>>> Aeson.encode (PlayStationId "A" "B")
"{\"Unknown\":\"0x42\",\"Name\":\"A\"}"
BinaryBit PlayStationId Source #

Each part is stored as exactly 16 bits.

>>> Binary.runGet (BinaryBit.runBitGet (BinaryBit.getBits 0)) "\x42\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x80" :: PlayStationId
PlayStationId {playStationIdName = "B", playStationIdUnknown = "\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\SOH"}
>>> Binary.runPut (BinaryBit.runBitPut (BinaryBit.putBits 0 (PlayStationId "A" "\x01")))
"\130\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\128"
NFData PlayStationId Source # 

Methods

rnf :: PlayStationId -> () #

HasField "name" PlayStationId Text Source # 

Methods

getField :: Proxy# Symbol "name" -> PlayStationId -> Text #

HasField "unknown" PlayStationId ByteString Source # 

Methods

getField :: Proxy# Symbol "unknown" -> PlayStationId -> ByteString #

ModifyField "name" PlayStationId PlayStationId Text Text Source # 
ModifyField "unknown" PlayStationId PlayStationId ByteString ByteString Source # 
ModifyRec "name" Text cs0 => HasField "name" (Rec cs0 PlayStationId) Text Source # 

Methods

getField :: Proxy# Symbol "name" -> Rec cs0 PlayStationId -> Text #

ModifyRec "unknown" ByteString cs0 => HasField "unknown" (Rec cs0 PlayStationId) ByteString Source # 

Methods

getField :: Proxy# Symbol "unknown" -> Rec cs0 PlayStationId -> ByteString #

ModifyRec "name" Text cs0 => ModifyField "name" (Rec cs0 PlayStationId) (Rec cs0 PlayStationId) Text Text Source # 

Methods

modifyField :: Proxy# Symbol "name" -> (Text -> Text) -> Rec cs0 PlayStationId -> Rec cs0 PlayStationId #

setField :: Proxy# Symbol "name" -> Rec cs0 PlayStationId -> Text -> Rec cs0 PlayStationId #

fieldLens :: Functor f => Proxy# Symbol "name" -> (Text -> f Text) -> Rec cs0 PlayStationId -> f (Rec cs0 PlayStationId) #

ModifyRec "unknown" ByteString cs0 => ModifyField "unknown" (Rec cs0 PlayStationId) (Rec cs0 PlayStationId) ByteString ByteString Source # 
type Rep PlayStationId Source # 
type Rep PlayStationId = D1 (MetaData "PlayStationId" "Octane.Type.RemoteId" "octane-0.14.0-IznL7Q8DYDX3jshGLPoKHr" False) (C1 (MetaCons "PlayStationId" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "playStationIdName") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "playStationIdUnknown") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ByteString))))
type FieldType "name" PlayStationId Source # 
type FieldType "unknown" PlayStationId Source # 
type UpdateType "name" PlayStationId Text Source # 
type UpdateType "unknown" PlayStationId ByteString Source # 

newtype SplitscreenId Source #

Constructors

SplitscreenId 

Instances

Eq SplitscreenId Source # 
Show SplitscreenId Source # 
Generic SplitscreenId Source # 

Associated Types

type Rep SplitscreenId :: * -> * #

ToJSON SplitscreenId Source #

Encoded as an optional number.

>>> Aeson.encode (SplitscreenId Nothing)
"null"
>>> Aeson.encode (SplitscreenId (Just 0))
"0"
BinaryBit SplitscreenId Source #

Stored as a bare byte string.

>>> Binary.runGet (BinaryBit.runBitGet (BinaryBit.getBits 0)) "\x00\x00\x00" :: SplitscreenId
SplitscreenId {splitscreenIdUnpack = Just 0}
>>> Binary.runPut (BinaryBit.runBitPut (BinaryBit.putBits 0 (SplitscreenId (Just 0))))
"\NUL\NUL\NUL"
NFData SplitscreenId Source # 

Methods

rnf :: SplitscreenId -> () #

ModifyField "unpack" SplitscreenId SplitscreenId (Maybe Int) (Maybe Int) Source # 
HasField "unpack" SplitscreenId (Maybe Int) Source # 

Methods

getField :: Proxy# Symbol "unpack" -> SplitscreenId -> Maybe Int #

ModifyRec "unpack" (Maybe Int) cs0 => HasField "unpack" (Rec cs0 SplitscreenId) (Maybe Int) Source # 

Methods

getField :: Proxy# Symbol "unpack" -> Rec cs0 SplitscreenId -> Maybe Int #

ModifyRec "unpack" (Maybe Int) cs0 => ModifyField "unpack" (Rec cs0 SplitscreenId) (Rec cs0 SplitscreenId) (Maybe Int) (Maybe Int) Source # 

Methods

modifyField :: Proxy# Symbol "unpack" -> (Maybe Int -> Maybe Int) -> Rec cs0 SplitscreenId -> Rec cs0 SplitscreenId #

setField :: Proxy# Symbol "unpack" -> Rec cs0 SplitscreenId -> Maybe Int -> Rec cs0 SplitscreenId #

fieldLens :: Functor f => Proxy# Symbol "unpack" -> (Maybe Int -> f (Maybe Int)) -> Rec cs0 SplitscreenId -> f (Rec cs0 SplitscreenId) #

type Rep SplitscreenId Source # 
type Rep SplitscreenId = D1 (MetaData "SplitscreenId" "Octane.Type.RemoteId" "octane-0.14.0-IznL7Q8DYDX3jshGLPoKHr" True) (C1 (MetaCons "SplitscreenId" PrefixI True) (S1 (MetaSel (Just Symbol "splitscreenIdUnpack") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int))))
type FieldType "unpack" SplitscreenId Source # 
type UpdateType "unpack" SplitscreenId (Maybe Int) Source # 

newtype XboxId Source #

Constructors

XboxId 

Fields

Instances

Eq XboxId Source # 

Methods

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

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

Show XboxId Source # 
Generic XboxId Source # 

Associated Types

type Rep XboxId :: * -> * #

Methods

from :: XboxId -> Rep XboxId x #

to :: Rep XboxId x -> XboxId #

ToJSON XboxId Source #

Encoded directly as a number.

>>> Aeson.encode (XboxId 1)
"1"
BinaryBit XboxId Source #

Stored as a plain Word64.

>>> Binary.runGet (BinaryBit.runBitGet (BinaryBit.getBits 0)) "\x80\x00\x00\x00\x00\x00\x00\x00" :: XboxId
XboxId {xboxIdUnpack = 0x0000000000000001}
>>> Binary.runPut (BinaryBit.runBitPut (BinaryBit.putBits 0 (XboxId 1)))
"\128\NUL\NUL\NUL\NUL\NUL\NUL\NUL"

Methods

putBits :: Int -> XboxId -> BitPut () #

getBits :: Int -> BitGet XboxId #

NFData XboxId Source # 

Methods

rnf :: XboxId -> () #

HasField "unpack" XboxId Word64 Source # 

Methods

getField :: Proxy# Symbol "unpack" -> XboxId -> Word64 #

ModifyField "unpack" XboxId XboxId Word64 Word64 Source # 

Methods

modifyField :: Proxy# Symbol "unpack" -> (Word64 -> Word64) -> XboxId -> XboxId #

setField :: Proxy# Symbol "unpack" -> XboxId -> Word64 -> XboxId #

fieldLens :: Functor f => Proxy# Symbol "unpack" -> (Word64 -> f Word64) -> XboxId -> f XboxId #

ModifyRec "unpack" Word64 cs0 => HasField "unpack" (Rec cs0 XboxId) Word64 Source # 

Methods

getField :: Proxy# Symbol "unpack" -> Rec cs0 XboxId -> Word64 #

ModifyRec "unpack" Word64 cs0 => ModifyField "unpack" (Rec cs0 XboxId) (Rec cs0 XboxId) Word64 Word64 Source # 

Methods

modifyField :: Proxy# Symbol "unpack" -> (Word64 -> Word64) -> Rec cs0 XboxId -> Rec cs0 XboxId #

setField :: Proxy# Symbol "unpack" -> Rec cs0 XboxId -> Word64 -> Rec cs0 XboxId #

fieldLens :: Functor f => Proxy# Symbol "unpack" -> (Word64 -> f Word64) -> Rec cs0 XboxId -> f (Rec cs0 XboxId) #

type Rep XboxId Source # 
type Rep XboxId = D1 (MetaData "XboxId" "Octane.Type.RemoteId" "octane-0.14.0-IznL7Q8DYDX3jshGLPoKHr" True) (C1 (MetaCons "XboxId" PrefixI True) (S1 (MetaSel (Just Symbol "xboxIdUnpack") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)))
type FieldType "unpack" XboxId Source # 
type FieldType "unpack" XboxId = Word64
type UpdateType "unpack" XboxId Word64 Source # 
type UpdateType "unpack" XboxId Word64 = XboxId