octane-0.14.0: Parse Rocket League replays.

Safe HaskellNone
LanguageHaskell2010

Octane.Type.Dictionary

Synopsis

Documentation

newtype Dictionary a Source #

A mapping between text and arbitrary values.

Constructors

Dictionary 

Instances

ModifyField "properties" ReplayWithoutFrames ReplayWithoutFrames (Dictionary Property) (Dictionary Property) # 
ModifyField "properties" ReplayWithFrames ReplayWithFrames (Dictionary Property) (Dictionary Property) # 
ModifyField "properties" OptimizedReplay OptimizedReplay (Dictionary Property) (Dictionary Property) # 
HasField "properties" ReplayWithoutFrames (Dictionary Property) # 
HasField "properties" ReplayWithFrames (Dictionary Property) # 
HasField "properties" OptimizedReplay (Dictionary Property) # 
ModifyField "unpack" (Dictionary a0) (Dictionary a0) (Map Text a0) (Map Text a0) Source # 

Methods

modifyField :: Proxy# Symbol "unpack" -> (Map Text a0 -> Map Text a0) -> Dictionary a0 -> Dictionary a0 #

setField :: Proxy# Symbol "unpack" -> Dictionary a0 -> Map Text a0 -> Dictionary a0 #

fieldLens :: Functor f => Proxy# Symbol "unpack" -> (Map Text a0 -> f (Map Text a0)) -> Dictionary a0 -> f (Dictionary a0) #

HasField "unpack" (Dictionary a0) (Map Text a0) Source # 

Methods

getField :: Proxy# Symbol "unpack" -> Dictionary a0 -> Map Text a0 #

ModifyRec "properties" (Dictionary Property) cs0 => HasField "properties" (Rec cs0 ReplayWithoutFrames) (Dictionary Property) # 
ModifyRec "properties" (Dictionary Property) cs0 => HasField "properties" (Rec cs0 ReplayWithFrames) (Dictionary Property) # 

Methods

getField :: Proxy# Symbol "properties" -> Rec cs0 ReplayWithFrames -> Dictionary Property #

ModifyRec "properties" (Dictionary Property) cs0 => HasField "properties" (Rec cs0 OptimizedReplay) (Dictionary Property) # 

Methods

getField :: Proxy# Symbol "properties" -> Rec cs0 OptimizedReplay -> Dictionary Property #

ModifyRec "unpack" (Map Text a0) cs0 => HasField "unpack" (Rec cs0 (Dictionary a0)) (Map Text a0) Source # 

Methods

getField :: Proxy# Symbol "unpack" -> Rec cs0 (Dictionary a0) -> Map Text a0 #

ModifyRec "properties" (Dictionary Property) cs0 => ModifyField "properties" (Rec cs0 ReplayWithoutFrames) (Rec cs0 ReplayWithoutFrames) (Dictionary Property) (Dictionary Property) # 
ModifyRec "properties" (Dictionary Property) cs0 => ModifyField "properties" (Rec cs0 ReplayWithFrames) (Rec cs0 ReplayWithFrames) (Dictionary Property) (Dictionary Property) # 
ModifyRec "properties" (Dictionary Property) cs0 => ModifyField "properties" (Rec cs0 OptimizedReplay) (Rec cs0 OptimizedReplay) (Dictionary Property) (Dictionary Property) # 
ModifyRec "unpack" (Map Text a0) cs0 => ModifyField "unpack" (Rec cs0 (Dictionary a0)) (Rec cs0 (Dictionary a0)) (Map Text a0) (Map Text a0) Source # 

Methods

modifyField :: Proxy# Symbol "unpack" -> (Map Text a0 -> Map Text a0) -> Rec cs0 (Dictionary a0) -> Rec cs0 (Dictionary a0) #

setField :: Proxy# Symbol "unpack" -> Rec cs0 (Dictionary a0) -> Map Text a0 -> Rec cs0 (Dictionary a0) #

fieldLens :: Functor f => Proxy# Symbol "unpack" -> (Map Text a0 -> f (Map Text a0)) -> Rec cs0 (Dictionary a0) -> f (Rec cs0 (Dictionary a0)) #

IsList (Dictionary a) Source #

Allows creating Dictionary values with fromList. Also allows Dictionary literals with the OverloadedLists extension.

>>> [("one", 1)] :: Dictionary Int
fromList [("one",1)]

Associated Types

type Item (Dictionary a) :: * #

Eq a => Eq (Dictionary a) Source # 

Methods

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

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

Show a => Show (Dictionary a) Source #

Shown as fromList [("key","value")].

>>> show ([("one", 1)] :: Dictionary Int)
"fromList [(\"one\",1)]"
Generic (Dictionary a) Source # 

Associated Types

type Rep (Dictionary a) :: * -> * #

Methods

from :: Dictionary a -> Rep (Dictionary a) x #

to :: Rep (Dictionary a) x -> Dictionary a #

ToJSON a => ToJSON (Dictionary a) Source #

Encoded directly as a JSON object.

>>> Aeson.encode ([("one", 1)] :: Dictionary Int)
"{\"one\":1}"
Binary a => Binary (Dictionary a) Source #

Elements are stored with the key first, then the value. The dictionary ends when a key is None.

>>> Binary.decode "\x02\x00\x00\x00k\x00\x01\x05\x00\x00\x00None\x00" :: Dictionary Word8
fromList [("k",0x01)]
>>> Binary.encode ([("k", 1)] :: Dictionary Word8)
"\STX\NUL\NUL\NULk\NUL\SOH\ENQ\NUL\NUL\NULNone\NUL"

Methods

put :: Dictionary a -> Put #

get :: Get (Dictionary a) #

putList :: [Dictionary a] -> Put #

NFData a => NFData (Dictionary a) Source # 

Methods

rnf :: Dictionary a -> () #

type UpdateType "properties" ReplayWithoutFrames (Dictionary Property) # 
type UpdateType "properties" ReplayWithFrames (Dictionary Property) # 
type UpdateType "properties" OptimizedReplay (Dictionary Property) # 
type FieldType "unpack" (Dictionary a0) Source # 
type FieldType "unpack" (Dictionary a0) = Map Text a0
type UpdateType "unpack" (Dictionary a0) (Map Text a0) Source # 
type UpdateType "unpack" (Dictionary a0) (Map Text a0) = Dictionary a0
type Rep (Dictionary a) Source # 
type Rep (Dictionary a) = D1 (MetaData "Dictionary" "Octane.Type.Dictionary" "octane-0.14.0-IznL7Q8DYDX3jshGLPoKHr" True) (C1 (MetaCons "Dictionary" PrefixI True) (S1 (MetaSel (Just Symbol "dictionaryUnpack") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Text a))))
type Item (Dictionary a) Source # 
type Item (Dictionary a) = (Text, a)