capnp-0.2.0.0: Cap'n Proto for Haskell

Safe HaskellNone
LanguageHaskell2010

Data.Capnp.Pure

Contents

Description

This module re-exports the most commonly used functionality from the high-level API. See also Data.Capnp, which does the same for the low-level API.

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

Synopsis

Reading and writing values

hPutValue :: (Cerialize RealWorld a, ToStruct (MutMsg RealWorld) (Cerial (MutMsg RealWorld) a)) => Handle -> a -> IO () Source #

hPutValue handle value writes value to handle, as the root object of a message. If it throws an exception, it will be an IOError raised by the underlying IO libraries.

hGetValue :: FromStruct ConstMsg a => Handle -> Int -> IO a Source #

hGetValue limit handle reads a message from handle, returning its root object. limit is used as both a cap on the size of a message which may be read and, for types in the high-level API, the traversal limit when decoding the message.

It may throw a Error if there is a problem decoding the message, or an IOError raised by the underlying IO libraries.

Working directly with messages

data ConstMsg Source #

A read-only capnproto message.

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

Instances
Thaw ConstMsg Source # 
Instance details

Defined in Data.Capnp.Message

Associated Types

type Mutable s ConstMsg :: * Source #

Monad 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

Thaw (Segment ConstMsg) Source # 
Instance details

Defined in Data.Capnp.Message

Associated Types

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

data Segment ConstMsg Source # 
Instance details

Defined in Data.Capnp.Message

type Mutable s ConstMsg Source # 
Instance details

Defined in Data.Capnp.Message

type Mutable s (Segment ConstMsg) Source # 
Instance details

Defined in Data.Capnp.Message

class Monad m => Message m msg where Source #

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

Associated Types

data Segment msg Source #

The type of segments in the message.

Methods

numSegs :: msg -> m Int Source #

numSegs gets the number of segments in a message.

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

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

numWords :: Segment msg -> m Int Source #

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

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

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

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

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

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

Convert a ByteString to a segment.

toByteString :: Segment msg -> m ByteString Source #

Convert a segment to a byte string.

Getting values in and out of messages

getRoot :: (FromStruct msg a, ReadCtx m msg) => msg -> m a Source #

getRoot returns the root object of a message.

class Decerialize a where Source #

Types which may be extracted from a message.

typically, instances of Decerialize will be the algebraic data types defined in generated code for the high-level API.

Minimal complete definition

decerialize

Associated Types

type Cerial msg a Source #

A variation on a which is encoded in the message.

For the case of instances in generated high-level API code, this will be the low-level API analouge of the type.

Methods

decerialize :: ReadCtx m ConstMsg => Cerial ConstMsg a -> m a Source #

Extract the value from the message.

Instances
Decerialize List Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Associated Types

type Cerial msg List :: * Source #

Decerialize Struct Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Associated Types

type Cerial msg Struct :: * Source #

Decerialize Text Source # 
Instance details

Defined in Data.Capnp.Basics.Pure

Associated Types

type Cerial msg Text :: * Source #

Decerialize Data Source # 
Instance details

Defined in Data.Capnp.Basics.Pure

Associated Types

type Cerial msg Data :: * Source #

Decerialize Type'anyPointer'unconstrained Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Type'anyPointer'unconstrained :: * Source #

Decerialize Type'anyPointer Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Type'anyPointer :: * Source #

Decerialize Node'Parameter Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Node'Parameter :: * Source #

Decerialize Node'NestedNode Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Node'NestedNode :: * Source #

Decerialize Node' Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Node' :: * Source #

Decerialize Field'ordinal Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Field'ordinal :: * Source #

Decerialize Field' Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Field' :: * Source #

Decerialize CodeGeneratorRequest'RequestedFile'Import Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Decerialize CodeGeneratorRequest'RequestedFile Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg CodeGeneratorRequest'RequestedFile :: * Source #

Decerialize Brand'Scope' Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Brand'Scope' :: * Source #

Decerialize Brand'Scope Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Brand'Scope :: * Source #

Decerialize Brand'Binding Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Brand'Binding :: * Source #

Decerialize Value Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Value :: * Source #

Decerialize Type Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Type :: * Source #

Decerialize Superclass Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Superclass :: * Source #

Decerialize Node Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Node :: * Source #

Decerialize Method Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Method :: * Source #

Decerialize Field Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Field :: * Source #

Decerialize Enumerant Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Enumerant :: * Source #

Decerialize CodeGeneratorRequest Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg CodeGeneratorRequest :: * Source #

