octane-0.13.4: 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 Word64 

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 {unpackSteamId = 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 -> () #

type Rep SteamId Source # 
type Rep SteamId = D1 (MetaData "SteamId" "Octane.Type.RemoteId" "octane-0.13.4-DJqUOnYo1oADH9HuNkv3YY" True) (C1 (MetaCons "SteamId" PrefixI True) (S1 (MetaSel (Just Symbol "unpackSteamId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)))

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 {playStationName = "B", playStationUnknown = "\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 -> () #

type Rep PlayStationId Source # 
type Rep PlayStationId = D1 (MetaData "PlayStationId" "Octane.Type.RemoteId" "octane-0.13.4-DJqUOnYo1oADH9HuNkv3YY" False) (C1 (MetaCons "PlayStationId" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "playStationName") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "playStationUnknown") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ByteString))))

newtype SplitscreenId Source #

Constructors

SplitscreenId (Maybe Int) 

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 {unpackSplitscreenId = Just 0}
>>> Binary.runPut (BinaryBit.runBitPut (BinaryBit.putBits 0 (SplitscreenId (Just 0))))
"\NUL\NUL\NUL"
NFData SplitscreenId Source # 

Methods

rnf :: SplitscreenId -> () #

type Rep SplitscreenId Source # 
type Rep SplitscreenId = D1 (MetaData "SplitscreenId" "Octane.Type.RemoteId" "octane-0.13.4-DJqUOnYo1oADH9HuNkv3YY" True) (C1 (MetaCons "SplitscreenId" PrefixI True) (S1 (MetaSel (Just Symbol "unpackSplitscreenId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int))))

newtype XboxId Source #

Constructors

XboxId Word64 

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 {unpackXboxId = 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 -> () #

type Rep XboxId Source # 
type Rep XboxId = D1 (MetaData "XboxId" "Octane.Type.RemoteId" "octane-0.13.4-DJqUOnYo1oADH9HuNkv3YY" True) (C1 (MetaCons "XboxId" PrefixI True) (S1 (MetaSel (Just Symbol "unpackXboxId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)))