capnp-0.1.0.0: Cap'n Proto for Haskell

Safe HaskellNone
LanguageHaskell2010

Data.Capnp

Contents

Description

Users getting acquainted with the library are *strongly* encouraged to read the Data.Capnp.Tutorial module before anything else.

Synopsis

Working with capnproto lists

class ListElem msg e where Source #

Types which may be stored as an element of a capnproto list.

Minimal complete definition

length, index

Associated Types

data List msg e Source #

The type of lists of e stored in messages of type msg

Methods

length :: List msg e -> Int Source #

Get the length of a list.

index :: ReadCtx m msg => Int -> List msg e -> m e Source #

index i list gets the ith element of a list.

Instances
ListElem msg Bool Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Bool :: * Source #

Methods

length :: List msg Bool -> Int Source #

index :: ReadCtx m msg => Int -> List msg Bool -> m Bool Source #

ListElem msg Double Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Double :: * Source #

Methods

length :: List msg Double -> Int Source #

index :: ReadCtx m msg => Int -> List msg Double -> m Double Source #

ListElem msg Float Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Float :: * Source #

Methods

length :: List msg Float -> Int Source #

index :: ReadCtx m msg => Int -> List msg Float -> m Float Source #

ListElem msg Word64 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Word64 :: * Source #

Methods

length :: List msg Word64 -> Int Source #

index :: ReadCtx m msg => Int -> List msg Word64 -> m Word64 Source #

ListElem msg Word32 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Word32 :: * Source #

Methods

length :: List msg Word32 -> Int Source #

index :: ReadCtx m msg => Int -> List msg Word32 -> m Word32 Source #

ListElem msg Word16 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Word16 :: * Source #

Methods

length :: List msg Word16 -> Int Source #

index :: ReadCtx m msg => Int -> List msg Word16 -> m Word16 Source #

ListElem msg Word8 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Word8 :: * Source #

Methods

length :: List msg Word8 -> Int Source #

index :: ReadCtx m msg => Int -> List msg Word8 -> m Word8 Source #

ListElem msg Int64 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Int64 :: * Source #

Methods

length :: List msg Int64 -> Int Source #

index :: ReadCtx m msg => Int -> List msg Int64 -> m Int64 Source #

ListElem msg Int32 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Int32 :: * Source #

Methods

length :: List msg Int32 -> Int Source #

index :: ReadCtx m msg => Int -> List msg Int32 -> m Int32 Source #

ListElem msg Int16 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Int16 :: * Source #

Methods

length :: List msg Int16 -> Int Source #

index :: ReadCtx m msg => Int -> List msg Int16 -> m Int16 Source #

ListElem msg Int8 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Int8 :: * Source #

Methods

length :: List msg Int8 -> Int Source #

index :: ReadCtx m msg => Int -> List msg Int8 -> m Int8 Source #

ListElem msg ElementSize Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg ElementSize :: * Source #

Methods

length :: List msg ElementSize -> Int Source #

index :: ReadCtx m msg => Int -> List msg ElementSize -> m ElementSize Source #

ListElem msg Side Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

data List msg Side :: * Source #

Methods

length :: List msg Side -> Int Source #

index :: ReadCtx m msg => Int -> List msg Side -> m Side Source #

ListElem msg Exception'Type Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg Exception'Type :: * Source #

ListElem msg (Type'anyPointer'unconstrained msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'anyPointer'unconstrained msg) :: * Source #

ListElem msg (Type'anyPointer'implicitMethodParameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ListElem msg (Type'anyPointer'parameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'anyPointer'parameter'group' msg) :: * Source #

ListElem msg (Type'anyPointer'unconstrained'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'anyPointer'unconstrained'group' msg) :: * Source #

ListElem msg (Type'anyPointer msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'anyPointer msg) :: * Source #

Methods

length :: List msg (Type'anyPointer msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Type'anyPointer msg) -> m (Type'anyPointer msg) Source #

ListElem msg (Node'Parameter msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node'Parameter msg) :: * Source #

Methods

length :: List msg (Node'Parameter msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Node'Parameter msg) -> m (Node'Parameter msg) Source #

ListElem msg (Node'NestedNode msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node'NestedNode msg) :: * Source #

Methods

length :: List msg (Node'NestedNode msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Node'NestedNode msg) -> m (Node'NestedNode msg) Source #

ListElem msg (Node'annotation'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node'annotation'group' msg) :: * Source #

ListElem msg (Node'const'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node'const'group' msg) :: * Source #

Methods

length :: List msg (Node'const'group' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Node'const'group' msg) -> m (Node'const'group' msg) Source #

ListElem msg (Node'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node'interface'group' msg) :: * Source #

ListElem msg (Node'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node'enum'group' msg) :: * Source #

Methods

length :: List msg (Node'enum'group' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Node'enum'group' msg) -> m (Node'enum'group' msg) Source #

ListElem msg (Node'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node'struct'group' msg) :: * Source #

Methods

length :: List msg (Node'struct'group' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Node'struct'group' msg) -> m (Node'struct'group' msg) Source #

ListElem msg (Node' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node' msg) :: * Source #

Methods

length :: List msg (Node' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Node' msg) -> m (Node' msg) Source #

ListElem msg (Field'ordinal msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Field'ordinal msg) :: * Source #

Methods

length :: List msg (Field'ordinal msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Field'ordinal msg) -> m (Field'ordinal msg) Source #

ListElem msg (Field'group'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Field'group'group' msg) :: * Source #

Methods

length :: List msg (Field'group'group' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Field'group'group' msg) -> m (Field'group'group' msg) Source #

ListElem msg (Field'slot'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Field'slot'group' msg) :: * Source #

Methods

length :: List msg (Field'slot'group' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Field'slot'group' msg) -> m (Field'slot'group' msg) Source #

ListElem msg (Field' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Field' msg) :: * Source #

Methods

length :: List msg (Field' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Field' msg) -> m (Field' msg) Source #

ListElem msg (CodeGeneratorRequest'RequestedFile'Import msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (CodeGeneratorRequest'RequestedFile'Import msg) :: * Source #

ListElem msg (CodeGeneratorRequest'RequestedFile msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (CodeGeneratorRequest'RequestedFile msg) :: * Source #

ListElem msg (Brand'Scope' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Brand'Scope' msg) :: * Source #

Methods

length :: List msg (Brand'Scope' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Brand'Scope' msg) -> m (Brand'Scope' msg) Source #

ListElem msg (Brand'Scope msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Brand'Scope msg) :: * Source #

Methods

length :: List msg (Brand'Scope msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Brand'Scope msg) -> m (Brand'Scope msg) Source #

ListElem msg (Brand'Binding msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Brand'Binding msg) :: * Source #

Methods

length :: List msg (Brand'Binding msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Brand'Binding msg) -> m (Brand'Binding msg) Source #

ListElem msg (Value msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Value msg) :: * Source #

Methods

length :: List msg (Value msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Value msg) -> m (Value msg) Source #

ListElem msg (Type'anyPointer'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'anyPointer'group' msg) :: * Source #

ListElem msg (Type'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'interface'group' msg) :: * Source #

ListElem msg (Type'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'struct'group' msg) :: * Source #

Methods

length :: List msg (Type'struct'group' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Type'struct'group' msg) -> m (Type'struct'group' msg) Source #

ListElem msg (Type'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'enum'group' msg) :: * Source #

Methods

length :: List msg (Type'enum'group' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Type'enum'group' msg) -> m (Type'enum'group' msg) Source #

ListElem msg (Type'list'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'list'group' msg) :: * Source #

Methods

length :: List msg (Type'list'group' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Type'list'group' msg) -> m (Type'list'group' msg) Source #

ListElem msg (Type msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type msg) :: * Source #

Methods

length :: List msg (Type msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Type msg) -> m (Type msg) Source #

ListElem msg (Superclass msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Superclass msg) :: * Source #

Methods

length :: List msg (Superclass msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Superclass msg) -> m (Superclass msg) Source #

ListElem msg (Node msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node msg) :: * Source #

Methods

length :: List msg (Node msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Node msg) -> m (Node msg) Source #

ListElem msg (Method msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Method msg) :: * Source #

Methods

length :: List msg (Method msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Method msg) -> m (Method msg) Source #

ListElem msg (Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Field msg) :: * Source #

Methods

length :: List msg (Field msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Field msg) -> m (Field msg) Source #

ListElem msg (Enumerant msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Enumerant msg) :: * Source #

Methods

length :: List msg (Enumerant msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Enumerant msg) -> m (Enumerant msg) Source #

ListElem msg (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (CodeGeneratorRequest msg) :: * Source #

Methods

length :: List msg (CodeGeneratorRequest msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (CodeGeneratorRequest msg) -> m (CodeGeneratorRequest msg) Source #

ListElem msg (CapnpVersion msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (CapnpVersion msg) :: * Source #

Methods

length :: List msg (CapnpVersion msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (CapnpVersion msg) -> m (CapnpVersion msg) Source #

ListElem msg (Brand msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Brand msg) :: * Source #

Methods

length :: List msg (Brand msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Brand msg) -> m (Brand msg) Source #

ListElem msg (Annotation msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Annotation msg) :: * Source #

Methods

length :: List msg (Annotation msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Annotation msg) -> m (Annotation msg) Source #

ListElem msg (VatId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

data List msg (VatId msg) :: * Source #

Methods

length :: List msg (VatId msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (VatId msg) -> m (VatId msg) Source #

ListElem msg (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

data List msg (ProvisionId msg) :: * Source #

Methods

length :: List msg (ProvisionId msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (ProvisionId msg) -> m (ProvisionId msg) Source #

ListElem msg (JoinResult msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

data List msg (JoinResult msg) :: * Source #

Methods

length :: List msg (JoinResult msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (JoinResult msg) -> m (JoinResult msg) Source #

ListElem msg (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

data List msg (JoinKeyPart msg) :: * Source #

Methods

length :: List msg (JoinKeyPart msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (JoinKeyPart msg) -> m (JoinKeyPart msg) Source #

ListElem msg (Return' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Return' msg) :: * Source #

Methods

length :: List msg (Return' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Return' msg) -> m (Return' msg) Source #

ListElem msg (Resolve' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Resolve' msg) :: * Source #

Methods

length :: List msg (Resolve' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Resolve' msg) -> m (Resolve' msg) Source #

ListElem msg (PromisedAnswer'Op msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (PromisedAnswer'Op msg) :: * Source #

Methods

length :: List msg (PromisedAnswer'Op msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (PromisedAnswer'Op msg) -> m (PromisedAnswer'Op msg) Source #

ListElem msg (Disembargo'context msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Disembargo'context msg) :: * Source #

Methods

length :: List msg (Disembargo'context msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Disembargo'context msg) -> m (Disembargo'context msg) Source #

ListElem msg (Call'sendResultsTo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Call'sendResultsTo msg) :: * Source #

Methods

length :: List msg (Call'sendResultsTo msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Call'sendResultsTo msg) -> m (Call'sendResultsTo msg) Source #

ListElem msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (ThirdPartyCapDescriptor msg) :: * Source #

ListElem msg (Return msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Return msg) :: * Source #

Methods

length :: List msg (Return msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Return msg) -> m (Return msg) Source #

ListElem msg (Resolve msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Resolve msg) :: * Source #

Methods

length :: List msg (Resolve msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Resolve msg) -> m (Resolve msg) Source #

ListElem msg (Release msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Release msg) :: * Source #

Methods

length :: List msg (Release msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Release msg) -> m (Release msg) Source #

ListElem msg (Provide msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Provide msg) :: * Source #

Methods

length :: List msg (Provide msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Provide msg) -> m (Provide msg) Source #

ListElem msg (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (PromisedAnswer msg) :: * Source #

Methods

length :: List msg (PromisedAnswer msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (PromisedAnswer msg) -> m (PromisedAnswer msg) Source #

ListElem msg (Payload msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Payload msg) :: * Source #

Methods

length :: List msg (Payload msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Payload msg) -> m (Payload msg) Source #

ListElem msg (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (MessageTarget msg) :: * Source #

Methods

length :: List msg (MessageTarget msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (MessageTarget msg) -> m (MessageTarget msg) Source #

ListElem msg (Message msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Message msg) :: * Source #

Methods

length :: List msg (Message msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Message msg) -> m (Message msg) Source #

ListElem msg (Join msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Join msg) :: * Source #

Methods

length :: List msg (Join msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Join msg) -> m (Join msg) Source #

ListElem msg (Finish msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Finish msg) :: * Source #

Methods

length :: List msg (Finish msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Finish msg) -> m (Finish msg) Source #

ListElem msg (Exception msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Exception msg) :: * Source #

Methods

length :: List msg (Exception msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Exception msg) -> m (Exception msg) Source #

ListElem msg (Disembargo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Disembargo msg) :: * Source #

Methods

length :: List msg (Disembargo msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Disembargo msg) -> m (Disembargo msg) Source #

ListElem msg (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (CapDescriptor msg) :: * Source #

Methods

length :: List msg (CapDescriptor msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (CapDescriptor msg) -> m (CapDescriptor msg) Source #

ListElem msg (Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Call msg) :: * Source #

Methods

length :: List msg (Call msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Call msg) -> m (Call msg) Source #

ListElem msg (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Bootstrap msg) :: * Source #

Methods

length :: List msg (Bootstrap msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Bootstrap msg) -> m (Bootstrap msg) Source #

ListElem msg (Accept msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Accept msg) :: * Source #

Methods

length :: List msg (Accept msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Accept msg) -> m (Accept msg) Source #

ListElem msg (Persistent'SaveResults msg) Source # 
Instance details

Defined in Capnp.Capnp.Persistent

Associated Types

data List msg (Persistent'SaveResults msg) :: * Source #

ListElem msg (Persistent'SaveParams msg) Source # 
Instance details

Defined in Capnp.Capnp.Persistent

Associated Types

data List msg (Persistent'SaveParams msg) :: * Source #

ListElem msg (JsonValue'Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Associated Types

data List msg (JsonValue'Field msg) :: * Source #

Methods

length :: List msg (JsonValue'Field msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (JsonValue'Field msg) -> m (JsonValue'Field msg) Source #

ListElem msg (JsonValue'Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Associated Types

data List msg (JsonValue'Call msg) :: * Source #

Methods

length :: List msg (JsonValue'Call msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (JsonValue'Call msg) -> m (JsonValue'Call msg) Source #

ListElem msg (JsonValue msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Associated Types

data List msg (JsonValue msg) :: * Source #

Methods

length :: List msg (JsonValue msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (JsonValue msg) -> m (JsonValue msg) Source #

class ListElem (MutMsg s) e => MutListElem s e where Source #

Types which may be stored as an element of a *mutable* capnproto list.

Minimal complete definition

setIndex, newList

Methods

setIndex :: RWCtx m s => e -> Int -> List (MutMsg s) e -> m () Source #

setIndex value i list sets the ith index in list to @value

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) e) Source #

newList msg size allocates and returns a new list of length size inside msg.

Instances
MutListElem s Bool Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

setIndex :: RWCtx m s => Bool -> Int -> List (MutMsg s) Bool -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) Bool) Source #

MutListElem s Double Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

setIndex :: RWCtx m s => Double -> Int -> List (MutMsg s) Double -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) Double) Source #

MutListElem s Float Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

setIndex :: RWCtx m s => Float -> Int -> List (MutMsg s) Float -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) Float) Source #

MutListElem s Word64 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

setIndex :: RWCtx m s => Word64 -> Int -> List (MutMsg s) Word64 -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) Word64) Source #

MutListElem s Word32 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

setIndex :: RWCtx m s => Word32 -> Int -> List (MutMsg s) Word32 -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) Word32) Source #

MutListElem s Word16 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

setIndex :: RWCtx m s => Word16 -> Int -> List (MutMsg s) Word16 -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) Word16) Source #

MutListElem s Word8 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

setIndex :: RWCtx m s => Word8 -> Int -> List (MutMsg s) Word8 -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) Word8) Source #

MutListElem s Int64 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

setIndex :: RWCtx m s => Int64 -> Int -> List (MutMsg s) Int64 -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) Int64) Source #

MutListElem s Int32 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

setIndex :: RWCtx m s => Int32 -> Int -> List (MutMsg s) Int32 -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) Int32) Source #

MutListElem s Int16 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

setIndex :: RWCtx m s => Int16 -> Int -> List (MutMsg s) Int16 -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) Int16) Source #

MutListElem s Int8 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

setIndex :: RWCtx m s => Int8 -> Int -> List (MutMsg s) Int8 -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) Int8) Source #

MutListElem s ElementSize Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => ElementSize -> Int -> List (MutMsg s) ElementSize -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) ElementSize) Source #

MutListElem s Side Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

setIndex :: RWCtx m s => Side -> Int -> List (MutMsg s) Side -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) Side) Source #

MutListElem s Exception'Type Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MutListElem s (Type'anyPointer'unconstrained (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'anyPointer'implicitMethodParameter'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'anyPointer'parameter'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'anyPointer'unconstrained'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'anyPointer (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Type'anyPointer (MutMsg s) -> Int -> List (MutMsg s) (Type'anyPointer (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Type'anyPointer (MutMsg s))) Source #

MutListElem s (Node'Parameter (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node'Parameter (MutMsg s) -> Int -> List (MutMsg s) (Node'Parameter (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node'Parameter (MutMsg s))) Source #

MutListElem s (Node'NestedNode (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node'NestedNode (MutMsg s) -> Int -> List (MutMsg s) (Node'NestedNode (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node'NestedNode (MutMsg s))) Source #

MutListElem s (Node'annotation'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Node'const'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node'const'group' (MutMsg s) -> Int -> List (MutMsg s) (Node'const'group' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node'const'group' (MutMsg s))) Source #

MutListElem s (Node'interface'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Node'enum'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node'enum'group' (MutMsg s) -> Int -> List (MutMsg s) (Node'enum'group' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node'enum'group' (MutMsg s))) Source #

MutListElem s (Node'struct'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Node' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node' (MutMsg s) -> Int -> List (MutMsg s) (Node' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node' (MutMsg s))) Source #

MutListElem s (Field'ordinal (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Field'ordinal (MutMsg s) -> Int -> List (MutMsg s) (Field'ordinal (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Field'ordinal (MutMsg s))) Source #

MutListElem s (Field'group'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Field'slot'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Field'slot'group' (MutMsg s) -> Int -> List (MutMsg s) (Field'slot'group' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Field'slot'group' (MutMsg s))) Source #

MutListElem s (Field' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Field' (MutMsg s) -> Int -> List (MutMsg s) (Field' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Field' (MutMsg s))) Source #

MutListElem s (CodeGeneratorRequest'RequestedFile'Import (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (CodeGeneratorRequest'RequestedFile (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Brand'Scope' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Brand'Scope' (MutMsg s) -> Int -> List (MutMsg s) (Brand'Scope' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Brand'Scope' (MutMsg s))) Source #

MutListElem s (Brand'Scope (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Brand'Scope (MutMsg s) -> Int -> List (MutMsg s) (Brand'Scope (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Brand'Scope (MutMsg s))) Source #

MutListElem s (Brand'Binding (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Brand'Binding (MutMsg s) -> Int -> List (MutMsg s) (Brand'Binding (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Brand'Binding (MutMsg s))) Source #

MutListElem s (Value (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Value (MutMsg s) -> Int -> List (MutMsg s) (Value (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Value (MutMsg s))) Source #

MutListElem s (Type'anyPointer'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'interface'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'struct'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'enum'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Type'enum'group' (MutMsg s) -> Int -> List (MutMsg s) (Type'enum'group' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Type'enum'group' (MutMsg s))) Source #

MutListElem s (Type'list'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Type'list'group' (MutMsg s) -> Int -> List (MutMsg s) (Type'list'group' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Type'list'group' (MutMsg s))) Source #

MutListElem s (Type (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Type (MutMsg s) -> Int -> List (MutMsg s) (Type (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Type (MutMsg s))) Source #

MutListElem s (Superclass (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Superclass (MutMsg s) -> Int -> List (MutMsg s) (Superclass (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Superclass (MutMsg s))) Source #

MutListElem s (Node (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node (MutMsg s) -> Int -> List (MutMsg s) (Node (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node (MutMsg s))) Source #

MutListElem s (Method (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Method (MutMsg s) -> Int -> List (MutMsg s) (Method (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Method (MutMsg s))) Source #

MutListElem s (Field (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Field (MutMsg s) -> Int -> List (MutMsg s) (Field (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Field (MutMsg s))) Source #

MutListElem s (Enumerant (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Enumerant (MutMsg s) -> Int -> List (MutMsg s) (Enumerant (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Enumerant (MutMsg s))) Source #

MutListElem s (CodeGeneratorRequest (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (CapnpVersion (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => CapnpVersion (MutMsg s) -> Int -> List (MutMsg s) (CapnpVersion (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (CapnpVersion (MutMsg s))) Source #

MutListElem s (Brand (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Brand (MutMsg s) -> Int -> List (MutMsg s) (Brand (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Brand (MutMsg s))) Source #

MutListElem s (Annotation (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Annotation (MutMsg s) -> Int -> List (MutMsg s) (Annotation (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Annotation (MutMsg s))) Source #

MutListElem s (VatId (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

setIndex :: RWCtx m s => VatId (MutMsg s) -> Int -> List (MutMsg s) (VatId (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (VatId (MutMsg s))) Source #

MutListElem s (ProvisionId (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

setIndex :: RWCtx m s => ProvisionId (MutMsg s) -> Int -> List (MutMsg s) (ProvisionId (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (ProvisionId (MutMsg s))) Source #

MutListElem s (JoinResult (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

setIndex :: RWCtx m s => JoinResult (MutMsg s) -> Int -> List (MutMsg s) (JoinResult (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (JoinResult (MutMsg s))) Source #

MutListElem s (JoinKeyPart (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

setIndex :: RWCtx m s => JoinKeyPart (MutMsg s) -> Int -> List (MutMsg s) (JoinKeyPart (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (JoinKeyPart (MutMsg s))) Source #

MutListElem s (Return' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Return' (MutMsg s) -> Int -> List (MutMsg s) (Return' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Return' (MutMsg s))) Source #

MutListElem s (Resolve' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Resolve' (MutMsg s) -> Int -> List (MutMsg s) (Resolve' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Resolve' (MutMsg s))) Source #

MutListElem s (PromisedAnswer'Op (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => PromisedAnswer'Op (MutMsg s) -> Int -> List (MutMsg s) (PromisedAnswer'Op (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (PromisedAnswer'Op (MutMsg s))) Source #

MutListElem s (Disembargo'context (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MutListElem s (Call'sendResultsTo (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MutListElem s (ThirdPartyCapDescriptor (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MutListElem s (Return (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Return (MutMsg s) -> Int -> List (MutMsg s) (Return (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Return (MutMsg s))) Source #

MutListElem s (Resolve (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Resolve (MutMsg s) -> Int -> List (MutMsg s) (Resolve (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Resolve (MutMsg s))) Source #

MutListElem s (Release (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Release (MutMsg s) -> Int -> List (MutMsg s) (Release (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Release (MutMsg s))) Source #

MutListElem s (Provide (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Provide (MutMsg s) -> Int -> List (MutMsg s) (Provide (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Provide (MutMsg s))) Source #

MutListElem s (PromisedAnswer (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => PromisedAnswer (MutMsg s) -> Int -> List (MutMsg s) (PromisedAnswer (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (PromisedAnswer (MutMsg s))) Source #

MutListElem s (Payload (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Payload (MutMsg s) -> Int -> List (MutMsg s) (Payload (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Payload (MutMsg s))) Source #

MutListElem s (MessageTarget (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => MessageTarget (MutMsg s) -> Int -> List (MutMsg s) (MessageTarget (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (MessageTarget (MutMsg s))) Source #

MutListElem s (Message (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Message (MutMsg s) -> Int -> List (MutMsg s) (Message (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Message (MutMsg s))) Source #

MutListElem s (Join (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Join (MutMsg s) -> Int -> List (MutMsg s) (Join (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Join (MutMsg s))) Source #

MutListElem s (Finish (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Finish (MutMsg s) -> Int -> List (MutMsg s) (Finish (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Finish (MutMsg s))) Source #

MutListElem s (Exception (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Exception (MutMsg s) -> Int -> List (MutMsg s) (Exception (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Exception (MutMsg s))) Source #

MutListElem s (Disembargo (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Disembargo (MutMsg s) -> Int -> List (MutMsg s) (Disembargo (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Disembargo (MutMsg s))) Source #

MutListElem s (CapDescriptor (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => CapDescriptor (MutMsg s) -> Int -> List (MutMsg s) (CapDescriptor (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (CapDescriptor (MutMsg s))) Source #

MutListElem s (Call (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Call (MutMsg s) -> Int -> List (MutMsg s) (Call (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Call (MutMsg s))) Source #

MutListElem s (Bootstrap (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Bootstrap (MutMsg s) -> Int -> List (MutMsg s) (Bootstrap (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Bootstrap (MutMsg s))) Source #

MutListElem s (Accept (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Accept (MutMsg s) -> Int -> List (MutMsg s) (Accept (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Accept (MutMsg s))) Source #

MutListElem s (Persistent'SaveResults (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Persistent

MutListElem s (Persistent'SaveParams (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Persistent

MutListElem s (JsonValue'Field (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

setIndex :: RWCtx m s => JsonValue'Field (MutMsg s) -> Int -> List (MutMsg s) (JsonValue'Field (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (JsonValue'Field (MutMsg s))) Source #

MutListElem s (JsonValue'Call (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

setIndex :: RWCtx m s => JsonValue'Call (MutMsg s) -> Int -> List (MutMsg s) (JsonValue'Call (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (JsonValue'Call (MutMsg s))) Source #

MutListElem s (JsonValue (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

setIndex :: RWCtx m s => JsonValue (MutMsg s) -> Int -> List (MutMsg s) (JsonValue (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (JsonValue (MutMsg s))) Source #

Working with capnproto Text and Data values.

data Data msg Source #

A blob of bytes (Data in capnproto's schema language). The argument to the data constructor is a slice into the message, containing the raw bytes.

Instances
IsPtr msg (Data msg) Source # 
Instance details

Defined in Data.Capnp.Basics

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Data msg) Source #

toPtr :: Data msg -> Maybe (Ptr msg) Source #

dataBytes :: ReadCtx m msg => Data msg -> m ByteString Source #

Convert a Data to a ByteString.

data Text msg Source #

A textual string (Text in capnproto's schema language). On the wire, this is NUL-terminated. The encoding should be UTF-8, but the library does not verify this; users of the library must do validation themselves, if they care about this.

Rationale: validation would require doing an up-front pass over the data, which runs counter to the overall design of capnproto.

Instances
IsPtr msg (Text msg) Source # 
Instance details

Defined in Data.Capnp.Basics

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Text msg) Source #

toPtr :: Text msg -> Maybe (Ptr msg) Source #

textBytes :: ReadCtx m msg => Text msg -> m ByteString Source #

Convert a Text to a ByteString, comprising the raw bytes of the text (not counting the NUL terminator).

Working with messages

data ConstMsg Source #

A read-only capnproto message.

ConstMsg is an instance of the generic Message type class. its implementations of toByteString and fromByteString are O(1); the underlying bytes are not copied.

Instances
MonadThrow m => Message m ConstMsg Source # 
Instance details

Defined in Data.Capnp.Message

Associated Types

data Segment ConstMsg :: * Source #

FromStruct ConstMsg Type'anyPointer'unconstrained Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Type'anyPointer Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Node'Parameter Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Node'NestedNode Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Node' Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Field'ordinal Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Field' Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg CodeGeneratorRequest'RequestedFile'Import Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg CodeGeneratorRequest'RequestedFile Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Brand'Scope' Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Brand'Scope Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Brand'Binding Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Value Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Type Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Superclass Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Node Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Method Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Field Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Enumerant Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg CodeGeneratorRequest Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg CapnpVersion Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Brand Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Annotation Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg VatId Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

FromStruct ConstMsg ProvisionId Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

FromStruct ConstMsg JoinResult Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

FromStruct ConstMsg JoinKeyPart Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

FromStruct ConstMsg Return' Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Resolve' Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg PromisedAnswer'Op Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Disembargo'context Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Call'sendResultsTo Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg ThirdPartyCapDescriptor Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Return Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Resolve Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Release Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Provide Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg PromisedAnswer Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Payload Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg MessageTarget Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Message Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Join Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Finish Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Exception Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Disembargo Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg CapDescriptor Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Call Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Bootstrap Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Accept Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Persistent'SaveResults Source # 
Instance details

Defined in Capnp.Capnp.Persistent.Pure

FromStruct ConstMsg Persistent'SaveParams Source # 
Instance details

Defined in Capnp.Capnp.Persistent.Pure

FromStruct ConstMsg JsonValue'Field Source # 
Instance details

Defined in Capnp.Capnp.Json.Pure

FromStruct ConstMsg JsonValue'Call Source # 
Instance details

Defined in Capnp.Capnp.Json.Pure

FromStruct ConstMsg JsonValue Source # 
Instance details

Defined in Capnp.Capnp.Json.Pure

data Segment ConstMsg Source # 
Instance details

Defined in Data.Capnp.Message

class Monad m => Message m msg where Source #

A Message is a (possibly read-only) capnproto message. It is parameterized over a monad in which operations are performed.

Associated Types

data Segment msg Source #

The type of segments in the message.

Methods

numSegs :: msg -> m Int Source #

numSegs gets the number of segments in a message.

internalGetSeg :: msg -> Int -> m (Segment msg) Source #

internalGetSeg message index gets the segment at index index in message. Most callers should use the getSegment wrapper, instead of calling this directly.

numWords :: Segment msg -> m Int Source #

Get the length of the segment, in units of 64-bit words.

slice :: Int -> Int -> Segment msg -> m (Segment msg) Source #

slice start length segment extracts a sub-section of the segment, starting at index start, of length length.

read :: Segment msg -> Int -> m Word64 Source #

read segment index reads a 64-bit word from the segement at the given index. Consider using getWord on the message, instead of calling this directly.

fromByteString :: ByteString -> m (Segment msg) Source #

Convert a ByteString to a segment.

toByteString :: Segment msg -> m ByteString Source #

Convert a segment to a byte string.

class Mutable a where Source #

The Mutable type class relates mutable and immutable versions of a type. The instance is defined on the mutable variant; Frozen a is the immutable version of a mutable type a.

Minimal complete definition

thaw, freeze

Associated Types

type Scope a Source #

The state token for a mutable value.

type Frozen a Source #

The immutable version of a.

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope a) => Frozen a -> m a Source #

Convert an immutable value to a mutable one.

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope a) => a -> m (Frozen a) Source #

Convert a mutable value to an immutable one.

Instances
Mutable (MutMsg s) Source # 
Instance details

Defined in Data.Capnp.Message

Associated Types

type Scope (MutMsg s) :: * Source #

type Frozen (MutMsg s) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (MutMsg s)) => Frozen (MutMsg s) -> m (MutMsg s) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (MutMsg s)) => MutMsg s -> m (Frozen (MutMsg s)) Source #

Mutable (Segment (MutMsg s)) Source # 
Instance details

Defined in Data.Capnp.Message

Associated Types

type Scope (Segment (MutMsg s)) :: * Source #

type Frozen (Segment (MutMsg s)) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (Segment (MutMsg s))) => Frozen (Segment (MutMsg s)) -> m (Segment (MutMsg s)) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (Segment (MutMsg s))) => Segment (MutMsg s) -> m (Frozen (Segment (MutMsg s))) Source #

Mutable msg => Mutable (Struct msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Scope (Struct msg) :: * Source #

type Frozen (Struct msg) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (Struct msg)) => Frozen (Struct msg) -> m (Struct msg) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (Struct msg)) => Struct msg -> m (Frozen (Struct msg)) Source #

Mutable msg => Mutable (List msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Scope (List msg) :: * Source #

type Frozen (List msg) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (List msg)) => Frozen (List msg) -> m (List msg) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (List msg)) => List msg -> m (Frozen (List msg)) Source #

Mutable msg => Mutable (Ptr msg) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Scope (Ptr msg) :: * Source #

type Frozen (Ptr msg) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (Ptr msg)) => Frozen (Ptr msg) -> m (Ptr msg) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (Ptr msg)) => Ptr msg -> m (Frozen (Ptr msg)) Source #

Mutable msg => Mutable (ListOf msg (Maybe (Ptr msg))) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg (Maybe (Ptr msg))) :: * Source #

type Frozen (ListOf msg (Maybe (Ptr msg))) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg (Maybe (Ptr msg)))) => Frozen (ListOf msg (Maybe (Ptr msg))) -> m (ListOf msg (Maybe (Ptr msg))) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg (Maybe (Ptr msg)))) => ListOf msg (Maybe (Ptr msg)) -> m (Frozen (ListOf msg (Maybe (Ptr msg)))) Source #

Mutable msg => Mutable (ListOf msg (Struct msg)) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg (Struct msg)) :: * Source #

type Frozen (ListOf msg (Struct msg)) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg (Struct msg))) => Frozen (ListOf msg (Struct msg)) -> m (ListOf msg (Struct msg)) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg (Struct msg))) => ListOf msg (Struct msg) -> m (Frozen (ListOf msg (Struct msg))) Source #

Mutable msg => Mutable (ListOf msg Word64) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg Word64) :: * Source #

type Frozen (ListOf msg Word64) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Word64)) => Frozen (ListOf msg Word64) -> m (ListOf msg Word64) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Word64)) => ListOf msg Word64 -> m (Frozen (ListOf msg Word64)) Source #

Mutable msg => Mutable (ListOf msg Word32) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg Word32) :: * Source #

type Frozen (ListOf msg Word32) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Word32)) => Frozen (ListOf msg Word32) -> m (ListOf msg Word32) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Word32)) => ListOf msg Word32 -> m (Frozen (ListOf msg Word32)) Source #

Mutable msg => Mutable (ListOf msg Word16) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg Word16) :: * Source #

type Frozen (ListOf msg Word16) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Word16)) => Frozen (ListOf msg Word16) -> m (ListOf msg Word16) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Word16)) => ListOf msg Word16 -> m (Frozen (ListOf msg Word16)) Source #

Mutable msg => Mutable (ListOf msg Word8) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg Word8) :: * Source #

type Frozen (ListOf msg Word8) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Word8)) => Frozen (ListOf msg Word8) -> m (ListOf msg Word8) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Word8)) => ListOf msg Word8 -> m (Frozen (ListOf msg Word8)) Source #

Mutable msg => Mutable (ListOf msg Bool) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg Bool) :: * Source #

type Frozen (ListOf msg Bool) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Bool)) => Frozen (ListOf msg Bool) -> m (ListOf msg Bool) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg Bool)) => ListOf msg Bool -> m (Frozen (ListOf msg Bool)) Source #

Mutable msg => Mutable (ListOf msg ()) Source # 
Instance details

Defined in Data.Capnp.Untyped

Associated Types

type Scope (ListOf msg ()) :: * Source #

type Frozen (ListOf msg ()) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg ())) => Frozen (ListOf msg ()) -> m (ListOf msg ()) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg ())) => ListOf msg () -> m (Frozen (ListOf msg ())) Source #

data MutMsg s Source #

A MutMsg is a mutable capnproto message. The type parameter s is the state token for the instance of PrimMonad in which the message may be modified.

Due to mutabilty, the implementations of toByteString and fromByteString must make full copies, and so are O(n) in the length of the segment.

Instances
WriteCtx m s => Message m (MutMsg s) Source # 
Instance details

Defined in Data.Capnp.Message

Associated Types

data Segment (MutMsg s) :: * Source #

Allocate s (Type'anyPointer'unconstrained (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Allocate s (Type'anyPointer'implicitMethodParameter'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Allocate s (Type'anyPointer'parameter'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Allocate s (Type'anyPointer'unconstrained'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Allocate s (Type'anyPointer (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Type'anyPointer (MutMsg s)) Source #

Allocate s (Node'Parameter (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node'Parameter (MutMsg s)) Source #

Allocate s (Node'NestedNode (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node'NestedNode (MutMsg s)) Source #

Allocate s (Node'annotation'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node'annotation'group' (MutMsg s)) Source #

Allocate s (Node'const'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node'const'group' (MutMsg s)) Source #

Allocate s (Node'interface'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node'interface'group' (MutMsg s)) Source #

Allocate s (Node'enum'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node'enum'group' (MutMsg s)) Source #

Allocate s (Node'struct'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node'struct'group' (MutMsg s)) Source #

Allocate s (Node' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node' (MutMsg s)) Source #

Allocate s (Field'ordinal (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Field'ordinal (MutMsg s)) Source #

Allocate s (Field'group'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Field'group'group' (MutMsg s)) Source #

Allocate s (Field'slot'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Field'slot'group' (MutMsg s)) Source #

Allocate s (Field' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Field' (MutMsg s)) Source #

Allocate s (CodeGeneratorRequest'RequestedFile'Import (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Allocate s (CodeGeneratorRequest'RequestedFile (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Allocate s (Brand'Scope' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Brand'Scope' (MutMsg s)) Source #

Allocate s (Brand'Scope (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Brand'Scope (MutMsg s)) Source #

Allocate s (Brand'Binding (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Brand'Binding (MutMsg s)) Source #

Allocate s (Value (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Value (MutMsg s)) Source #

Allocate s (Type'anyPointer'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Type'anyPointer'group' (MutMsg s)) Source #

Allocate s (Type'interface'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Type'interface'group' (MutMsg s)) Source #

Allocate s (Type'struct'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Type'struct'group' (MutMsg s)) Source #

Allocate s (Type'enum'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Type'enum'group' (MutMsg s)) Source #

Allocate s (Type'list'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Type'list'group' (MutMsg s)) Source #

Allocate s (Type (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Type (MutMsg s)) Source #

Allocate s (Superclass (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Superclass (MutMsg s)) Source #

Allocate s (Node (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node (MutMsg s)) Source #

Allocate s (Method (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Method (MutMsg s)) Source #

Allocate s (Field (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Field (MutMsg s)) Source #

Allocate s (Enumerant (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Enumerant (MutMsg s)) Source #

Allocate s (CodeGeneratorRequest (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (CodeGeneratorRequest (MutMsg s)) Source #

Allocate s (CapnpVersion (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (CapnpVersion (MutMsg s)) Source #

Allocate s (Brand (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Brand (MutMsg s)) Source #

Allocate s (Annotation (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Annotation (MutMsg s)) Source #

Allocate s (VatId (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

new :: WriteCtx m s => MutMsg s -> m (VatId (MutMsg s)) Source #

Allocate s (ProvisionId (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

new :: WriteCtx m s => MutMsg s -> m (ProvisionId (MutMsg s)) Source #

Allocate s (JoinResult (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

new :: WriteCtx m s => MutMsg s -> m (JoinResult (MutMsg s)) Source #

Allocate s (JoinKeyPart (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

new :: WriteCtx m s => MutMsg s -> m (JoinKeyPart (MutMsg s)) Source #

Allocate s (Return' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Return' (MutMsg s)) Source #

Allocate s (Resolve' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Resolve' (MutMsg s)) Source #

Allocate s (PromisedAnswer'Op (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (PromisedAnswer'Op (MutMsg s)) Source #

Allocate s (Disembargo'context (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Disembargo'context (MutMsg s)) Source #

Allocate s (Call'sendResultsTo (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Call'sendResultsTo (MutMsg s)) Source #

Allocate s (ThirdPartyCapDescriptor (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (ThirdPartyCapDescriptor (MutMsg s)) Source #

Allocate s (Return (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Return (MutMsg s)) Source #

Allocate s (Resolve (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Resolve (MutMsg s)) Source #

Allocate s (Release (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Release (MutMsg s)) Source #

Allocate s (Provide (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Provide (MutMsg s)) Source #

Allocate s (PromisedAnswer (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (PromisedAnswer (MutMsg s)) Source #

Allocate s (Payload (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Payload (MutMsg s)) Source #

Allocate s (MessageTarget (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (MessageTarget (MutMsg s)) Source #

Allocate s (Message (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Message (MutMsg s)) Source #

Allocate s (Join (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Join (MutMsg s)) Source #

Allocate s (Finish (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Finish (MutMsg s)) Source #

Allocate s (Exception (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Exception (MutMsg s)) Source #

Allocate s (Disembargo (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Disembargo (MutMsg s)) Source #

Allocate s (CapDescriptor (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (CapDescriptor (MutMsg s)) Source #

Allocate s (Call (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Call (MutMsg s)) Source #

Allocate s (Bootstrap (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Bootstrap (MutMsg s)) Source #

Allocate s (Accept (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

new :: WriteCtx m s => MutMsg s -> m (Accept (MutMsg s)) Source #

Allocate s (Persistent'SaveResults (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Persistent

Methods

new :: WriteCtx m s => MutMsg s -> m (Persistent'SaveResults (MutMsg s)) Source #

Allocate s (Persistent'SaveParams (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Persistent

Methods

new :: WriteCtx m s => MutMsg s -> m (Persistent'SaveParams (MutMsg s)) Source #

Allocate s (JsonValue'Field (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

new :: WriteCtx m s => MutMsg s -> m (JsonValue'Field (MutMsg s)) Source #

Allocate s (JsonValue'Call (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

new :: WriteCtx m s => MutMsg s -> m (JsonValue'Call (MutMsg s)) Source #

Allocate s (JsonValue (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

new :: WriteCtx m s => MutMsg s -> m (JsonValue (MutMsg s)) Source #

MutListElem s (Type'anyPointer'unconstrained (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'anyPointer'implicitMethodParameter'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'anyPointer'parameter'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'anyPointer'unconstrained'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'anyPointer (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Type'anyPointer (MutMsg s) -> Int -> List (MutMsg s) (Type'anyPointer (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Type'anyPointer (MutMsg s))) Source #

MutListElem s (Node'Parameter (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node'Parameter (MutMsg s) -> Int -> List (MutMsg s) (Node'Parameter (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node'Parameter (MutMsg s))) Source #

MutListElem s (Node'NestedNode (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node'NestedNode (MutMsg s) -> Int -> List (MutMsg s) (Node'NestedNode (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node'NestedNode (MutMsg s))) Source #

MutListElem s (Node'annotation'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Node'const'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node'const'group' (MutMsg s) -> Int -> List (MutMsg s) (Node'const'group' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node'const'group' (MutMsg s))) Source #

MutListElem s (Node'interface'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Node'enum'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node'enum'group' (MutMsg s) -> Int -> List (MutMsg s) (Node'enum'group' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node'enum'group' (MutMsg s))) Source #

MutListElem s (Node'struct'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Node' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node' (MutMsg s) -> Int -> List (MutMsg s) (Node' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node' (MutMsg s))) Source #

MutListElem s (Field'ordinal (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Field'ordinal (MutMsg s) -> Int -> List (MutMsg s) (Field'ordinal (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Field'ordinal (MutMsg s))) Source #

MutListElem s (Field'group'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Field'slot'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Field'slot'group' (MutMsg s) -> Int -> List (MutMsg s) (Field'slot'group' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Field'slot'group' (MutMsg s))) Source #

MutListElem s (Field' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Field' (MutMsg s) -> Int -> List (MutMsg s) (Field' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Field' (MutMsg s))) Source #

MutListElem s (CodeGeneratorRequest'RequestedFile'Import (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (CodeGeneratorRequest'RequestedFile (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Brand'Scope' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Brand'Scope' (MutMsg s) -> Int -> List (MutMsg s) (Brand'Scope' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Brand'Scope' (MutMsg s))) Source #

MutListElem s (Brand'Scope (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Brand'Scope (MutMsg s) -> Int -> List (MutMsg s) (Brand'Scope (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Brand'Scope (MutMsg s))) Source #

MutListElem s (Brand'Binding (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Brand'Binding (MutMsg s) -> Int -> List (MutMsg s) (Brand'Binding (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Brand'Binding (MutMsg s))) Source #

MutListElem s (Value (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Value (MutMsg s) -> Int -> List (MutMsg s) (Value (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Value (MutMsg s))) Source #

MutListElem s (Type'anyPointer'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'interface'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'struct'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'enum'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Type'enum'group' (MutMsg s) -> Int -> List (MutMsg s) (Type'enum'group' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Type'enum'group' (MutMsg s))) Source #

MutListElem s (Type'list'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Type'list'group' (MutMsg s) -> Int -> List (MutMsg s) (Type'list'group' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Type'list'group' (MutMsg s))) Source #

MutListElem s (Type (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Type (MutMsg s) -> Int -> List (MutMsg s) (Type (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Type (MutMsg s))) Source #

MutListElem s (Superclass (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Superclass (MutMsg s) -> Int -> List (MutMsg s) (Superclass (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Superclass (MutMsg s))) Source #

MutListElem s (Node (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node (MutMsg s) -> Int -> List (MutMsg s) (Node (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node (MutMsg s))) Source #

MutListElem s (Method (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Method (MutMsg s) -> Int -> List (MutMsg s) (Method (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Method (MutMsg s))) Source #

MutListElem s (Field (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Field (MutMsg s) -> Int -> List (MutMsg s) (Field (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Field (MutMsg s))) Source #

MutListElem s (Enumerant (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Enumerant (MutMsg s) -> Int -> List (MutMsg s) (Enumerant (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Enumerant (MutMsg s))) Source #

MutListElem s (CodeGeneratorRequest (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (CapnpVersion (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => CapnpVersion (MutMsg s) -> Int -> List (MutMsg s) (CapnpVersion (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (CapnpVersion (MutMsg s))) Source #

MutListElem s (Brand (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Brand (MutMsg s) -> Int -> List (MutMsg s) (Brand (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Brand (MutMsg s))) Source #

MutListElem s (Annotation (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Annotation (MutMsg s) -> Int -> List (MutMsg s) (Annotation (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Annotation (MutMsg s))) Source #

MutListElem s (VatId (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

setIndex :: RWCtx m s => VatId (MutMsg s) -> Int -> List (MutMsg s) (VatId (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (VatId (MutMsg s))) Source #

MutListElem s (ProvisionId (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

setIndex :: RWCtx m s => ProvisionId (MutMsg s) -> Int -> List (MutMsg s) (ProvisionId (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (ProvisionId (MutMsg s))) Source #

MutListElem s (JoinResult (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

setIndex :: RWCtx m s => JoinResult (MutMsg s) -> Int -> List (MutMsg s) (JoinResult (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (JoinResult (MutMsg s))) Source #

MutListElem s (JoinKeyPart (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

setIndex :: RWCtx m s => JoinKeyPart (MutMsg s) -> Int -> List (MutMsg s) (JoinKeyPart (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (JoinKeyPart (MutMsg s))) Source #

MutListElem s (Return' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Return' (MutMsg s) -> Int -> List (MutMsg s) (Return' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Return' (MutMsg s))) Source #

MutListElem s (Resolve' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Resolve' (MutMsg s) -> Int -> List (MutMsg s) (Resolve' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Resolve' (MutMsg s))) Source #

MutListElem s (PromisedAnswer'Op (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => PromisedAnswer'Op (MutMsg s) -> Int -> List (MutMsg s) (PromisedAnswer'Op (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (PromisedAnswer'Op (MutMsg s))) Source #

MutListElem s (Disembargo'context (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MutListElem s (Call'sendResultsTo (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MutListElem s (ThirdPartyCapDescriptor (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MutListElem s (Return (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Return (MutMsg s) -> Int -> List (MutMsg s) (Return (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Return (MutMsg s))) Source #

MutListElem s (Resolve (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Resolve (MutMsg s) -> Int -> List (MutMsg s) (Resolve (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Resolve (MutMsg s))) Source #

MutListElem s (Release (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Release (MutMsg s) -> Int -> List (MutMsg s) (Release (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Release (MutMsg s))) Source #

MutListElem s (Provide (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Provide (MutMsg s) -> Int -> List (MutMsg s) (Provide (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Provide (MutMsg s))) Source #

MutListElem s (PromisedAnswer (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => PromisedAnswer (MutMsg s) -> Int -> List (MutMsg s) (PromisedAnswer (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (PromisedAnswer (MutMsg s))) Source #

MutListElem s (Payload (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Payload (MutMsg s) -> Int -> List (MutMsg s) (Payload (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Payload (MutMsg s))) Source #

MutListElem s (MessageTarget (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => MessageTarget (MutMsg s) -> Int -> List (MutMsg s) (MessageTarget (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (MessageTarget (MutMsg s))) Source #

MutListElem s (Message (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Message (MutMsg s) -> Int -> List (MutMsg s) (Message (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Message (MutMsg s))) Source #

MutListElem s (Join (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Join (MutMsg s) -> Int -> List (MutMsg s) (Join (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Join (MutMsg s))) Source #

MutListElem s (Finish (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Finish (MutMsg s) -> Int -> List (MutMsg s) (Finish (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Finish (MutMsg s))) Source #

MutListElem s (Exception (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Exception (MutMsg s) -> Int -> List (MutMsg s) (Exception (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Exception (MutMsg s))) Source #

MutListElem s (Disembargo (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Disembargo (MutMsg s) -> Int -> List (MutMsg s) (Disembargo (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Disembargo (MutMsg s))) Source #

MutListElem s (CapDescriptor (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => CapDescriptor (MutMsg s) -> Int -> List (MutMsg s) (CapDescriptor (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (CapDescriptor (MutMsg s))) Source #

MutListElem s (Call (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Call (MutMsg s) -> Int -> List (MutMsg s) (Call (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Call (MutMsg s))) Source #

MutListElem s (Bootstrap (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Bootstrap (MutMsg s) -> Int -> List (MutMsg s) (Bootstrap (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Bootstrap (MutMsg s))) Source #

MutListElem s (Accept (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

setIndex :: RWCtx m s => Accept (MutMsg s) -> Int -> List (MutMsg s) (Accept (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Accept (MutMsg s))) Source #

MutListElem s (Persistent'SaveResults (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Persistent

MutListElem s (Persistent'SaveParams (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Persistent

MutListElem s (JsonValue'Field (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

setIndex :: RWCtx m s => JsonValue'Field (MutMsg s) -> Int -> List (MutMsg s) (JsonValue'Field (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (JsonValue'Field (MutMsg s))) Source #

MutListElem s (JsonValue'Call (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

setIndex :: RWCtx m s => JsonValue'Call (MutMsg s) -> Int -> List (MutMsg s) (JsonValue'Call (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (JsonValue'Call (MutMsg s))) Source #

MutListElem s (JsonValue (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

setIndex :: RWCtx m s => JsonValue (MutMsg s) -> Int -> List (MutMsg s) (JsonValue (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (JsonValue (MutMsg s))) Source #

Mutable (MutMsg s) Source # 
Instance details

Defined in Data.Capnp.Message

Associated Types

type Scope (MutMsg s) :: * Source #

type Frozen (MutMsg s) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (MutMsg s)) => Frozen (MutMsg s) -> m (MutMsg s) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (MutMsg s)) => MutMsg s -> m (Frozen (MutMsg s)) Source #

Mutable (Segment (MutMsg s)) Source # 
Instance details

Defined in Data.Capnp.Message

Associated Types

type Scope (Segment (MutMsg s)) :: * Source #

type Frozen (Segment (MutMsg s)) :: * Source #

Methods

thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (Segment (MutMsg s))) => Frozen (Segment (MutMsg s)) -> m (Segment (MutMsg s)) Source #

freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (Segment (MutMsg s))) => Segment (MutMsg s) -> m (Frozen (Segment (MutMsg s))) Source #

type Scope (MutMsg s) Source # 
Instance details

Defined in Data.Capnp.Message

type Scope (MutMsg s) = s
type Scope (Segment (MutMsg s)) Source # 
Instance details

Defined in Data.Capnp.Message

type Scope (Segment (MutMsg s)) = s
type Frozen (MutMsg s) Source # 
Instance details

Defined in Data.Capnp.Message

type Frozen (Segment (MutMsg s)) Source # 
Instance details

Defined in Data.Capnp.Message

data Segment (MutMsg s) Source # 
Instance details

Defined in Data.Capnp.Message

data Segment (MutMsg s) = MutSegment {}

newMessage :: WriteCtx m s => m (MutMsg s) Source #

Allocate a new empty message.

decodeMessage :: MonadThrow m => ByteString -> m ConstMsg Source #

Alias for decode

encodeMessage :: MonadThrow m => ConstMsg -> m Builder Source #

Alias for encode

Reading and writing messages

hPutMsg :: Handle -> ConstMsg -> IO () Source #

hPutMsg handle msg writes msg to handle.

putMsg :: ConstMsg -> IO () Source #

Equivalent to hPutMsg stdout

hGetMsg :: Handle -> Int -> IO ConstMsg Source #

hGetMsg handle limit reads a message from handle that is at most limit 64-bit words in length.

getMsg :: Int -> IO ConstMsg Source #

Equivalent to hGetMsg stdin

Manipulating the root object of a message

getRoot :: (FromStruct msg a, ReadCtx m msg) => msg -> m a Source #

getRoot returns the root object of a message.

newRoot :: (ToStruct (MutMsg s) a, Allocate s a, WriteCtx m s) => MutMsg s -> m a Source #

newRoot allocates and returns a new value inside the message, setting it as the root object of the message.

setRoot :: (ToStruct (MutMsg s) a, WriteCtx m s) => a -> m () Source #

setRoot sets its argument to be the root object in its message.

Reading values

hGetValue :: FromStruct ConstMsg a => Handle -> Int -> IO a Source #

hGetValue limit handle reads a message from handle, returning its root object. limit is used as both a cap on the size of a message which may be read and, for types in the high-level API, the traversal limit when decoding the message.

Type aliases for common contexts

type WriteCtx m s = (PrimMonad m, s ~ PrimState m, MonadThrow m) Source #

WriteCtx is the context needed for most write operations.

type ReadCtx m msg = (Message m msg, MonadThrow m, MonadLimit m) Source #

Type (constraint) synonym for the constraints needed for most read operations.

type RWCtx m s = (ReadCtx m (MutMsg s), WriteCtx m s) Source #

Synonym for ReadCtx + WriteCtx

Managing resource limits