capnp-0.10.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 mut 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

Instances details
ToPtr s (Text ('Mut s)) Source # 
Instance details

Defined in Capnp.Basics

Methods

toPtr :: WriteCtx m s => Message ('Mut s) -> Text ('Mut s) -> m (Maybe (Ptr ('Mut s))) Source #

FromPtr mut (Text mut) Source # 
Instance details

Defined in Capnp.Basics

Methods

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

MutListElem s (Text ('Mut s)) Source # 
Instance details

Defined in Capnp.Basics

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Text ('Mut s))) Source #

ListElem mut (Text mut) Source # 
Instance details

Defined in Capnp.Basics

Associated Types

data List mut (Text mut) Source #

Methods

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

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

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

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

Thaw (Text 'Const) Source # 
Instance details

Defined in Capnp.Basics

Associated Types

type Mutable s (Text 'Const) Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => Text 'Const -> m (Mutable s (Text 'Const)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Text 'Const) -> m (Text 'Const) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Text 'Const -> m (Mutable s (Text 'Const)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Text 'Const) -> m (Text 'Const) Source #

type Mutable s (Text 'Const) Source # 
Instance details

Defined in Capnp.Basics

type Mutable s (Text 'Const) = Text ('Mut s)
newtype List mut (Text mut) Source # 
Instance details

Defined in Capnp.Basics

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

newtype Data mut 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 mut Word8) 

Instances

Instances details
ToPtr s (Data ('Mut s)) Source # 
Instance details

Defined in Capnp.Basics

Methods

toPtr :: WriteCtx m s => Message ('Mut s) -> Data ('Mut s) -> m (Maybe (Ptr ('Mut s))) Source #

FromPtr mut (Data mut) Source # 
Instance details

Defined in Capnp.Basics

Methods

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

MutListElem s (Data ('Mut s)) Source # 
Instance details

Defined in Capnp.Basics

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Data ('Mut s))) Source #

ListElem mut (Data mut) Source # 
Instance details

Defined in Capnp.Basics

Associated Types

data List mut (Data mut) Source #

Methods

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

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

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

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

Thaw (Data 'Const) Source # 
Instance details

Defined in Capnp.Basics

Associated Types

type Mutable s (Data 'Const) Source #

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => Data 'Const -> m (Mutable s (Data 'Const)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Data 'Const) -> m (Data 'Const) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Data 'Const -> m (Mutable s (Data 'Const)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Data 'Const) -> m (Data 'Const) Source #

type Mutable s (Data 'Const) Source # 
Instance details

Defined in Capnp.Basics

type Mutable s (Data 'Const) = Data ('Mut s)
newtype List mut (Data mut) Source # 
Instance details

Defined in Capnp.Basics

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

class ListElem mut e where Source #

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

Associated Types

data List mut e Source #

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

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut 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 mut e -> List mut Source #

length :: List mut e -> Int Source #

Get the length of a list.

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

index i list gets the ith element of a list.

Instances

Instances details
ListElem msg Bool Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Bool Source #

Methods

listFromPtr :: ReadCtx m msg => Message 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 Source #

Methods

listFromPtr :: ReadCtx m msg => Message 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 Source #

Methods

listFromPtr :: ReadCtx m msg => Message 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 Source #

Methods

listFromPtr :: ReadCtx m msg => Message 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 Source #

Methods

listFromPtr :: ReadCtx m msg => Message 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 Source #

Methods

listFromPtr :: ReadCtx m msg => Message 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 Source #

Methods

listFromPtr :: ReadCtx m msg => Message 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 Source #

Methods

listFromPtr :: ReadCtx m msg => Message 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 Source #

Methods

listFromPtr :: ReadCtx m msg => Message 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 Source #

Methods

listFromPtr :: ReadCtx m msg => Message 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 Source #

Methods

listFromPtr :: ReadCtx m msg => Message 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 mut ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut ElementSize Source #

Methods

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

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

length :: List mut ElementSize -> Int Source #

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

ListElem mut Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

data List mut Side Source #

Methods

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

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

length :: List mut Side -> Int Source #

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

ListElem mut Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut Exception'Type Source #

ListElem mut (Text mut) Source # 
Instance details

Defined in Capnp.Basics

Associated Types

data List mut (Text mut) Source #

Methods

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

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

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

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

ListElem mut (Data mut) Source # 
Instance details

Defined in Capnp.Basics

Associated Types

data List mut (Data mut) Source #

Methods

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

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

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

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

ListElem mut (StreamResult mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Stream

Associated Types

data List mut (StreamResult mut) Source #

Methods

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

toUntypedList :: List mut (StreamResult mut) -> List mut Source #

length :: List mut (StreamResult mut) -> Int Source #

index :: ReadCtx m mut => Int -> List mut (StreamResult mut) -> m (StreamResult mut) Source #

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (CodeGeneratorRequest'RequestedFile mut) Source #

ListElem mut (CodeGeneratorRequest mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (CodeGeneratorRequest mut) Source #

Methods

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

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

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

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

ListElem mut (CapnpVersion mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (CapnpVersion mut) Source #

Methods

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

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

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

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

ListElem mut (Annotation mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Annotation mut) Source #

Methods

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

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

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

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

ListElem mut (Value mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Value mut) Source #

Methods

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

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

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Brand'Binding mut) Source #

Methods

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

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

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Brand'Scope mut) Source #

Methods

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

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

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

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

ListElem mut (Brand mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Brand mut) Source #

Methods

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

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

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

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

ListElem mut (Type mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Type mut) Source #

Methods

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

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

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

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

ListElem mut (Method mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Method mut) Source #

Methods

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

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

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

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

ListElem mut (Superclass mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Superclass mut) Source #

Methods

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

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

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

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

ListElem mut (Enumerant mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Enumerant mut) Source #

Methods

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

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

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

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

ListElem mut (Field mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Field mut) Source #

Methods

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

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

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Node'SourceInfo'Member mut) Source #

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Node'SourceInfo mut) Source #

Methods

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

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

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Node'NestedNode mut) Source #

Methods

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

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

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Node'Parameter mut) Source #

Methods

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

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

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

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

ListElem mut (Node mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Node mut) Source #

Methods

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

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

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

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

ListElem mut (JoinResult mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

data List mut (JoinResult mut) Source #

Methods

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

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

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

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

ListElem mut (JoinKeyPart mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

data List mut (JoinKeyPart mut) Source #

Methods

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

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

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

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

ListElem mut (ThirdPartyCapId mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

data List mut (ThirdPartyCapId mut) Source #

Methods

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

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

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

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

ListElem mut (RecipientId mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

data List mut (RecipientId mut) Source #

Methods

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

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

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

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

ListElem mut (ProvisionId mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

data List mut (ProvisionId mut) Source #

Methods

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

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

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

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

ListElem mut (VatId mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

data List mut (VatId mut) Source #

Methods

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

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

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

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

ListElem mut (Exception mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Exception mut) Source #

Methods

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

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

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

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

ListElem mut (ThirdPartyCapDescriptor mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (ThirdPartyCapDescriptor mut) Source #

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

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (PromisedAnswer'Op mut) Source #

Methods

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

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

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

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

ListElem mut (PromisedAnswer mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (PromisedAnswer mut) Source #

Methods

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

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

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

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

ListElem mut (CapDescriptor mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (CapDescriptor mut) Source #

Methods

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

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

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

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

ListElem mut (Payload mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Payload mut) Source #

Methods

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

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

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

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

ListElem mut (MessageTarget mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (MessageTarget mut) Source #

Methods

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

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

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

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

ListElem mut (Join mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Join mut) Source #

Methods

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

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

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

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

ListElem mut (Accept mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Accept mut) Source #

Methods

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

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

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

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

ListElem mut (Provide mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Provide mut) Source #

Methods

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

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

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

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

ListElem mut (Disembargo mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Disembargo mut) Source #

Methods

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

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

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

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

ListElem mut (Release mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Release mut) Source #

Methods

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

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

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

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

ListElem mut (Resolve mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Resolve mut) Source #

Methods

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

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

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

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

ListElem mut (Finish mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Finish mut) Source #

Methods

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

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

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

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

ListElem mut (Return mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Return mut) Source #

Methods

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

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

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

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

ListElem mut (Call mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Call mut) Source #

Methods

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

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

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

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

ListElem mut (Bootstrap mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Bootstrap mut) Source #

Methods

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

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

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

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

ListElem mut (Message mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Message mut) Source #

Methods

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

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

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

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

ListElem mut (DiscriminatorOptions mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Associated Types

data List mut (DiscriminatorOptions mut) Source #

Methods

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

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

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

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

ListElem mut (FlattenOptions mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Associated Types

data List mut (FlattenOptions mut) Source #

Methods

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

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

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

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

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

Defined in Capnp.Gen.Capnp.Compat.Json

Associated Types

data List mut (Value'Call mut) Source #

Methods

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

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

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

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

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

Defined in Capnp.Gen.Capnp.Compat.Json

Associated Types

data List mut (Value'Field mut) Source #

Methods

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

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

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

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

ListElem mut (Value mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Associated Types

data List mut (Value mut) Source #

Methods

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

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

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

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

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

Defined in Capnp.Classes

Associated Types

data List mut (List mut e) Source #

Methods

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

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

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

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

ListElem mut (Persistent'SaveResults sturdyRef owner mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Associated Types

data List mut (Persistent'SaveResults sturdyRef owner mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (Persistent'SaveResults sturdyRef owner mut)) Source #

toUntypedList :: List mut (Persistent'SaveResults sturdyRef owner mut) -> List mut Source #

length :: List mut (Persistent'SaveResults sturdyRef owner mut) -> Int Source #

index :: ReadCtx m mut => Int -> List mut (Persistent'SaveResults sturdyRef owner mut) -> m (Persistent'SaveResults sturdyRef owner mut) Source #

ListElem mut (Persistent'SaveParams sturdyRef owner mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Associated Types

data List mut (Persistent'SaveParams sturdyRef owner mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (Persistent'SaveParams sturdyRef owner mut)) Source #

toUntypedList :: List mut (Persistent'SaveParams sturdyRef owner mut) -> List mut Source #

length :: List mut (Persistent'SaveParams sturdyRef owner mut) -> Int Source #

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

ListElem mut (RealmGateway'export'params internalRef externalRef internalOwner externalOwner mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Associated Types

data List mut (RealmGateway'export'params internalRef externalRef internalOwner externalOwner mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (RealmGateway'export'params internalRef externalRef internalOwner externalOwner mut)) Source #

toUntypedList :: List mut (RealmGateway'export'params internalRef externalRef internalOwner externalOwner mut) -> List mut Source #

length :: List mut (RealmGateway'export'params internalRef externalRef internalOwner externalOwner mut) -> Int Source #

index :: ReadCtx m mut => Int -> List mut (RealmGateway'export'params internalRef externalRef internalOwner externalOwner mut) -> m (RealmGateway'export'params internalRef externalRef internalOwner externalOwner mut) Source #

ListElem mut (RealmGateway'import'params internalRef externalRef internalOwner externalOwner mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Associated Types

data List mut (RealmGateway'import'params internalRef externalRef internalOwner externalOwner mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (RealmGateway'import'params internalRef externalRef internalOwner externalOwner mut)) Source #

toUntypedList :: List mut (RealmGateway'import'params internalRef externalRef internalOwner externalOwner mut) -> List mut Source #

length :: List mut (RealmGateway'import'params internalRef externalRef internalOwner externalOwner mut) -> Int Source #

index :: ReadCtx m mut => Int -> List mut (RealmGateway'import'params internalRef externalRef internalOwner externalOwner mut) -> m (RealmGateway'import'params internalRef externalRef internalOwner externalOwner mut) Source #

class ListElem ('Mut 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 ('Mut s) e -> m () Source #

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) e) Source #

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

Instances

Instances details
MutListElem s Bool Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) Bool) Source #

MutListElem s Double Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) Double) Source #

MutListElem s Float Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) Float) Source #

MutListElem s Word64 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) Word64) Source #

MutListElem s Word32 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) Word32) Source #

MutListElem s Word16 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) Word16) Source #

MutListElem s Word8 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) Word8) Source #

MutListElem s Int64 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) Int64) Source #

MutListElem s Int32 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) Int32) Source #

MutListElem s Int16 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) Int16) Source #

MutListElem s Int8 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) Int8) Source #

MutListElem s ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) ElementSize) Source #

MutListElem s Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) Side) Source #

MutListElem s Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) Exception'Type) Source #

MutListElem s (Text ('Mut s)) Source # 
Instance details

Defined in Capnp.Basics

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Text ('Mut s))) Source #

MutListElem s (Data ('Mut s)) Source # 
Instance details

Defined in Capnp.Basics

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Data ('Mut s))) Source #

MutListElem s (StreamResult ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Stream

Methods

setIndex :: RWCtx m s => StreamResult ('Mut s) -> Int -> List ('Mut s) (StreamResult ('Mut s)) -> m () Source #

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (StreamResult ('Mut s))) Source #

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

MutListElem s (CodeGeneratorRequest ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

setIndex :: RWCtx m s => CodeGeneratorRequest ('Mut s) -> Int -> List ('Mut s) (CodeGeneratorRequest ('Mut s)) -> m () Source #

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (CodeGeneratorRequest ('Mut s))) Source #

MutListElem s (CapnpVersion ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (CapnpVersion ('Mut s))) Source #

MutListElem s (Annotation ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Annotation ('Mut s))) Source #

MutListElem s (Value ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

MutListElem s (Brand ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

MutListElem s (Type ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

MutListElem s (Method ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Method ('Mut s))) Source #

MutListElem s (Superclass ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Superclass ('Mut s))) Source #

MutListElem s (Enumerant ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Enumerant ('Mut s))) Source #

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

MutListElem s (Node'SourceInfo'Member ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

MutListElem s (JoinResult ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (JoinResult ('Mut s))) Source #

MutListElem s (JoinKeyPart ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (JoinKeyPart ('Mut s))) Source #

MutListElem s (ThirdPartyCapId ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (ThirdPartyCapId ('Mut s))) Source #

MutListElem s (RecipientId ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (RecipientId ('Mut s))) Source #

MutListElem s (ProvisionId ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (ProvisionId ('Mut s))) Source #

MutListElem s (VatId ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (VatId ('Mut s))) Source #

MutListElem s (Exception ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Exception ('Mut s))) Source #

MutListElem s (ThirdPartyCapDescriptor ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

setIndex :: RWCtx m s => ThirdPartyCapDescriptor ('Mut s) -> Int -> List ('Mut s) (ThirdPartyCapDescriptor ('Mut s)) -> m () Source #

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (ThirdPartyCapDescriptor ('Mut s))) Source #

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

MutListElem s (PromisedAnswer ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

MutListElem s (CapDescriptor ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (CapDescriptor ('Mut s))) Source #

MutListElem s (Payload ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Payload ('Mut s))) Source #

MutListElem s (MessageTarget ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (MessageTarget ('Mut s))) Source #

MutListElem s (Join ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Join ('Mut s))) Source #

MutListElem s (Accept ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Accept ('Mut s))) Source #

MutListElem s (Provide ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Provide ('Mut s))) Source #

MutListElem s (Disembargo ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Disembargo ('Mut s))) Source #

MutListElem s (Release ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Release ('Mut s))) Source #

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

MutListElem s (Finish ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Finish ('Mut s))) Source #

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

MutListElem s (Call ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

MutListElem s (Bootstrap ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Bootstrap ('Mut s))) Source #

MutListElem s (Message ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message0 ('Mut s) -> Int -> m (List ('Mut s) (Message ('Mut s))) Source #

MutListElem s (DiscriminatorOptions ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

setIndex :: RWCtx m s => DiscriminatorOptions ('Mut s) -> Int -> List ('Mut s) (DiscriminatorOptions ('Mut s)) -> m () Source #

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (DiscriminatorOptions ('Mut s))) Source #

MutListElem s (FlattenOptions ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (FlattenOptions ('Mut s))) Source #

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

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

MutListElem s (Value ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

MutListElem s e => MutListElem s (List ('Mut s) e) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (List ('Mut s) e)) Source #

MutListElem s (Persistent'SaveResults sturdyRef owner ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Methods

setIndex :: RWCtx m s => Persistent'SaveResults sturdyRef owner ('Mut s) -> Int -> List ('Mut s) (Persistent'SaveResults sturdyRef owner ('Mut s)) -> m () Source #

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Persistent'SaveResults sturdyRef owner ('Mut s))) Source #

MutListElem s (Persistent'SaveParams sturdyRef owner ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Methods

setIndex :: RWCtx m s => Persistent'SaveParams sturdyRef owner ('Mut s) -> Int -> List ('Mut s) (Persistent'SaveParams sturdyRef owner ('Mut s)) -> m () Source #

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Persistent'SaveParams sturdyRef owner ('Mut s))) Source #

MutListElem s (RealmGateway'export'params internalRef externalRef internalOwner externalOwner ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Methods

setIndex :: RWCtx m s => RealmGateway'export'params internalRef externalRef internalOwner externalOwner ('Mut s) -> Int -> List ('Mut s) (RealmGateway'export'params internalRef externalRef internalOwner externalOwner ('Mut s)) -> m () Source #

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (RealmGateway'export'params internalRef externalRef internalOwner externalOwner ('Mut s))) Source #

MutListElem s (RealmGateway'import'params internalRef externalRef internalOwner externalOwner ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Methods

setIndex :: RWCtx m s => RealmGateway'import'params internalRef externalRef internalOwner externalOwner ('Mut s) -> Int -> List ('Mut s) (RealmGateway'import'params internalRef externalRef internalOwner externalOwner ('Mut s)) -> m () Source #

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (RealmGateway'import'params internalRef externalRef internalOwner externalOwner ('Mut s))) Source #

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

Interpret a list of Word8 as a capnproto Data value.

getText :: ReadCtx m mut => ListOf mut Word8 -> m (Text mut) 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 => Message ('Mut s) -> Int -> m (Data ('Mut s)) Source #

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

newText :: WriteCtx m s => Message ('Mut s) -> Int -> m (Text ('Mut s)) Source #

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

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

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

textBytes :: ReadCtx m 'Const => Text 'Const -> m ByteString Source #

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