capnp-0.11.0.0: Cap'n Proto for Haskell
Safe HaskellNone
LanguageHaskell2010

Capnp.New

Description

 
Synopsis

Documentation

data LimitT m a Source #

Monad transformer implementing MonadLimit. The underlying monad must implement MonadThrow. invoice calls throwM TraversalLimitError when the limit is exhausted.

Instances

Instances details
MonadTrans LimitT Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

lift :: Monad m => m a -> LimitT m a #

MonadState s m => MonadState s (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

get :: LimitT m s #

put :: s -> LimitT m () #

state :: (s -> (a, s)) -> LimitT m a #

Monad m => Monad (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

(>>=) :: LimitT m a -> (a -> LimitT m b) -> LimitT m b #

(>>) :: LimitT m a -> LimitT m b -> LimitT m b #

return :: a -> LimitT m a #

Functor m => Functor (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

fmap :: (a -> b) -> LimitT m a -> LimitT m b #

(<$) :: a -> LimitT m b -> LimitT m a #

MonadFail m => MonadFail (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

fail :: String -> LimitT m a #

Monad m => Applicative (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

pure :: a -> LimitT m a #

(<*>) :: LimitT m (a -> b) -> LimitT m a -> LimitT m b #

liftA2 :: (a -> b -> c) -> LimitT m a -> LimitT m b -> LimitT m c #

(*>) :: LimitT m a -> LimitT m b -> LimitT m b #

(<*) :: LimitT m a -> LimitT m b -> LimitT m a #

MonadIO m => MonadIO (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

liftIO :: IO a -> LimitT m a #

MonadThrow m => MonadThrow (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

throwM :: Exception e => e -> LimitT m a #

MonadCatch m => MonadCatch (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

catch :: Exception e => LimitT m a -> (e -> LimitT m a) -> LimitT m a #

(PrimMonad m, s ~ PrimState m) => PrimMonad (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Associated Types

type PrimState (LimitT m) #

Methods

primitive :: (State# (PrimState (LimitT m)) -> (# State# (PrimState (LimitT m)), a #)) -> LimitT m a #

MonadThrow m => MonadLimit (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

invoice :: WordCount -> LimitT m () Source #

type PrimState (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

class Monad m => MonadLimit m where Source #

mtl-style type class to track the traversal limit. This is used by other parts of the library which actually do the reading.

Methods

invoice :: WordCount -> m () Source #

invoice n deducts n from the traversal limit, signaling an error if the limit is exhausted.

Instances

Instances details
MonadThrow m => MonadLimit (LimitT m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

invoice :: WordCount -> LimitT m () Source #

MonadLimit (PureBuilder s) Source # 
Instance details

Defined in Internal.BuildPure

MonadLimit m => MonadLimit (ReaderT r m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

invoice :: WordCount -> ReaderT r m () Source #

(Monoid w, MonadLimit m) => MonadLimit (WriterT w m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

invoice :: WordCount -> WriterT w m () Source #

MonadLimit m => MonadLimit (StateT s m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

invoice :: WordCount -> StateT s m () Source #

MonadLimit m => MonadLimit (StateT s m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

invoice :: WordCount -> StateT s m () Source #

(Monoid w, MonadLimit m) => MonadLimit (RWST r w s m) Source # 
Instance details

Defined in Capnp.TraversalLimit

Methods

invoice :: WordCount -> RWST r w s m () Source #

runLimitT :: MonadThrow m => WordCount -> LimitT m a -> m (a, WordCount) Source #

Run a LimitT, returning the value from the computation and the remaining traversal limit.

evalLimitT :: MonadThrow m => WordCount -> LimitT m a -> m a Source #

Run a LimitT, returning the value from the computation.

execLimitT :: MonadThrow m => WordCount -> LimitT m a -> m WordCount Source #

Run a LimitT, returning the remaining traversal limit.

defaultLimit :: WordCount Source #

A sensible default traversal limit. Currently 64 MiB.

hPutMsg :: Handle -> Message 'Const -> IO () Source #

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

putMsg :: Message 'Const -> IO () Source #

Equivalent to hPutMsg stdout

hGetMsg :: Handle -> WordCount -> IO (Message 'Const) Source #

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

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.

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

Instances details
IsWord Bool Source # 
Instance details

Defined in Capnp.Classes

IsWord Double Source # 
Instance details

Defined in Capnp.Classes

IsWord Float Source # 
Instance details

Defined in Capnp.Classes

IsWord Int8 Source # 
Instance details

Defined in Capnp.Classes

IsWord Int16 Source # 
Instance details

Defined in Capnp.Classes

IsWord Int32 Source # 
Instance details

Defined in Capnp.Classes

IsWord Int64 Source # 
Instance details

Defined in Capnp.Classes

IsWord Word8 Source # 
Instance details

Defined in Capnp.Classes

IsWord Word16 Source # 
Instance details

Defined in Capnp.Classes

IsWord Word32 Source # 
Instance details

Defined in Capnp.Classes

IsWord Word64 Source # 
Instance details

Defined in Capnp.Classes

IsWord Word1 Source # 
Instance details

Defined in Capnp.Classes

IsWord ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

IsWord Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

IsWord Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

IsWord ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

IsWord Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

IsWord Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

class (Parse a ap, Allocate (List a)) => EstimateListAlloc a ap where Source #

Minimal complete definition

Nothing

Instances

Instances details
EstimateListAlloc Bool Bool Source # 
Instance details

Defined in Capnp.New.Classes

EstimateListAlloc Double Double Source # 
Instance details

Defined in Capnp.New.Classes

EstimateListAlloc Float Float Source # 
Instance details

Defined in Capnp.New.Classes

EstimateListAlloc Int8 Int8 Source # 
Instance details

Defined in Capnp.New.Classes

EstimateListAlloc Int16 Int16 Source # 
Instance details

Defined in Capnp.New.Classes

EstimateListAlloc Int32 Int32 Source # 
Instance details

Defined in Capnp.New.Classes

EstimateListAlloc Int64 Int64 Source # 
Instance details

Defined in Capnp.New.Classes

EstimateListAlloc Word8 Word8 Source # 
Instance details

Defined in Capnp.New.Classes

EstimateListAlloc Word16 Word16 Source # 
Instance details

Defined in Capnp.New.Classes

EstimateListAlloc Word32 Word32 Source # 
Instance details

Defined in Capnp.New.Classes

EstimateListAlloc Word64 Word64 Source # 
Instance details

Defined in Capnp.New.Classes

EstimateListAlloc () () Source # 
Instance details

Defined in Capnp.New.Classes

EstimateListAlloc Data ByteString Source # 
Instance details

Defined in Capnp.New.Basics

EstimateListAlloc Text Text Source # 
Instance details

Defined in Capnp.New.Basics

EstimateListAlloc ElementSize ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Side Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

EstimateListAlloc Exception'Type Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc AnyStruct (Parsed AnyStruct) Source # 
Instance details

Defined in Capnp.New.Basics

EstimateListAlloc AnyPointer (Parsed AnyPointer) Source # 
Instance details

Defined in Capnp.New.Basics

EstimateListAlloc StreamResult (Parsed StreamResult) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Stream.New

EstimateListAlloc CodeGeneratorRequest'RequestedFile'Import (Parsed CodeGeneratorRequest'RequestedFile'Import) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc CodeGeneratorRequest'RequestedFile (Parsed CodeGeneratorRequest'RequestedFile) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc CodeGeneratorRequest (Parsed CodeGeneratorRequest) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc CapnpVersion (Parsed CapnpVersion) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Annotation (Parsed Annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Value (Parsed Value) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Brand'Binding (Parsed Brand'Binding) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Brand'Scope (Parsed Brand'Scope) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Brand (Parsed Brand) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Type'anyPointer'implicitMethodParameter (Parsed Type'anyPointer'implicitMethodParameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Type'anyPointer'parameter (Parsed Type'anyPointer'parameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Type'anyPointer'unconstrained (Parsed Type'anyPointer'unconstrained) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Type'anyPointer (Parsed Type'anyPointer) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Type'interface (Parsed Type'interface) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Type'struct (Parsed Type'struct) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Type'enum (Parsed Type'enum) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Type'list (Parsed Type'list) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Type (Parsed Type) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Method (Parsed Method) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Superclass (Parsed Superclass) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Enumerant (Parsed Enumerant) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Field'ordinal (Parsed Field'ordinal) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Field'group (Parsed Field'group) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Field'slot (Parsed Field'slot) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Field (Parsed Field) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Node'SourceInfo'Member (Parsed Node'SourceInfo'Member) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Node'SourceInfo (Parsed Node'SourceInfo) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Node'NestedNode (Parsed Node'NestedNode) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Node'Parameter (Parsed Node'Parameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Node'annotation (Parsed Node'annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Node'const (Parsed Node'const) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Node'interface (Parsed Node'interface) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Node'enum (Parsed Node'enum) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Node'struct (Parsed Node'struct) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc Node (Parsed Node) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateListAlloc JoinResult (Parsed JoinResult) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

EstimateListAlloc JoinKeyPart (Parsed JoinKeyPart) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

EstimateListAlloc ThirdPartyCapId (Parsed ThirdPartyCapId) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

EstimateListAlloc RecipientId (Parsed RecipientId) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

EstimateListAlloc ProvisionId (Parsed ProvisionId) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

EstimateListAlloc VatId (Parsed VatId) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

EstimateListAlloc Exception (Parsed Exception) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc ThirdPartyCapDescriptor (Parsed ThirdPartyCapDescriptor) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc PromisedAnswer'Op (Parsed PromisedAnswer'Op) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc PromisedAnswer (Parsed PromisedAnswer) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc CapDescriptor (Parsed CapDescriptor) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc Payload (Parsed Payload) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc MessageTarget (Parsed MessageTarget) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc Join (Parsed Join) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc Accept (Parsed Accept) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc Provide (Parsed Provide) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc Disembargo'context (Parsed Disembargo'context) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc Disembargo (Parsed Disembargo) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc Release (Parsed Release) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc Resolve (Parsed Resolve) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc Finish (Parsed Finish) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc Return (Parsed Return) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc Call'sendResultsTo (Parsed Call'sendResultsTo) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc Call (Parsed Call) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc Bootstrap (Parsed Bootstrap) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc Message (Parsed Message) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateListAlloc DiscriminatorOptions (Parsed DiscriminatorOptions) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

EstimateListAlloc FlattenOptions (Parsed FlattenOptions) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

EstimateListAlloc Value'Call (Parsed Value'Call) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

EstimateListAlloc Value'Field (Parsed Value'Field) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

EstimateListAlloc Value (Parsed Value) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

(Parse (List a) (Vector ap), Allocate (List a)) => EstimateListAlloc (List a) (Vector ap) Source # 
Instance details

Defined in Capnp.New.Classes

(TypeParam sturdyRef, TypeParam owner) => EstimateListAlloc (Persistent'SaveResults sturdyRef owner) (Parsed (Persistent'SaveResults sturdyRef owner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

(TypeParam sturdyRef, TypeParam owner) => EstimateListAlloc (Persistent'SaveParams sturdyRef owner) (Parsed (Persistent'SaveParams sturdyRef owner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

estimateListAlloc :: Vector (Parsed (Persistent'SaveParams sturdyRef owner)) -> AllocHint (List (Persistent'SaveParams sturdyRef owner)) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => EstimateListAlloc (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) (Parsed (RealmGateway'export'params internalRef externalRef internalOwner externalOwner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

estimateListAlloc :: Vector (Parsed (RealmGateway'export'params internalRef externalRef internalOwner externalOwner)) -> AllocHint (List (RealmGateway'export'params internalRef externalRef internalOwner externalOwner)) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => EstimateListAlloc (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) (Parsed (RealmGateway'import'params internalRef externalRef internalOwner externalOwner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

estimateListAlloc :: Vector (Parsed (RealmGateway'import'params internalRef externalRef internalOwner externalOwner)) -> AllocHint (List (RealmGateway'import'params internalRef externalRef internalOwner externalOwner)) Source #

type MarshalElement a ap = (Parse a ap, EstimateListAlloc a ap, Element (ReprFor a), MarshalElementByRepr (ListReprFor (ReprFor a)), MarshalElementReprConstraints (ListReprFor (ReprFor a)) a ap) Source #

Type alias capturing the constraints on a type needed by marshalElement

class (IsStruct a, Allocate a, AllocHint a ~ ()) => TypedStruct a where Source #

Operations on typed structs.

Instances

Instances details
TypedStruct StreamResult Source # 
Instance details

Defined in Capnp.Gen.Capnp.Stream.New

TypedStruct CodeGeneratorRequest'RequestedFile'Import Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct CodeGeneratorRequest'RequestedFile Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct CodeGeneratorRequest Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct CapnpVersion Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Annotation Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Brand'Binding Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Brand'Scope Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Brand Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Type'anyPointer'implicitMethodParameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Type'anyPointer'parameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Type'anyPointer'unconstrained Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Type'anyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Type'interface Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Type'struct Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Type'enum Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Type'list Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Method Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Superclass Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Enumerant Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Field'ordinal Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Field'group Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Field'slot Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Field Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Node'SourceInfo'Member Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Node'SourceInfo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Node'NestedNode Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Node'Parameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Node'annotation Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Node'const Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Node'interface Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Node'enum Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Node'struct Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct Node Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

TypedStruct JoinResult Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

TypedStruct JoinKeyPart Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

TypedStruct ThirdPartyCapId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

TypedStruct RecipientId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

TypedStruct ProvisionId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

TypedStruct VatId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

TypedStruct Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct ThirdPartyCapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct PromisedAnswer'Op Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct PromisedAnswer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct CapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct Payload Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct MessageTarget Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct Join Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct Accept Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct Provide Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct Disembargo'context Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct Disembargo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct Release Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct Resolve Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct Finish Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct Return Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct Call'sendResultsTo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct Bootstrap Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct Message Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

TypedStruct DiscriminatorOptions Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

TypedStruct FlattenOptions Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

TypedStruct Value'Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

TypedStruct Value'Field Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

TypedStruct Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

(TypeParam sturdyRef, TypeParam owner) => TypedStruct (Persistent'SaveResults sturdyRef owner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

(TypeParam sturdyRef, TypeParam owner) => TypedStruct (Persistent'SaveParams sturdyRef owner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => TypedStruct (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => TypedStruct (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

class Parse t p => Marshal t p where Source #

An instance of marshal allows a parsed value to be inserted into pre-allocated space in a message.

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) t -> p -> 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

Instances details
Marshal Data ByteString Source # 
Instance details

Defined in Capnp.New.Basics

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Data -> ByteString -> m () Source #

Marshal AnyStruct (Parsed AnyStruct) Source # 
Instance details

Defined in Capnp.New.Basics

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) AnyStruct -> Parsed AnyStruct -> m () Source #

Marshal StreamResult (Parsed StreamResult) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Stream.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) StreamResult -> Parsed StreamResult -> m () Source #

Marshal CodeGeneratorRequest'RequestedFile'Import (Parsed CodeGeneratorRequest'RequestedFile'Import) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal CodeGeneratorRequest'RequestedFile (Parsed CodeGeneratorRequest'RequestedFile) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal CodeGeneratorRequest (Parsed CodeGeneratorRequest) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal CapnpVersion (Parsed CapnpVersion) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) CapnpVersion -> Parsed CapnpVersion -> m () Source #

Marshal Annotation (Parsed Annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Annotation -> Parsed Annotation -> m () Source #

Marshal Value (Parsed Value) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Value -> Parsed Value -> m () Source #

Marshal Brand'Binding (Parsed Brand'Binding) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Brand'Binding -> Parsed Brand'Binding -> m () Source #

Marshal Brand'Scope (Parsed Brand'Scope) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Brand'Scope -> Parsed Brand'Scope -> m () Source #

Marshal Brand (Parsed Brand) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Brand -> Parsed Brand -> m () Source #

Marshal Type'anyPointer'implicitMethodParameter (Parsed Type'anyPointer'implicitMethodParameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal Type'anyPointer'parameter (Parsed Type'anyPointer'parameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal Type'anyPointer'unconstrained (Parsed Type'anyPointer'unconstrained) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal Type'anyPointer (Parsed Type'anyPointer) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal Type'interface (Parsed Type'interface) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal Type'struct (Parsed Type'struct) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Type'struct -> Parsed Type'struct -> m () Source #

Marshal Type'enum (Parsed Type'enum) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Type'enum -> Parsed Type'enum -> m () Source #

