capnp-0.3.0.0: Cap'n Proto for Haskell

Safe HaskellNone
LanguageHaskell2010

Data.Capnp.Classes

Description

This module defines several type classes concerning encoding and decoding values in the capnproto wire format (as well as instances for some basic types).

Note that much of this is unlikely to be used directly by developers. Typically these are either used internally by generated code, or transitively via higher level functions in the API. It is recommended to look elsewhere in the library for what you need, and refer to this module only when trying to understand what the class constraints on a function mean.

Synopsis

Documentation

class IsWord a where Source #

Types that can be converted to and from a 64-bit word.

Anything that goes in the data section of a struct will have an instance of this.

Minimal complete definition

fromWord, toWord

Methods

fromWord :: Word64 -> a Source #

Convert from a 64-bit words Truncates the word if the type has less than 64 bits.

toWord :: a -> Word64 Source #

Convert to a 64-bit word.

Instances
IsWord Bool Source # 
Instance details

Defined in Data.Capnp.Classes

IsWord Double Source # 
Instance details

Defined in Data.Capnp.Classes

IsWord Float Source # 
Instance details

Defined in Data.Capnp.Classes

IsWord Int8 Source # 
Instance details

Defined in Data.Capnp.Classes

IsWord Int16 Source # 
Instance details

Defined in Data.Capnp.Classes

IsWord Int32 Source # 
Instance details

Defined in Data.Capnp.Classes

IsWord Int64 Source # 
Instance details

Defined in Data.Capnp.Classes

IsWord Word8 Source # 
Instance details

Defined in Data.Capnp.Classes

IsWord Word16 Source # 
Instance details

Defined in Data.Capnp.Classes

IsWord Word32 Source # 
Instance details

Defined in Data.Capnp.Classes

IsWord Word64 Source # 
Instance details

Defined in Data.Capnp.Classes

IsWord Word1 Source # 
Instance details

Defined in Data.Capnp.Classes

IsWord ElementSize Source # 
Instance details

Defined in Capnp.Capnp.Schema

IsWord Side Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

IsWord Exception'Type Source # 
Instance details

Defined in Capnp.Capnp.Rpc

class ListElem msg e where Source #

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

Minimal complete definition

length, index

Associated Types

data List msg e Source #

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

Methods

length :: List msg e -> Int Source #

Get the length of a list.

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

index i list gets the ith element of a list.

Instances
ListElem msg Bool Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Bool :: * Source #

Methods

length :: List msg Bool -> Int Source #

index :: ReadCtx m msg => Int -> List msg Bool -> m Bool Source #

ListElem msg Double Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Double :: * Source #

Methods

length :: List msg Double -> Int Source #

index :: ReadCtx m msg => Int -> List msg Double -> m Double Source #

ListElem msg Float Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Float :: * Source #

Methods

length :: List msg Float -> Int Source #

index :: ReadCtx m msg => Int -> List msg Float -> m Float Source #

ListElem msg Word64 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Word64 :: * Source #

Methods

length :: List msg Word64 -> Int Source #

index :: ReadCtx m msg => Int -> List msg Word64 -> m Word64 Source #

ListElem msg Word32 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Word32 :: * Source #

Methods

length :: List msg Word32 -> Int Source #

index :: ReadCtx m msg => Int -> List msg Word32 -> m Word32 Source #

ListElem msg Word16 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Word16 :: * Source #

Methods

length :: List msg Word16 -> Int Source #

index :: ReadCtx m msg => Int -> List msg Word16 -> m Word16 Source #

ListElem msg Word8 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Word8 :: * Source #

Methods

length :: List msg Word8 -> Int Source #

index :: ReadCtx m msg => Int -> List msg Word8 -> m Word8 Source #

ListElem msg Int64 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Int64 :: * Source #

Methods

length :: List msg Int64 -> Int Source #

index :: ReadCtx m msg => Int -> List msg Int64 -> m Int64 Source #

ListElem msg Int32 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Int32 :: * Source #

Methods

length :: List msg Int32 -> Int Source #

index :: ReadCtx m msg => Int -> List msg Int32 -> m Int32 Source #

ListElem msg Int16 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Int16 :: * Source #

Methods

length :: List msg Int16 -> Int Source #

index :: ReadCtx m msg => Int -> List msg Int16 -> m Int16 Source #

ListElem msg Int8 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

data List msg Int8 :: * Source #

Methods

