capnp-0.1.0.0: Cap'n Proto for Haskell

Safe HaskellNone
LanguageHaskell2010

Data.Capnp.Message

Description

 
Synopsis

Documentation

class Monad m => Message m msg where Source #

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

Associated Types

data Segment msg Source #

The type of segments in the message.

Methods

numSegs :: msg -> m Int Source #

numSegs gets the number of segments in a message.

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

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

numWords :: Segment msg -> m Int Source #

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

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

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

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

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

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

Convert a ByteString to a segment.

toByteString :: Segment msg -> m ByteString Source #

Convert a segment to a byte string.

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

Constructors

ConstMsg (Vector (Segment ConstMsg)) 
Instances
MonadThrow m => Message m ConstMsg Source # 
Instance details

Defined in Data.Capnp.Message

Associated Types

data Segment ConstMsg :: * Source #

FromStruct ConstMsg Type'anyPointer'unconstrained Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Type'anyPointer Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Node'Parameter Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Node'NestedNode Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Node' Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Field'ordinal Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Field' Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg CodeGeneratorRequest'RequestedFile'Import Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg CodeGeneratorRequest'RequestedFile Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Brand'Scope' Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Brand'Scope Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Brand'Binding Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Value Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Type Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Superclass Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Node Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Method Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Field Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Enumerant Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg CodeGeneratorRequest Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg CapnpVersion Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Brand Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg Annotation Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

FromStruct ConstMsg VatId Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

FromStruct ConstMsg ProvisionId Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

FromStruct ConstMsg JoinResult Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

FromStruct ConstMsg JoinKeyPart Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

FromStruct ConstMsg Return' Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Resolve' Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg PromisedAnswer'Op Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Disembargo'context Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Call'sendResultsTo Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg ThirdPartyCapDescriptor Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Return Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Resolve Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Release Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Provide Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg PromisedAnswer Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Payload Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg MessageTarget Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Message Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Join Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Finish Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Exception Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Disembargo Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg CapDescriptor Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Call Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Bootstrap Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Accept Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

FromStruct ConstMsg Persistent'SaveResults Source # 
Instance details

Defined in Capnp.Capnp.Persistent.Pure

FromStruct ConstMsg Persistent'SaveParams Source # 
Instance details

Defined in Capnp.Capnp.Persistent.Pure

FromStruct ConstMsg JsonValue'Field Source # 
Instance details

Defined in Capnp.Capnp.Json.Pure

FromStruct ConstMsg JsonValue'Call Source # 
Instance details

Defined in Capnp.Capnp.Json.Pure

FromStruct ConstMsg JsonValue Source # 
Instance details

Defined in Capnp.Capnp.Json.Pure

data Segment ConstMsg Source # 
Instance details

Defined in Data.Capnp.Message

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.

Constructors

MutMsg 

Fields

  • mutMsgSegs :: MutVar s (MVector s (Segment (MutMsg s)))

    A vector of segments. A suffix of this may be unused; see below.

  • mutMsgLen :: MutVar s Int

    The "true" number of segments in the message. This may be shorter than length mutMsgSegs; the remainder is considered unallocated space, and is used for amortized O(1) appending.

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

Defined in Data.Capnp.Message

Associated Types

data Segment (MutMsg s) :: * Source #

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Persistent

Methods

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

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

Defined in Capnp.Capnp.Persistent

Methods

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

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

Defined in Capnp.Capnp.Json

Methods

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

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

Defined in Capnp.Capnp.Json

Methods

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

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

Defined in Capnp.Capnp.Json

Methods

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

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

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

Defined in Capnp.Capnp.Rpc

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

Defined in Capnp.Capnp.Rpc

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Persistent

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

Defined in Capnp.Capnp.Persistent

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

Defined in Capnp.Capnp.Json

Methods

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

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

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

Defined in Capnp.Capnp.Json

Methods

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

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

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

Defined in Capnp.Capnp.Json

Methods

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

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

Mutable (MutMsg s) Source # 
Instance details

Defined in Data.Capnp.Message

Associated Types

type Scope (MutMsg s) :: * Source #

type Frozen (MutMsg s) :: * Source #

Methods

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

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

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

Defined in Data.Capnp.Message

Associated Types

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

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

Methods

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

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

type Scope (MutMsg s) Source # 
Instance details

Defined in Data.Capnp.Message

type Scope (MutMsg s) = s
type Scope (Segment (MutMsg s)) Source # 
Instance details

Defined in Data.Capnp.Message

type Scope (Segment (MutMsg s)) = s
type Frozen (MutMsg s) Source # 
Instance details

Defined in Data.Capnp.Message

type Frozen (Segment (MutMsg s)) Source # 
Instance details

Defined in Data.Capnp.Message

data Segment (MutMsg s) Source # 
Instance details

Defined in Data.Capnp.Message

data Segment (MutMsg s) = MutSegment {}

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

WriteCtx is the context needed for most write operations.

class Mutable a where Source #

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

Minimal complete definition

thaw, freeze

Associated Types

type Scope a Source #

The state token for a mutable value.

type Frozen a Source #

The immutable version of a.

Methods

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

Convert an immutable value to a mutable one.

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

Convert a mutable value to an immutable one.

Instances
Mutable (MutMsg s) Source # 
Instance details

Defined in Data.Capnp.Message

Associated Types

type Scope (MutMsg s) :: * Source #

type Frozen (MutMsg s) :: * Source #

Methods

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

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

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

Defined in Data.Capnp.Message

Associated Types

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

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

Methods

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

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

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

Defined in Data.Capnp.Untyped

Associated Types

type Scope (Struct msg) :: * Source #

type Frozen (Struct msg) :: * Source #

Methods

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

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

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

Defined in Data.Capnp.Untyped

Associated Types

type Scope (List msg) :: * Source #

type Frozen (List msg) :: * Source #

Methods

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

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

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

Defined in Data.Capnp.Untyped

Associated Types

type Scope (Ptr msg) :: * Source #

type Frozen (Ptr msg) :: * Source #

Methods

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

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

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

Defined in Data.Capnp.Untyped

Associated Types

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

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

Methods

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

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

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

Defined in Data.Capnp.Untyped

Associated Types

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

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

Methods

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

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

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

Defined in Data.Capnp.Untyped

Associated Types

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

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

Methods

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

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

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

Defined in Data.Capnp.Untyped

Associated Types

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

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

Methods

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

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

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

Defined in Data.Capnp.Untyped

Associated Types

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

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

Methods

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

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

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

Defined in Data.Capnp.Untyped

Associated Types

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

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

Methods

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

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

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

Defined in Data.Capnp.Untyped

Associated Types

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

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

Methods

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

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

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

Defined in Data.Capnp.Untyped

Associated Types

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

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

Methods

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

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

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.

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.

encode :: MonadThrow 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).

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.

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

Allocate a new empty message.

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

empty :: ConstMsg Source #

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

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.

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

hPutMsg handle msg writes msg to handle.

hGetMsg :: Handle -> Int -> 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

getMsg :: Int -> IO ConstMsg Source #

Equivalent to hGetMsg stdin