Marshal Type'list (Parsed Type'list) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Type'list -> Parsed Type'list -> m () Source #

Marshal Type (Parsed Type) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Type -> Parsed Type -> m () Source #

Marshal Method (Parsed Method) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Method -> Parsed Method -> m () Source #

Marshal Superclass (Parsed Superclass) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Superclass -> Parsed Superclass -> m () Source #

Marshal Enumerant (Parsed Enumerant) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Enumerant -> Parsed Enumerant -> m () Source #

Marshal Field'ordinal (Parsed Field'ordinal) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Field'ordinal -> Parsed Field'ordinal -> m () Source #

Marshal Field'group (Parsed Field'group) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Field'group -> Parsed Field'group -> m () Source #

Marshal Field'slot (Parsed Field'slot) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Field'slot -> Parsed Field'slot -> m () Source #

Marshal Field (Parsed Field) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Field -> Parsed Field -> m () Source #

Marshal Node'SourceInfo'Member (Parsed Node'SourceInfo'Member) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal Node'SourceInfo (Parsed Node'SourceInfo) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal Node'NestedNode (Parsed Node'NestedNode) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal Node'Parameter (Parsed Node'Parameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal Node'annotation (Parsed Node'annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal Node'const (Parsed Node'const) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Node'const -> Parsed Node'const -> m () Source #

Marshal Node'interface (Parsed Node'interface) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal Node'enum (Parsed Node'enum) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Node'enum -> Parsed Node'enum -> m () Source #

Marshal Node'struct (Parsed Node'struct) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Node'struct -> Parsed Node'struct -> m () Source #

Marshal Node (Parsed Node) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Node -> Parsed Node -> m () Source #

Marshal JoinResult (Parsed JoinResult) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) JoinResult -> Parsed JoinResult -> m () Source #

Marshal JoinKeyPart (Parsed JoinKeyPart) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) JoinKeyPart -> Parsed JoinKeyPart -> m () Source #

Marshal ThirdPartyCapId (Parsed ThirdPartyCapId) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Marshal RecipientId (Parsed RecipientId) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) RecipientId -> Parsed RecipientId -> m () Source #

Marshal ProvisionId (Parsed ProvisionId) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) ProvisionId -> Parsed ProvisionId -> m () Source #

Marshal VatId (Parsed VatId) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) VatId -> Parsed VatId -> m () Source #

Marshal Exception (Parsed Exception) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Exception -> Parsed Exception -> m () Source #

Marshal ThirdPartyCapDescriptor (Parsed ThirdPartyCapDescriptor) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Marshal PromisedAnswer'Op (Parsed PromisedAnswer'Op) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Marshal PromisedAnswer (Parsed PromisedAnswer) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Marshal CapDescriptor (Parsed CapDescriptor) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) CapDescriptor -> Parsed CapDescriptor -> m () Source #

Marshal Payload (Parsed Payload) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Payload -> Parsed Payload -> m () Source #

Marshal MessageTarget (Parsed MessageTarget) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) MessageTarget -> Parsed MessageTarget -> m () Source #

Marshal Join (Parsed Join) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Join -> Parsed Join -> m () Source #

Marshal Accept (Parsed Accept) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Accept -> Parsed Accept -> m () Source #

Marshal Provide (Parsed Provide) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Provide -> Parsed Provide -> m () Source #

Marshal Disembargo'context (Parsed Disembargo'context) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Marshal Disembargo (Parsed Disembargo) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Disembargo -> Parsed Disembargo -> m () Source #

Marshal Release (Parsed Release) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Release -> Parsed Release -> m () Source #

Marshal Resolve (Parsed Resolve) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Resolve -> Parsed Resolve -> m () Source #

Marshal Finish (Parsed Finish) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Finish -> Parsed Finish -> m () Source #

Marshal Return (Parsed Return) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Return -> Parsed Return -> m () Source #

Marshal Call'sendResultsTo (Parsed Call'sendResultsTo) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Marshal Call (Parsed Call) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Call -> Parsed Call -> m () Source #

Marshal Bootstrap (Parsed Bootstrap) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Bootstrap -> Parsed Bootstrap -> m () Source #

Marshal Message (Parsed Message) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Message -> Parsed Message -> m () Source #

Marshal DiscriminatorOptions (Parsed DiscriminatorOptions) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Marshal FlattenOptions (Parsed FlattenOptions) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Marshal Value'Call (Parsed Value'Call) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Value'Call -> Parsed Value'Call -> m () Source #

Marshal Value'Field (Parsed Value'Field) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Value'Field -> Parsed Value'Field -> m () Source #

Marshal Value (Parsed Value) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) Value -> Parsed Value -> m () Source #

MarshalElement a ap => Marshal (List a) (Vector ap) Source # 
Instance details

Defined in Capnp.New.Classes

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) (List a) -> Vector ap -> m () Source #

Marshal (Which Value) (Parsed (Which Value)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) (Which Value) -> Parsed (Which Value) -> m () Source #

Marshal (Which Brand'Binding) (Parsed (Which Brand'Binding)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal (Which Brand'Scope) (Parsed (Which Brand'Scope)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) (Which Brand'Scope) -> Parsed (Which Brand'Scope) -> m () Source #

Marshal (Which Type'anyPointer'unconstrained) (Parsed (Which Type'anyPointer'unconstrained)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal (Which Type'anyPointer) (Parsed (Which Type'anyPointer)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal (Which Type) (Parsed (Which Type)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) (Which Type) -> Parsed (Which Type) -> m () Source #

Marshal (Which Field'ordinal) (Parsed (Which Field'ordinal)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Marshal (Which Field) (Parsed (Which Field)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) (Which Field) -> Parsed (Which Field) -> m () Source #

Marshal (Which Node) (Parsed (Which Node)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) (Which Node) -> Parsed (Which Node) -> m () Source #

Marshal (Which PromisedAnswer'Op) (Parsed (Which PromisedAnswer'Op)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Marshal (Which CapDescriptor) (Parsed (Which CapDescriptor)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Marshal (Which MessageTarget) (Parsed (Which MessageTarget)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Marshal (Which Disembargo'context) (Parsed (Which Disembargo'context)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Marshal (Which Resolve) (Parsed (Which Resolve)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) (Which Resolve) -> Parsed (Which Resolve) -> m () Source #

Marshal (Which Return) (Parsed (Which Return)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) (Which Return) -> Parsed (Which Return) -> m () Source #

Marshal (Which Call'sendResultsTo) (Parsed (Which Call'sendResultsTo)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Marshal (Which Message) (Parsed (Which Message)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) (Which Message) -> Parsed (Which Message) -> m () Source #

Marshal (Which Value) (Parsed (Which Value)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) (Which Value) -> Parsed (Which Value) -> m () Source #

(TypeParam sturdyRef, TypeParam owner) => Marshal (Persistent'SaveResults sturdyRef owner) (Parsed (Persistent'SaveResults sturdyRef owner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) (Persistent'SaveResults sturdyRef owner) -> Parsed (Persistent'SaveResults sturdyRef owner) -> m () Source #

(TypeParam sturdyRef, TypeParam owner) => Marshal (Persistent'SaveParams sturdyRef owner) (Parsed (Persistent'SaveParams sturdyRef owner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) (Persistent'SaveParams sturdyRef owner) -> Parsed (Persistent'SaveParams sturdyRef owner) -> m () Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => Marshal (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) (Parsed (RealmGateway'export'params internalRef externalRef internalOwner externalOwner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) -> Parsed (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) -> m () Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => Marshal (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) (Parsed (RealmGateway'import'params internalRef externalRef internalOwner externalOwner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) -> Parsed (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) -> m () Source #

class AllocateList a where Source #

Like Allocate, but for allocating *lists* of a.

Minimal complete definition

Nothing

Associated Types

type ListAllocHint a Source #

Extra information needed to allocate a list of as.

Methods

newList :: RWCtx m s => ListAllocHint a -> Message ('Mut s) -> m (Raw ('Mut s) (List a)) Source #

default newList :: forall m s lr r. (RWCtx m s, lr ~ ListReprFor (ReprFor a), r ~ 'List ('Just lr), Allocate r, AllocHint r ~ ListAllocHint a) => ListAllocHint a -> Message ('Mut s) -> m (Raw ('Mut s) (List a)) Source #

Instances

Instances details
AllocateList Bool Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type ListAllocHint Bool Source #

Methods

newList :: RWCtx m s => ListAllocHint Bool -> Message ('Mut s) -> m (Raw ('Mut s) (List Bool)) Source #

AllocateList Double Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type ListAllocHint Double Source #

Methods

newList :: RWCtx m s => ListAllocHint Double -> Message ('Mut s) -> m (Raw ('Mut s) (List Double)) Source #

AllocateList Float Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type ListAllocHint Float Source #

Methods

newList :: RWCtx m s => ListAllocHint Float -> Message ('Mut s) -> m (Raw ('Mut s) (List Float)) Source #

AllocateList Int8 Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type ListAllocHint Int8 Source #

Methods

newList :: RWCtx m s => ListAllocHint Int8 -> Message ('Mut s) -> m (Raw ('Mut s) (List Int8)) Source #

AllocateList Int16 Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type ListAllocHint Int16 Source #

Methods

newList :: RWCtx m s => ListAllocHint Int16 -> Message ('Mut s) -> m (Raw ('Mut s) (List Int16)) Source #

AllocateList Int32 Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type ListAllocHint Int32 Source #

Methods

newList :: RWCtx m s => ListAllocHint Int32 -> Message ('Mut s) -> m (Raw ('Mut s) (List Int32)) Source #

AllocateList Int64 Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type ListAllocHint Int64 Source #

Methods

newList :: RWCtx m s => ListAllocHint Int64 -> Message ('Mut s) -> m (Raw ('Mut s) (List Int64)) Source #

AllocateList Word8 Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type ListAllocHint Word8 Source #

Methods

newList :: RWCtx m s => ListAllocHint Word8 -> Message ('Mut s) -> m (Raw ('Mut s) (List Word8)) Source #

AllocateList Word16 Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type ListAllocHint Word16 Source #

Methods

newList :: RWCtx m s => ListAllocHint Word16 -> Message ('Mut s) -> m (Raw ('Mut s) (List Word16)) Source #

AllocateList Word32 Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type ListAllocHint Word32 Source #

Methods

newList :: RWCtx m s => ListAllocHint Word32 -> Message ('Mut s) -> m (Raw ('Mut s) (List Word32)) Source #

AllocateList Word64 Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type ListAllocHint Word64 Source #

Methods

newList :: RWCtx m s => ListAllocHint Word64 -> Message ('Mut s) -> m (Raw ('Mut s) (List Word64)) Source #

AllocateList () Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type ListAllocHint () Source #

Methods

newList :: RWCtx m s => ListAllocHint () -> Message ('Mut s) -> m (Raw ('Mut s) (List ())) Source #

AllocateList AnyStruct Source # 
Instance details

Defined in Capnp.New.Basics

Associated Types

type ListAllocHint AnyStruct Source #

Methods

newList :: RWCtx m s => ListAllocHint AnyStruct -> Message ('Mut s) -> m (Raw ('Mut s) (List AnyStruct)) Source #

AllocateList AnyPointer Source # 
Instance details

Defined in Capnp.New.Basics

Associated Types

type ListAllocHint AnyPointer Source #

Methods

newList :: RWCtx m s => ListAllocHint AnyPointer -> Message ('Mut s) -> m (Raw ('Mut s) (List AnyPointer)) Source #

AllocateList Data Source # 
Instance details

Defined in Capnp.New.Basics

Associated Types

type ListAllocHint Data Source #

Methods

newList :: RWCtx m s => ListAllocHint Data -> Message ('Mut s) -> m (Raw ('Mut s) (List Data)) Source #

AllocateList Text Source # 
Instance details

Defined in Capnp.New.Basics

Associated Types

type ListAllocHint Text Source #

Methods

newList :: RWCtx m s => ListAllocHint Text -> Message ('Mut s) -> m (Raw ('Mut s) (List Text)) Source #

AllocateList StreamResult Source # 
Instance details

Defined in Capnp.Gen.Capnp.Stream.New

Associated Types

type ListAllocHint StreamResult Source #

AllocateList CodeGeneratorRequest'RequestedFile'Import Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

AllocateList CodeGeneratorRequest'RequestedFile Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

AllocateList CodeGeneratorRequest Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

AllocateList CapnpVersion Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint CapnpVersion Source #

AllocateList ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint ElementSize Source #

Methods

newList :: RWCtx m s => ListAllocHint ElementSize -> Message ('Mut s) -> m (Raw ('Mut s) (List ElementSize)) Source #

AllocateList Annotation Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Annotation Source #

Methods

newList :: RWCtx m s => ListAllocHint Annotation -> Message ('Mut s) -> m (Raw ('Mut s) (List Annotation)) Source #

AllocateList Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Value Source #

Methods

newList :: RWCtx m s => ListAllocHint Value -> Message ('Mut s) -> m (Raw ('Mut s) (List Value)) Source #

AllocateList Brand'Binding Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Brand'Binding Source #

AllocateList Brand'Scope Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Brand'Scope Source #

Methods

newList :: RWCtx m s => ListAllocHint Brand'Scope -> Message ('Mut s) -> m (Raw ('Mut s) (List Brand'Scope)) Source #

AllocateList Brand Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Brand Source #

Methods

newList :: RWCtx m s => ListAllocHint Brand -> Message ('Mut s) -> m (Raw ('Mut s) (List Brand)) Source #

AllocateList Type'anyPointer'implicitMethodParameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

AllocateList Type'anyPointer'parameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

AllocateList Type'anyPointer'unconstrained Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

AllocateList Type'anyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Type'anyPointer Source #

AllocateList Type'interface Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Type'interface Source #

AllocateList Type'struct Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Type'struct Source #

Methods

newList :: RWCtx m s => ListAllocHint Type'struct -> Message ('Mut s) -> m (Raw ('Mut s) (List Type'struct)) Source #

AllocateList Type'enum Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Type'enum Source #

Methods

newList :: RWCtx m s => ListAllocHint Type'enum -> Message ('Mut s) -> m (Raw ('Mut s) (List Type'enum)) Source #

AllocateList Type'list Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Type'list Source #

Methods