Decerialize CapnpVersion Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg CapnpVersion :: * Source #

Decerialize Brand Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Brand :: * Source #

Decerialize Annotation Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Associated Types

type Cerial msg Annotation :: * Source #

Decerialize VatId Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

Associated Types

type Cerial msg VatId :: * Source #

Decerialize ProvisionId Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

Associated Types

type Cerial msg ProvisionId :: * Source #

Decerialize JoinResult Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

Associated Types

type Cerial msg JoinResult :: * Source #

Decerialize JoinKeyPart Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

Associated Types

type Cerial msg JoinKeyPart :: * Source #

Decerialize Return' Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Return' :: * Source #

Decerialize Resolve' Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Resolve' :: * Source #

Decerialize PromisedAnswer'Op Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg PromisedAnswer'Op :: * Source #

Decerialize Disembargo'context Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Disembargo'context :: * Source #

Decerialize Call'sendResultsTo Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Call'sendResultsTo :: * Source #

Decerialize ThirdPartyCapDescriptor Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg ThirdPartyCapDescriptor :: * Source #

Decerialize Return Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Return :: * Source #

Decerialize Resolve Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Resolve :: * Source #

Decerialize Release Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Release :: * Source #

Decerialize Provide Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Provide :: * Source #

Decerialize PromisedAnswer Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg PromisedAnswer :: * Source #

Decerialize Payload Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Payload :: * Source #

Decerialize MessageTarget Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg MessageTarget :: * Source #

Decerialize Message Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Message :: * Source #

Decerialize Join Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Join :: * Source #

Decerialize Finish Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Finish :: * Source #

Decerialize Exception Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Exception :: * Source #

Decerialize Disembargo Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Disembargo :: * Source #

Decerialize CapDescriptor Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg CapDescriptor :: * Source #

Decerialize Call Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Call :: * Source #

Decerialize Bootstrap Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Bootstrap :: * Source #

Decerialize Accept Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Associated Types

type Cerial msg Accept :: * Source #

Decerialize Persistent'SaveResults Source # 
Instance details

Defined in Capnp.Capnp.Persistent.Pure

Associated Types

type Cerial msg Persistent'SaveResults :: * Source #

Decerialize Persistent'SaveParams Source # 
Instance details

Defined in Capnp.Capnp.Persistent.Pure

Associated Types

type Cerial msg Persistent'SaveParams :: * Source #

Decerialize JsonValue'Field Source # 
Instance details

Defined in Capnp.Capnp.Json.Pure

Associated Types

type Cerial msg JsonValue'Field :: * Source #

Decerialize JsonValue'Call Source # 
Instance details

Defined in Capnp.Capnp.Json.Pure

Associated Types

type Cerial msg JsonValue'Call :: * Source #

Decerialize JsonValue Source # 
Instance details

Defined in Capnp.Capnp.Json.Pure

Associated Types

type Cerial msg JsonValue :: * Source #

Decerialize (Maybe PtrType) Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Associated Types

type Cerial msg (Maybe PtrType) :: * Source #

(ListElem ConstMsg (Cerial ConstMsg a), Decerialize a) => Decerialize (ListOf a) Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Associated Types

type Cerial msg (ListOf a) :: * Source #

class Decerialize a => Cerialize s a where Source #

Types which may be inserted into a message.

Methods

cerialize :: RWCtx m s => MutMsg s -> a -> m (Cerial (MutMsg s) a) Source #

Cerialize a value into the supplied message, returning the result.

cerialize :: (RWCtx m s, Marshal a, Allocate s (Cerial (MutMsg s) a)) => MutMsg s -> a -> m (Cerial (MutMsg s) a) Source #

Cerialize a value into the supplied message, returning the result.

Instances
Cerialize s List Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> List -> m (Cerial (MutMsg s) List) Source #

Cerialize s Struct Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Struct -> m (Cerial (MutMsg s) Struct) Source #

Cerialize s Text Source # 
Instance details

Defined in Data.Capnp.Basics.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Text -> m (Cerial (MutMsg s) Text) Source #

Cerialize s Type'anyPointer'unconstrained Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Cerialize s Type'anyPointer Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Cerialize s Node'Parameter Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Cerialize s Node'NestedNode Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Cerialize s Node' Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Node' -> m (Cerial (MutMsg s) Node') Source #

Cerialize s Field'ordinal Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Cerialize s Field' Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Field' -> m (Cerial (MutMsg s) Field') Source #

