octane-0.15.0: Parse Rocket League replays.

Safe HaskellNone
LanguageHaskell2010

Octane.Type.Property

Synopsis

Documentation

data Property Source #

A metadata property. All properties have a size, but only some actually use it. The value stored in the property can be an array, a boolean, and so on.

Instances

Eq Property Source # 
Show Property Source # 
Generic Property Source # 

Associated Types

type Rep Property :: * -> * #

Methods

from :: Property -> Rep Property x #

to :: Rep Property x -> Property #

ToJSON Property Source # 
Binary Property Source #

Stored with the size first, then the value.

Methods

put :: Property -> Put #

get :: Get Property #

putList :: [Property] -> Put #

NFData Property Source # 

Methods

rnf :: Property -> () #

ModifyField "content" ArrayProperty ArrayProperty (List (Dictionary Property)) (List (Dictionary Property)) Source # 
ModifyField "properties" ReplayWithoutFrames ReplayWithoutFrames (Dictionary Property) (Dictionary Property) # 
ModifyField "properties" ReplayWithFrames ReplayWithFrames (Dictionary Property) (Dictionary Property) # 
ModifyField "properties" OptimizedReplay OptimizedReplay (Dictionary Property) (Dictionary Property) # 
ModifyField "metadata" Replay Replay (Map Text Property) (Map Text Property) # 

Methods

modifyField :: Proxy# Symbol "metadata" -> (Map Text Property -> Map Text Property) -> Replay -> Replay #

setField :: Proxy# Symbol "metadata" -> Replay -> Map Text Property -> Replay #

fieldLens :: Functor f => Proxy# Symbol "metadata" -> (Map Text Property -> f (Map Text Property)) -> Replay -> f Replay #

HasField "content" ArrayProperty (List (Dictionary Property)) Source # 
HasField "properties" ReplayWithoutFrames (Dictionary Property) # 
HasField "properties" ReplayWithFrames (Dictionary Property) # 
HasField "properties" OptimizedReplay (Dictionary Property) # 
HasField "metadata" Replay (Map Text Property) # 

Methods

getField :: Proxy# Symbol "metadata" -> Replay -> Map Text Property #

ModifyRec "content" (List (Dictionary Property)) cs0 => HasField "content" (Rec cs0 ArrayProperty) (List (Dictionary Property)) Source # 

Methods

getField :: Proxy# Symbol "content" -> Rec cs0 ArrayProperty -> List (Dictionary Property) #

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 "metadata" (Map Text Property) cs0 => HasField "metadata" (Rec cs0 Replay) (Map Text Property) # 

Methods

getField :: Proxy# Symbol "metadata" -> Rec cs0 Replay -> Map Text Property #

ModifyRec "content" (List (Dictionary Property)) cs0 => ModifyField "content" (Rec cs0 ArrayProperty) (Rec cs0 ArrayProperty) (List (Dictionary Property)) (List (Dictionary Property)) Source # 
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 "metadata" (Map Text Property) cs0 => ModifyField "metadata" (Rec cs0 Replay) (Rec cs0 Replay) (Map Text Property) (Map Text Property) # 

Methods

modifyField :: Proxy# Symbol "metadata" -> (Map Text Property -> Map Text Property) -> Rec cs0 Replay -> Rec cs0 Replay #

setField :: Proxy# Symbol "metadata" -> Rec cs0 Replay -> Map Text Property -> Rec cs0 Replay #

fieldLens :: Functor f => Proxy# Symbol "metadata" -> (Map Text Property -> f (Map Text Property)) -> Rec cs0 Replay -> f (Rec cs0 Replay) #

type Rep Property Source # 
type UpdateType "content" ArrayProperty (List (Dictionary Property)) Source # 
type UpdateType "properties" ReplayWithoutFrames (Dictionary Property) # 
type UpdateType "properties" ReplayWithFrames (Dictionary Property) # 
type UpdateType "properties" OptimizedReplay (Dictionary Property) # 
type UpdateType "metadata" Replay (Map Text Property) # 
type UpdateType "metadata" Replay (Map Text Property) = Replay

data ArrayProperty Source #

Instances