newList :: RWCtx m s => ListAllocHint Type'list -> Message ('Mut s) -> m (Raw ('Mut s) (List Type'list)) Source #

AllocateList Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Type Source #

Methods

newList :: RWCtx m s => ListAllocHint Type -> Message ('Mut s) -> m (Raw ('Mut s) (List Type)) Source #

AllocateList Method Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Method Source #

Methods

newList :: RWCtx m s => ListAllocHint Method -> Message ('Mut s) -> m (Raw ('Mut s) (List Method)) Source #

AllocateList Superclass Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Superclass Source #

Methods

newList :: RWCtx m s => ListAllocHint Superclass -> Message ('Mut s) -> m (Raw ('Mut s) (List Superclass)) Source #

AllocateList Enumerant Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Enumerant Source #

Methods

newList :: RWCtx m s => ListAllocHint Enumerant -> Message ('Mut s) -> m (Raw ('Mut s) (List Enumerant)) Source #

AllocateList Field'ordinal Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Field'ordinal Source #

AllocateList Field'group Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Field'group Source #

Methods

newList :: RWCtx m s => ListAllocHint Field'group -> Message ('Mut s) -> m (Raw ('Mut s) (List Field'group)) Source #

AllocateList Field'slot Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Field'slot Source #

Methods

newList :: RWCtx m s => ListAllocHint Field'slot -> Message ('Mut s) -> m (Raw ('Mut s) (List Field'slot)) Source #

AllocateList Field Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Field Source #

Methods

newList :: RWCtx m s => ListAllocHint Field -> Message ('Mut s) -> m (Raw ('Mut s) (List Field)) Source #

AllocateList Node'SourceInfo'Member Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

AllocateList Node'SourceInfo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Node'SourceInfo Source #

AllocateList Node'NestedNode Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Node'NestedNode Source #

AllocateList Node'Parameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Node'Parameter Source #

AllocateList Node'annotation Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Node'annotation Source #

AllocateList Node'const Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Node'const Source #

Methods

newList :: RWCtx m s => ListAllocHint Node'const -> Message ('Mut s) -> m (Raw ('Mut s) (List Node'const)) Source #

AllocateList Node'interface Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Node'interface Source #

AllocateList Node'enum Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Node'enum Source #

Methods

newList :: RWCtx m s => ListAllocHint Node'enum -> Message ('Mut s) -> m (Raw ('Mut s) (List Node'enum)) Source #

AllocateList Node'struct Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Node'struct Source #

Methods

newList :: RWCtx m s => ListAllocHint Node'struct -> Message ('Mut s) -> m (Raw ('Mut s) (List Node'struct)) Source #

AllocateList Node Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type ListAllocHint Node Source #

Methods

newList :: RWCtx m s => ListAllocHint Node -> Message ('Mut s) -> m (Raw ('Mut s) (List Node)) Source #

AllocateList JoinResult Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Associated Types

type ListAllocHint JoinResult Source #

Methods

newList :: RWCtx m s => ListAllocHint JoinResult -> Message ('Mut s) -> m (Raw ('Mut s) (List JoinResult)) Source #

AllocateList JoinKeyPart Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Associated Types

type ListAllocHint JoinKeyPart Source #

Methods

newList :: RWCtx m s => ListAllocHint JoinKeyPart -> Message ('Mut s) -> m (Raw ('Mut s) (List JoinKeyPart)) Source #

AllocateList ThirdPartyCapId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Associated Types

type ListAllocHint ThirdPartyCapId Source #

AllocateList RecipientId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Associated Types

type ListAllocHint RecipientId Source #

Methods

newList :: RWCtx m s => ListAllocHint RecipientId -> Message ('Mut s) -> m (Raw ('Mut s) (List RecipientId)) Source #

AllocateList ProvisionId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Associated Types

type ListAllocHint ProvisionId Source #

Methods

newList :: RWCtx m s => ListAllocHint ProvisionId -> Message ('Mut s) -> m (Raw ('Mut s) (List ProvisionId)) Source #

AllocateList VatId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Associated Types

type ListAllocHint VatId Source #

Methods

newList :: RWCtx m s => ListAllocHint VatId -> Message ('Mut s) -> m (Raw ('Mut s) (List VatId)) Source #

AllocateList Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Associated Types

type ListAllocHint Side Source #

Methods

newList :: RWCtx m s => ListAllocHint Side -> Message ('Mut s) -> m (Raw ('Mut s) (List Side)) Source #

AllocateList Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint Exception'Type Source #

AllocateList Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint Exception Source #

Methods

newList :: RWCtx m s => ListAllocHint Exception -> Message ('Mut s) -> m (Raw ('Mut s) (List Exception)) Source #

AllocateList ThirdPartyCapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

AllocateList PromisedAnswer'Op Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

AllocateList PromisedAnswer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint PromisedAnswer Source #

AllocateList CapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint CapDescriptor Source #

AllocateList Payload Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint Payload Source #

Methods

newList :: RWCtx m s => ListAllocHint Payload -> Message ('Mut s) -> m (Raw ('Mut s) (List Payload)) Source #

AllocateList MessageTarget Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint MessageTarget Source #

AllocateList Join Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint Join Source #

Methods

newList :: RWCtx m s => ListAllocHint Join -> Message ('Mut s) -> m (Raw ('Mut s) (List Join)) Source #

AllocateList Accept Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint Accept Source #

Methods

newList :: RWCtx m s => ListAllocHint Accept -> Message ('Mut s) -> m (Raw ('Mut s) (List Accept)) Source #

AllocateList Provide Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint Provide Source #

Methods

newList :: RWCtx m s => ListAllocHint Provide -> Message ('Mut s) -> m (Raw ('Mut s) (List Provide)) Source #

AllocateList Disembargo'context Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

AllocateList Disembargo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint Disembargo Source #

Methods

newList :: RWCtx m s => ListAllocHint Disembargo -> Message ('Mut s) -> m (Raw ('Mut s) (List Disembargo)) Source #

AllocateList Release Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint Release Source #

Methods

newList :: RWCtx m s => ListAllocHint Release -> Message ('Mut s) -> m (Raw ('Mut s) (List Release)) Source #

AllocateList Resolve Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint Resolve Source #

Methods

newList :: RWCtx m s => ListAllocHint Resolve -> Message ('Mut s) -> m (Raw ('Mut s) (List Resolve)) Source #

AllocateList Finish Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint Finish Source #

Methods

newList :: RWCtx m s => ListAllocHint Finish -> Message ('Mut s) -> m (Raw ('Mut s) (List Finish)) Source #

AllocateList Return Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint Return Source #

Methods

newList :: RWCtx m s => ListAllocHint Return -> Message ('Mut s) -> m (Raw ('Mut s) (List Return)) Source #

AllocateList Call'sendResultsTo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

AllocateList Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint Call Source #

Methods

newList :: RWCtx m s => ListAllocHint Call -> Message ('Mut s) -> m (Raw ('Mut s) (List Call)) Source #

AllocateList Bootstrap Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint Bootstrap Source #

Methods

newList :: RWCtx m s => ListAllocHint Bootstrap -> Message ('Mut s) -> m (Raw ('Mut s) (List Bootstrap)) Source #

AllocateList Message Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type ListAllocHint Message Source #

Methods

newList :: RWCtx m s => ListAllocHint Message -> Message0 ('Mut s) -> m (Raw ('Mut s) (List Message)) Source #

AllocateList DiscriminatorOptions Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

AllocateList FlattenOptions Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Associated Types

type ListAllocHint FlattenOptions Source #

AllocateList Value'Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Associated Types

type ListAllocHint Value'Call Source #

Methods

newList :: RWCtx m s => ListAllocHint Value'Call -> Message ('Mut s) -> m (Raw ('Mut s) (List Value'Call)) Source #

AllocateList Value'Field Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Associated Types

type ListAllocHint Value'Field Source #

Methods

newList :: RWCtx m s => ListAllocHint Value'Field -> Message ('Mut s) -> m (Raw ('Mut s) (List Value'Field)) Source #

AllocateList Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Associated Types

type ListAllocHint Value Source #

Methods

newList :: RWCtx m s => ListAllocHint Value -> Message ('Mut s) -> m (Raw ('Mut s) (List Value)) Source #

AllocateList (List a) Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type ListAllocHint (List a) Source #

Methods

newList :: RWCtx m s => ListAllocHint (List a) -> Message ('Mut s) -> m (Raw ('Mut s) (List (List a))) Source #

(TypeParam sturdyRef, TypeParam owner) => AllocateList (Persistent'SaveResults sturdyRef owner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Associated Types

type ListAllocHint (Persistent'SaveResults sturdyRef owner) Source #

Methods

newList :: RWCtx m s => ListAllocHint (Persistent'SaveResults sturdyRef owner) -> Message ('Mut s) -> m (Raw ('Mut s) (List (Persistent'SaveResults sturdyRef owner))) Source #

(TypeParam sturdyRef, TypeParam owner) => AllocateList (Persistent'SaveParams sturdyRef owner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Associated Types

type ListAllocHint (Persistent'SaveParams sturdyRef owner) Source #

Methods

newList :: RWCtx m s => ListAllocHint (Persistent'SaveParams sturdyRef owner) -> Message ('Mut s) -> m (Raw ('Mut s) (List (Persistent'SaveParams sturdyRef owner))) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => AllocateList (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Associated Types

type ListAllocHint (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) Source #

Methods

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

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => AllocateList (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Associated Types

type ListAllocHint (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) Source #

Methods

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

class Allocate a where Source #

Types which may be allocated directly inside a message.

Minimal complete definition

Nothing

Associated Types

type AllocHint a Source #

Extra information needed to allocate a value of this type, e.g. the length for a list. May be () if no extra info is needed.

Methods

new :: RWCtx m s => AllocHint a -> Message ('Mut s) -> m (Raw ('Mut s) a) Source #

new hint msg allocates a new value of type a inside msg.

default new :: (ReprFor a ~ 'Ptr ('Just pr), Allocate pr, AllocHint a ~ AllocHint pr, RWCtx m s) => AllocHint a -> Message ('Mut s) -> m (Raw ('Mut s) a) Source #

Instances

Instances details
Allocate AnyStruct Source # 
Instance details

Defined in Capnp.New.Basics

Associated Types

type AllocHint AnyStruct Source #

Methods

new :: RWCtx m s => AllocHint AnyStruct -> Message ('Mut s) -> m (Raw ('Mut s) AnyStruct) Source #

Allocate Data Source # 
Instance details

Defined in Capnp.New.Basics

Associated Types

type AllocHint Data Source #

Methods

new :: RWCtx m s => AllocHint Data -> Message ('Mut s) -> m (Raw ('Mut s) Data) Source #

Allocate Text Source # 
Instance details

Defined in Capnp.New.Basics

Associated Types

type AllocHint Text Source #

Methods

new :: RWCtx m s => AllocHint Text -> Message ('Mut s) -> m (Raw ('Mut s) Text) Source #

Allocate StreamResult Source # 
Instance details

Defined in Capnp.Gen.Capnp.Stream.New

Associated Types

type AllocHint StreamResult Source #

Methods

new :: RWCtx m s => AllocHint StreamResult -> Message ('Mut s) -> m (Raw ('Mut s) StreamResult) Source #

Allocate CodeGeneratorRequest'RequestedFile'Import Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Allocate CodeGeneratorRequest'RequestedFile Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Allocate CodeGeneratorRequest Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint CodeGeneratorRequest Source #

Allocate CapnpVersion Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint CapnpVersion Source #

Methods

new :: RWCtx m s => AllocHint CapnpVersion -> Message ('Mut s) -> m (Raw ('Mut s) CapnpVersion) Source #

Allocate Annotation Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Annotation Source #

Methods

new :: RWCtx m s => AllocHint Annotation -> Message ('Mut s) -> m (Raw ('Mut s) Annotation) Source #

Allocate Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Value Source #

Methods

new :: RWCtx m s => AllocHint Value -> Message ('Mut s) -> m (Raw ('Mut s) Value) Source #

Allocate Brand'Binding Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Brand'Binding Source #

Methods

new :: RWCtx m s => AllocHint Brand'Binding -> Message ('Mut s) -> m (Raw ('Mut s) Brand'Binding) Source #

Allocate Brand'Scope Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Brand'Scope Source #

Methods

new :: RWCtx m s => AllocHint Brand'Scope -> Message ('Mut s) -> m (Raw ('Mut s) Brand'Scope) Source #

Allocate Brand Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Brand Source #

Methods

new :: RWCtx m s => AllocHint Brand -> Message ('Mut s) -> m (Raw ('Mut s) Brand) Source #

Allocate Type'anyPointer'implicitMethodParameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Allocate Type'anyPointer'parameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Allocate Type'anyPointer'unconstrained Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Allocate Type'anyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Type'anyPointer Source #

Methods

new :: RWCtx m s => AllocHint Type'anyPointer -> Message ('Mut s) -> m (Raw ('Mut s) Type'anyPointer) Source #

Allocate Type'interface Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Type'interface Source #

Methods

new :: RWCtx m s => AllocHint Type'interface -> Message ('Mut s) -> m (Raw ('Mut s) Type'interface) Source #

Allocate Type'struct Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Type'struct Source #

Methods

new :: RWCtx m s => AllocHint Type'struct -> Message ('Mut s) -> m (Raw ('Mut s) Type'struct) Source #

Allocate Type'enum Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Type'enum Source #

Methods

new :: RWCtx m s => AllocHint Type'enum -> Message ('Mut s) -> m (Raw ('Mut s) Type'enum) Source #

Allocate Type'list Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Type'list Source #

Methods

new :: RWCtx m s => AllocHint Type'list -> Message ('Mut s) -> m (Raw ('Mut s) Type'list) Source #

Allocate Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Type Source #

Methods

new :: RWCtx m s => AllocHint Type -> Message ('Mut s) -> m (Raw ('Mut s) Type) Source #

Allocate Method Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Method Source #

Methods

new :: RWCtx m s => AllocHint Method -> Message ('Mut s) -> m (Raw ('Mut s) Method) Source #

Allocate Superclass Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Superclass Source #

Methods

new :: RWCtx m s => AllocHint Superclass -> Message ('Mut s) -> m (Raw ('Mut s) Superclass) Source #

Allocate Enumerant Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Enumerant Source #

Methods

new :: RWCtx m s => AllocHint Enumerant -> Message ('Mut s) -> m (Raw ('Mut s) Enumerant) Source #

Allocate Field'ordinal Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Field'ordinal Source #

Methods

new :: RWCtx m s => AllocHint Field'ordinal -> Message ('Mut s) -> m (Raw ('Mut s) Field'ordinal) Source #

Allocate Field'group Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Field'group Source #

Methods

new :: RWCtx m s => AllocHint Field'group -> Message ('Mut s) -> m (Raw ('Mut s) Field'group) Source #

Allocate Field'slot Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Field'slot Source #

Methods

new :: RWCtx m s => AllocHint Field'slot -> Message ('Mut s) -> m (Raw ('Mut s) Field'slot) Source #

Allocate Field Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Field Source #

Methods

new :: RWCtx m s => AllocHint Field -> Message ('Mut s) -> m (Raw ('Mut s) Field) Source #

Allocate Node'SourceInfo'Member Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Allocate Node'SourceInfo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Node'SourceInfo Source #

Methods

