capnp-0.4.0.0: Cap'n Proto for Haskell

Safe HaskellNone
LanguageHaskell2010

Capnp.Message

Contents

Description

This module provides support for working directly with Cap'N Proto messages.

Synopsis

Reading and writing messages

hPutMsg :: Handle -> ConstMsg -> IO () Source #

hPutMsg handle msg writes msg to handle. If there is an exception, it will be an IOError raised by the underlying IO libraries.

hGetMsg :: Handle -> WordCount -> IO ConstMsg Source #

hGetMsg handle limit reads a message from handle that is at most limit 64-bit words in length.

putMsg :: ConstMsg -> IO () Source #

Equivalent to hPutMsg stdout

readMessage :: (MonadThrow m, MonadLimit m) => m Word32 -> (WordCount -> m (Segment ConstMsg)) -> m ConstMsg Source #

readMessage read32 readSegment reads in a message using the monadic context, which should manage the current read position, into a message. read32 should read a 32-bit little-endian integer, and readSegment n should read a blob of n 64-bit words. The size of the message (in 64-bit words) is deducted from the traversal, limit which can be used to set the maximum message size.

writeMessage :: MonadThrow m => ConstMsg -> (Word32 -> m ()) -> (Segment ConstMsg -> m ()) -> m () Source #

writeMesage write32 writeSegment writes out the message. write32 should write a 32-bit word in little-endian format to the output stream. writeSegment should write a blob.

Limits on message size

maxSegmentSize :: Int Source #

The maximum size of a segment supported by this libarary, in words.

maxSegments :: Int Source #

The maximum number of segments allowed in a message by this library.

maxCaps :: Int Source #

The maximum number of capabilities allowed in a message by this library.

Converting between messages and ByteStrings

encode :: Monad m => ConstMsg -> m Builder Source #

encode encodes a message as a bytestring builder.

decode :: MonadThrow m => ByteString -> m ConstMsg Source #

decode decodes a message from a bytestring.

The segments will not be copied; the resulting message will be a view into the original bytestring. Runs in O(number of segments in the message).

Message type class

class Monad m => Message m msg where Source #

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

Associated Types

data Segment msg Source #

The type of segments in the message.

Methods

numSegs :: msg -> m Int Source #

numSegs gets the number of segments in a message.

numWords :: Segment msg -> m WordCount Source #

numWords gets the number of words in a segment.

numCaps :: msg -> m Int Source #

numCaps gets the number of capabilities in a message's capability table.

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

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

internalGetCap :: msg -> Int -> m Client Source #

internalGetCap cap index reads a capability from the message's capability table, returning the client. does not check bounds. Callers should use getCap instead.

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

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

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

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

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

Convert a ByteString to a segment.

toByteString :: Segment msg -> m ByteString Source #

Convert a segment to a byte string.

Immutable messages

data ConstMsg Source #

A read-only capnproto message.

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

Instances
Eq ConstMsg Source # 
Instance details

Defined in Capnp.Message

Thaw ConstMsg Source # 
Instance details

Defined in Capnp.Message

Associated Types

type Mutable s ConstMsg :: Type Source #

Monad m => Message m ConstMsg Source # 
Instance details

Defined in Capnp.Message

Associated Types

data Segment ConstMsg :: Type Source #

FromStruct ConstMsg Struct Source # 
Instance details

Defined in Capnp.Untyped.Pure

FromStruct ConstMsg CodeGeneratorRequest'RequestedFile'Import Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg CodeGeneratorRequest'RequestedFile Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg CodeGeneratorRequest Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg CapnpVersion Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Annotation Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Brand'Binding Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Brand'Scope' Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Brand'Scope Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Brand Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Type'anyPointer'implicitMethodParameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Type'anyPointer'parameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Type'anyPointer'unconstrained Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Type'anyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Type'interface Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Type'struct Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Type'enum Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Type'list Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Method Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Superclass Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Enumerant Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Field'ordinal Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Field'group Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Field'slot Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Field' Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Field Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Node'SourceInfo'Member Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Node'SourceInfo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Node'NestedNode Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Node'Parameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Node'annotation Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Node'const Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Node'interface Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Node'enum Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Node'struct Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Node' Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg Node Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

FromStruct ConstMsg JoinResult Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.Pure

FromStruct ConstMsg JoinKeyPart Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.Pure

FromStruct ConstMsg ThirdPartyCapId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.Pure

FromStruct ConstMsg RecipientId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.Pure

FromStruct ConstMsg ProvisionId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.Pure

FromStruct ConstMsg VatId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.Pure