Eq ArrayProperty Source # 
Show ArrayProperty Source # 
Generic ArrayProperty Source # 

Associated Types

type Rep ArrayProperty :: * -> * #

ToJSON ArrayProperty Source # 
Binary ArrayProperty Source # 
NFData ArrayProperty Source # 

Methods

rnf :: ArrayProperty -> () #

HasField "size" ArrayProperty Word64 Source # 

Methods

getField :: Proxy# Symbol "size" -> ArrayProperty -> Word64 #

ModifyField "size" ArrayProperty ArrayProperty Word64 Word64 Source # 
ModifyField "content" ArrayProperty ArrayProperty (List (Dictionary Property)) (List (Dictionary Property)) Source # 
HasField "content" ArrayProperty (List (Dictionary Property)) Source # 
ModifyRec "size" Word64 cs0 => HasField "size" (Rec cs0 ArrayProperty) Word64 Source # 

Methods

getField :: Proxy# Symbol "size" -> Rec cs0 ArrayProperty -> Word64 #

ModifyRec "content" (List (Dictionary Property)) cs0 => HasField "content" (Rec cs0 ArrayProperty) (List (Dictionary Property)) Source # 

Methods

getField :: Proxy# Symbol "content" -> Rec cs0 ArrayProperty -> List (Dictionary Property) #

ModifyRec "size" Word64 cs0 => ModifyField "size" (Rec cs0 ArrayProperty) (Rec cs0 ArrayProperty) Word64 Word64 Source # 

Methods

modifyField :: Proxy# Symbol "size" -> (Word64 -> Word64) -> Rec cs0 ArrayProperty -> Rec cs0 ArrayProperty #

setField :: Proxy# Symbol "size" -> Rec cs0 ArrayProperty -> Word64 -> Rec cs0 ArrayProperty #

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

ModifyRec "content" (List (Dictionary Property)) cs0 => ModifyField "content" (Rec cs0 ArrayProperty) (Rec cs0 ArrayProperty) (List (Dictionary Property)) (List (Dictionary Property)) Source # 
type Rep ArrayProperty Source # 
type Rep ArrayProperty = D1 (MetaData "ArrayProperty" "Octane.Type.Property" "octane-0.15.0-4F9EHXv8Fsx4ap3JJhWldo" False) (C1 (MetaCons "ArrayProperty" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "arrayPropertySize") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word64)) (S1 (MetaSel (Just Symbol "arrayPropertyContent") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (List (Dictionary Property))))))
type FieldType "content" ArrayProperty Source # 
type FieldType "size" ArrayProperty Source # 
type UpdateType "size" ArrayProperty Word64 Source # 
type UpdateType "content" ArrayProperty (List (Dictionary Property)) Source # 

data BoolProperty Source #

Instances

Eq BoolProperty Source # 
Show BoolProperty Source # 
Generic BoolProperty Source # 

Associated Types

type Rep BoolProperty :: * -> * #

ToJSON BoolProperty Source # 
Binary BoolProperty Source # 
NFData BoolProperty Source # 

Methods

rnf :: BoolProperty -> () #

HasField "content" BoolProperty Boolean Source # 

Methods

getField :: Proxy# Symbol "content" -> BoolProperty -> Boolean #

HasField "size" BoolProperty Word64 Source # 

Methods

getField :: Proxy# Symbol "size" -> BoolProperty -> Word64 #

ModifyField "content" BoolProperty BoolProperty Boolean Boolean Source # 
ModifyField "size" BoolProperty BoolProperty Word64 Word64 Source # 
ModifyRec "content" Boolean cs0 => HasField "content" (Rec cs0 BoolProperty) Boolean Source # 

Methods

getField :: Proxy# Symbol "content" -> Rec cs0 BoolProperty -> Boolean #

ModifyRec "size" Word64 cs0 => HasField "size" (Rec cs0 BoolProperty) Word64 Source # 

Methods

getField :: Proxy# Symbol "size" -> Rec cs0 BoolProperty -> Word64 #

ModifyRec "content" Boolean cs0 => ModifyField "content" (Rec cs0 BoolProperty) (Rec cs0 BoolProperty) Boolean Boolean Source # 

Methods