new :: RWCtx m s => AllocHint Node'SourceInfo -> Message ('Mut s) -> m (Raw ('Mut s) Node'SourceInfo) Source #

Allocate Node'NestedNode Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Node'NestedNode Source #

Methods

new :: RWCtx m s => AllocHint Node'NestedNode -> Message ('Mut s) -> m (Raw ('Mut s) Node'NestedNode) Source #

Allocate Node'Parameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Node'Parameter Source #

Methods

new :: RWCtx m s => AllocHint Node'Parameter -> Message ('Mut s) -> m (Raw ('Mut s) Node'Parameter) Source #

Allocate Node'annotation Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Node'annotation Source #

Methods

new :: RWCtx m s => AllocHint Node'annotation -> Message ('Mut s) -> m (Raw ('Mut s) Node'annotation) Source #

Allocate Node'const Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Node'const Source #

Methods

new :: RWCtx m s => AllocHint Node'const -> Message ('Mut s) -> m (Raw ('Mut s) Node'const) Source #

Allocate Node'interface Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Node'interface Source #

Methods

new :: RWCtx m s => AllocHint Node'interface -> Message ('Mut s) -> m (Raw ('Mut s) Node'interface) Source #

Allocate Node'enum Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Node'enum Source #

Methods

new :: RWCtx m s => AllocHint Node'enum -> Message ('Mut s) -> m (Raw ('Mut s) Node'enum) Source #

Allocate Node'struct Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Node'struct Source #

Methods

new :: RWCtx m s => AllocHint Node'struct -> Message ('Mut s) -> m (Raw ('Mut s) Node'struct) Source #

Allocate Node Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

type AllocHint Node Source #

Methods

new :: RWCtx m s => AllocHint Node -> Message ('Mut s) -> m (Raw ('Mut s) Node) Source #

Allocate JoinResult Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Associated Types

type AllocHint JoinResult Source #

Methods

new :: RWCtx m s => AllocHint JoinResult -> Message ('Mut s) -> m (Raw ('Mut s) JoinResult) Source #

Allocate JoinKeyPart Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Associated Types

type AllocHint JoinKeyPart Source #

Methods

new :: RWCtx m s => AllocHint JoinKeyPart -> Message ('Mut s) -> m (Raw ('Mut s) JoinKeyPart) Source #

Allocate ThirdPartyCapId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Associated Types

type AllocHint ThirdPartyCapId Source #

Methods

new :: RWCtx m s => AllocHint ThirdPartyCapId -> Message ('Mut s) -> m (Raw ('Mut s) ThirdPartyCapId) Source #

Allocate RecipientId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Associated Types

type AllocHint RecipientId Source #

Methods

new :: RWCtx m s => AllocHint RecipientId -> Message ('Mut s) -> m (Raw ('Mut s) RecipientId) Source #

Allocate ProvisionId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Associated Types

type AllocHint ProvisionId Source #

Methods

new :: RWCtx m s => AllocHint ProvisionId -> Message ('Mut s) -> m (Raw ('Mut s) ProvisionId) Source #

Allocate VatId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Associated Types

type AllocHint VatId Source #

Methods

new :: RWCtx m s => AllocHint VatId -> Message ('Mut s) -> m (Raw ('Mut s) VatId) Source #

Allocate Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint Exception Source #

Methods

new :: RWCtx m s => AllocHint Exception -> Message ('Mut s) -> m (Raw ('Mut s) Exception) Source #

Allocate ThirdPartyCapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Allocate PromisedAnswer'Op Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint PromisedAnswer'Op Source #

Allocate PromisedAnswer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint PromisedAnswer Source #

Methods

new :: RWCtx m s => AllocHint PromisedAnswer -> Message ('Mut s) -> m (Raw ('Mut s) PromisedAnswer) Source #

Allocate CapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint CapDescriptor Source #

Methods

new :: RWCtx m s => AllocHint CapDescriptor -> Message ('Mut s) -> m (Raw ('Mut s) CapDescriptor) Source #

Allocate Payload Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint Payload Source #

Methods

new :: RWCtx m s => AllocHint Payload -> Message ('Mut s) -> m (Raw ('Mut s) Payload) Source #

Allocate MessageTarget Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint MessageTarget Source #

Methods

new :: RWCtx m s => AllocHint MessageTarget -> Message ('Mut s) -> m (Raw ('Mut s) MessageTarget) Source #

Allocate Join Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint Join Source #

Methods

new :: RWCtx m s => AllocHint Join -> Message ('Mut s) -> m (Raw ('Mut s) Join) Source #

Allocate Accept Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint Accept Source #

Methods

new :: RWCtx m s => AllocHint Accept -> Message ('Mut s) -> m (Raw ('Mut s) Accept) Source #

Allocate Provide Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint Provide Source #

Methods

new :: RWCtx m s => AllocHint Provide -> Message ('Mut s) -> m (Raw ('Mut s) Provide) Source #

Allocate Disembargo'context Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint Disembargo'context Source #

Allocate Disembargo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint Disembargo Source #

Methods

new :: RWCtx m s => AllocHint Disembargo -> Message ('Mut s) -> m (Raw ('Mut s) Disembargo) Source #

Allocate Release Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint Release Source #

Methods

new :: RWCtx m s => AllocHint Release -> Message ('Mut s) -> m (Raw ('Mut s) Release) Source #

Allocate Resolve Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint Resolve Source #

Methods

new :: RWCtx m s => AllocHint Resolve -> Message ('Mut s) -> m (Raw ('Mut s) Resolve) Source #

Allocate Finish Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint Finish Source #

Methods

new :: RWCtx m s => AllocHint Finish -> Message ('Mut s) -> m (Raw ('Mut s) Finish) Source #

Allocate Return Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint Return Source #

Methods

new :: RWCtx m s => AllocHint Return -> Message ('Mut s) -> m (Raw ('Mut s) Return) Source #

Allocate Call'sendResultsTo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint Call'sendResultsTo Source #

Allocate Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint Call Source #

Methods

new :: RWCtx m s => AllocHint Call -> Message ('Mut s) -> m (Raw ('Mut s) Call) Source #

Allocate Bootstrap Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint Bootstrap Source #

Methods

new :: RWCtx m s => AllocHint Bootstrap -> Message ('Mut s) -> m (Raw ('Mut s) Bootstrap) Source #

Allocate Message Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

type AllocHint Message Source #

Methods

new :: RWCtx m s => AllocHint Message -> Message0 ('Mut s) -> m (Raw ('Mut s) Message) Source #

Allocate DiscriminatorOptions Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Associated Types

type AllocHint DiscriminatorOptions Source #

Allocate FlattenOptions Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Associated Types

type AllocHint FlattenOptions Source #

Methods

new :: RWCtx m s => AllocHint FlattenOptions -> Message ('Mut s) -> m (Raw ('Mut s) FlattenOptions) Source #

Allocate Value'Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Associated Types

type AllocHint Value'Call Source #

Methods

new :: RWCtx m s => AllocHint Value'Call -> Message ('Mut s) -> m (Raw ('Mut s) Value'Call) Source #

Allocate Value'Field Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Associated Types

type AllocHint Value'Field Source #

Methods

new :: RWCtx m s => AllocHint Value'Field -> Message ('Mut s) -> m (Raw ('Mut s) Value'Field) Source #

Allocate Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Associated Types

type AllocHint Value Source #

Methods

new :: RWCtx m s => AllocHint Value -> Message ('Mut s) -> m (Raw ('Mut s) Value) Source #

AllocateList a => Allocate (List a) Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type AllocHint (List a) Source #

Methods

new :: RWCtx m s => AllocHint (List a) -> Message ('Mut s) -> m (Raw ('Mut s) (List a)) Source #

(Allocate a, HasUnion a, IsStruct (Which a)) => Allocate (Which a) Source # 
Instance details

Defined in Capnp.Fields

Associated Types

type AllocHint (Which a) Source #

Methods

new :: RWCtx m s => AllocHint (Which a) -> Message ('Mut s) -> m (Raw ('Mut s) (Which a)) Source #

(TypeParam sturdyRef, TypeParam owner) => Allocate (Persistent'SaveResults sturdyRef owner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Associated Types

type AllocHint (Persistent'SaveResults sturdyRef owner) Source #

Methods

new :: RWCtx m s => AllocHint (Persistent'SaveResults sturdyRef owner) -> Message ('Mut s) -> m (Raw ('Mut s) (Persistent'SaveResults sturdyRef owner)) Source #

(TypeParam sturdyRef, TypeParam owner) => Allocate (Persistent'SaveParams sturdyRef owner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Associated Types

type AllocHint (Persistent'SaveParams sturdyRef owner) Source #

Methods

new :: RWCtx m s => AllocHint (Persistent'SaveParams sturdyRef owner) -> Message ('Mut s) -> m (Raw ('Mut s) (Persistent'SaveParams sturdyRef owner)) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => Allocate (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Associated Types

type AllocHint (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) Source #

Methods

new :: RWCtx m s => AllocHint (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) -> Message ('Mut s) -> m (Raw ('Mut s) (RealmGateway'export'params internalRef externalRef internalOwner externalOwner)) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => Allocate (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Associated Types

type AllocHint (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) Source #

Methods

new :: RWCtx m s => AllocHint (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) -> Message ('Mut s) -> m (Raw ('Mut s) (RealmGateway'import'params internalRef externalRef internalOwner externalOwner)) Source #

class (Parse t p, Allocate t) => EstimateAlloc t p where Source #

Types where the necessary allocation is inferrable from the parsed form.

...this is most types.

Minimal complete definition

Nothing

Methods

estimateAlloc :: p -> AllocHint t Source #

Determine the appropriate hint needed to allocate space for the serialied form of the value.

default estimateAlloc :: AllocHint t ~ () => p -> AllocHint t Source #

Instances

Instances details
EstimateAlloc Data ByteString Source # 
Instance details

Defined in Capnp.New.Basics

EstimateAlloc AnyStruct (Parsed AnyStruct) Source # 
Instance details

Defined in Capnp.New.Basics

EstimateAlloc StreamResult (Parsed StreamResult) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Stream.New

EstimateAlloc CodeGeneratorRequest'RequestedFile'Import (Parsed CodeGeneratorRequest'RequestedFile'Import) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc CodeGeneratorRequest'RequestedFile (Parsed CodeGeneratorRequest'RequestedFile) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc CodeGeneratorRequest (Parsed CodeGeneratorRequest) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc CapnpVersion (Parsed CapnpVersion) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Annotation (Parsed Annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Value (Parsed Value) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Brand'Binding (Parsed Brand'Binding) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Brand'Scope (Parsed Brand'Scope) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Brand (Parsed Brand) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Type'anyPointer'implicitMethodParameter (Parsed Type'anyPointer'implicitMethodParameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Type'anyPointer'parameter (Parsed Type'anyPointer'parameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Type'anyPointer'unconstrained (Parsed Type'anyPointer'unconstrained) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Type'anyPointer (Parsed Type'anyPointer) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Type'interface (Parsed Type'interface) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Type'struct (Parsed Type'struct) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Type'enum (Parsed Type'enum) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Type'list (Parsed Type'list) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Type (Parsed Type) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Method (Parsed Method) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Superclass (Parsed Superclass) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Enumerant (Parsed Enumerant) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Field'ordinal (Parsed Field'ordinal) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Field'group (Parsed Field'group) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Field'slot (Parsed Field'slot) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Field (Parsed Field) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Node'SourceInfo'Member (Parsed Node'SourceInfo'Member) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Node'SourceInfo (Parsed Node'SourceInfo) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Node'NestedNode (Parsed Node'NestedNode) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Node'Parameter (Parsed Node'Parameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Node'annotation (Parsed Node'annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Node'const (Parsed Node'const) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Node'interface (Parsed Node'interface) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Node'enum (Parsed Node'enum) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Node'struct (Parsed Node'struct) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc Node (Parsed Node) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

EstimateAlloc JoinResult (Parsed JoinResult) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

EstimateAlloc JoinKeyPart (Parsed JoinKeyPart) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

EstimateAlloc ThirdPartyCapId (Parsed ThirdPartyCapId) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

EstimateAlloc RecipientId (Parsed RecipientId) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

EstimateAlloc ProvisionId (Parsed ProvisionId) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

EstimateAlloc VatId (Parsed VatId) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

EstimateAlloc Exception (Parsed Exception) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc ThirdPartyCapDescriptor (Parsed ThirdPartyCapDescriptor) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc PromisedAnswer'Op (Parsed PromisedAnswer'Op) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc PromisedAnswer (Parsed PromisedAnswer) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc CapDescriptor (Parsed CapDescriptor) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc Payload (Parsed Payload) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc MessageTarget (Parsed MessageTarget) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc Join (Parsed Join) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc Accept (Parsed Accept) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc Provide (Parsed Provide) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc Disembargo'context (Parsed Disembargo'context) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc Disembargo (Parsed Disembargo) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc Release (Parsed Release) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc Resolve (Parsed Resolve) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc Finish (Parsed Finish) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc Return (Parsed Return) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc Call'sendResultsTo (Parsed Call'sendResultsTo) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc Call (Parsed Call) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc Bootstrap (Parsed Bootstrap) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc Message (Parsed Message) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

EstimateAlloc DiscriminatorOptions (Parsed DiscriminatorOptions) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

EstimateAlloc FlattenOptions (Parsed FlattenOptions) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

EstimateAlloc Value'Call (Parsed Value'Call) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

EstimateAlloc Value'Field (Parsed Value'Field) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

EstimateAlloc Value (Parsed Value) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

(Allocate (Which a), AllocHint (Which a) ~ (), Parse (Which a) p) => EstimateAlloc (Which a) p Source # 
Instance details

Defined in Capnp.Fields

Methods

estimateAlloc :: p -> AllocHint (Which a) Source #

MarshalElement a ap => EstimateAlloc (List a) (Vector ap) Source # 
Instance details

Defined in Capnp.New.Classes