length :: List msg Int8 -> Int Source #

index :: ReadCtx m msg => Int -> List msg Int8 -> m Int8 Source #

ListElem msg ElementSize Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg ElementSize :: * Source #

Methods

length :: List msg ElementSize -> Int Source #

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

ListElem msg Side Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

data List msg Side :: * Source #

Methods

length :: List msg Side -> Int Source #

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

ListElem msg Exception'Type Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg Exception'Type :: * Source #

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

Defined in Capnp.Capnp.Schema

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Associated Types

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

Methods

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

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

ListElem msg (Node' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node' msg) :: * Source #

Methods

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

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

ListElem msg (Field' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Field' msg) :: * Source #

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Associated Types

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

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

Defined in Capnp.Capnp.Schema

Associated Types

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

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

Defined in Capnp.Capnp.Schema

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Schema

Associated Types

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

Methods

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

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

ListElem msg (Value msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

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

Methods

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

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

ListElem msg (Type msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

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

Methods

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

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

ListElem msg (Superclass msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

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

Methods

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

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

ListElem msg (Node msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

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

Methods

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

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

ListElem msg (Method msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

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

Methods

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

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

ListElem msg (Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

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

Methods

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

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

ListElem msg (Enumerant msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

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

Methods

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

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

ListElem msg (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

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

Methods

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

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

ListElem msg (CapnpVersion msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

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

Methods

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

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

ListElem msg (Brand msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

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

Methods

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

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

ListElem msg (Annotation msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

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

Methods

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

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

ListElem msg (VatId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

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

Methods

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

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

ListElem msg (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

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

Methods

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

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

ListElem msg (JoinResult msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

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

Methods

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

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

ListElem msg (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

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

Methods

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

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

ListElem msg (Return' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Return' msg) :: * Source #

Methods

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

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

ListElem msg (Resolve' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg (Resolve' msg) :: * Source #

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

ListElem msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

ListElem msg (Return msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

ListElem msg (Resolve msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

ListElem msg (Release msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

ListElem msg (Provide msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

ListElem msg (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

ListElem msg (Payload msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

ListElem msg (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

ListElem msg (Message msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

ListElem msg (Join msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

ListElem msg (Finish msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

ListElem msg (Exception msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

ListElem msg (Disembargo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

ListElem msg (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

ListElem msg (Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

ListElem msg (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

ListElem msg (Accept msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Persistent

Associated Types

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

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

Defined in Capnp.Capnp.Persistent

Associated Types

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

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

Defined in Capnp.Capnp.Json

Associated Types

data List msg (JsonValue'Field msg) :: * Source #

Methods

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

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

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

Defined in Capnp.Capnp.Json

Associated Types

data List msg (JsonValue'Call msg) :: * Source #

Methods

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

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

ListElem msg (JsonValue msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Associated Types

data List msg (JsonValue msg) :: * Source #

Methods

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

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

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

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

Minimal complete definition

setIndex, newList

Methods

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

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

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

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

Instances
MutListElem s Bool Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

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

MutListElem s Double Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

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

MutListElem s Float Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

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

MutListElem s Word64 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

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

MutListElem s Word32 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

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

MutListElem s Word16 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

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

MutListElem s Word8 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

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

MutListElem s Int64 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

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

MutListElem s Int32 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

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

MutListElem s Int16 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

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

MutListElem s Int8 Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

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

MutListElem s ElementSize Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

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

MutListElem s Side Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

MutListElem s Exception'Type Source # 
Instance details

Defined in Capnp.Capnp.Rpc

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' (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' (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 (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 (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 #

class IsPtr msg a where Source #

Types that can be converted to and from an untyped pointer.

Note that this should not involve a marshalling step, and that decoding does not have to succeed, if the pointer is the wrong type.

TODO: split this into FromPtr and ToPtr, for symmetry with FromStruct and ToStruct?

Minimal complete definition

fromPtr, toPtr

Methods

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

Convert an untyped pointer to an a.

toPtr :: a -> Maybe (Ptr msg) Source #

Convert an a to an untyped pointer.

Instances
IsPtr msg (Struct msg) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

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

toPtr :: Struct msg -> Maybe (Ptr msg) Source #

IsPtr msg (Maybe (Ptr msg)) Source #

IsPtr instance for pointers -- this is just the identity.

Instance details

Defined in Data.Capnp.Classes

Methods

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

toPtr :: Maybe (Ptr msg) -> Maybe (Ptr msg) Source #

IsPtr msg (Text msg) Source # 
Instance details

Defined in Data.Capnp.Basics

Methods

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

toPtr :: Text msg -> Maybe (Ptr msg) Source #

IsPtr msg (Data msg) Source # 
Instance details

Defined in Data.Capnp.Basics

Methods

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

toPtr :: Data msg -> Maybe (Ptr msg) Source #

IsPtr msg (Node'Parameter msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: Node'Parameter msg -> Maybe (Ptr msg) Source #

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

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: Node'NestedNode msg -> Maybe (Ptr msg) Source #

IsPtr msg (Node' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: Node' msg -> Maybe (Ptr msg) Source #

IsPtr msg (Field' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: Field' msg -> Maybe (Ptr msg) Source #

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

IsPtr msg (Brand'Scope' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: Brand'Scope' msg -> Maybe (Ptr msg) Source #

IsPtr msg (Brand'Scope msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: Brand'Scope msg -> Maybe (Ptr msg) Source #

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

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: Brand'Binding msg -> Maybe (Ptr msg) Source #

IsPtr msg (Value msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: Value msg -> Maybe (Ptr msg) Source #

IsPtr msg (Type msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: Type msg -> Maybe (Ptr msg) Source #

IsPtr msg (Superclass msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: Superclass msg -> Maybe (Ptr msg) Source #

IsPtr msg (Node msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: Node msg -> Maybe (Ptr msg) Source #

IsPtr msg (Method msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: Method msg -> Maybe (Ptr msg) Source #

IsPtr msg (Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: Field msg -> Maybe (Ptr msg) Source #

IsPtr msg (Enumerant msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: Enumerant msg -> Maybe (Ptr msg) Source #

IsPtr msg (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: CodeGeneratorRequest msg -> Maybe (Ptr msg) Source #

IsPtr msg (CapnpVersion msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: CapnpVersion msg -> Maybe (Ptr msg) Source #

IsPtr msg (Brand msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: Brand msg -> Maybe (Ptr msg) Source #

IsPtr msg (Annotation msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: Annotation msg -> Maybe (Ptr msg) Source #

IsPtr msg (VatId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

toPtr :: VatId msg -> Maybe (Ptr msg) Source #

IsPtr msg (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

toPtr :: ProvisionId msg -> Maybe (Ptr msg) Source #

IsPtr msg (JoinResult msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

toPtr :: JoinResult msg -> Maybe (Ptr msg) Source #

IsPtr msg (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

toPtr :: JoinKeyPart msg -> Maybe (Ptr msg) Source #

IsPtr msg (Return' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: Return' msg -> Maybe (Ptr msg) Source #

IsPtr msg (Resolve' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: Resolve' msg -> Maybe (Ptr msg) Source #

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

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: PromisedAnswer'Op msg -> Maybe (Ptr msg) Source #

IsPtr msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: ThirdPartyCapDescriptor msg -> Maybe (Ptr msg) Source #

IsPtr msg (Return msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: Return msg -> Maybe (Ptr msg) Source #

IsPtr msg (Resolve msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: Resolve msg -> Maybe (Ptr msg) Source #

IsPtr msg (Release msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: Release msg -> Maybe (Ptr msg) Source #

IsPtr msg (Provide msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: Provide msg -> Maybe (Ptr msg) Source #

IsPtr msg (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: PromisedAnswer msg -> Maybe (Ptr msg) Source #

IsPtr msg (Payload msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: Payload msg -> Maybe (Ptr msg) Source #

IsPtr msg (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: MessageTarget msg -> Maybe (Ptr msg) Source #

IsPtr msg (Message msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: Message msg -> Maybe (Ptr msg) Source #

IsPtr msg (Join msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: Join msg -> Maybe (Ptr msg) Source #

IsPtr msg (Finish msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: Finish msg -> Maybe (Ptr msg) Source #

IsPtr msg (Exception msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: Exception msg -> Maybe (Ptr msg) Source #

IsPtr msg (Disembargo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: Disembargo msg -> Maybe (Ptr msg) Source #

IsPtr msg (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: CapDescriptor msg -> Maybe (Ptr msg) Source #

IsPtr msg (Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: Call msg -> Maybe (Ptr msg) Source #

IsPtr msg (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: Bootstrap msg -> Maybe (Ptr msg) Source #

IsPtr msg (Accept msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: Accept msg -> Maybe (Ptr msg) Source #

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

Defined in Capnp.Capnp.Persistent

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Persistent'SaveResults msg) Source #

toPtr :: Persistent'SaveResults msg -> Maybe (Ptr msg) Source #

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

Defined in Capnp.Capnp.Persistent

Methods

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

toPtr :: Persistent'SaveParams msg -> Maybe (Ptr msg) Source #

IsPtr msg (JsonValue'Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (JsonValue'Field msg) Source #

toPtr :: JsonValue'Field msg -> Maybe (Ptr msg) Source #

IsPtr msg (JsonValue'Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (JsonValue'Call msg) Source #

toPtr :: JsonValue'Call msg -> Maybe (Ptr msg) Source #

IsPtr msg (JsonValue msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

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

toPtr :: JsonValue msg -> Maybe (Ptr msg) Source #

IsPtr msg (ListOf msg (Struct msg)) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

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

toPtr :: ListOf msg (Struct msg) -> Maybe (Ptr msg) Source #

IsPtr msg (ListOf msg Bool) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

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

toPtr :: ListOf msg Bool -> Maybe (Ptr msg) Source #

IsPtr msg (ListOf msg Word64) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

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

toPtr :: ListOf msg Word64 -> Maybe (Ptr msg) Source #

IsPtr msg (ListOf msg Word32) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

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

toPtr :: ListOf msg Word32 -> Maybe (Ptr msg) Source #

IsPtr msg (ListOf msg Word16) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

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

toPtr :: ListOf msg Word16 -> Maybe (Ptr msg) Source #

IsPtr msg (ListOf msg Word8) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

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

toPtr :: ListOf msg Word8 -> Maybe (Ptr msg) Source #

IsPtr msg (ListOf msg ()) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

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

toPtr :: ListOf msg () -> Maybe (Ptr msg) Source #

IsPtr msg (List msg Bool) Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

toPtr :: List msg Bool -> Maybe (Ptr msg) Source #

IsPtr msg (List msg Double) Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

toPtr :: List msg Double -> Maybe (Ptr msg) Source #

IsPtr msg (List msg Float) Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

toPtr :: List msg Float -> Maybe (Ptr msg) Source #

IsPtr msg (List msg Word64) Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

toPtr :: List msg Word64 -> Maybe (Ptr msg) Source #

IsPtr msg (List msg Word32) Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

toPtr :: List msg Word32 -> Maybe (Ptr msg) Source #

IsPtr msg (List msg Word16) Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

toPtr :: List msg Word16 -> Maybe (Ptr msg) Source #

IsPtr msg (List msg Word8) Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

toPtr :: List msg Word8 -> Maybe (Ptr msg) Source #

IsPtr msg (List msg Int64) Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

toPtr :: List msg Int64 -> Maybe (Ptr msg) Source #

IsPtr msg (List msg Int32) Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

toPtr :: List msg Int32 -> Maybe (Ptr msg) Source #

IsPtr msg (List msg Int16) Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

toPtr :: List msg Int16 -> Maybe (Ptr msg) Source #

IsPtr msg (List msg Int8) Source # 
Instance details

Defined in Internal.Gen.Instances

Methods

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

toPtr :: List msg Int8 -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Node'Parameter msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (Node'Parameter msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Node'NestedNode msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (Node'NestedNode msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Node' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (Node' msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Field' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (Field' msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (CodeGeneratorRequest'RequestedFile'Import msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

IsPtr msg (List msg (CodeGeneratorRequest'RequestedFile msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (CodeGeneratorRequest'RequestedFile msg)) Source #

toPtr :: List msg (CodeGeneratorRequest'RequestedFile msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Brand'Scope' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (Brand'Scope' msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Brand'Scope msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (Brand'Scope msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Brand'Binding msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (Brand'Binding msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Value msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (Value msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Type msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (Type msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Superclass msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (Superclass msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Node msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (Node msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Method msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (Method msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Field msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (Field msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Enumerant msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (Enumerant msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg ElementSize) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg ElementSize -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (CodeGeneratorRequest msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (CodeGeneratorRequest msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (CapnpVersion msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (CapnpVersion msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Brand msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (Brand msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Annotation msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

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

toPtr :: List msg (Annotation msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (VatId msg)) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

toPtr :: List msg (VatId msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg Side) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

toPtr :: List msg Side -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (ProvisionId msg)) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

toPtr :: List msg (ProvisionId msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (JoinResult msg)) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

toPtr :: List msg (JoinResult msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (JoinKeyPart msg)) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

toPtr :: List msg (JoinKeyPart msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Return' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (Return' msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Resolve' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (Resolve' msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (PromisedAnswer'Op msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (PromisedAnswer'Op msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg Exception'Type) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg Exception'Type) Source #

toPtr :: List msg Exception'Type -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (ThirdPartyCapDescriptor msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (ThirdPartyCapDescriptor msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Return msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (Return msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Resolve msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (Resolve msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Release msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (Release msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Provide msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (Provide msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (PromisedAnswer msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (PromisedAnswer msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Payload msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (Payload msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (MessageTarget msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (MessageTarget msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Message msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (Message msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Join msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (Join msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Finish msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (Finish msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Exception msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (Exception msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Disembargo msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (Disembargo msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (CapDescriptor msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (CapDescriptor msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Call msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (Call msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Bootstrap msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (Bootstrap msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Accept msg)) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

toPtr :: List msg (Accept msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Persistent'SaveResults msg)) Source # 
Instance details

Defined in Capnp.Capnp.Persistent

Methods

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

toPtr :: List msg (Persistent'SaveResults msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (Persistent'SaveParams msg)) Source # 
Instance details

Defined in Capnp.Capnp.Persistent

Methods

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

toPtr :: List msg (Persistent'SaveParams msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (JsonValue'Field msg)) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

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

toPtr :: List msg (JsonValue'Field msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (JsonValue'Call msg)) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

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

toPtr :: List msg (JsonValue'Call msg) -> Maybe (Ptr msg) Source #

IsPtr msg (List msg (JsonValue msg)) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

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

toPtr :: List msg (JsonValue msg) -> Maybe (Ptr msg) Source #

class FromStruct msg a where Source #

Types that can be extracted from a struct.

Minimal complete definition

fromStruct

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m a Source #

Extract a value from a struct.

Instances
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

FromStruct msg (Struct msg) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Struct msg) Source #

FromStruct msg (Type'anyPointer'unconstrained' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Type'anyPointer'unconstrained msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Type'anyPointer' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Type'anyPointer' msg) Source #

FromStruct msg (Type'anyPointer'implicitMethodParameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Type'anyPointer'parameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Type'anyPointer'unconstrained'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Type'anyPointer msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Type'anyPointer msg) Source #

FromStruct msg (Node'Parameter msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node'Parameter msg) Source #

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

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node'NestedNode msg) Source #

FromStruct msg (Node'' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node'' msg) Source #

FromStruct msg (Node'annotation'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node'annotation'group' msg) Source #

FromStruct msg (Node'const'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node'const'group' msg) Source #

FromStruct msg (Node'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node'interface'group' msg) Source #

FromStruct msg (Node'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node'enum'group' msg) Source #

FromStruct msg (Node'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node'struct'group' msg) Source #

FromStruct msg (Node' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node' msg) Source #

FromStruct msg (Field'ordinal' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Field'ordinal' msg) Source #

FromStruct msg (Field'ordinal msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Field'ordinal msg) Source #

FromStruct msg (Field'' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Field'' msg) Source #

FromStruct msg (Field'group'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Field'group'group' msg) Source #

FromStruct msg (Field'slot'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Field'slot'group' msg) Source #

FromStruct msg (Field' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Field' msg) Source #

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

FromStruct msg (Brand'Scope'' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Brand'Scope'' msg) Source #

FromStruct msg (Brand'Scope' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Brand'Scope' msg) Source #

FromStruct msg (Brand'Scope msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Brand'Scope msg) Source #

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

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Brand'Binding' msg) Source #

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

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Brand'Binding msg) Source #

FromStruct msg (Value' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Value' msg) Source #

FromStruct msg (Value msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Value msg) Source #

FromStruct msg (Type' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Type' msg) Source #

FromStruct msg (Type'anyPointer'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Type'anyPointer'group' msg) Source #

FromStruct msg (Type'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Type'interface'group' msg) Source #

FromStruct msg (Type'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Type'struct'group' msg) Source #

FromStruct msg (Type'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Type'enum'group' msg) Source #

FromStruct msg (Type'list'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Type'list'group' msg) Source #

FromStruct msg (Type msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Type msg) Source #

FromStruct msg (Superclass msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Superclass msg) Source #

FromStruct msg (Node msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node msg) Source #

FromStruct msg (Method msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Method msg) Source #

FromStruct msg (Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Field msg) Source #

FromStruct msg (Enumerant msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Enumerant msg) Source #

FromStruct msg (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (CodeGeneratorRequest msg) Source #

FromStruct msg (CapnpVersion msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (CapnpVersion msg) Source #

FromStruct msg (Brand msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Brand msg) Source #

FromStruct msg (Annotation msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Annotation msg) Source #

FromStruct msg (VatId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (VatId msg) Source #

FromStruct msg (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (ProvisionId msg) Source #

FromStruct msg (JoinResult msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (JoinResult msg) Source #

FromStruct msg (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (JoinKeyPart msg) Source #

FromStruct msg (Return'' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Return'' msg) Source #

FromStruct msg (Return' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Return' msg) Source #

FromStruct msg (Resolve'' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Resolve'' msg) Source #

FromStruct msg (Resolve' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Resolve' msg) Source #

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

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (PromisedAnswer'Op' msg) Source #

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

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (PromisedAnswer'Op msg) Source #

FromStruct msg (Disembargo'context' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Disembargo'context' msg) Source #

FromStruct msg (Disembargo'context msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Disembargo'context msg) Source #

FromStruct msg (Call'sendResultsTo' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Call'sendResultsTo' msg) Source #

FromStruct msg (Call'sendResultsTo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Call'sendResultsTo msg) Source #

FromStruct msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (ThirdPartyCapDescriptor msg) Source #

FromStruct msg (Return msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Return msg) Source #

FromStruct msg (Resolve msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Resolve msg) Source #

FromStruct msg (Release msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Release msg) Source #

FromStruct msg (Provide msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Provide msg) Source #

FromStruct msg (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (PromisedAnswer msg) Source #

FromStruct msg (Payload msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Payload msg) Source #

FromStruct msg (MessageTarget' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (MessageTarget' msg) Source #

FromStruct msg (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (MessageTarget msg) Source #

FromStruct msg (Message' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Message' msg) Source #

FromStruct msg (Message msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Message msg) Source #

FromStruct msg (Join msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Join msg) Source #

FromStruct msg (Finish msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Finish msg) Source #

FromStruct msg (Exception msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Exception msg) Source #

FromStruct msg (Disembargo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Disembargo msg) Source #

FromStruct msg (CapDescriptor' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (CapDescriptor' msg) Source #

FromStruct msg (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (CapDescriptor msg) Source #

FromStruct msg (Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Call msg) Source #

FromStruct msg (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Bootstrap msg) Source #

FromStruct msg (Accept msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Accept msg) Source #

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

Defined in Capnp.Capnp.Persistent

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Persistent'SaveResults msg) Source #

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

Defined in Capnp.Capnp.Persistent

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Persistent'SaveParams msg) Source #

FromStruct msg (JsonValue'Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (JsonValue'Field msg) Source #

FromStruct msg (JsonValue'Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (JsonValue'Call msg) Source #

FromStruct msg (JsonValue' msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (JsonValue' msg) Source #

FromStruct msg (JsonValue msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (JsonValue msg) Source #

class ToStruct msg a where Source #

Types that can be converted to a struct.

Minimal complete definition

toStruct

Methods

toStruct :: a -> Struct msg Source #

Convert a value to a struct.

Instances
ToStruct msg (Struct msg) Source # 
Instance details

Defined in Data.Capnp.Classes

Methods

toStruct :: Struct msg -> Struct msg Source #

ToStruct msg (Type'anyPointer'unconstrained msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ToStruct msg (Type'anyPointer'implicitMethodParameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ToStruct msg (Type'anyPointer'parameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ToStruct msg (Type'anyPointer'unconstrained'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ToStruct msg (Type'anyPointer msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Type'anyPointer msg -> Struct msg Source #

ToStruct msg (Node'Parameter msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Node'Parameter msg -> Struct msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Node'NestedNode msg -> Struct msg Source #

ToStruct msg (Node'annotation'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ToStruct msg (Node'const'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ToStruct msg (Node'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ToStruct msg (Node'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Node'enum'group' msg -> Struct msg Source #

ToStruct msg (Node'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ToStruct msg (Node' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Node' msg -> Struct msg Source #

ToStruct msg (Field'ordinal msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Field'ordinal msg -> Struct msg Source #

ToStruct msg (Field'group'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ToStruct msg (Field'slot'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ToStruct msg (Field' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Field' msg -> Struct msg Source #

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

Defined in Capnp.Capnp.Schema

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

Defined in Capnp.Capnp.Schema

ToStruct msg (Brand'Scope' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Brand'Scope' msg -> Struct msg Source #

ToStruct msg (Brand'Scope msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Brand'Scope msg -> Struct msg Source #

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

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Brand'Binding msg -> Struct msg Source #

ToStruct msg (Value msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Value msg -> Struct msg Source #

ToStruct msg (Type'anyPointer'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ToStruct msg (Type'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ToStruct msg (Type'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ToStruct msg (Type'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Type'enum'group' msg -> Struct msg Source #

ToStruct msg (Type'list'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Type'list'group' msg -> Struct msg Source #

ToStruct msg (Type msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Type msg -> Struct msg Source #

ToStruct msg (Superclass msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Superclass msg -> Struct msg Source #

ToStruct msg (Node msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Node msg -> Struct msg Source #

ToStruct msg (Method msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Method msg -> Struct msg Source #

ToStruct msg (Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Field msg -> Struct msg Source #

ToStruct msg (Enumerant msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Enumerant msg -> Struct msg Source #

ToStruct msg (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ToStruct msg (CapnpVersion msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: CapnpVersion msg -> Struct msg Source #

ToStruct msg (Brand msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Brand msg -> Struct msg Source #

ToStruct msg (Annotation msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Annotation msg -> Struct msg Source #

ToStruct msg (VatId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

toStruct :: VatId msg -> Struct msg Source #

ToStruct msg (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

toStruct :: ProvisionId msg -> Struct msg Source #

ToStruct msg (JoinResult msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

toStruct :: JoinResult msg -> Struct msg Source #

ToStruct msg (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

toStruct :: JoinKeyPart msg -> Struct msg Source #

ToStruct msg (Return' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Return' msg -> Struct msg Source #

ToStruct msg (Resolve' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Resolve' msg -> Struct msg Source #

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

Defined in Capnp.Capnp.Rpc

ToStruct msg (Disembargo'context msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

ToStruct msg (Call'sendResultsTo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

ToStruct msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

ToStruct msg (Return msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Return msg -> Struct msg Source #

ToStruct msg (Resolve msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Resolve msg -> Struct msg Source #

ToStruct msg (Release msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Release msg -> Struct msg Source #

ToStruct msg (Provide msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Provide msg -> Struct msg Source #

ToStruct msg (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: PromisedAnswer msg -> Struct msg Source #

ToStruct msg (Payload msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Payload msg -> Struct msg Source #

ToStruct msg (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: MessageTarget msg -> Struct msg Source #

ToStruct msg (Message msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Message msg -> Struct msg Source #

ToStruct msg (Join msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Join msg -> Struct msg Source #

ToStruct msg (Finish msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Finish msg -> Struct msg Source #

ToStruct msg (Exception msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Exception msg -> Struct msg Source #

ToStruct msg (Disembargo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Disembargo msg -> Struct msg Source #

ToStruct msg (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: CapDescriptor msg -> Struct msg Source #

ToStruct msg (Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Call msg -> Struct msg Source #

ToStruct msg (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Bootstrap msg -> Struct msg Source #

ToStruct msg (Accept msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Accept msg -> Struct msg Source #

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

Defined in Capnp.Capnp.Persistent

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

Defined in Capnp.Capnp.Persistent

ToStruct msg (JsonValue'Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

toStruct :: JsonValue'Field msg -> Struct msg Source #

ToStruct msg (JsonValue'Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

toStruct :: JsonValue'Call msg -> Struct msg Source #

ToStruct msg (JsonValue msg) Source # 
Instance details

Defined in Capnp.Capnp.Json

Methods

toStruct :: JsonValue msg -> Struct msg Source #

class Allocate s e where Source #

Types which may be stored in a capnproto message, and have a fixed size.

This applies to typed structs, but not e.g. lists, because the length must be known to allocate a list.

Minimal complete definition

new

Methods

new :: WriteCtx m s => MutMsg s -> m e Source #

Instances
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' (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' (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 (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 (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 #

class Decerialize a => Marshal a where Source #

Types which may be marshaled into a pre-allocated object in a message.

Minimal complete definition

marshalInto

Methods

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

Marshal a value into the pre-allocated object inside the message.

Note that caller must arrange for the object to be of the correct size. This is is not necessarily guaranteed; for example, list types must coordinate the length of the list.

Instances
Marshal Struct Source # 
Instance details

Defined in Data.Capnp.Untyped.Pure

Methods

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

Marshal Text Source # 
Instance details

Defined in Data.Capnp.Basics.Pure

Methods

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

Marshal Data Source # 
Instance details

Defined in Data.Capnp.Basics.Pure

Methods

marshalInto :: RWCtx m s => Cerial (MutMsg s) Data -> Data -> m () Source #

Marshal Type'anyPointer'unconstrained Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Marshal Type'anyPointer Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Marshal Node'Parameter Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Marshal Node'NestedNode Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Marshal Node' Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

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

Marshal Field'ordinal Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Marshal Field' Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

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

Marshal CodeGeneratorRequest'RequestedFile'Import Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Marshal CodeGeneratorRequest'RequestedFile Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Marshal Brand'Scope' Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Marshal Brand'Scope Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

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

Marshal Brand'Binding Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Marshal Value Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

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

Marshal Type Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

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

Marshal Superclass Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

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

Marshal Node Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

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

Marshal Method Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

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

Marshal Field Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

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

Marshal Enumerant Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

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

Marshal CodeGeneratorRequest Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Marshal CapnpVersion Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Marshal Brand Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

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

Marshal Annotation Source # 
Instance details

Defined in Capnp.Capnp.Schema.Pure

Methods

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

Marshal VatId Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

Methods

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

Marshal ProvisionId Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

Methods

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

Marshal JoinResult Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

Methods

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

Marshal JoinKeyPart Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty.Pure

Methods

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

Marshal Return' Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

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

Marshal Resolve' Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

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

Marshal PromisedAnswer'Op Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Marshal Disembargo'context Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Marshal Call'sendResultsTo Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Marshal ThirdPartyCapDescriptor Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Marshal Return Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

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

Marshal Resolve Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

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

Marshal Release Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

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

Marshal Provide Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

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

Marshal PromisedAnswer Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Marshal Payload Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

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

Marshal MessageTarget Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Marshal Message Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

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

Marshal Join Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

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

Marshal Finish Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

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

Marshal Exception Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

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

Marshal Disembargo Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

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

Marshal CapDescriptor Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Marshal Call Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

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

Marshal Bootstrap Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

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

Marshal Accept Source # 
Instance details

Defined in Capnp.Capnp.Rpc.Pure

Methods

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

Marshal Persistent'SaveResults Source # 
Instance details

Defined in Capnp.Capnp.Persistent.Pure

Marshal Persistent'SaveParams Source # 
Instance details

Defined in Capnp.Capnp.Persistent.Pure

Marshal JsonValue'Field Source # 
Instance details

Defined in Capnp.Capnp.Json.Pure

Marshal JsonValue'Call Source # 
Instance details

Defined in Capnp.Capnp.Json.Pure

Marshal JsonValue Source # 
Instance details

Defined in Capnp.Capnp.Json.Pure

Methods

marshalInto :: RWCtx m s => Cerial (MutMsg s) JsonValue -> JsonValue -> m () 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 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' 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 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 #

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

Defined in Internal.Gen.Instances

Associated Types

type Cerial msg Bool :: * Source #

Decerialize Double Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

type Cerial msg Double :: * Source #

Decerialize Float Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

type Cerial msg Float :: * Source #

Decerialize Int8 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

type Cerial msg Int8 :: * Source #

Decerialize Int16 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

type Cerial msg Int16 :: * Source #

Decerialize Int32 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

type Cerial msg Int32 :: * Source #

Decerialize Int64 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

type Cerial msg Int64 :: * Source #

Decerialize Word8 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

type Cerial msg Word8 :: * Source #

Decerialize Word16 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

type Cerial msg Word16 :: * Source #

Decerialize Word32 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

type Cerial msg Word32 :: * Source #

Decerialize Word64 Source # 
Instance details

Defined in Internal.Gen.Instances

Associated Types

type Cerial msg Word64 :: * Source #

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 #