modifyField :: Proxy# Symbol "content" -> (Boolean -> Boolean) -> Rec cs0 BoolProperty -> Rec cs0 BoolProperty #

setField :: Proxy# Symbol "content" -> Rec cs0 BoolProperty -> Boolean -> Rec cs0 BoolProperty #

fieldLens :: Functor f => Proxy# Symbol "content" -> (Boolean -> f Boolean) -> Rec cs0 BoolProperty -> f (Rec cs0 BoolProperty) #

ModifyRec "size" Word64 cs0 => ModifyField "size" (Rec cs0 BoolProperty) (Rec cs0 BoolProperty) Word64 Word64 Source # 

Methods

modifyField :: Proxy# Symbol "size" -> (Word64 -> Word64) -> Rec cs0 BoolProperty -> Rec cs0 BoolProperty #

setField :: Proxy# Symbol "size" -> Rec cs0 BoolProperty -> Word64 -> Rec cs0 BoolProperty #

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

type Rep BoolProperty Source # 
type Rep BoolProperty = D1 (MetaData "BoolProperty" "Octane.Type.Property" "octane-0.15.0-4F9EHXv8Fsx4ap3JJhWldo" False) (C1 (MetaCons "BoolProperty" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "boolPropertySize") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word64)) (S1 (MetaSel (Just Symbol "boolPropertyContent") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Boolean))))
type FieldType "content" BoolProperty Source # 
type FieldType "content" BoolProperty = Boolean
type FieldType "size" BoolProperty Source # 
type UpdateType "content" BoolProperty Boolean Source # 
type UpdateType "size" BoolProperty Word64 Source # 

data ByteProperty Source #

Instances

Eq ByteProperty Source # 
Show ByteProperty Source # 
Generic ByteProperty Source # 

Associated Types

type Rep ByteProperty :: * -> * #

ToJSON ByteProperty Source # 
Binary ByteProperty Source # 
NFData ByteProperty Source # 

Methods

rnf :: ByteProperty -> () #

HasField "key" ByteProperty Text Source # 

Methods

getField :: Proxy# Symbol "key" -> ByteProperty -> Text #

HasField "size" ByteProperty Word64 Source # 

Methods

getField :: Proxy# Symbol "size" -> ByteProperty -> Word64 #

HasField "value" ByteProperty Text Source # 

Methods

getField :: Proxy# Symbol "value" -> ByteProperty -> Text #

ModifyField "key" ByteProperty ByteProperty Text Text Source # 
ModifyField "size" ByteProperty ByteProperty Word64 Word64 Source # 
ModifyField "value" ByteProperty ByteProperty Text Text Source # 
ModifyRec "key" Text cs0 => HasField "key" (Rec cs0 ByteProperty) Text Source # 

Methods

getField :: Proxy# Symbol "key" -> Rec cs0 ByteProperty -> Text #

ModifyRec "size" Word64 cs0 => HasField "size" (Rec cs0 ByteProperty) Word64 Source # 

Methods

getField :: Proxy# Symbol "size" -> Rec cs0 ByteProperty -> Word64 #

ModifyRec "value" Text cs0 => HasField "value" (Rec cs0 ByteProperty) Text Source # 

Methods

getField :: Proxy# Symbol "value" -> Rec cs0 ByteProperty -> Text #

ModifyRec "key" Text cs0 => ModifyField "key" (Rec cs0 ByteProperty) (Rec cs0 ByteProperty) Text Text Source # 

Methods

modifyField :: Proxy# Symbol "key" -> (Text -> Text) -> Rec cs0 ByteProperty -> Rec cs0 ByteProperty #

setField :: Proxy# Symbol "key" -> Rec cs0 ByteProperty -> Text -> Rec cs0 ByteProperty #

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

ModifyRec "size" Word64 cs0 => ModifyField "size" (Rec cs0 ByteProperty) (Rec cs0 ByteProperty) Word64 Word64 Source # 

Methods

modifyField :: Proxy# Symbol "size" -> (Word64 -> Word64) -> Rec cs0 ByteProperty -> Rec cs0 ByteProperty #

setField :: Proxy# Symbol "size" -> Rec cs0 ByteProperty -> Word64 -> Rec cs0 ByteProperty #

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