(TypeParam sturdyRef, TypeParam owner) => EstimateAlloc (Persistent'SaveResults sturdyRef owner) (Parsed (Persistent'SaveResults sturdyRef owner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

estimateAlloc :: Parsed (Persistent'SaveResults sturdyRef owner) -> AllocHint (Persistent'SaveResults sturdyRef owner) Source #

(TypeParam sturdyRef, TypeParam owner) => EstimateAlloc (Persistent'SaveParams sturdyRef owner) (Parsed (Persistent'SaveParams sturdyRef owner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

estimateAlloc :: Parsed (Persistent'SaveParams sturdyRef owner) -> AllocHint (Persistent'SaveParams sturdyRef owner) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => EstimateAlloc (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) (Parsed (RealmGateway'export'params internalRef externalRef internalOwner externalOwner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

estimateAlloc :: Parsed (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) -> AllocHint (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => EstimateAlloc (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) (Parsed (RealmGateway'import'params internalRef externalRef internalOwner externalOwner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

estimateAlloc :: Parsed (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) -> AllocHint (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) Source #

class Parse t p | t -> p, p -> t where Source #

Capnp types that can be parsed into a more "natural" Haskell form.

  • t is the capnproto type.
  • p is the type of the parsed value.

Minimal complete definition

parse

Methods

parse :: ReadCtx m 'Const => Raw 'Const t -> m p Source #

Parse a value from a constant message

encode :: RWCtx m s => Message ('Mut s) -> p -> m (Raw ('Mut s) t) Source #

Encode a value into Raw form, using the message as storage.

default encode :: (RWCtx m s, EstimateAlloc t p, Marshal t p) => Message ('Mut s) -> p -> m (Raw ('Mut s) t) Source #

Instances

Instances details
Parse Bool Bool Source # 
Instance details

Defined in Capnp.New.Classes

Methods

parse :: ReadCtx m 'Const => Raw 'Const Bool -> m Bool Source #

encode :: RWCtx m s => Message ('Mut s) -> Bool -> m (Raw ('Mut s) Bool) Source #

Parse Double Double Source # 
Instance details

Defined in Capnp.New.Classes

Methods

parse :: ReadCtx m 'Const => Raw 'Const Double -> m Double Source #

encode :: RWCtx m s => Message ('Mut s) -> Double -> m (Raw ('Mut s) Double) Source #

Parse Float Float Source # 
Instance details

Defined in Capnp.New.Classes

Methods

parse :: ReadCtx m 'Const => Raw 'Const Float -> m Float Source #

encode :: RWCtx m s => Message ('Mut s) -> Float -> m (Raw ('Mut s) Float) Source #

Parse Int8 Int8 Source # 
Instance details

Defined in Capnp.New.Classes

Methods

parse :: ReadCtx m 'Const => Raw 'Const Int8 -> m Int8 Source #

encode :: RWCtx m s => Message ('Mut s) -> Int8 -> m (Raw ('Mut s) Int8) Source #

Parse Int16 Int16 Source # 
Instance details

Defined in Capnp.New.Classes

Methods

parse :: ReadCtx m 'Const => Raw 'Const Int16 -> m Int16 Source #

encode :: RWCtx m s => Message ('Mut s) -> Int16 -> m (Raw ('Mut s) Int16) Source #

Parse Int32 Int32 Source # 
Instance details

Defined in Capnp.New.Classes

Methods

parse :: ReadCtx m 'Const => Raw 'Const Int32 -> m Int32 Source #

encode :: RWCtx m s => Message ('Mut s) -> Int32 -> m (Raw ('Mut s) Int32) Source #

Parse Int64 Int64 Source # 
Instance details

Defined in Capnp.New.Classes

Methods

parse :: ReadCtx m 'Const => Raw 'Const Int64 -> m Int64 Source #

encode :: RWCtx m s => Message ('Mut s) -> Int64 -> m (Raw ('Mut s) Int64) Source #

Parse Word8 Word8 Source # 
Instance details

Defined in Capnp.New.Classes

Methods

parse :: ReadCtx m 'Const => Raw 'Const Word8 -> m Word8 Source #

encode :: RWCtx m s => Message ('Mut s) -> Word8 -> m (Raw ('Mut s) Word8) Source #

Parse Word16 Word16 Source # 
Instance details

Defined in Capnp.New.Classes

Methods

parse :: ReadCtx m 'Const => Raw 'Const Word16 -> m Word16 Source #

encode :: RWCtx m s => Message ('Mut s) -> Word16 -> m (Raw ('Mut s) Word16) Source #

Parse Word32 Word32 Source # 
Instance details

Defined in Capnp.New.Classes

Methods

parse :: ReadCtx m 'Const => Raw 'Const Word32 -> m Word32 Source #

encode :: RWCtx m s => Message ('Mut s) -> Word32 -> m (Raw ('Mut s) Word32) Source #

Parse Word64 Word64 Source # 
Instance details

Defined in Capnp.New.Classes

Methods

parse :: ReadCtx m 'Const => Raw 'Const Word64 -> m Word64 Source #

encode :: RWCtx m s => Message ('Mut s) -> Word64 -> m (Raw ('Mut s) Word64) Source #

Parse () () Source # 
Instance details

Defined in Capnp.New.Classes

Methods

parse :: ReadCtx m 'Const => Raw 'Const () -> m () Source #

encode :: RWCtx m s => Message ('Mut s) -> () -> m (Raw ('Mut s) ()) Source #

Parse Capability Client Source # 
Instance details

Defined in Capnp.New.Basics

Methods

parse :: ReadCtx m 'Const => Raw 'Const Capability -> m Client Source #

encode :: RWCtx m s => Message ('Mut s) -> Client -> m (Raw ('Mut s) Capability) Source #

Parse Data ByteString Source # 
Instance details

Defined in Capnp.New.Basics

Methods

parse :: ReadCtx m 'Const => Raw 'Const Data -> m ByteString Source #

encode :: RWCtx m s => Message ('Mut s) -> ByteString -> m (Raw ('Mut s) Data) Source #

Parse Text Text Source # 
Instance details

Defined in Capnp.New.Basics

Methods

parse :: ReadCtx m 'Const => Raw 'Const Text -> m Text0 Source #

encode :: RWCtx m s => Message ('Mut s) -> Text0 -> m (Raw ('Mut s) Text) Source #

Parse ElementSize ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Side Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Side -> m Side Source #

encode :: RWCtx m s => Message ('Mut s) -> Side -> m (Raw ('Mut s) Side) Source #

Parse Exception'Type Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Parse AnyStruct (Parsed AnyStruct) Source # 
Instance details

Defined in Capnp.New.Basics

Parse AnyList (Parsed AnyList) Source # 
Instance details

Defined in Capnp.New.Basics

Methods