Cerialize s CodeGeneratorRequest'RequestedFile'Import Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Cerialize s CodeGeneratorRequest'RequestedFile Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Cerialize s Brand'Scope' Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Cerialize s Brand'Scope Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Brand'Scope -> m (Cerial (MutMsg s) Brand'Scope) Source #

Cerialize s Brand'Binding Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Cerialize s Value Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Value -> m (Cerial (MutMsg s) Value) Source #

Cerialize s Type Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Type -> m (Cerial (MutMsg s) Type) Source #

Cerialize s Superclass Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Superclass -> m (Cerial (MutMsg s) Superclass) Source #

Cerialize s Node Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Node -> m (Cerial (MutMsg s) Node) Source #

Cerialize s Method Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Method -> m (Cerial (MutMsg s) Method) Source #

Cerialize s Field Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Field -> m (Cerial (MutMsg s) Field) Source #

Cerialize s Enumerant Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Enumerant -> m (Cerial (MutMsg s) Enumerant) Source #

Cerialize s CodeGeneratorRequest Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Cerialize s CapnpVersion Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Cerialize s Brand Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Brand -> m (Cerial (MutMsg s) Brand) Source #

Cerialize s Annotation Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Annotation -> m (Cerial (MutMsg s) Annotation) Source #

Cerialize s VatId Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> VatId -> m (Cerial (MutMsg s) VatId) Source #

Cerialize s ProvisionId Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> ProvisionId -> m (Cerial (MutMsg s) ProvisionId) Source #

Cerialize s JoinResult Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> JoinResult -> m (Cerial (MutMsg s) JoinResult) Source #

Cerialize s JoinKeyPart Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> JoinKeyPart -> m (Cerial (MutMsg s) JoinKeyPart) Source #

Cerialize s Return' Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Return' -> m (Cerial (MutMsg s) Return') Source #

Cerialize s Resolve' Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Resolve' -> m (Cerial (MutMsg s) Resolve') Source #

Cerialize s PromisedAnswer'Op Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Cerialize s Disembargo'context Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Cerialize s Call'sendResultsTo Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Cerialize s ThirdPartyCapDescriptor Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Cerialize s Return Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Return -> m (Cerial (MutMsg s) Return) Source #

Cerialize s Resolve Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Resolve -> m (Cerial (MutMsg s) Resolve) Source #

Cerialize s Release Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Release -> m (Cerial (MutMsg s) Release) Source #

Cerialize s Provide Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Provide -> m (Cerial (MutMsg s) Provide) Source #

Cerialize s PromisedAnswer Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Cerialize s Payload Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Payload -> m (Cerial (MutMsg s) Payload) Source #

Cerialize s MessageTarget Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Cerialize s Message Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Message -> m (Cerial (MutMsg s) Message) Source #

Cerialize s Join Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Join -> m (Cerial (MutMsg s) Join) Source #

Cerialize s Finish Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Finish -> m (Cerial (MutMsg s) Finish) Source #

Cerialize s Exception Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Exception -> m (Cerial (MutMsg s) Exception) Source #

Cerialize s Disembargo Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Disembargo -> m (Cerial (MutMsg s) Disembargo) Source #

Cerialize s CapDescriptor Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Cerialize s Call Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Call -> m (Cerial (MutMsg s) Call) Source #

Cerialize s Bootstrap Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Bootstrap -> m (Cerial (MutMsg s) Bootstrap) Source #

Cerialize s Accept Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Accept -> m (Cerial (MutMsg s) Accept) Source #

Cerialize s Persistent'SaveResults Source # 
Instance details

Defined in Capnp.Capnp.Persistent.Pure

Cerialize s Persistent'SaveParams Source # 
Instance details

Defined in Capnp.Capnp.Persistent.Pure

Cerialize s JsonValue'Field Source # 
Instance details

Defined in Capnp.Capnp.Json.Pure

Cerialize s JsonValue'Call Source # 
Instance details

Defined in Capnp.Capnp.Json.Pure

Cerialize s JsonValue Source # 
Instance details

Defined in Capnp.Capnp.Json.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> JsonValue -> m (Cerial (MutMsg s) JsonValue) Source #

Cerialize s (Maybe PtrType) Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Maybe PtrType -> m (Cerial (MutMsg s) (Maybe PtrType)) Source #

Managing resource limits

Aliases for built-in capnproto types.

type Text = Text Source #

A capnproto Text. This is just an alias for the text package's Text.

type Data = ByteString Source #

A capnproto Data value. This is just an alias for ByteString.

Re-exported from data-default

def :: Default a => a #

The default value for this type.