ModifyRec "value" Text cs0 => ModifyField "value" (Rec cs0 ByteProperty) (Rec cs0 ByteProperty) Text Text Source # 

Methods

modifyField :: Proxy# Symbol "value" -> (Text -> Text) -> Rec cs0 ByteProperty -> Rec cs0 ByteProperty #

setField :: Proxy# Symbol "value" -> Rec cs0 ByteProperty -> Text -> Rec cs0 ByteProperty #

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

type Rep ByteProperty Source # 
type Rep ByteProperty = D1 (MetaData "ByteProperty" "Octane.Type.Property" "octane-0.15.0-4F9EHXv8Fsx4ap3JJhWldo" False) (C1 (MetaCons "ByteProperty" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "bytePropertySize") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word64)) ((:*:) (S1 (MetaSel (Just Symbol "bytePropertyKey") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "bytePropertyValue") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text)))))
type FieldType "key" ByteProperty Source # 
type FieldType "size" ByteProperty Source # 
type FieldType "value" ByteProperty Source # 
type FieldType "value" ByteProperty = Text
type UpdateType "key" ByteProperty Text Source # 
type UpdateType "size" ByteProperty Word64 Source # 
type UpdateType "value" ByteProperty Text Source # 

data FloatProperty Source #

Instances

Eq FloatProperty Source # 
Show FloatProperty Source # 
Generic FloatProperty Source # 

Associated Types

type Rep FloatProperty :: * -> * #

ToJSON FloatProperty Source # 
Binary FloatProperty Source # 
NFData FloatProperty Source # 

Methods

rnf :: FloatProperty -> () #

HasField "content" FloatProperty Float32 Source # 

Methods

getField :: Proxy# Symbol "content" -> FloatProperty -> Float32 #

HasField "size" FloatProperty Word64 Source # 

Methods

getField :: Proxy# Symbol "size" -> FloatProperty -> Word64 #

ModifyField "content" FloatProperty FloatProperty Float32 Float32 Source # 
ModifyField "size" FloatProperty FloatProperty Word64 Word64 Source # 
ModifyRec "content" Float32 cs0 => HasField "content" (Rec cs0 FloatProperty) Float32 Source # 

Methods

getField :: Proxy# Symbol "content" -> Rec cs0 FloatProperty -> Float32 #

ModifyRec "size" Word64 cs0 => HasField "size" (Rec cs0 FloatProperty) Word64 Source # 

Methods

getField :: Proxy# Symbol "size" -> Rec cs0 FloatProperty -> Word64 #

ModifyRec "content" Float32 cs0 => ModifyField "content" (Rec cs0 FloatProperty) (Rec cs0 FloatProperty) Float32 Float32 Source # 

Methods

modifyField :: Proxy# Symbol "content" -> (Float32 -> Float32) -> Rec cs0 FloatProperty -> Rec cs0 FloatProperty #

setField :: Proxy# Symbol "content" -> Rec cs0 FloatProperty -> Float32 -> Rec cs0 FloatProperty #

fieldLens :: Functor f => Proxy# Symbol "content" -> (Float32 -> f Float32) -> Rec cs0 FloatProperty -> f (Rec cs0 FloatProperty) #

ModifyRec "size" Word64 cs0 => ModifyField "size" (Rec cs0 FloatProperty) (Rec cs0 FloatProperty) Word64 Word64 Source # 

Methods

modifyField :: Proxy# Symbol "size" -> (Word64 -> Word64) -> Rec cs0 FloatProperty -> Rec cs0 FloatProperty #

setField :: Proxy# Symbol "size" -> Rec cs0 FloatProperty -> Word64 -> Rec cs0 FloatProperty #

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

type Rep FloatProperty Source # 
type Rep FloatProperty = D1 (MetaData "FloatProperty" "Octane.Type.Property" "octane-0.15.0-4F9EHXv8Fsx4ap3JJhWldo" False) (C1 (MetaCons "FloatProperty" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "floatPropertySize") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word64)) (S1 (MetaSel (Just Symbol "floatPropertyContent") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Float32))))
type FieldType "content" FloatProperty Source # 
type FieldType "size" FloatProperty Source # 
type UpdateType "content" FloatProperty Float32 Source # 
type UpdateType "size" FloatProperty Word64 Source # 