FromStruct ConstMsg Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg ThirdPartyCapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg PromisedAnswer'Op Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg PromisedAnswer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg CapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg Payload Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg MessageTarget Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg Join Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg Accept Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg Provide Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg Disembargo'context Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg Disembargo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg Release Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg Resolve' Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg Resolve Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg Finish Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg Return' Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg Return Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg Call'sendResultsTo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg Bootstrap Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg Message Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

FromStruct ConstMsg DiscriminatorOptions Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json.Pure

FromStruct ConstMsg FlattenOptions Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json.Pure

FromStruct ConstMsg Value'Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json.Pure

FromStruct ConstMsg Value'Field Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json.Pure

FromStruct ConstMsg Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Json.Pure

FromStruct ConstMsg RealmGateway'export'params Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.Pure

FromStruct ConstMsg RealmGateway'import'params Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.Pure

FromStruct ConstMsg Persistent'SaveResults Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.Pure

FromStruct ConstMsg Persistent'SaveParams Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.Pure

Eq (Segment ConstMsg) Source # 
Instance details

Defined in Capnp.Message

Thaw (Segment ConstMsg) Source # 
Instance details

Defined in Capnp.Message

Associated Types

type Mutable s (Segment ConstMsg) :: Type Source #

newtype Segment ConstMsg Source # 
Instance details

Defined in Capnp.Message

type Mutable s ConstMsg Source # 
Instance details

Defined in Capnp.Message

type Mutable s (Segment ConstMsg) Source # 
Instance details

Defined in Capnp.Message

empty :: ConstMsg Source #

empty is an empty message, i.e. a minimal message with a null pointer as its root object.

Reading data from messages

getSegment :: (MonadThrow m, Message m msg) => msg -> Int -> m (Segment msg) Source #

getSegment message index fetches the given segment in the message. It throws a BoundsError if the address is out of bounds.

getWord :: (MonadThrow m, Message m msg) => msg -> WordAddr -> m Word64 Source #

getWord msg addr returns the word at addr within msg. It throws a BoundsError if the address is out of bounds.

getCap :: (MonadThrow m, Message m msg) => msg -> Int -> m Client Source #

getCap message index gets the capability with the given index from the message. throws BoundsError if the index is out of bounds.

getCapTable :: ConstMsg -> Vector Client Source #

getCapTable gets the capability table from a ConstMsg.

Mutable Messages

data MutMsg s Source #

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

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

Instances
(PrimMonad m, s ~ PrimState m) => Message m (MutMsg s) Source # 
Instance details

Defined in Capnp.Message

Associated Types

data Segment (MutMsg s) :: Type Source #

ToPtr s (Maybe (Cap (MutMsg s))) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

ToPtr s (Struct (MutMsg s)) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

ToPtr s (Maybe (Ptr (MutMsg s))) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

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 #

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 #

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

toPtr :: WriteCtx m s => MutMsg s -> Brand'Binding (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

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

Defined in Capnp.Gen.Capnp.Schema

Methods

toPtr :: WriteCtx m s => MutMsg s -> Brand'Scope (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (Node'SourceInfo'Member (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