parse :: ReadCtx m 'Const => Raw 'Const AnyList -> m (Parsed AnyList) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed AnyList -> m (Raw ('Mut s) AnyList) Source #

Parse AnyPointer (Parsed AnyPointer) Source # 
Instance details

Defined in Capnp.New.Basics

Parse StreamResult (Parsed StreamResult) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Stream.New

Parse CodeGeneratorRequest'RequestedFile'Import (Parsed CodeGeneratorRequest'RequestedFile'Import) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse CodeGeneratorRequest'RequestedFile (Parsed CodeGeneratorRequest'RequestedFile) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse CodeGeneratorRequest (Parsed CodeGeneratorRequest) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse CapnpVersion (Parsed CapnpVersion) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Annotation (Parsed Annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Value (Parsed Value) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Value -> m (Parsed Value) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed Value -> m (Raw ('Mut s) Value) Source #

Parse Brand'Binding (Parsed Brand'Binding) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Brand'Scope (Parsed Brand'Scope) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Brand (Parsed Brand) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Brand -> m (Parsed Brand) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed Brand -> m (Raw ('Mut s) Brand) Source #

Parse Type'anyPointer'implicitMethodParameter (Parsed Type'anyPointer'implicitMethodParameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Type'anyPointer'parameter (Parsed Type'anyPointer'parameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Type'anyPointer'unconstrained (Parsed Type'anyPointer'unconstrained) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Type'anyPointer (Parsed Type'anyPointer) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Type'interface (Parsed Type'interface) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Type'struct (Parsed Type'struct) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Type'enum (Parsed Type'enum) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Type'list (Parsed Type'list) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Type (Parsed Type) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Type -> m (Parsed Type) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed Type -> m (Raw ('Mut s) Type) Source #

Parse Method (Parsed Method) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Method -> m (Parsed Method) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed Method -> m (Raw ('Mut s) Method) Source #

Parse Superclass (Parsed Superclass) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Enumerant (Parsed Enumerant) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Field'ordinal (Parsed Field'ordinal) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Field'group (Parsed Field'group) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Field'slot (Parsed Field'slot) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Field (Parsed Field) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Field -> m (Parsed Field) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed Field -> m (Raw ('Mut s) Field) Source #

Parse Node'SourceInfo'Member (Parsed Node'SourceInfo'Member) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Node'SourceInfo (Parsed Node'SourceInfo) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Node'NestedNode (Parsed Node'NestedNode) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Node'Parameter (Parsed Node'Parameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Node'annotation (Parsed Node'annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Node'const (Parsed Node'const) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Node'interface (Parsed Node'interface) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Node'enum (Parsed Node'enum) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Node'struct (Parsed Node'struct) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse Node (Parsed Node) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Node -> m (Parsed Node) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed Node -> m (Raw ('Mut s) Node) Source #

Parse JoinResult (Parsed JoinResult) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Parse JoinKeyPart (Parsed JoinKeyPart) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Parse ThirdPartyCapId (Parsed ThirdPartyCapId) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Parse RecipientId (Parsed RecipientId) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Parse ProvisionId (Parsed ProvisionId) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Parse VatId (Parsed VatId) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const VatId -> m (Parsed VatId) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed VatId -> m (Raw ('Mut s) VatId) Source #

Parse Exception (Parsed Exception) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Parse ThirdPartyCapDescriptor (Parsed ThirdPartyCapDescriptor) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Parse PromisedAnswer'Op (Parsed PromisedAnswer'Op) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Parse PromisedAnswer (Parsed PromisedAnswer) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Parse CapDescriptor (Parsed CapDescriptor) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Parse Payload (Parsed Payload) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Payload -> m (Parsed Payload) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed Payload -> m (Raw ('Mut s) Payload) Source #

Parse MessageTarget (Parsed MessageTarget) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Parse Join (Parsed Join) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Join -> m (Parsed Join) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed Join -> m (Raw ('Mut s) Join) Source #

Parse Accept (Parsed Accept) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Accept -> m (Parsed Accept) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed Accept -> m (Raw ('Mut s) Accept) Source #

Parse Provide (Parsed Provide) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Provide -> m (Parsed Provide) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed Provide -> m (Raw ('Mut s) Provide) Source #

Parse Disembargo'context (Parsed Disembargo'context) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Parse Disembargo (Parsed Disembargo) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Parse Release (Parsed Release) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Release -> m (Parsed Release) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed Release -> m (Raw ('Mut s) Release) Source #

Parse Resolve (Parsed Resolve) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Resolve -> m (Parsed Resolve) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed Resolve -> m (Raw ('Mut s) Resolve) Source #

Parse Finish (Parsed Finish) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Finish -> m (Parsed Finish) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed Finish -> m (Raw ('Mut s) Finish) Source #

Parse Return (Parsed Return) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Return -> m (Parsed Return) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed Return -> m (Raw ('Mut s) Return) Source #

Parse Call'sendResultsTo (Parsed Call'sendResultsTo) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Parse Call (Parsed Call) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Call -> m (Parsed Call) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed Call -> m (Raw ('Mut s) Call) Source #

Parse Bootstrap (Parsed Bootstrap) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Parse Message (Parsed Message) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Message -> m (Parsed Message) Source #

encode :: RWCtx m s => Message0 ('Mut s) -> Parsed Message -> m (Raw ('Mut s) Message) Source #

Parse DiscriminatorOptions (Parsed DiscriminatorOptions) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Parse FlattenOptions (Parsed FlattenOptions) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Parse Value'Call (Parsed Value'Call) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Parse Value'Field (Parsed Value'Field) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Parse Value (Parsed Value) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const Value -> m (Parsed Value) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed Value -> m (Raw ('Mut s) Value) Source #

MarshalElement a ap => Parse (List a) (Vector ap) Source # 
Instance details

Defined in Capnp.New.Classes

Methods

parse :: ReadCtx m 'Const => Raw 'Const (List a) -> m (Vector ap) Source #

encode :: RWCtx m s => Message ('Mut s) -> Vector ap -> m (Raw ('Mut s) (List a)) Source #

Parse (Which Value) (Parsed (Which Value)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (Which Value) -> m (Parsed (Which Value)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed (Which Value) -> m (Raw ('Mut s) (Which Value)) Source #

Parse (Which Brand'Binding) (Parsed (Which Brand'Binding)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse (Which Brand'Scope) (Parsed (Which Brand'Scope)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse (Which Type'anyPointer'unconstrained) (Parsed (Which Type'anyPointer'unconstrained)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse (Which Type'anyPointer) (Parsed (Which Type'anyPointer)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse (Which Type) (Parsed (Which Type)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (Which Type) -> m (Parsed (Which Type)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed (Which Type) -> m (Raw ('Mut s) (Which Type)) Source #

Parse (Which Field'ordinal) (Parsed (Which Field'ordinal)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Parse (Which Field) (Parsed (Which Field)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (Which Field) -> m (Parsed (Which Field)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed (Which Field) -> m (Raw ('Mut s) (Which Field)) Source #

Parse (Which Node) (Parsed (Which Node)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (Which Node) -> m (Parsed (Which Node)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed (Which Node) -> m (Raw ('Mut s) (Which Node)) Source #

Parse (Which PromisedAnswer'Op) (Parsed (Which PromisedAnswer'Op)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Parse (Which CapDescriptor) (Parsed (Which CapDescriptor)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Parse (Which MessageTarget) (Parsed (Which MessageTarget)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Parse (Which Disembargo'context) (Parsed (Which Disembargo'context)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Parse (Which Resolve) (Parsed (Which Resolve)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (Which Resolve) -> m (Parsed (Which Resolve)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed (Which Resolve) -> m (Raw ('Mut s) (Which Resolve)) Source #

Parse (Which Return) (Parsed (Which Return)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (Which Return) -> m (Parsed (Which Return)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed (Which Return) -> m (Raw ('Mut s) (Which Return)) Source #

Parse (Which Call'sendResultsTo) (Parsed (Which Call'sendResultsTo)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Parse (Which Message) (Parsed (Which Message)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (Which Message) -> m (Parsed (Which Message)) Source #

encode :: RWCtx m s => Message0 ('Mut s) -> Parsed (Which Message) -> m (Raw ('Mut s) (Which Message)) Source #

Parse (Which Value) (Parsed (Which Value)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (Which Value) -> m (Parsed (Which Value)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed (Which Value) -> m (Raw ('Mut s) (Which Value)) Source #

(TypeParam sturdyRef, TypeParam owner) => Parse (Persistent'SaveResults sturdyRef owner) (Parsed (Persistent'SaveResults sturdyRef owner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (Persistent'SaveResults sturdyRef owner) -> m (Parsed (Persistent'SaveResults sturdyRef owner)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed (Persistent'SaveResults sturdyRef owner) -> m (Raw ('Mut s) (Persistent'SaveResults sturdyRef owner)) Source #

(TypeParam sturdyRef, TypeParam owner) => Parse (Persistent'SaveParams sturdyRef owner) (Parsed (Persistent'SaveParams sturdyRef owner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (Persistent'SaveParams sturdyRef owner) -> m (Parsed (Persistent'SaveParams sturdyRef owner)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed (Persistent'SaveParams sturdyRef owner) -> m (Raw ('Mut s) (Persistent'SaveParams sturdyRef owner)) Source #

(TypeParam sturdyRef, TypeParam owner) => Parse (Persistent sturdyRef owner) (Client (Persistent sturdyRef owner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (Persistent sturdyRef owner) -> m (Client (Persistent sturdyRef owner)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Client (Persistent sturdyRef owner) -> m (Raw ('Mut s) (Persistent sturdyRef owner)) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => Parse (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) (Parsed (RealmGateway'export'params internalRef externalRef internalOwner externalOwner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) -> m (Parsed (RealmGateway'export'params internalRef externalRef internalOwner externalOwner)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) -> m (Raw ('Mut s) (RealmGateway'export'params internalRef externalRef internalOwner externalOwner)) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => Parse (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) (Parsed (RealmGateway'import'params internalRef externalRef internalOwner externalOwner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) -> m (Parsed (RealmGateway'import'params internalRef externalRef internalOwner externalOwner)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Parsed (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) -> m (Raw ('Mut s) (RealmGateway'import'params internalRef externalRef internalOwner externalOwner)) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => Parse (RealmGateway internalRef externalRef internalOwner externalOwner) (Client (RealmGateway internalRef externalRef internalOwner externalOwner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (RealmGateway internalRef externalRef internalOwner externalOwner) -> m (Client (RealmGateway internalRef externalRef internalOwner externalOwner)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Client (RealmGateway internalRef externalRef internalOwner externalOwner) -> m (Raw ('Mut s) (RealmGateway internalRef externalRef internalOwner externalOwner)) Source #

newFromRepr :: forall a r m s. (Allocate r, 'Ptr ('Just r) ~ ReprFor a, RWCtx m s) => AllocHint r -> Message ('Mut s) -> m (Raw ('Mut s) a) Source #

Implementation of new valid for types whose AllocHint is the same as that of their underlying representation.

newTypedStruct :: forall a m s. (TypedStruct a, RWCtx m s) => Message ('Mut s) -> m (Raw ('Mut s) a) Source #

Allocate a new typed struct. Mainly used as the value for new for in generated instances of Allocate.

newTypedStructList :: forall a m s. (TypedStruct a, RWCtx m s) => Int -> Message ('Mut s) -> m (Raw ('Mut s) (List a)) Source #

Like newTypedStruct, but for lists.

structSizes :: forall a. TypedStruct a => (Word16, Word16) Source #

Get the maximum word and pointer counts needed for a struct type's fields.

newRoot :: forall a m s. (RWCtx m s, IsStruct a, Allocate a) => AllocHint a -> Message ('Mut s) -> m (Raw ('Mut s) a) Source #

Like new, but also sets the value as the root of the message.

readField :: forall k a b mut m. (IsStruct a, ReadCtx m mut) => Field k a b -> Raw mut a -> m (Raw mut b) Source #

Read the value of a field of a struct.

hasField :: (ReadCtx m mut, IsStruct a, IsPtr b) => Field 'Slot a b -> Raw mut a -> m Bool Source #

Return whether the specified field is present. Only applicable for pointer fields.

getField :: (IsStruct a, ReprFor b ~ 'Data sz, Parse b bp) => Field 'Slot a b -> Raw 'Const a -> bp Source #

Like readField, but:

  • Doesn't need the monadic context; can be used in pure code.
  • Only works for immutable values.
  • Only works for fields in the struct's data section.

setField :: forall a b m s. (IsStruct a, RWCtx m s) => Field 'Slot a b -> Raw ('Mut s) b -> Raw ('Mut s) a -> m () Source #

Set a struct field to a value. Not usable for group fields.

newField :: forall a b m s. (IsStruct a, Allocate b, RWCtx m s) => Field 'Slot a b -> AllocHint b -> Raw ('Mut s) a -> m (Raw ('Mut s) b) Source #

Allocate space for the value of a field, and return it.

encodeField :: forall a b m s bp. (IsStruct a, Parse b bp, RWCtx m s) => Field 'Slot a b -> bp -> Raw ('Mut s) a -> m () Source #

Marshal a parsed value into a struct's field.

parseField :: (IsStruct a, Parse b bp, ReadCtx m 'Const) => Field k a b -> Raw 'Const a -> m bp Source #

parse a struct's field and return its parsed form.

setVariant :: forall a b m s. (HasUnion a, RWCtx m s) => Variant 'Slot a b -> Raw ('Mut s) a -> Raw ('Mut s) b -> m () Source #

Set the struct's anonymous union to the given variant, with the supplied value as its argument. Not applicable for variants whose argument is a group; use initVariant instead.

encodeVariant :: forall a b m s bp. (HasUnion a, Parse b bp, RWCtx m s) => Variant 'Slot a b -> bp -> Raw ('Mut s) a -> m () Source #

Set the struct's anonymous union to the given variant, marshalling the supplied value into the message to be its argument. Not applicable for variants whose argument is a group; use initVariant instead.

initVariant :: forall a b m s. (HasUnion a, RWCtx m s) => Variant 'Group a b -> Raw ('Mut s) a -> m (Raw ('Mut s) b) Source #

Set the struct's anonymous union to the given variant, returning the variant's argument, which must be a group (for non-group fields, use setVariant or encodeVariant.

structUnion :: HasUnion a => Raw mut a -> Raw mut (Which a) Source #

Get the anonymous union for a struct.

unionStruct :: HasUnion a => Raw mut (Which a) -> Raw mut a Source #

Get the struct enclosing an anonymous union.

structWhich :: forall a mut m. (ReadCtx m mut, HasUnion a) => Raw mut a -> m (RawWhich mut a) Source #

Get a non-opaque view on the struct's anonymous union, which can be used to pattern match on.

unionWhich :: forall a mut m. (ReadCtx m mut, HasUnion a) => Raw mut (Which a) -> m (RawWhich mut a) Source #

Get a non-opaque view on the anonymous union, which can be used to pattern match on.

msgToBuilder :: Message 'Const -> Builder Source #

Convert an immutable message to a bytestring Builder. To convert a mutable message, freeze it first.

msgToLBS :: Message 'Const -> ByteString Source #

Convert an immutable message to a lazy ByteString. To convert a mutable message, freeze it first.

msgToBS :: Message 'Const -> ByteString Source #

Convert an immutable message to a strict ByteString. To convert a mutable message, freeze it first.

msgToValue :: (MonadThrow m, MonadReadMessage mut (LimitT m), MonadReadMessage mut m, FromStruct mut a) => Message mut -> m a Source #

Convert a message to a value.

bsToMsg :: MonadThrow m => ByteString -> m (Message 'Const) Source #

Convert a strict ByteString to a message.

bsToValue :: (MonadThrow m, FromStruct 'Const a) => ByteString -> m a Source #

Convert a strict ByteString to a value.

lbsToMsg :: MonadThrow m => ByteString -> m (Message 'Const) Source #

Convert a lazy ByteString to a message.

lbsToValue :: (MonadThrow m, FromStruct 'Const a) => ByteString -> m a Source #

Convert a lazy ByteString to a value.

valueToBuilder :: (MonadLimit m, WriteCtx m s, Cerialize s a, ToStruct ('Mut s) (Cerial ('Mut s) a)) => a -> m Builder Source #

Convert a value to a Builder.

valueToBS :: (MonadLimit m, WriteCtx m s, Cerialize s a, ToStruct ('Mut s) (Cerial ('Mut s) a)) => a -> m ByteString Source #

Convert a value to a strict ByteString.

valueToLBS :: (MonadLimit m, WriteCtx m s, Cerialize s a, ToStruct ('Mut s) (Cerial ('Mut s) a)) => a -> m ByteString Source #

Convert a value to a lazy ByteString.

valueToMsg :: (MonadLimit m, WriteCtx m s, Cerialize s a, ToStruct ('Mut s) (Cerial ('Mut s) a)) => a -> m (Message ('Mut s)) Source #

Convert a value to a message.

msgToRaw :: forall a m mut. (ReadCtx m mut, IsStruct a) => Message mut -> m (Raw mut a) Source #

Get the root pointer of a message, wrapped as a Raw.

msgToParsed :: forall a m pa. (ReadCtx m 'Const, IsStruct a, Parse a pa) => Message 'Const -> m pa Source #

Get the root pointer of a message, as a parsed ADT.

parsedToRaw :: forall a m pa s. (RWCtx m s, IsStruct a, Parse a pa) => pa -> m (Raw ('Mut s) a) Source #

Serialize the parsed form of a struct into its Raw form, and make it the root of its message.

parsedToMsg :: forall a m pa s. (RWCtx m s, IsStruct a, Parse a pa) => pa -> m (Message ('Mut s)) Source #

Serialize the parsed form of a struct into a message with that value as its root, returning the message.

parsedToBuilder :: forall a m pa s. (RWCtx m s, IsStruct a, Parse a pa) => pa -> m Builder Source #

Serialize the parsed form of a struct and return it as a Builder

parsedToLBS :: forall a m pa s. (RWCtx m s, IsStruct a, Parse a pa) => pa -> m ByteString Source #

Serialize the parsed form of a struct and return it as a lazy ByteString

parsedToBS :: forall a m pa s. (RWCtx m s, IsStruct a, Parse a pa) => pa -> m ByteString Source #

Serialize the parsed form of a struct and return it as a strict ByteString

hGetValue :: FromStruct 'Const a => Handle -> WordCount -> IO a Source #

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

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

sGetValue :: FromStruct 'Const a => Socket -> WordCount -> IO a Source #

Like hGetValue, except that it takes a socket instead of a Handle.

sGetMsg :: Socket -> WordCount -> IO (Message 'Const) Source #

Like hGetMsg, except that it takes a socket instead of a Handle.

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

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

sPutMsg :: Socket -> Message 'Const -> IO () Source #

Like hPutMsg, except that it takes a Socket instead of a Handle.

sPutValue :: (Cerialize RealWorld a, ToStruct ('Mut RealWorld) (Cerial ('Mut RealWorld) a)) => Socket -> a -> IO () Source #

Like hPutValue, except that it takes a Socket instead of a Handle.

hGetParsed :: forall a pa. (IsStruct a, Parse a pa) => Handle -> WordCount -> IO pa Source #

Read a struct from the handle in its parsed form, using the supplied read limit.

sGetParsed :: forall a pa. (IsStruct a, Parse a pa) => Socket -> WordCount -> IO pa Source #

Read a struct from the socket in its parsed form, using the supplied read limit.

getParsed :: (IsStruct a, Parse a pa) => WordCount -> IO pa Source #

Read a struct from stdin in its parsed form, using the supplied read limit.

hPutParsed :: (IsStruct a, Parse a pa) => Handle -> pa -> IO () Source #

Write the parsed form of a struct to the handle

putParsed :: (IsStruct a, Parse a pa) => pa -> IO () Source #

Write the parsed form of a struct to stdout

sPutParsed :: (IsStruct a, Parse a pa) => Socket -> pa -> IO () Source #

Write the parsed form of a struct to the socket.

hGetRaw :: IsStruct a => Handle -> WordCount -> IO (Raw 'Const a) Source #

Read a struct from the handle using the supplied read limit, and return its root pointer.

getRaw :: IsStruct a => WordCount -> IO (Raw 'Const a) Source #

Read a struct from stdin using the supplied read limit, and return its root pointer.

sGetRaw :: IsStruct a => Socket -> WordCount -> IO (Raw 'Const a) Source #

Read a struct from the socket using the supplied read limit, and return its root pointer.

class AsClient f where Source #

The AsClient class allows callers of rpc methods to abstract over Clients and Pipelines. asClient converts either of those to a client so that methods can be invoked on it.

Methods

asClient :: MonadSTM m => IsCap c => f c -> m (Client c) Source #

Instances

Instances details
AsClient Client Source # 
Instance details

Defined in Capnp.Repr.Methods

Methods

asClient :: (MonadSTM m, IsCap c) => Client c -> m (Client c) Source #

AsClient Pipeline Source # 
Instance details

Defined in Capnp.Repr.Methods

Methods

asClient :: (MonadSTM m, IsCap c) => Pipeline c -> m (Client c) Source #

newtype Client a Source #

Constructors

Client Client 

Instances

Instances details
AsClient Client Source # 
Instance details

Defined in Capnp.Repr.Methods

Methods

asClient :: (MonadSTM m, IsCap c) => Client c -> m (Client c) Source #

Eq (Client a) Source # 
Instance details

Defined in Capnp.Repr.Methods

Methods

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

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

Show (Client a) Source # 
Instance details

Defined in Capnp.Repr.Methods

Methods

showsPrec :: Int -> Client a -> ShowS #

show :: Client a -> String #

showList :: [Client a] -> ShowS #

ReprFor a ~ 'Ptr ('Just 'Cap) => IsClient (Client a) Source # 
Instance details

Defined in Capnp.Repr.Methods

(TypeParam sturdyRef, TypeParam owner) => Parse (Persistent sturdyRef owner) (Client (Persistent sturdyRef owner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (Persistent sturdyRef owner) -> m (Client (Persistent sturdyRef owner)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Client (Persistent sturdyRef owner) -> m (Raw ('Mut s) (Persistent sturdyRef owner)) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => Parse (RealmGateway internalRef externalRef internalOwner externalOwner) (Client (RealmGateway internalRef externalRef internalOwner externalOwner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (RealmGateway internalRef externalRef internalOwner externalOwner) -> m (Client (RealmGateway internalRef externalRef internalOwner externalOwner)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Client (RealmGateway internalRef externalRef internalOwner externalOwner) -> m (Raw ('Mut s) (RealmGateway internalRef externalRef internalOwner externalOwner)) Source #

newtype Pipeline a Source #

A Pipeline a is a reference to possibly-not-resolved result from a method call.

Constructors

Pipeline Pipeline 

Instances

Instances details
AsClient Pipeline Source # 
Instance details

Defined in Capnp.Repr.Methods

Methods

asClient :: (MonadSTM m, IsCap c) => Pipeline c -> m (Client c) Source #

class (IsCap c, IsStruct p, IsStruct r) => HasMethod (name :: Symbol) c p r | name c -> p r where Source #

An instance HasMethod name c p r indicates that the interface type c has a method named name with parameter type p and return type r. The generated code includes instances of this for each method in the schema.

Methods

methodByLabel :: Method c p r Source #

Instances

Instances details
(TypeParam sturdyRef, TypeParam owner) => HasMethod "save" (Persistent sturdyRef owner) (Persistent'SaveParams sturdyRef owner) (Persistent'SaveResults sturdyRef owner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

methodByLabel :: Method (Persistent sturdyRef owner) (Persistent'SaveParams sturdyRef owner) (Persistent'SaveResults sturdyRef owner) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => HasMethod "export" (RealmGateway internalRef externalRef internalOwner externalOwner) (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) (Persistent'SaveResults externalRef externalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

methodByLabel :: Method (RealmGateway internalRef externalRef internalOwner externalOwner) (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) (Persistent'SaveResults externalRef externalOwner) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => HasMethod "import_" (RealmGateway internalRef externalRef internalOwner externalOwner) (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) (Persistent'SaveResults internalRef internalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

methodByLabel :: Method (RealmGateway internalRef externalRef internalOwner externalOwner) (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) (Persistent'SaveResults internalRef internalOwner) Source #

data Method c p r Source #

Represents a method on the interface type c with parameter type p and return type r.

Constructors

Method 

Instances

Instances details
HasMethod name c p r => IsLabel name (Method c p r) Source # 
Instance details

Defined in Capnp.Repr.Methods

Methods

fromLabel :: Method c p r #

callB :: (AsClient f, IsCap c, IsStruct p, MonadSTM m) => Method c p r -> (forall s. PureBuilder s (Raw ('Mut s) p)) -> f c -> m (Pipeline r) Source #

Call a method. Use the provided PureBuilder to construct the parameters.

callR :: (AsClient f, IsCap c, IsStruct p, MonadSTM m) => Method c p r -> Raw 'Const p -> f c -> m (Pipeline r) Source #

Call a method, supplying the parameters as a Raw struct.

callP :: forall c p r f m pp. (AsClient f, IsCap c, IsStruct p, Parse p pp, MonadSTM m, MonadThrow m) => Method c p r -> pp -> f c -> m (Pipeline r) Source #

Call a method, supplying the parmaeters in parsed form.

pipe :: (IsStruct a, ReprFor b ~ 'Ptr pr) => Field k a b -> Pipeline a -> Pipeline b Source #

Project a pipeline to a struct onto one of its pointer fields.

pipelineClient :: (IsCap a, MonadSTM m) => Pipeline a -> m (Client a) Source #

Convert a Pipeline for a capability into a Client.

waitPipeline :: forall a m pr. ('Ptr pr ~ ReprFor a, IsPtrRepr pr, MonadSTM m) => Pipeline a -> m (Raw 'Const a) Source #

Wait for the result of a pipeline, and return its value.

type TypeParam a = (IsPtr a, Parse a (Parsed a)) Source #

Constraints needed for a to be a capnproto type parameter.

type Parsed a = ParsedByRepr (ReprFor a) a Source #

Parsed a is the high-level/ADT representation of the capnproto type a. For struct types this is equivalent to Parsed a, but we special case other types, such that e.g. Parsed Data = ByteString.

Working with raw values

data Raw (mut :: Mutability) (a :: Type) Source #

A Raw mut a is an a embedded in a capnproto message with mutability mut.

Instances

Instances details
ReprFor a ~ 'Ptr ('Just 'Struct) => ToStruct mut (Raw mut a) Source # 
Instance details

Defined in Capnp.Repr

Methods

toStruct :: Raw mut a -> Struct mut Source #

ReprFor a ~ 'Ptr ('Just 'Struct) => FromStruct mut (Raw mut a) Source # 
Instance details

Defined in Capnp.Repr

Methods

fromStruct :: ReadCtx m mut => Struct mut -> m (Raw mut a) Source #

(IsPtrRepr r, ReprFor a ~ 'Ptr r) => ToPtr s (Raw ('Mut s) a) Source # 
Instance details

Defined in Capnp.Repr

Methods

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

(IsPtrRepr r, ReprFor a ~ 'Ptr r) => FromPtr mut (Raw mut a) Source # 
Instance details

Defined in Capnp.Repr

Methods

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

Eq (Untyped mut (ReprFor a)) => Eq (Raw mut a) Source # 
Instance details

Defined in Capnp.Repr

Methods

(==) :: Raw mut a -> Raw mut a -> Bool #

(/=) :: Raw mut a -> Raw mut a -> Bool #

Read (Untyped mut (ReprFor a)) => Read (Raw mut a) Source # 
Instance details

Defined in Capnp.Repr

Methods

readsPrec :: Int -> ReadS (Raw mut a) #

readList :: ReadS [Raw mut a] #

readPrec :: ReadPrec (Raw mut a) #

readListPrec :: ReadPrec [Raw mut a] #

Show (Untyped mut (ReprFor a)) => Show (Raw mut a) Source # 
Instance details

Defined in Capnp.Repr

Methods

showsPrec :: Int -> Raw mut a -> ShowS #

show :: Raw mut a -> String #

showList :: [Raw mut a] -> ShowS #

Generic (Untyped mut (ReprFor a)) => Generic (Raw mut a) Source # 
Instance details

Defined in Capnp.Repr

Associated Types

type Rep (Raw mut a) :: Type -> Type #

Methods

from :: Raw mut a -> Rep (Raw mut a) x #

to :: Rep (Raw mut a) x -> Raw mut a #

MessageDefault (Raw 'Const a) 'Const => Default (Raw 'Const a) Source # 
Instance details

Defined in Capnp.Repr

Methods

def :: Raw 'Const a #

MessageDefault (Untyped mut (ReprFor a)) mut => MessageDefault (Raw mut a) mut Source # 
Instance details

Defined in Capnp.Repr

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Raw mut a) Source #

HasMessage (Untyped mut (ReprFor a)) mut => HasMessage (Raw mut a) mut Source # 
Instance details

Defined in Capnp.Repr

Methods

message :: Raw mut a -> Message mut Source #

type Rep (Raw mut a) Source # 
Instance details

Defined in Capnp.Repr

type Rep (Raw mut a) = D1 ('MetaData "Raw" "Capnp.Repr" "capnp-0.11.0.0-50ovYl0NjrHDYHPSniP5DX" 'True) (C1 ('MetaCons "Raw" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromRaw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Untyped mut (ReprFor a)))))

Working with raw lists

data List a Source #

A phantom type denoting capnproto lists of type a.

Instances

Instances details
HasVariant "array" 'Slot Value (List Value) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasVariant "bind" 'Slot Brand'Scope (List Brand'Binding) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "object" 'Slot Value (List Value'Field) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasField "annotations" 'Slot Method (List Annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "annotations" 'Slot Enumerant (List Annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "annotations" 'Slot Field (List Annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "annotations" 'Slot Node (List Annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "capTable" 'Slot Payload (List CapDescriptor) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "enumerants" 'Slot Node'enum (List Enumerant) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "fields" 'Slot Node'struct (List Field) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "implicitParameters" 'Slot Method (List Node'Parameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "imports" 'Slot CodeGeneratorRequest'RequestedFile (List CodeGeneratorRequest'RequestedFile'Import) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "members" 'Slot Node'SourceInfo (List Node'SourceInfo'Member) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "methods" 'Slot Node'interface (List Method) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "nestedNodes" 'Slot Node (List Node'NestedNode) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "nodes" 'Slot CodeGeneratorRequest (List Node) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "parameters" 'Slot Node (List Node'Parameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "params" 'Slot Value'Call (List Value) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasField "requestedFiles" 'Slot CodeGeneratorRequest (List CodeGeneratorRequest'RequestedFile) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "scopes" 'Slot Brand (List Brand'Scope) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "sourceInfo" 'Slot CodeGeneratorRequest (List Node'SourceInfo) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "superclasses" 'Slot Node'interface (List Superclass) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "transform" 'Slot PromisedAnswer (List PromisedAnswer'Op) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

AllocateList (List a) Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type ListAllocHint (List a) Source #

Methods

newList :: RWCtx m s => ListAllocHint (List a) -> Message ('Mut s) -> m (Raw ('Mut s) (List (List a))) Source #

AllocateList a => Allocate (List a) Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type AllocHint (List a) Source #

Methods

new :: RWCtx m s => AllocHint (List a) -> Message ('Mut s) -> m (Raw ('Mut s) (List a)) Source #

(Parse (List a) (Vector ap), Allocate (List a)) => EstimateListAlloc (List a) (Vector ap) Source # 
Instance details

Defined in Capnp.New.Classes

MarshalElement a ap => Marshal (List a) (Vector ap) Source # 
Instance details

Defined in Capnp.New.Classes

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) (List a) -> Vector ap -> m () Source #

MarshalElement a ap => EstimateAlloc (List a) (Vector ap) Source # 
Instance details

Defined in Capnp.New.Classes

MarshalElement a ap => Parse (List a) (Vector ap) Source # 
Instance details

Defined in Capnp.New.Classes

Methods

parse :: ReadCtx m 'Const => Raw 'Const (List a) -> m (Vector ap) Source #

encode :: RWCtx m s => Message ('Mut s) -> Vector ap -> m (Raw ('Mut s) (List a)) Source #

type ReprFor (List a) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (List a) = 'Ptr ('Just ('List ('Just (ListReprFor (ReprFor a)))))
type ListAllocHint (List a) Source # 
Instance details

Defined in Capnp.New.Classes

type AllocHint (List a) Source # 
Instance details

Defined in Capnp.New.Classes

index :: forall a m mut. (ReadCtx m mut, Element (ReprFor a)) => Int -> Raw mut (List a) -> m (Raw mut a) Source #

index i list gets the ith element of the list.

setIndex :: forall a m s. (RWCtx m s, Element (ReprFor a)) => Raw ('Mut s) a -> Int -> Raw ('Mut s) (List a) -> m () Source #

setIndex value i list sets the ith element of list to value.

length :: Raw mut (List a) -> Int Source #

Get the length of a capnproto list.

Working with fields

data Field (k :: FieldKind) a b Source #

Field k a b is a first-class representation of a field of type b within an a, where a must be a struct type.

Instances

Instances details
HasField name k a b => IsLabel name (Field k a b) Source # 
Instance details

Defined in Capnp.Fields

Methods

fromLabel :: Field k a b #

data FieldKind Source #

What sort of field is this? This corresponds to the slot/group variants in the Field type in schema.capnp. Mostly used at the type level with the DataKinds extension.

(Note that this has nothing to do with kinds in the usual type system sense of the word).

Instances

Instances details
Eq FieldKind Source # 
Instance details

Defined in Capnp.Fields

Read FieldKind Source # 
Instance details

Defined in Capnp.Fields

Show FieldKind Source # 
Instance details

Defined in Capnp.Fields

class IsStruct a => HasField (name :: Symbol) k a b | a name -> k b where Source #

An instance HasField name k a b indicates that the struct type a has a field named name with type b (with k being the FieldKind for the field). The generated code includes instances of this for each field in the schema.

Methods

fieldByLabel :: Field k a b Source #

Instances

Instances details
HasField "allowThirdPartyTailCall" 'Slot Call Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "answerId" 'Slot Return Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "attachedFd" 'Slot CapDescriptor Word8 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "brand" 'Slot Annotation Brand Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "brand" 'Slot Type'interface Brand Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "brand" 'Slot Type'struct Brand Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "brand" 'Slot Type'enum Brand Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "brand" 'Slot Superclass Brand Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "cap" 'Slot JoinResult AnyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

HasField "capnpVersion" 'Slot CodeGeneratorRequest CapnpVersion Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "codeOrder" 'Slot Method Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "codeOrder" 'Slot Enumerant Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "codeOrder" 'Slot Field Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "content" 'Slot Payload AnyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "context" 'Group Disembargo Disembargo'context Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "dataWordCount" 'Slot Node'struct Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "defaultValue" 'Slot Field'slot Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "deprecatedObjectId" 'Slot Bootstrap AnyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "discriminantCount" 'Slot Node'struct Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "discriminantOffset" 'Slot Node'struct Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "discriminantValue" 'Slot Field Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "displayName" 'Slot Node Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "displayNamePrefixLength" 'Slot Node Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "docComment" 'Slot Node'SourceInfo'Member Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "docComment" 'Slot Node'SourceInfo Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "elementType" 'Slot Type'list Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "embargo" 'Slot Accept Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "filename" 'Slot CodeGeneratorRequest'RequestedFile Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "function" 'Slot Value'Call Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasField "hadExplicitDefault" 'Slot Field'slot Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "id" 'Slot CodeGeneratorRequest'RequestedFile'Import Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "id" 'Slot CodeGeneratorRequest'RequestedFile Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "id" 'Slot Annotation Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "id" 'Slot Superclass Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "id" 'Slot Node'SourceInfo Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "id" 'Slot Node'NestedNode Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "id" 'Slot Node Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "id" 'Slot ThirdPartyCapDescriptor AnyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "id" 'Slot Release Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "interfaceId" 'Slot Call Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "isGeneric" 'Slot Node Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "isGroup" 'Slot Node'struct Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "joinId" 'Slot JoinResult Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

HasField "joinId" 'Slot JoinKeyPart Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

HasField "joinId" 'Slot ProvisionId Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

HasField "keyPart" 'Slot Join AnyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "major" 'Slot CapnpVersion Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "methodId" 'Slot Call Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "micro" 'Slot CapnpVersion Word8 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "minor" 'Slot CapnpVersion Word8 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "name" 'Slot CodeGeneratorRequest'RequestedFile'Import Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "name" 'Slot Method Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "name" 'Slot Enumerant Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "name" 'Slot Field Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "name" 'Slot Node'NestedNode Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "name" 'Slot Node'Parameter Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "name" 'Slot DiscriminatorOptions Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasField "name" 'Slot Value'Field Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasField "obsoleteDurability" 'Slot Exception Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "obsoleteIsCallersFault" 'Slot Exception Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "offset" 'Slot Field'slot Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "ordinal" 'Group Field Field'ordinal Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "paramBrand" 'Slot Method Brand Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "paramStructType" 'Slot Method Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "parameterIndex" 'Slot Type'anyPointer'implicitMethodParameter Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "parameterIndex" 'Slot Type'anyPointer'parameter Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "params" 'Slot Call Payload Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "partCount" 'Slot JoinKeyPart Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

HasField "partNum" 'Slot JoinKeyPart Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

HasField "pointerCount" 'Slot Node'struct Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "preferredListEncoding" 'Slot Node'struct ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "prefix" 'Slot FlattenOptions Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasField "promiseId" 'Slot Resolve Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "provision" 'Slot Accept AnyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "questionId" 'Slot PromisedAnswer Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "questionId" 'Slot Join Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "questionId" 'Slot Accept Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "questionId" 'Slot Provide Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "questionId" 'Slot Finish Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "questionId" 'Slot Call Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "questionId" 'Slot Bootstrap Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "reason" 'Slot Exception Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "recipient" 'Slot Provide AnyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "referenceCount" 'Slot Release Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "releaseParamCaps" 'Slot Return Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "releaseResultCaps" 'Slot Finish Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "resultBrand" 'Slot Method Brand Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "resultStructType" 'Slot Method Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "scopeId" 'Slot Brand'Scope Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "scopeId" 'Slot Type'anyPointer'parameter Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "scopeId" 'Slot Node Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "sendResultsTo" 'Group Call Call'sendResultsTo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "side" 'Slot VatId Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

HasField "succeeded" 'Slot JoinResult Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

HasField "target" 'Slot Join MessageTarget Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "target" 'Slot Provide MessageTarget Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "target" 'Slot Disembargo MessageTarget Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "target" 'Slot Call MessageTarget Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "targetsAnnotation" 'Slot Node'annotation Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "targetsConst" 'Slot Node'annotation Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "targetsEnum" 'Slot Node'annotation Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "targetsEnumerant" 'Slot Node'annotation Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "targetsField" 'Slot Node'annotation Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "targetsFile" 'Slot Node'annotation Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "targetsGroup" 'Slot Node'annotation Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "targetsInterface" 'Slot Node'annotation Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "targetsMethod" 'Slot Node'annotation Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "targetsParam" 'Slot Node'annotation Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "targetsStruct" 'Slot Node'annotation Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "targetsUnion" 'Slot Node'annotation Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "typeId" 'Slot Type'interface Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "typeId" 'Slot Type'struct Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "typeId" 'Slot Type'enum Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "typeId" 'Slot Field'group Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "type_" 'Slot Field'slot Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "type_" 'Slot Node'annotation Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "type_" 'Slot Node'const Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "type_" 'Slot Exception Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "value" 'Slot Annotation Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "value" 'Slot Node'const Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "value" 'Slot Value'Field Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasField "valueName" 'Slot DiscriminatorOptions Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasField "vineId" 'Slot ThirdPartyCapDescriptor Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "annotations" 'Slot Method (List Annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "annotations" 'Slot Enumerant (List Annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "annotations" 'Slot Field (List Annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "annotations" 'Slot Node (List Annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "capTable" 'Slot Payload (List CapDescriptor) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "enumerants" 'Slot Node'enum (List Enumerant) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "fields" 'Slot Node'struct (List Field) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "implicitParameters" 'Slot Method (List Node'Parameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "imports" 'Slot CodeGeneratorRequest'RequestedFile (List CodeGeneratorRequest'RequestedFile'Import) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "members" 'Slot Node'SourceInfo (List Node'SourceInfo'Member) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "methods" 'Slot Node'interface (List Method) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "nestedNodes" 'Slot Node (List Node'NestedNode) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "nodes" 'Slot CodeGeneratorRequest (List Node) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "parameters" 'Slot Node (List Node'Parameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "params" 'Slot Value'Call (List Value) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasField "requestedFiles" 'Slot CodeGeneratorRequest (List CodeGeneratorRequest'RequestedFile) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "scopes" 'Slot Brand (List Brand'Scope) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "sourceInfo" 'Slot CodeGeneratorRequest (List Node'SourceInfo) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "superclasses" 'Slot Node'interface (List Superclass) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "transform" 'Slot PromisedAnswer (List PromisedAnswer'Op) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

(TypeParam sturdyRef, TypeParam owner) => HasField "sealFor" 'Slot (Persistent'SaveParams sturdyRef owner) owner Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

fieldByLabel :: Field 'Slot (Persistent'SaveParams sturdyRef owner) owner Source #

(TypeParam sturdyRef, TypeParam owner) => HasField "sturdyRef" 'Slot (Persistent'SaveResults sturdyRef owner) sturdyRef Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

fieldByLabel :: Field 'Slot (Persistent'SaveResults sturdyRef owner) sturdyRef Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => HasField "cap" 'Slot (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) (Persistent internalRef internalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

fieldByLabel :: Field 'Slot (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) (Persistent internalRef internalOwner) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => HasField "cap" 'Slot (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) (Persistent externalRef externalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

fieldByLabel :: Field 'Slot (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) (Persistent externalRef externalOwner) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => HasField "params" 'Slot (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) (Persistent'SaveParams externalRef externalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

fieldByLabel :: Field 'Slot (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) (Persistent'SaveParams externalRef externalOwner) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => HasField "params" 'Slot (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) (Persistent'SaveParams internalRef internalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

fieldByLabel :: Field 'Slot (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) (Persistent'SaveParams internalRef internalOwner) Source #

class IsStruct a => HasUnion a where Source #

An instance of HasUnion indicates that the given type is a capnproto struct (or group) with an anonymous union.

Associated Types

data Which a Source #

Which is the abstract capnproto type of the union itself. Like generated struct types (in this case a), this is typically uninhabitied, and used to define instances and/or act as a phantom type.

data RawWhich (mut :: Mutability) a Source #

Concrete view into a union embedded in a message. This will be a sum type with other Raw values as arguments.

Methods

unionField :: Field 'Slot a Word16 Source #

unionField is a field holding the union's tag.

internalWhich :: ReadCtx m mut => Word16 -> Raw mut a -> m (RawWhich mut a) Source #

Helper used in generated code to extract a RawWhich from its surrounding struct.

Instances

Instances details
HasUnion Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

data Which Value Source #

data RawWhich mut Value Source #

Methods

unionField :: Field 'Slot Value Word16 Source #

internalWhich :: forall m (mut :: Mutability). ReadCtx m mut => Word16 -> Raw mut Value -> m (RawWhich mut Value) Source #

HasUnion Brand'Binding Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

data Which Brand'Binding Source #

data RawWhich mut Brand'Binding Source #

HasUnion Brand'Scope Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

data Which Brand'Scope Source #

data RawWhich mut Brand'Scope Source #

HasUnion Type'anyPointer'unconstrained Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasUnion Type'anyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasUnion Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

data Which Type Source #

data RawWhich mut Type Source #

Methods

unionField :: Field 'Slot Type Word16 Source #

internalWhich :: forall m (mut :: Mutability). ReadCtx m mut => Word16 -> Raw mut Type -> m (RawWhich mut Type) Source #

HasUnion Field'ordinal Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

data Which Field'ordinal Source #

data RawWhich mut Field'ordinal Source #

HasUnion Field Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

data Which Field Source #

data RawWhich mut Field Source #

Methods

unionField :: Field0 'Slot Field Word16 Source #

internalWhich :: forall m (mut :: Mutability). ReadCtx m mut => Word16 -> Raw mut Field -> m (RawWhich mut Field) Source #

HasUnion Node Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

Associated Types

data Which Node Source #

data RawWhich mut Node Source #

Methods

unionField :: Field 'Slot Node Word16 Source #

internalWhich :: forall m (mut :: Mutability). ReadCtx m mut => Word16 -> Raw mut Node -> m (RawWhich mut Node) Source #

HasUnion PromisedAnswer'Op Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasUnion CapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

data Which CapDescriptor Source #

data RawWhich mut CapDescriptor Source #

HasUnion MessageTarget Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

data Which MessageTarget Source #

data RawWhich mut MessageTarget Source #

HasUnion Disembargo'context Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasUnion Resolve Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

data Which Resolve Source #

data RawWhich mut Resolve Source #

Methods

unionField :: Field 'Slot Resolve Word16 Source #

internalWhich :: forall m (mut :: Mutability). ReadCtx m mut => Word16 -> Raw mut Resolve -> m (RawWhich mut Resolve) Source #

HasUnion Return Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

data Which Return Source #

data RawWhich mut Return Source #

Methods

unionField :: Field 'Slot Return Word16 Source #

internalWhich :: forall m (mut :: Mutability). ReadCtx m mut => Word16 -> Raw mut Return -> m (RawWhich mut Return) Source #

HasUnion Call'sendResultsTo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasUnion Message Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

Associated Types

data Which Message Source #

data RawWhich mut Message Source #

Methods

unionField :: Field 'Slot Message Word16 Source #

internalWhich :: forall m (mut :: Mutability). ReadCtx m mut => Word16 -> Raw mut Message -> m (RawWhich mut Message) Source #

HasUnion Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Associated Types

data Which Value Source #

data RawWhich mut Value Source #

Methods

unionField :: Field 'Slot Value Word16 Source #

internalWhich :: forall m (mut :: Mutability). ReadCtx m mut => Word16 -> Raw mut Value -> m (RawWhich mut Value) Source #

class HasUnion a => HasVariant (name :: Symbol) k a b | a name -> k b where Source #

An instance 'HasVariant name k a b indicates that the struct type a has an anonymous union with a variant named name, whose argument is of type b.

Methods

variantByLabel :: Variant k a b Source #

Instances

Instances details
HasVariant "abort" 'Slot Message Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "accept" 'Slot Disembargo'context () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "accept" 'Slot Message Accept Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "acceptFromThirdParty" 'Slot Return AnyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "annotation" 'Group Node Node'annotation Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "anyKind" 'Slot Type'anyPointer'unconstrained () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "anyPointer" 'Slot Value AnyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "anyPointer" 'Group Type Type'anyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "bool" 'Slot Value Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "bool" 'Slot Type () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "boolean" 'Slot Value Bool Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasVariant "bootstrap" 'Slot Message Bootstrap Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "call" 'Slot Message Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "call" 'Slot Value Value'Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasVariant "caller" 'Slot Call'sendResultsTo () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "canceled" 'Slot Return () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "cap" 'Slot Resolve CapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "capability" 'Slot Type'anyPointer'unconstrained () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "const" 'Group Node Node'const Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "data_" 'Slot Value Data Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "data_" 'Slot Type () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "disembargo" 'Slot Message Disembargo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "enum" 'Slot Value Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "enum" 'Group Type Type'enum Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "enum" 'Group Node Node'enum Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "exception" 'Slot Resolve Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "exception" 'Slot Return Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "explicit" 'Slot Field'ordinal Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "file" 'Slot Node () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "finish" 'Slot Message Finish Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "float32" 'Slot Value Float Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "float32" 'Slot Type () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "float64" 'Slot Value Double Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "float64" 'Slot Type () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "getPointerField" 'Slot PromisedAnswer'Op Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "group" 'Group Field Field'group Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "implicit" 'Slot Field'ordinal () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "implicitMethodParameter" 'Group Type'anyPointer Type'anyPointer'implicitMethodParameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "importedCap" 'Slot MessageTarget Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "inherit" 'Slot Brand'Scope () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "int16" 'Slot Value Int16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "int16" 'Slot Type () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "int32" 'Slot Value Int32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "int32" 'Slot Type () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "int64" 'Slot Value Int64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "int64" 'Slot Type () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "int8" 'Slot Value Int8 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "int8" 'Slot Type () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "interface" 'Slot Value () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "interface" 'Group Type Type'interface Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "interface" 'Group Node Node'interface Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "join" 'Slot Message Join Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "list" 'Slot Value AnyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "list" 'Slot Type'anyPointer'unconstrained () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "list" 'Group Type Type'list Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "none" 'Slot CapDescriptor () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "noop" 'Slot PromisedAnswer'Op () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "null" 'Slot Value () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasVariant "number" 'Slot Value Double Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasVariant "obsoleteDelete" 'Slot Message AnyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "obsoleteSave" 'Slot Message AnyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "parameter" 'Group Type'anyPointer Type'anyPointer'parameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "promisedAnswer" 'Slot MessageTarget PromisedAnswer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "provide" 'Slot Disembargo'context Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "provide" 'Slot Message Provide Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "receiverAnswer" 'Slot CapDescriptor PromisedAnswer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "receiverHosted" 'Slot CapDescriptor Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "receiverLoopback" 'Slot Disembargo'context Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "release" 'Slot Message Release Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "resolve" 'Slot Message Resolve Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "results" 'Slot Return Payload Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "resultsSentElsewhere" 'Slot Return () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "return" 'Slot Message Return Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "senderHosted" 'Slot CapDescriptor Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "senderLoopback" 'Slot Disembargo'context Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "senderPromise" 'Slot CapDescriptor Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "slot" 'Group Field Field'slot Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "string" 'Slot Value Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasVariant "struct" 'Slot Value AnyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "struct" 'Slot Type'anyPointer'unconstrained () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "struct" 'Group Type Type'struct Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "struct" 'Group Node Node'struct Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "takeFromOtherQuestion" 'Slot Return Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "text" 'Slot Value Text Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "text" 'Slot Type () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "thirdParty" 'Slot Call'sendResultsTo AnyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "thirdPartyHosted" 'Slot CapDescriptor ThirdPartyCapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "type_" 'Slot Brand'Binding Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "uint16" 'Slot Value Word16 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "uint16" 'Slot Type () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "uint32" 'Slot Value Word32 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "uint32" 'Slot Type () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "uint64" 'Slot Value Word64 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "uint64" 'Slot Type () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "uint8" 'Slot Value Word8 Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "uint8" 'Slot Type () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "unbound" 'Slot Brand'Binding () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "unconstrained" 'Group Type'anyPointer Type'anyPointer'unconstrained Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "unimplemented" 'Slot Message Message Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "void" 'Slot Value () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "void" 'Slot Type () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "yourself" 'Slot Call'sendResultsTo () Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasVariant "array" 'Slot Value (List Value) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasVariant "bind" 'Slot Brand'Scope (List Brand'Binding) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "object" 'Slot Value (List Value'Field) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

Working with messages

data Message (mut :: Mutability) Source #

A Cap'n Proto message, parametrized over its mutability.

Instances

Instances details
Eq (Message mut) Source # 
Instance details

Defined in Capnp.Message

Methods

(==) :: Message mut -> Message mut -> Bool #

(/=) :: Message mut -> Message mut -> Bool #

Thaw (Message 'Const) Source # 
Instance details

Defined in Capnp.Message

Associated Types

type Mutable s (Message 'Const) Source #

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

Defined in Capnp.Message

type Mutable s (Message 'Const) = Message ('Mut s)

data Segment (mut :: Mutability) Source #

A segment in a Cap'n Proto message.

Instances

Instances details
Eq (Segment mut) Source # 
Instance details

Defined in Capnp.Message

Methods

(==) :: Segment mut -> Segment mut -> Bool #

(/=) :: Segment mut -> Segment mut -> Bool #

Thaw (Segment 'Const) Source # 
Instance details

Defined in Capnp.Message

Associated Types

type Mutable s (Segment 'Const) Source #

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

Defined in Capnp.Message

type Mutable s (Segment 'Const) = Segment ('Mut s)

data Mutability Source #

Mutability is used as a type parameter (with the DataKinds extension) to indicate the mutability of some values in this library; Const denotes an immutable value, while Mut s denotes a value that can be mutated in the scope of the state token s.

Constructors

Const 
Mut Type 

class Monad m => MonadReadMessage mut m where Source #

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

Methods

numSegs :: Message mut -> m Int Source #

numSegs gets the number of segments in a message.

numWords :: Segment mut -> m WordCount Source #

numWords gets the number of words in a segment.

numCaps :: Message mut -> m Int Source #

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

internalGetSeg :: Message mut -> Int -> m (Segment mut) Source #

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

internalGetCap :: Message mut -> Int -> m Client Source #

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

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

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

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

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

Instances

Instances details
Monad m => MonadReadMessage 'Const m Source # 
Instance details

Defined in Capnp.Message

(PrimMonad m, s ~ PrimState m) => MonadReadMessage ('Mut s) m Source # 
Instance details

Defined in Capnp.Message

newMessage :: WriteCtx m s => Maybe WordCount -> m (Message ('Mut s)) Source #

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

fromByteString :: ByteString -> Segment 'Const Source #

Convert a ByteString to a segment. O(1)

toByteString :: Segment 'Const -> ByteString Source #

Convert a segment to a byte string. O(1)

Building messages in pure code

data PureBuilder s a Source #

PureBuilder is a monad transformer stack with the instnaces needed manipulate mutable messages. PureBuilder s a is morally equivalent to LimitT (CatchT (ST s)) a

Instances

Instances details
Monad (PureBuilder s) Source # 
Instance details

Defined in Internal.BuildPure

Methods

(>>=) :: PureBuilder s a -> (a -> PureBuilder s b) -> PureBuilder s b #

(>>) :: PureBuilder s a -> PureBuilder s b -> PureBuilder s b #

return :: a -> PureBuilder s a #

Functor (PureBuilder s) Source # 
Instance details

Defined in Internal.BuildPure

Methods

fmap :: (a -> b) -> PureBuilder s a -> PureBuilder s b #

(<$) :: a -> PureBuilder s b -> PureBuilder s a #

Applicative (PureBuilder s) Source # 
Instance details

Defined in Internal.BuildPure

Methods

pure :: a -> PureBuilder s a #

(<*>) :: PureBuilder s (a -> b) -> PureBuilder s a -> PureBuilder s b #

liftA2 :: (a -> b -> c) -> PureBuilder s a -> PureBuilder s b -> PureBuilder s c #

(*>) :: PureBuilder s a -> PureBuilder s b -> PureBuilder s b #

(<*) :: PureBuilder s a -> PureBuilder s b -> PureBuilder s a #

MonadThrow (PureBuilder s) Source # 
Instance details

Defined in Internal.BuildPure

Methods

throwM :: Exception e => e -> PureBuilder s a #

PrimMonad (PureBuilder s) Source # 
Instance details

Defined in Internal.BuildPure

Associated Types

type PrimState (PureBuilder s) #

Methods

primitive :: (State# (PrimState (PureBuilder s)) -> (# State# (PrimState (PureBuilder s)), a #)) -> PureBuilder s a #

MonadLimit (PureBuilder s) Source # 
Instance details

Defined in Internal.BuildPure

type PrimState (PureBuilder s) Source # 
Instance details

Defined in Internal.BuildPure

type PrimState (PureBuilder s) = s

createPure :: (MonadThrow m, Thaw a) => WordCount -> (forall s. PureBuilder s (Mutable s a)) -> m a Source #

createPure limit m creates a capnproto value in pure code according to m, then freezes it without copying. If m calls throwM then createPure rethrows the exception in the specified monad.

Re-exported from Data.Default, for convienence.

def :: Default a => a #

The default value for this type.