data IntProperty Source #

Instances

Eq IntProperty Source # 
Show IntProperty Source # 
Generic IntProperty Source # 

Associated Types

type Rep IntProperty :: * -> * #

ToJSON IntProperty Source # 
Binary IntProperty Source # 
NFData IntProperty Source # 

Methods

rnf :: IntProperty -> () #

HasField "content" IntProperty Int32 Source # 

Methods

getField :: Proxy# Symbol "content" -> IntProperty -> Int32 #

HasField "size" IntProperty Word64 Source # 

Methods

getField :: Proxy# Symbol "size" -> IntProperty -> Word64 #

ModifyField "content" IntProperty IntProperty Int32 Int32 Source # 

Methods

modifyField :: Proxy# Symbol "content" -> (Int32 -> Int32) -> IntProperty -> IntProperty #

setField :: Proxy# Symbol "content" -> IntProperty -> Int32 -> IntProperty #

fieldLens :: Functor f => Proxy# Symbol "content" -> (Int32 -> f Int32) -> IntProperty -> f IntProperty #

ModifyField "size" IntProperty IntProperty Word64 Word64 Source # 
ModifyRec "content" Int32 cs0 => HasField "content" (Rec cs0 IntProperty) Int32 Source # 

Methods

getField :: Proxy# Symbol "content" -> Rec cs0 IntProperty -> Int32 #

ModifyRec "size" Word64 cs0 => HasField "size" (Rec cs0 IntProperty) Word64 Source # 

Methods

getField :: Proxy# Symbol "size" -> Rec cs0 IntProperty -> Word64 #

ModifyRec "content" Int32 cs0 => ModifyField "content" (Rec cs0 IntProperty) (Rec cs0 IntProperty) Int32 Int32 Source # 

Methods

modifyField :: Proxy# Symbol "content" -> (Int32 -> Int32) -> Rec cs0 IntProperty -> Rec cs0 IntProperty #

setField :: Proxy# Symbol "content" -> Rec cs0 IntProperty -> Int32 -> Rec cs0 IntProperty #

fieldLens :: Functor f => Proxy# Symbol "content" -> (Int32 -> f Int32) -> Rec cs0 IntProperty -> f (Rec cs0 IntProperty) #

ModifyRec "size" Word64 cs0 => ModifyField "size" (Rec cs0 IntProperty) (Rec cs0 IntProperty) Word64 Word64 Source # 

Methods

modifyField :: Proxy# Symbol "size" -> (Word64 -> Word64) -> Rec cs0 IntProperty -> Rec cs0 IntProperty #

setField :: Proxy# Symbol "size" -> Rec cs0 IntProperty -> Word64 -> Rec cs0 IntProperty #

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

type Rep IntProperty Source # 
type Rep IntProperty = D1 (MetaData "IntProperty" "Octane.Type.Property" "octane-0.15.0-4F9EHXv8Fsx4ap3JJhWldo" False) (C1 (MetaCons "IntProperty" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "intPropertySize") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word64)) (S1 (MetaSel (Just Symbol "intPropertyContent") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int32))))
type FieldType "content" IntProperty Source # 
type FieldType "content" IntProperty = Int32
type FieldType "size" IntProperty Source # 
type UpdateType "content" IntProperty Int32 Source # 
type UpdateType "size" IntProperty Word64 Source # 

data NameProperty Source #

Instances

Eq NameProperty Source # 
Show NameProperty Source # 
Generic NameProperty Source # 

Associated Types

type Rep NameProperty :: * -> * #

ToJSON NameProperty Source # 
Binary NameProperty Source # 
NFData NameProperty Source # 

Methods

rnf :: NameProperty -> () #

HasField "content" NameProperty Text Source # 

Methods

getField :: Proxy# Symbol "content" -> NameProperty -> Text #

HasField "size" NameProperty Word64 Source # 

Methods

getField :: Proxy# Symbol "size" -> NameProperty -> Word64 #

ModifyField "content" NameProperty NameProperty Text Text Source # 

