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

Capnp.Gen.Capnp.Rpc

Documentation

newtype Message msg Source #

Constructors

Message'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (Message msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

toStruct :: Message msg -> Struct msg Source #

FromStruct msg (Message msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Message msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem msg (Message msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (Message msg) Source #

Methods

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

toUntypedList :: List msg (Message msg) -> List msg Source #

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

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

MessageDefault (Message msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

HasMessage (Message msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Message msg) Source #

Methods

message :: Message msg -> InMessage (Message msg) Source #

newtype List msg (Message msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List msg (Message msg) = Message'List_ (ListOf msg (Struct msg))
type InMessage (Message msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (Message msg) = msg

get_Message' :: (ReadCtx m msg, FromStruct msg (Message' msg)) => Message msg -> m (Message' msg) Source #

set_Message'call :: (RWCtx m s, ToPtr s (Call (MutMsg s))) => Message (MutMsg s) -> Call (MutMsg s) -> m () Source #

set_Message'return :: (RWCtx m s, ToPtr s (Return (MutMsg s))) => Message (MutMsg s) -> Return (MutMsg s) -> m () Source #

set_Message'finish :: (RWCtx m s, ToPtr s (Finish (MutMsg s))) => Message (MutMsg s) -> Finish (MutMsg s) -> m () Source #

set_Message'resolve :: (RWCtx m s, ToPtr s (Resolve (MutMsg s))) => Message (MutMsg s) -> Resolve (MutMsg s) -> m () Source #

set_Message'release :: (RWCtx m s, ToPtr s (Release (MutMsg s))) => Message (MutMsg s) -> Release (MutMsg s) -> m () Source #

set_Message'obsoleteSave :: (RWCtx m s, ToPtr s (Maybe (Ptr (MutMsg s)))) => Message (MutMsg s) -> Maybe (Ptr (MutMsg s)) -> m () Source #

set_Message'obsoleteDelete :: (RWCtx m s, ToPtr s (Maybe (Ptr (MutMsg s)))) => Message (MutMsg s) -> Maybe (Ptr (MutMsg s)) -> m () Source #

set_Message'provide :: (RWCtx m s, ToPtr s (Provide (MutMsg s))) => Message (MutMsg s) -> Provide (MutMsg s) -> m () Source #

set_Message'accept :: (RWCtx m s, ToPtr s (Accept (MutMsg s))) => Message (MutMsg s) -> Accept (MutMsg s) -> m () Source #

set_Message'join :: (RWCtx m s, ToPtr s (Join (MutMsg s))) => Message (MutMsg s) -> Join (MutMsg s) -> m () Source #

newtype Bootstrap msg Source #

Constructors

Bootstrap'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

toStruct :: Bootstrap msg -> Struct msg Source #

FromStruct msg (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem msg (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (Bootstrap msg) Source #

Methods

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

toUntypedList :: List msg (Bootstrap msg) -> List msg Source #

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

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

MessageDefault (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

HasMessage (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Bootstrap msg) Source #

Methods

message :: Bootstrap msg -> InMessage (Bootstrap msg) Source #

newtype List msg (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List msg (Bootstrap msg) = Bootstrap'List_ (ListOf msg (Struct msg))
type InMessage (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (Bootstrap msg) = msg

get_Bootstrap'deprecatedObjectId :: (ReadCtx m msg, FromPtr msg (Maybe (Ptr msg))) => Bootstrap msg -> m (Maybe (Ptr msg)) Source #

newtype Call msg Source #

Constructors

Call'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

toStruct :: Call msg -> Struct msg Source #

FromStruct msg (Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem msg (Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (Call msg) Source #

Methods

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

toUntypedList :: List msg (Call msg) -> List msg Source #

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

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

MessageDefault (Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

messageDefault :: InMessage (Call msg) -> Call msg Source #

HasMessage (Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Call msg) Source #

Methods

message :: Call msg -> InMessage (Call msg) Source #

newtype List msg (Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List msg (Call msg) = Call'List_ (ListOf msg (Struct msg))
type InMessage (Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (Call msg) = msg

get_Call'target :: (ReadCtx m msg, FromPtr msg (MessageTarget msg)) => Call msg -> m (MessageTarget msg) Source #

has_Call'target :: ReadCtx m msg => Call msg -> m Bool Source #

set_Call'methodId :: RWCtx m s => Call (MutMsg s) -> Word16 -> m () Source #

get_Call'params :: (ReadCtx m msg, FromPtr msg (Payload msg)) => Call msg -> m (Payload msg) Source #

set_Call'params :: (RWCtx m s, ToPtr s (Payload (MutMsg s))) => Call (MutMsg s) -> Payload (MutMsg s) -> m () Source #

has_Call'params :: ReadCtx m msg => Call msg -> m Bool Source #

newtype Call'sendResultsTo msg Source #

Instances

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

Defined in Capnp.Gen.Capnp.Rpc

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

MessageDefault (Call'sendResultsTo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

HasMessage (Call'sendResultsTo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Call'sendResultsTo msg) Source #

type InMessage (Call'sendResultsTo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (Call'sendResultsTo msg) = msg

newtype Return msg Source #

Constructors

Return'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (Return msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

toStruct :: Return msg -> Struct msg Source #

FromStruct msg (Return msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Return msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem msg (Return msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (Return msg) Source #

Methods

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

toUntypedList :: List msg (Return msg) -> List msg Source #

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

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

MessageDefault (Return msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

messageDefault :: InMessage (Return msg) -> Return msg Source #

HasMessage (Return msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Return msg) Source #

Methods

message :: Return msg -> InMessage (Return msg) Source #

newtype List msg (Return msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List msg (Return msg) = Return'List_ (ListOf msg (Struct msg))
type InMessage (Return msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (Return msg) = msg

get_Return' :: (ReadCtx m msg, FromStruct msg (Return' msg)) => Return msg -> m (Return' msg) Source #

set_Return'results :: (RWCtx m s, ToPtr s (Payload (MutMsg s))) => Return (MutMsg s) -> Payload (MutMsg s) -> m () Source #

newtype Finish msg Source #

Constructors

Finish'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (Finish msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

toStruct :: Finish msg -> Struct msg Source #

FromStruct msg (Finish msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Finish msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem msg (Finish msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (Finish msg) Source #

Methods

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

toUntypedList :: List msg (Finish msg) -> List msg Source #

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

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

MessageDefault (Finish msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

messageDefault :: InMessage (Finish msg) -> Finish msg Source #

HasMessage (Finish msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Finish msg) Source #

Methods

message :: Finish msg -> InMessage (Finish msg) Source #

newtype List msg (Finish msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List msg (Finish msg) = Finish'List_ (ListOf msg (Struct msg))
type InMessage (Finish msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (Finish msg) = msg

newtype Resolve msg Source #

Constructors

Resolve'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (Resolve msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

toStruct :: Resolve msg -> Struct msg Source #

FromStruct msg (Resolve msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Resolve msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem msg (Resolve msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (Resolve msg) Source #

Methods

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

toUntypedList :: List msg (Resolve msg) -> List msg Source #

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

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

MessageDefault (Resolve msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

HasMessage (Resolve msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Resolve msg) Source #

Methods

message :: Resolve msg -> InMessage (Resolve msg) Source #

newtype List msg (Resolve msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List msg (Resolve msg) = Resolve'List_ (ListOf msg (Struct msg))
type InMessage (Resolve msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (Resolve msg) = msg

data Resolve' msg Source #

Instances

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

get_Resolve' :: (ReadCtx m msg, FromStruct msg (Resolve' msg)) => Resolve msg -> m (Resolve' msg) Source #

newtype Release msg Source #

Constructors

Release'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (Release msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

toStruct :: Release msg -> Struct msg Source #

FromStruct msg (Release msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Release msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem msg (Release msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (Release msg) Source #

Methods

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

toUntypedList :: List msg (Release msg) -> List msg Source #

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

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

MessageDefault (Release msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

HasMessage (Release msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Release msg) Source #

Methods

message :: Release msg -> InMessage (Release msg) Source #

newtype List msg (Release msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List msg (Release msg) = Release'List_ (ListOf msg (Struct msg))
type InMessage (Release msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (Release msg) = msg

set_Release'id :: RWCtx m s => Release (MutMsg s) -> Word32 -> m () Source #

newtype Disembargo msg Source #

Constructors

Disembargo'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (Disembargo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

toStruct :: Disembargo msg -> Struct msg Source #

FromStruct msg (Disembargo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Disembargo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem msg (Disembargo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (Disembargo msg) Source #

Methods

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

toUntypedList :: List msg (Disembargo msg) -> List msg Source #

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

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

MessageDefault (Disembargo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

HasMessage (Disembargo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Disembargo msg) Source #

newtype List msg (Disembargo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List msg (Disembargo msg) = Disembargo'List_ (ListOf msg (Struct msg))
type InMessage (Disembargo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (Disembargo msg) = msg

newtype Disembargo'context msg Source #

Instances

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

Defined in Capnp.Gen.Capnp.Rpc

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

MessageDefault (Disembargo'context msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

HasMessage (Disembargo'context msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Disembargo'context msg) Source #

type InMessage (Disembargo'context msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (Disembargo'context msg) = msg

newtype Provide msg Source #

Constructors

Provide'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (Provide msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

toStruct :: Provide msg -> Struct msg Source #

FromStruct msg (Provide msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Provide msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem msg (Provide msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (Provide msg) Source #

Methods

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

toUntypedList :: List msg (Provide msg) -> List msg Source #

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

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

MessageDefault (Provide msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

HasMessage (Provide msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Provide msg) Source #

Methods

message :: Provide msg -> InMessage (Provide msg) Source #

newtype List msg (Provide msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List msg (Provide msg) = Provide'List_ (ListOf msg (Struct msg))
type InMessage (Provide msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (Provide msg) = msg

get_Provide'recipient :: (ReadCtx m msg, FromPtr msg (Maybe (Ptr msg))) => Provide msg -> m (Maybe (Ptr msg)) Source #

set_Provide'recipient :: (RWCtx m s, ToPtr s (Maybe (Ptr (MutMsg s)))) => Provide (MutMsg s) -> Maybe (Ptr (MutMsg s)) -> m () Source #

newtype Accept msg Source #

Constructors

Accept'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (Accept msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

toStruct :: Accept msg -> Struct msg Source #

FromStruct msg (Accept msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Accept msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem msg (Accept msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (Accept msg) Source #

Methods

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

toUntypedList :: List msg (Accept msg) -> List msg Source #

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

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

MessageDefault (Accept msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

messageDefault :: InMessage (Accept msg) -> Accept msg Source #

HasMessage (Accept msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Accept msg) Source #

Methods

message :: Accept msg -> InMessage (Accept msg) Source #

newtype List msg (Accept msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List msg (Accept msg) = Accept'List_ (ListOf msg (Struct msg))
type InMessage (Accept msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (Accept msg) = msg

get_Accept'provision :: (ReadCtx m msg, FromPtr msg (Maybe (Ptr msg))) => Accept msg -> m (Maybe (Ptr msg)) Source #

set_Accept'provision :: (RWCtx m s, ToPtr s (Maybe (Ptr (MutMsg s)))) => Accept (MutMsg s) -> Maybe (Ptr (MutMsg s)) -> m () Source #

set_Accept'embargo :: RWCtx m s => Accept (MutMsg s) -> Bool -> m () Source #

newtype Join msg Source #

Constructors

Join'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (Join msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

toStruct :: Join msg -> Struct msg Source #

FromStruct msg (Join msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Join msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem msg (Join msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (Join msg) Source #

Methods

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

toUntypedList :: List msg (Join msg) -> List msg Source #

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

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

MessageDefault (Join msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

messageDefault :: InMessage (Join msg) -> Join msg Source #

HasMessage (Join msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Join msg) Source #

Methods

message :: Join msg -> InMessage (Join msg) Source #

newtype List msg (Join msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List msg (Join msg) = Join'List_ (ListOf msg (Struct msg))
type InMessage (Join msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (Join msg) = msg

get_Join'target :: (ReadCtx m msg, FromPtr msg (MessageTarget msg)) => Join msg -> m (MessageTarget msg) Source #

has_Join'target :: ReadCtx m msg => Join msg -> m Bool Source #

get_Join'keyPart :: (ReadCtx m msg, FromPtr msg (Maybe (Ptr msg))) => Join msg -> m (Maybe (Ptr msg)) Source #

set_Join'keyPart :: (RWCtx m s, ToPtr s (Maybe (Ptr (MutMsg s)))) => Join (MutMsg s) -> Maybe (Ptr (MutMsg s)) -> m () Source #

has_Join'keyPart :: ReadCtx m msg => Join msg -> m Bool Source #

newtype MessageTarget msg Source #

Constructors

MessageTarget'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

toStruct :: MessageTarget msg -> Struct msg Source #

FromStruct msg (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem msg (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (MessageTarget msg) Source #

Methods

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

toUntypedList :: List msg (MessageTarget msg) -> List msg Source #

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

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

MessageDefault (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

HasMessage (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (MessageTarget msg) Source #

newtype List msg (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List msg (MessageTarget msg) = MessageTarget'List_ (ListOf msg (Struct msg))
type InMessage (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (MessageTarget msg) = msg

data MessageTarget' msg Source #

Instances

Instances details
FromStruct msg (MessageTarget' msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newtype Payload msg Source #

Constructors

Payload'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (Payload msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

toStruct :: Payload msg -> Struct msg Source #

FromStruct msg (Payload msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Payload msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem msg (Payload msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (Payload msg) Source #

Methods

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

toUntypedList :: List msg (Payload msg) -> List msg Source #

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

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

MessageDefault (Payload msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

HasMessage (Payload msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Payload msg) Source #

Methods

message :: Payload msg -> InMessage (Payload msg) Source #

newtype List msg (Payload msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List msg (Payload msg) = Payload'List_ (ListOf msg (Struct msg))
type InMessage (Payload msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (Payload msg) = msg

get_Payload'content :: (ReadCtx m msg, FromPtr msg (Maybe (Ptr msg))) => Payload msg -> m (Maybe (Ptr msg)) Source #

set_Payload'content :: (RWCtx m s, ToPtr s (Maybe (Ptr (MutMsg s)))) => Payload (MutMsg s) -> Maybe (Ptr (MutMsg s)) -> m () Source #

get_Payload'capTable :: (ReadCtx m msg, FromPtr msg (List msg (CapDescriptor msg))) => Payload msg -> m (List msg (CapDescriptor msg)) Source #

newtype CapDescriptor msg Source #

Constructors

CapDescriptor'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

toStruct :: CapDescriptor msg -> Struct msg Source #

FromStruct msg (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem msg (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (CapDescriptor msg) Source #

Methods

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

toUntypedList :: List msg (CapDescriptor msg) -> List msg Source #

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

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

MessageDefault (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

HasMessage (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (CapDescriptor msg) Source #

newtype List msg (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List msg (CapDescriptor msg) = CapDescriptor'List_ (ListOf msg (Struct msg))
type InMessage (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (CapDescriptor msg) = msg

newtype PromisedAnswer msg Source #

Constructors

PromisedAnswer'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

toStruct :: PromisedAnswer msg -> Struct msg Source #

FromStruct msg (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem msg (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (PromisedAnswer msg) Source #

Methods

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

toUntypedList :: List msg (PromisedAnswer msg) -> List msg Source #

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

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

MessageDefault (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

HasMessage (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (PromisedAnswer msg) Source #

newtype List msg (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List msg (PromisedAnswer msg) = PromisedAnswer'List_ (ListOf msg (Struct msg))
type InMessage (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (PromisedAnswer msg) = msg

newtype PromisedAnswer'Op msg Source #

Instances

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

Defined in Capnp.Gen.Capnp.Rpc

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (PromisedAnswer'Op msg) Source #

Methods

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

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

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

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

MessageDefault (PromisedAnswer'Op msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

HasMessage (PromisedAnswer'Op msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (PromisedAnswer'Op msg) Source #

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

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (PromisedAnswer'Op msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (PromisedAnswer'Op msg) = msg

newtype ThirdPartyCapDescriptor msg Source #

Instances

Instances details
ToStruct msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

FromStruct msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

ListElem msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (ThirdPartyCapDescriptor msg) Source #

MessageDefault (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

HasMessage (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (ThirdPartyCapDescriptor msg) Source #

newtype List msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype Exception msg Source #

Constructors

Exception'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (Exception msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

toStruct :: Exception msg -> Struct msg Source #

FromStruct msg (Exception msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Exception msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem msg (Exception msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg (Exception msg) Source #

Methods

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

toUntypedList :: List msg (Exception msg) -> List msg Source #

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

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

MessageDefault (Exception msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

HasMessage (Exception msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type InMessage (Exception msg) Source #

Methods

message :: Exception msg -> InMessage (Exception msg) Source #

newtype List msg (Exception msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List msg (Exception msg) = Exception'List_ (ListOf msg (Struct msg))
type InMessage (Exception msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type InMessage (Exception msg) = msg

get_Exception'reason :: (ReadCtx m msg, FromPtr msg (Text msg)) => Exception msg -> m (Text msg) Source #

set_Exception'reason :: (RWCtx m s, ToPtr s (Text (MutMsg s))) => Exception (MutMsg s) -> Text (MutMsg s) -> m () Source #

data Exception'Type Source #

Instances

Instances details
Enum Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Eq Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Read Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Show Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Generic Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

type Rep Exception'Type :: Type -> Type #

Decerialize Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

Associated Types

type Cerial msg Exception'Type Source #

IsWord Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Cerialize s Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

MutListElem s Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

ListElem msg Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List msg Exception'Type Source #

Cerialize s (Vector (Vector (Vector (Vector (Vector (Vector Exception'Type)))))) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

Cerialize s (Vector (Vector (Vector (Vector (Vector Exception'Type))))) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

Cerialize s (Vector (Vector (Vector (Vector Exception'Type)))) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

Cerialize s (Vector (Vector (Vector Exception'Type))) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

Cerialize s (Vector (Vector Exception'Type)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

Cerialize s (Vector Exception'Type) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

type Rep Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type Rep Exception'Type = D1 ('MetaData "Exception'Type" "Capnp.Gen.Capnp.Rpc" "capnp-0.8.0.0-GCjrmYaekqlKa81VtWWpNE" 'False) ((C1 ('MetaCons "Exception'Type'failed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Exception'Type'overloaded" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Exception'Type'disconnected" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Exception'Type'unimplemented" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Exception'Type'unknown'" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16)))))
type Cerial msg Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

newtype List msg Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc