capnp-0.5.0.0: Cap'n Proto for Haskell

Safe HaskellNone
LanguageHaskell2010

Capnp.Basics

Description

In particular

  • Text and Data (which are primitive types in the schema language, but are both the same as List(UInt8) on the wire).
  • Lists of types other than those in Capnp.Untyped. Whereas ListOf only deals with low-level encodings of lists, this module's List type can represent typed lists.
Synopsis

Documentation

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
ToPtr s (Text (MutMsg s)) Source # 
Instance details

Defined in Capnp.Basics

Methods

toPtr :: WriteCtx m s => MutMsg s -> Text (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

FromPtr msg (Text msg) Source # 
Instance details

Defined in Capnp.Basics

Methods

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

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

Defined in Capnp.Basics

Methods

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

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

ListElem msg (Text msg) Source # 
Instance details

Defined in Capnp.Basics

Associated Types

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

Methods

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

toUntypedList :: List msg (Text msg) -> List msg Source #

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

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

newtype List msg (Text msg) Source # 
Instance details

Defined in Capnp.Basics

newtype List msg (Text msg) = TextList (ListOf msg (Maybe (Ptr msg)))

newtype 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.

Constructors

Data (ListOf msg Word8) 
Instances
ToPtr s (Data (MutMsg s)) Source # 
Instance details

Defined in Capnp.Basics

Methods

toPtr :: WriteCtx m s => MutMsg s -> Data (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

FromPtr msg (Data msg) Source # 
Instance details

Defined in Capnp.Basics

Methods

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

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

Defined in Capnp.Basics

Methods

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

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

ListElem msg (Data msg) Source # 
Instance details

Defined in Capnp.Basics

Associated Types

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

Methods

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

toUntypedList :: List msg (Data msg) -> List msg Source #

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

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

newtype List msg (Data msg) Source # 
Instance details

Defined in Capnp.Basics

newtype List msg (Data msg) = DataList (ListOf msg (Maybe (Ptr msg)))

class ListElem msg e where Source #

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

Associated Types

data List msg e Source #

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg e) Source #

Convert an untyped list to a list of this type. May fail with a SchemaViolationError if the list does not have the correct representation.

TODO: this is basically just fromPtr; refactor so this is less redundant.

toUntypedList :: List msg e -> List msg Source #

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 :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg Bool) Source #

toUntypedList :: List msg Bool -> List msg Source #

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 :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg Double) Source #

toUntypedList :: List msg Double -> List msg Source #

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 :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg Float) Source #

toUntypedList :: List msg Float -> List msg Source #

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 :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg Word64) Source #

toUntypedList :: List msg Word64 -> List msg Source #

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 :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg Word32) Source #

toUntypedList :: List msg Word32 -> List msg Source #

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 :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg Word16) Source #

toUntypedList :: List msg Word16 -> List msg Source #

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 :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg Word8) Source #

toUntypedList :: List msg Word8 -> List msg Source #

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 :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg Int64) Source #

toUntypedList :: List msg Int64 -> List msg Source #

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 :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg Int32) Source #

toUntypedList :: List msg Int32 -> List msg Source #

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 :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg Int16) Source #

toUntypedList :: List msg Int16 -> List msg Source #

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 :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg Int8) Source #

toUntypedList :: List msg Int8 -> List msg Source #

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.Gen.Capnp.Schema

Associated Types

data List msg ElementSize :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg ElementSize) Source #

toUntypedList :: List msg ElementSize -> List msg Source #

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.Gen.Capnp.RpcTwoparty

Associated Types

data List msg Side :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg Side) Source #

toUntypedList :: List msg Side -> List msg Source #

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.Gen.Capnp.Rpc

Associated Types

data List msg Exception'Type :: Type Source #

ListElem msg (Text msg) Source # 
Instance details

Defined in Capnp.Basics

Associated Types

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

Methods

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

toUntypedList :: List msg (Text msg) -> List msg Source #

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

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

ListElem msg (Data msg) Source # 
Instance details

Defined in Capnp.Basics

Associated Types

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

Methods

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

toUntypedList :: List msg (Data msg) -> List msg Source #

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

ListElem msg (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (CodeGeneratorRequest msg)) Source #

toUntypedList :: List msg (CodeGeneratorRequest msg) -> List msg Source #

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.Gen.Capnp.Schema

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (CapnpVersion msg)) Source #

toUntypedList :: List msg (CapnpVersion msg) -> List msg Source #

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

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

ListElem msg (Annotation msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Annotation msg)) Source #

toUntypedList :: List msg (Annotation msg) -> List msg Source #

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

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

ListElem msg (Value msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Value msg)) Source #

toUntypedList :: List msg (Value msg) -> List msg Source #

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Brand'Binding msg)) Source #

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

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 (Brand'Scope msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Brand'Scope msg)) Source #

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

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 msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Brand msg)) Source #

toUntypedList :: List msg (Brand msg) -> List msg Source #

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

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

ListElem msg (Type msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Type msg)) Source #

toUntypedList :: List msg (Type msg) -> List msg Source #

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

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

ListElem msg (Method msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Method msg)) Source #

toUntypedList :: List msg (Method msg) -> List msg Source #

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

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

ListElem msg (Superclass msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Superclass msg)) Source #

toUntypedList :: List msg (Superclass msg) -> List msg Source #

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

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

ListElem msg (Enumerant msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Enumerant msg)) Source #

toUntypedList :: List msg (Enumerant msg) -> List msg Source #

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

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

ListElem msg (Field msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Field msg)) Source #

toUntypedList :: List msg (Field msg) -> List msg Source #

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

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

ListElem msg (Node'SourceInfo'Member msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List msg (Node'SourceInfo'Member msg) :: Type Source #

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List msg (Node'SourceInfo msg) :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Node'SourceInfo msg)) Source #

toUntypedList :: List msg (Node'SourceInfo msg) -> List msg Source #

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Node'NestedNode msg)) Source #

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

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'Parameter msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Node'Parameter msg)) Source #

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

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 msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Node msg)) Source #

toUntypedList :: List msg (Node msg) -> List msg Source #

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

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

ListElem msg (JoinResult msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (JoinResult msg)) Source #

toUntypedList :: List msg (JoinResult msg) -> List msg Source #

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.Gen.Capnp.RpcTwoparty

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (JoinKeyPart msg)) Source #

toUntypedList :: List msg (JoinKeyPart msg) -> List msg Source #

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

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

ListElem msg (ThirdPartyCapId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (ThirdPartyCapId msg)) Source #

toUntypedList :: List msg (ThirdPartyCapId msg) -> List msg Source #

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

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

ListElem msg (RecipientId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (RecipientId msg)) Source #

toUntypedList :: List msg (RecipientId msg) -> List msg Source #

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

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

ListElem msg (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (ProvisionId msg)) Source #

toUntypedList :: List msg (ProvisionId msg) -> List msg Source #

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

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

ListElem msg (VatId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (VatId msg)) Source #

toUntypedList :: List msg (VatId msg) -> List msg Source #

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

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

ListElem msg (Exception msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Exception msg)) Source #

toUntypedList :: List msg (Exception msg) -> List msg Source #

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

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

ListElem msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

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

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (PromisedAnswer'Op msg)) Source #

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

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 (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (PromisedAnswer msg)) Source #

toUntypedList :: List msg (PromisedAnswer msg) -> List msg Source #

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

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

ListElem msg (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (CapDescriptor msg)) Source #

toUntypedList :: List msg (CapDescriptor msg) -> List msg Source #

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

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

ListElem msg (Payload msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Payload msg)) Source #

toUntypedList :: List msg (Payload msg) -> List msg Source #

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.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (MessageTarget msg)) Source #

toUntypedList :: List msg (MessageTarget msg) -> List msg Source #

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

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

ListElem msg (Join msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Join msg)) Source #

toUntypedList :: List msg (Join msg) -> List msg Source #

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

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

ListElem msg (Accept msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Accept msg)) Source #

toUntypedList :: List msg (Accept msg) -> List msg Source #

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

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

ListElem msg (Provide msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Provide msg)) Source #

toUntypedList :: List msg (Provide msg) -> List msg Source #

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

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

ListElem msg (Disembargo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Disembargo msg)) Source #

toUntypedList :: List msg (Disembargo msg) -> List msg Source #

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

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

ListElem msg (Release msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Release msg)) Source #

toUntypedList :: List msg (Release msg) -> List msg Source #

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

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

ListElem msg (Resolve msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Resolve msg)) Source #

toUntypedList :: List msg (Resolve msg) -> List msg Source #

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

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

ListElem msg (Finish msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Finish msg)) Source #

toUntypedList :: List msg (Finish msg) -> List msg Source #

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

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

ListElem msg (Return msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Return msg)) Source #

toUntypedList :: List msg (Return msg) -> List msg Source #

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

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

ListElem msg (Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Call msg)) Source #

toUntypedList :: List msg (Call msg) -> List msg Source #

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.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Bootstrap msg)) Source #

toUntypedList :: List msg (Bootstrap msg) -> List msg Source #

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

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

ListElem msg (Message msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Message msg)) Source #

toUntypedList :: List msg (Message msg) -> List msg Source #

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

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

ListElem msg (RealmGateway'export'params msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Associated Types

data List msg (RealmGateway'export'params msg) :: Type Source #

ListElem msg (RealmGateway'import'params msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Associated Types

data List msg (RealmGateway'import'params msg) :: Type Source #

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

Defined in Capnp.Gen.Capnp.Persistent

Associated Types

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

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

Defined in Capnp.Gen.Capnp.Persistent

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Persistent'SaveParams msg)) Source #

toUntypedList :: List msg (Persistent'SaveParams msg) -> List msg Source #

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

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

ListElem msg (DiscriminatorOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (DiscriminatorOptions msg)) Source #

toUntypedList :: List msg (DiscriminatorOptions msg) -> List msg Source #

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

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

ListElem msg (FlattenOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (FlattenOptions msg)) Source #

toUntypedList :: List msg (FlattenOptions msg) -> List msg Source #

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

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

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

Defined in Capnp.Gen.Capnp.Json

Associated Types

data List msg (Value'Call msg) :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Value'Call msg)) Source #

toUntypedList :: List msg (Value'Call msg) -> List msg Source #

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

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

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

Defined in Capnp.Gen.Capnp.Json

Associated Types

data List msg (Value'Field msg) :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Value'Field msg)) Source #

toUntypedList :: List msg (Value'Field msg) -> List msg Source #

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

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

ListElem msg (Value msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Value msg)) Source #

toUntypedList :: List msg (Value msg) -> List msg Source #

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

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

ListElem msg e => ListElem msg (List msg e) Source # 
Instance details

Defined in Capnp.Classes

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (List msg e)) Source #

toUntypedList :: List msg (List msg e) -> List0 msg Source #

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

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

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

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

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.Gen.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.Gen.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.Gen.Capnp.Rpc

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

Defined in Capnp.Basics

Methods

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

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

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

Defined in Capnp.Basics

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.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 (Annotation (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Value (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Brand'Binding (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Brand'Scope (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Type (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Method (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Superclass (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Enumerant (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Field (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Node'SourceInfo'Member (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Gen.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'Parameter (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (JoinResult (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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.Gen.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 (ThirdPartyCapId (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

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

Defined in Capnp.Gen.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 (VatId (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Exception (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (ThirdPartyCapDescriptor (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

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

Defined in Capnp.Gen.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 (PromisedAnswer (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (CapDescriptor (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Payload (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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.Gen.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 (Join (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Accept (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Provide (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Disembargo (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Release (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Resolve (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Finish (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Return (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (Call (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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.Gen.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 (Message (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.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 (RealmGateway'export'params (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

MutListElem s (RealmGateway'import'params (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

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

Defined in Capnp.Gen.Capnp.Persistent

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

Defined in Capnp.Gen.Capnp.Persistent

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

Defined in Capnp.Gen.Capnp.Json

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

Defined in Capnp.Gen.Capnp.Json

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Json

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Json

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Json

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 e => MutListElem s (List (MutMsg s) e) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

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

getData :: ReadCtx m msg => ListOf msg Word8 -> m (Data msg) Source #

Interpret a list of Word8 as a capnproto Data value.

getText :: ReadCtx m msg => ListOf msg Word8 -> m (Text msg) Source #

Interpret a list of Word8 as a capnproto Text value.

This vaildates that the list is NUL-terminated, but not that it is valid UTF-8. If it is not NUL-terminaed, a SchemaViolationError is thrown.

newData :: WriteCtx m s => MutMsg s -> Int -> m (Data (MutMsg s)) Source #

newData msg len allocates a new data blob of length len bytes inside the message.

newText :: WriteCtx m s => MutMsg s -> Int -> m (Text (MutMsg s)) Source #

newText msg len Allocates a new Text inside the message. The value has space for len *bytes* (not characters).

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

Convert a Data to a ByteString.

textBuffer :: ReadCtx m msg => Text msg -> m (ListOf msg Word8) Source #

Return the underlying buffer containing the text. This does not include the null terminator.

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).