Methods

modifyField :: Proxy# Symbol "content" -> (Text -> Text) -> NameProperty -> NameProperty #

setField :: Proxy# Symbol "content" -> NameProperty -> Text -> NameProperty #

fieldLens :: Functor f => Proxy# Symbol "content" -> (Text -> f Text) -> NameProperty -> f NameProperty #

ModifyField "size" NameProperty NameProperty Word64 Word64 Source # 
ModifyRec "content" Text cs0 => HasField "content" (Rec cs0 NameProperty) Text Source # 

Methods

getField :: Proxy# Symbol "content" -> Rec cs0 NameProperty -> Text #

ModifyRec "size" Word64 cs0 => HasField "size" (Rec cs0 NameProperty) Word64 Source # 

Methods

getField :: Proxy# Symbol "size" -> Rec cs0 NameProperty -> Word64 #

ModifyRec "content" Text cs0 => ModifyField "content" (Rec cs0 NameProperty) (Rec cs0 NameProperty) Text Text Source # 

Methods

modifyField :: Proxy# Symbol "content" -> (Text -> Text) -> Rec cs0 NameProperty -> Rec cs0 NameProperty #

setField :: Proxy# Symbol "content" -> Rec cs0 NameProperty -> Text -> Rec cs0 NameProperty #

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

ModifyRec "size" Word64 cs0 => ModifyField "size" (Rec cs0 NameProperty) (Rec cs0 NameProperty) Word64 Word64 Source # 

Methods

modifyField :: Proxy# Symbol "size" -> (Word64 -> Word64) -> Rec cs0 NameProperty -> Rec cs0 NameProperty #

setField :: Proxy# Symbol "size" -> Rec cs0 NameProperty -> Word64 -> Rec cs0 NameProperty #

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

type Rep NameProperty Source # 
type Rep NameProperty = D1 (MetaData "NameProperty" "Octane.Type.Property" "octane-0.15.0-4F9EHXv8Fsx4ap3JJhWldo" False) (C1 (MetaCons "NameProperty" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "namePropertySize") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word64)) (S1 (MetaSel (Just Symbol "namePropertyContent") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text))))
type FieldType "content" NameProperty Source # 
type FieldType "content" NameProperty = Text
type FieldType "size" NameProperty Source # 
type UpdateType "content" NameProperty Text Source # 
type UpdateType "size" NameProperty Word64 Source # 

data QWordProperty Source #

Instances

Eq QWordProperty Source # 
Show QWordProperty Source # 
Generic QWordProperty Source # 

Associated Types

type Rep QWordProperty :: * -> * #

ToJSON QWordProperty Source # 
Binary QWordProperty Source # 
NFData QWordProperty Source # 

Methods

rnf :: QWordProperty -> () #

HasField "content" QWordProperty Word64 Source # 

Methods

getField :: Proxy# Symbol "content" -> QWordProperty -> Word64 #

HasField "size" QWordProperty Word64 Source # 

Methods

getField :: Proxy# Symbol "size" -> QWordProperty -> Word64 #

ModifyField "content" QWordProperty QWordProperty Word64 Word64 Source # 
ModifyField "size" QWordProperty QWordProperty Word64 Word64 Source # 
ModifyRec "content" Word64 cs0 => HasField "content" (Rec cs0 QWordProperty) Word64 Source # 

Methods

getField :: Proxy# Symbol "content" -> Rec cs0 QWordProperty -> Word64 #

ModifyRec "size" Word64 cs0 => HasField "size" (Rec cs0 QWordProperty) Word64 Source # 

Methods

getField :: Proxy# Symbol "size" -> Rec cs0 QWordProperty -> Word64 #

ModifyRec "content" Word64 cs0 => ModifyField "content" (Rec cs0 QWordProperty) (Rec cs0 QWordProperty) Word64 Word64 Source # 

Methods

modifyField :: Proxy# Symbol "content" -> (Word64 -> Word64) -> Rec cs0 QWordProperty -> Rec cs0 QWordProperty #

setField :: Proxy# Symbol "content" -> Rec cs0 QWordProperty -> Word64 -> Rec cs0 QWordProperty #

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