toPtr :: WriteCtx m s => MutMsg s -> Node'SourceInfo'Member (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

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

Defined in Capnp.Gen.Capnp.Schema

Methods

toPtr :: WriteCtx m s => MutMsg s -> Node'SourceInfo (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

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

Defined in Capnp.Gen.Capnp.Schema

Methods

toPtr :: WriteCtx m s => MutMsg s -> Node'NestedNode (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

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

Defined in Capnp.Gen.Capnp.Schema

Methods

toPtr :: WriteCtx m s => MutMsg s -> Node'Parameter (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

ToPtr s (ThirdPartyCapId (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

toPtr :: WriteCtx m s => MutMsg s -> PromisedAnswer'Op (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

ToPtr s (RealmGateway'export'params (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Methods

toPtr :: WriteCtx m s => MutMsg s -> RealmGateway'export'params (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

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

Defined in Capnp.Gen.Capnp.Persistent

Methods

toPtr :: WriteCtx m s => MutMsg s -> RealmGateway'import'params (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

ToPtr s (RealmGateway (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Methods

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

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

Defined in Capnp.Gen.Capnp.Persistent

Methods

toPtr :: WriteCtx m s => MutMsg s -> Persistent'SaveResults (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

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

Defined in Capnp.Gen.Capnp.Persistent

Methods

toPtr :: WriteCtx m s => MutMsg s -> Persistent'SaveParams (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

ToPtr s (Persistent (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

Methods

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

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

Defined in Capnp.Gen.Capnp.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Json

Methods

toPtr :: WriteCtx m s => MutMsg s -> Value'Call (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

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

Defined in Capnp.Gen.Capnp.Json

Methods

toPtr :: WriteCtx m s => MutMsg s -> Value'Field (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

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

Defined in Capnp.Gen.Capnp.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

Allocate s (RealmGateway'export'params (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

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

Defined in Capnp.Gen.Capnp.Persistent

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

Defined in Capnp.Gen.Capnp.Persistent

Methods

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

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

Defined in Capnp.Gen.Capnp.Persistent

Methods

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

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

Defined in Capnp.Gen.Capnp.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Json

Methods

new :: WriteCtx m s => MutMsg s -> m (Value (MutMsg s)) 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 #

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 #

ListElem (MutMsg s) e => ToPtr s (List (MutMsg s) e) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

ToPtr s (ListOf (MutMsg s) (Maybe (Ptr (MutMsg s)))) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

ToPtr s (ListOf (MutMsg s) (Struct (MutMsg s))) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

ToPtr s (ListOf (MutMsg s) Bool) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

ToPtr s (ListOf (MutMsg s) Word64) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

ToPtr s (ListOf (MutMsg s) Word32) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

ToPtr s (ListOf (MutMsg s) Word16) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

ToPtr s (ListOf (MutMsg s) Word8) Source # 
Instance details

Defined in Capnp.Classes

Methods

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

ToPtr s (ListOf (MutMsg s) ()) Source # 
Instance details

Defined in Capnp.Classes

Methods

toPtr :: WriteCtx m s => MutMsg s -> ListOf (MutMsg s) () -> m (Maybe (Ptr (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 #

Eq (MutMsg s) Source # 
Instance details

Defined in Capnp.Message

Methods

(==) :: MutMsg s -> MutMsg s -> Bool #

(/=) :: MutMsg s -> MutMsg s -> Bool #

newtype Segment (MutMsg s) Source # 
Instance details

Defined in Capnp.Message

newtype Segment (MutMsg s) = MutSegment (AppendVec MVector s Word64)

newMessage :: WriteCtx m s => Maybe WordCount -> m (MutMsg s) Source #

newMessage sizeHint allocates a new empty message, with a single segment having capacity sizeHint. If sizeHint is Nothing, defaults to a sensible value.

Allocating space in messages

alloc :: WriteCtx m s => MutMsg s -> WordCount -> m WordAddr Source #

alloc size allocates size words within a message. it returns the starting address of the allocated memory.

allocInSeg :: WriteCtx m s => MutMsg s -> Int -> WordCount -> m WordAddr Source #

Like alloc, but the second argument allows the caller to specify the index of the segment in which to allocate the data.

newSegment :: WriteCtx m s => MutMsg s -> Int -> m (Int, Segment (MutMsg s)) Source #

newSegment msg sizeHint allocates a new, initially empty segment in msg with a capacity of sizeHint. It returns the a pair of the segment number and the segment itself. Amortized O(1).

Modifying messages

setSegment :: (WriteCtx m s, MonadThrow m) => MutMsg s -> Int -> Segment (MutMsg s) -> m () Source #

setSegment message index segment sets the segment at the given index in the message. It throws a BoundsError if the address is out of bounds.

setWord :: (WriteCtx m s, MonadThrow m) => MutMsg s -> WordAddr -> Word64 -> m () Source #

setWord message address value sets the word at address in the message to value. If the address is not valid in the message, a BoundsError will be thrown.

setCap :: (WriteCtx m s, MonadThrow m) => MutMsg s -> Int -> Client -> m () Source #

setCap message index cap sets the sets the capability at index in the message's capability table to cap. If the index is out of bounds, a BoundsError will be thrown.

appendCap :: WriteCtx m s => MutMsg s -> Client -> m Int Source #

appendCap appends a new capabilty to the end of a message's capability table, returning its index.

type WriteCtx m s = (PrimMonad m, s ~ PrimState m, MonadThrow m) Source #

WriteCtx is the context needed for most write operations.

data Client Source #

Instances
Eq Client Source # 
Instance details

Defined in Capnp.Rpc.Untyped

Methods

(==) :: Client -> Client -> Bool #

(/=) :: Client -> Client -> Bool #

Show Client Source # 
Instance details

Defined in Capnp.Rpc.Untyped

withCapTable :: Vector Client -> ConstMsg -> ConstMsg Source #

withCapTable replaces the capability table in the message.