ModifyRec "size" Word64 cs0 => ModifyField "size" (Rec cs0 QWordProperty) (Rec cs0 QWordProperty) Word64 Word64 Source # 

Methods

modifyField :: Proxy# Symbol "size" -> (Word64 -> Word64) -> Rec cs0 QWordProperty -> Rec cs0 QWordProperty #

setField :: Proxy# Symbol "size" -> Rec cs0 QWordProperty -> Word64 -> Rec cs0 QWordProperty #

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

type Rep QWordProperty Source # 
type Rep QWordProperty = D1 (MetaData "QWordProperty" "Octane.Type.Property" "octane-0.15.0-4F9EHXv8Fsx4ap3JJhWldo" False) (C1 (MetaCons "QWordProperty" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "qWordPropertySize") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word64)) (S1 (MetaSel (Just Symbol "qWordPropertyContent") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word64))))
type FieldType "content" QWordProperty Source # 
type FieldType "content" QWordProperty = Word64
type FieldType "size" QWordProperty Source # 
type UpdateType "content" QWordProperty Word64 Source # 
type UpdateType "size" QWordProperty Word64 Source # 

data StrProperty Source #

Instances

Eq StrProperty Source # 
Show StrProperty Source # 
Generic StrProperty Source # 

Associated Types

type Rep StrProperty :: * -> * #

ToJSON StrProperty Source # 
Binary StrProperty Source # 
NFData StrProperty Source # 

Methods

rnf :: StrProperty -> () #

HasField "content" StrProperty Text Source # 

Methods

getField :: Proxy# Symbol "content" -> StrProperty -> Text #

HasField "size" StrProperty Word64 Source # 

Methods

getField :: Proxy# Symbol "size" -> StrProperty -> Word64 #

ModifyField "content" StrProperty StrProperty Text Text Source # 

Methods

modifyField :: Proxy# Symbol "content" -> (Text -> Text) -> StrProperty -> StrProperty #

setField :: Proxy# Symbol "content" -> StrProperty -> Text -> StrProperty #

fieldLens :: Functor f => Proxy# Symbol "content" -> (Text -> f Text) -> StrProperty -> f StrProperty #

ModifyField "size" StrProperty StrProperty Word64 Word64 Source # 
ModifyRec "content" Text cs0 => HasField "content" (Rec cs0 StrProperty) Text Source # 

Methods

getField :: Proxy# Symbol "content" -> Rec cs0 StrProperty -> Text #

ModifyRec "size" Word64 cs0 => HasField "size" (Rec cs0 StrProperty) Word64 Source # 

Methods

getField :: Proxy# Symbol "size" -> Rec cs0 StrProperty -> Word64 #

ModifyRec "content" Text cs0 => ModifyField "content" (Rec cs0 StrProperty) (Rec cs0 StrProperty) Text Text Source # 

Methods

modifyField :: Proxy# Symbol "content" -> (Text -> Text) -> Rec cs0 StrProperty -> Rec cs0 StrProperty #

setField :: Proxy# Symbol "content" -> Rec cs0 StrProperty -> Text -> Rec cs0 StrProperty #

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

ModifyRec "size" Word64 cs0 => ModifyField "size" (Rec cs0 StrProperty) (Rec cs0 StrProperty) Word64 Word64 Source # 

Methods

modifyField :: Proxy# Symbol "size" -> (Word64 -> Word64) -> Rec cs0 StrProperty -> Rec cs0 StrProperty #

setField :: Proxy# Symbol "size" -> Rec cs0 StrProperty -> Word64 -> Rec cs0 StrProperty #

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

type Rep StrProperty Source # 
type Rep StrProperty = D1 (MetaData "StrProperty" "Octane.Type.Property" "octane-0.15.0-4F9EHXv8Fsx4ap3JJhWldo" False) (C1 (MetaCons "StrProperty" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "strPropertySize") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word64)) (S1 (MetaSel (Just Symbol "strPropertyContent") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text))))
type FieldType "content" StrProperty Source # 
type FieldType "content" StrProperty = Text
type FieldType "size" StrProperty Source # 
type UpdateType "content" StrProperty Text Source # 
type UpdateType "size" StrProperty Word64 Source #