capnp-0.12.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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Message msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

Allocate s (Message ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

new :: WriteCtx m s => Message0 ('Mut s) -> m (Message ('Mut s)) Source #

MutListElem s (Message ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message0 ('Mut s) -> Int -> m (List ('Mut s) (Message ('Mut s))) Source #

ListElem mut (Message mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Message mut) Source #

Methods

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

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

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

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

MessageDefault (Message mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (Message mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

message :: Message mut -> Message0 mut Source #

newtype List mut (Message mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (Message mut) = Message'List_ (ListOf mut (Struct mut))

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

set_Message'unimplemented :: (RWCtx m s, ToPtr s (Message (Mut s))) => Message (Mut s) -> Message (Mut s) -> m () Source #

set_Message'abort :: (RWCtx m s, ToPtr s (Exception (Mut s))) => Message (Mut s) -> Exception (Mut s) -> m () Source #

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

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

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

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

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

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

set_Message'bootstrap :: (RWCtx m s, ToPtr s (Bootstrap (Mut s))) => Message (Mut s) -> Bootstrap (Mut s) -> m () Source #

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

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

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

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

set_Message'disembargo :: (RWCtx m s, ToPtr s (Disembargo (Mut s))) => Message (Mut s) -> Disembargo (Mut 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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

Allocate s (Bootstrap ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Bootstrap ('Mut s)) Source #

MutListElem s (Bootstrap ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Bootstrap ('Mut s))) Source #

ListElem mut (Bootstrap mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Bootstrap mut) Source #

Methods

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

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

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

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

MessageDefault (Bootstrap mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (Bootstrap mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

message :: Bootstrap mut -> Message mut Source #

newtype List mut (Bootstrap mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (Bootstrap mut) = Bootstrap'List_ (ListOf mut (Struct mut))

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

set_Bootstrap'deprecatedObjectId :: (RWCtx m s, ToPtr s (Maybe (Ptr (Mut s)))) => Bootstrap (Mut s) -> Maybe (Ptr (Mut s)) -> m () 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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

Allocate s (Call ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Call ('Mut s)) Source #

MutListElem s (Call ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem mut (Call mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Call mut) Source #

Methods

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

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

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

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

MessageDefault (Call mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (Call mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

message :: Call mut -> Message mut Source #

newtype List mut (Call mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (Call mut) = Call'List_ (ListOf mut (Struct mut))

set_Call'questionId :: RWCtx m s => Call (Mut s) -> Word32 -> m () Source #

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

set_Call'target :: (RWCtx m s, ToPtr s (MessageTarget (Mut s))) => Call (Mut s) -> MessageTarget (Mut s) -> m () Source #

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

set_Call'interfaceId :: RWCtx m s => Call (Mut s) -> Word64 -> m () Source #

set_Call'methodId :: RWCtx m s => Call (Mut 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 (Mut s))) => Call (Mut s) -> Payload (Mut s) -> m () Source #

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

new_Call'params :: RWCtx m s => Call (Mut s) -> m (Payload (Mut s)) 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 mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Call'sendResultsTo mut) Source #

HasMessage (Call'sendResultsTo mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Return msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem mut (Return mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Return mut) Source #

Methods

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

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

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

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

MessageDefault (Return mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (Return mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

message :: Return mut -> Message mut Source #

newtype List mut (Return mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (Return mut) = Return'List_ (ListOf mut (Struct mut))

set_Return'answerId :: RWCtx m s => Return (Mut s) -> Word32 -> m () Source #

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

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

set_Return'exception :: (RWCtx m s, ToPtr s (Exception (Mut s))) => Return (Mut s) -> Exception (Mut s) -> m () Source #

set_Return'canceled :: RWCtx m s => Return (Mut s) -> m () Source #

set_Return'acceptFromThirdParty :: (RWCtx m s, ToPtr s (Maybe (Ptr (Mut s)))) => Return (Mut s) -> Maybe (Ptr (Mut s)) -> m () Source #

set_Return'unknown' :: RWCtx m s => Return (Mut s) -> Word16 -> 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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Finish msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

Allocate s (Finish ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Finish ('Mut s)) Source #

MutListElem s (Finish ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Finish ('Mut s))) Source #

ListElem mut (Finish mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Finish mut) Source #

Methods

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

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

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

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

MessageDefault (Finish mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (Finish mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

message :: Finish mut -> Message mut Source #

newtype List mut (Finish mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (Finish mut) = Finish'List_ (ListOf mut (Struct mut))

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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Resolve msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem mut (Resolve mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Resolve mut) Source #

Methods

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

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

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

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

MessageDefault (Resolve mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (Resolve mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

message :: Resolve mut -> Message mut Source #

newtype List mut (Resolve mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (Resolve mut) = Resolve'List_ (ListOf mut (Struct mut))

data Resolve' (mut :: Mutability) Source #

Instances

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

set_Resolve'cap :: (RWCtx m s, ToPtr s (CapDescriptor (Mut s))) => Resolve (Mut s) -> CapDescriptor (Mut s) -> m () Source #

set_Resolve'exception :: (RWCtx m s, ToPtr s (Exception (Mut s))) => Resolve (Mut s) -> Exception (Mut s) -> m () 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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Release msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

Allocate s (Release ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Release ('Mut s)) Source #

MutListElem s (Release ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Release ('Mut s))) Source #

ListElem mut (Release mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Release mut) Source #

Methods

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

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

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

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

MessageDefault (Release mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (Release mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

message :: Release mut -> Message mut Source #

newtype List mut (Release mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (Release mut) = Release'List_ (ListOf mut (Struct mut))

set_Release'id :: RWCtx m s => Release (Mut 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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Disembargo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

Allocate s (Disembargo ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Disembargo ('Mut s)) Source #

MutListElem s (Disembargo ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Disembargo ('Mut s))) Source #

ListElem mut (Disembargo mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Disembargo mut) Source #

Methods

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

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

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

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

MessageDefault (Disembargo mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (Disembargo mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

message :: Disembargo mut -> Message mut Source #

newtype List mut (Disembargo mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (Disembargo mut) = Disembargo'List_ (ListOf mut (Struct mut))

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Disembargo'context mut) Source #

HasMessage (Disembargo'context mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Provide msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

Allocate s (Provide ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Provide ('Mut s)) Source #

MutListElem s (Provide ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Provide ('Mut s))) Source #

ListElem mut (Provide mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Provide mut) Source #

Methods

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

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

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

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

MessageDefault (Provide mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (Provide mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

message :: Provide mut -> Message mut Source #

newtype List mut (Provide mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (Provide mut) = Provide'List_ (ListOf mut (Struct mut))

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 (Mut s)))) => Provide (Mut s) -> Maybe (Ptr (Mut 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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Accept msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

Allocate s (Accept ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Accept ('Mut s)) Source #

MutListElem s (Accept ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Accept ('Mut s))) Source #

ListElem mut (Accept mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Accept mut) Source #

Methods

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

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

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

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

MessageDefault (Accept mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (Accept mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

message :: Accept mut -> Message mut Source #

newtype List mut (Accept mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (Accept mut) = Accept'List_ (ListOf mut (Struct mut))

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 (Mut s)))) => Accept (Mut s) -> Maybe (Ptr (Mut s)) -> m () Source #

set_Accept'embargo :: RWCtx m s => Accept (Mut 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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Join msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

Allocate s (Join ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Join ('Mut s)) Source #

MutListElem s (Join ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Join ('Mut s))) Source #

ListElem mut (Join mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Join mut) Source #

Methods

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

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

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

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

MessageDefault (Join mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (Join mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

message :: Join mut -> Message mut Source #

newtype List mut (Join mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (Join mut) = Join'List_ (ListOf mut (Struct mut))

set_Join'questionId :: RWCtx m s => Join (Mut s) -> Word32 -> m () Source #

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

set_Join'target :: (RWCtx m s, ToPtr s (MessageTarget (Mut s))) => Join (Mut s) -> MessageTarget (Mut s) -> m () 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 (Mut s)))) => Join (Mut s) -> Maybe (Ptr (Mut 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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

Allocate s (MessageTarget ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (MessageTarget ('Mut s)) Source #

MutListElem s (MessageTarget ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (MessageTarget ('Mut s))) Source #

ListElem mut (MessageTarget mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (MessageTarget mut) Source #

Methods

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

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

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

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

MessageDefault (MessageTarget mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (MessageTarget mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

message :: MessageTarget mut -> Message mut Source #

newtype List mut (MessageTarget mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (MessageTarget mut) = MessageTarget'List_ (ListOf mut (Struct mut))

data MessageTarget' (mut :: Mutability) Source #

Instances

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

fromStruct :: ReadCtx m mut => Struct mut -> m (MessageTarget' mut) 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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Payload msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

Allocate s (Payload ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Payload ('Mut s)) Source #

MutListElem s (Payload ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Payload ('Mut s))) Source #

ListElem mut (Payload mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Payload mut) Source #

Methods

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

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

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

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

MessageDefault (Payload mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (Payload mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

message :: Payload mut -> Message mut Source #

newtype List mut (Payload mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (Payload mut) = Payload'List_ (ListOf mut (Struct mut))

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 (Mut s)))) => Payload (Mut s) -> Maybe (Ptr (Mut s)) -> m () Source #

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

set_Payload'capTable :: (RWCtx m s, ToPtr s (List (Mut s) (CapDescriptor (Mut s)))) => Payload (Mut s) -> List (Mut s) (CapDescriptor (Mut s)) -> m () 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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

Allocate s (CapDescriptor ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (CapDescriptor ('Mut s)) Source #

MutListElem s (CapDescriptor ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (CapDescriptor ('Mut s))) Source #

ListElem mut (CapDescriptor mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (CapDescriptor mut) Source #

Methods

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

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

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

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

MessageDefault (CapDescriptor mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (CapDescriptor mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

message :: CapDescriptor mut -> Message mut Source #

newtype List mut (CapDescriptor mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (CapDescriptor mut) = CapDescriptor'List_ (ListOf mut (Struct mut))

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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

Allocate s (PromisedAnswer ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (PromisedAnswer ('Mut s)) Source #

MutListElem s (PromisedAnswer ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

ListElem mut (PromisedAnswer mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (PromisedAnswer mut) Source #

Methods

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

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

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

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

MessageDefault (PromisedAnswer mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (PromisedAnswer mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

message :: PromisedAnswer mut -> Message mut Source #

newtype List mut (PromisedAnswer mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (PromisedAnswer mut) = PromisedAnswer'List_ (ListOf mut (Struct mut))

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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (PromisedAnswer'Op mut) Source #

Methods

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

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

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

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

MessageDefault (PromisedAnswer'Op mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (PromisedAnswer'Op mut) Source #

HasMessage (PromisedAnswer'Op mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

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

Defined in Capnp.Gen.Capnp.Rpc

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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

Allocate s (ThirdPartyCapDescriptor ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (ThirdPartyCapDescriptor ('Mut s)) Source #

MutListElem s (ThirdPartyCapDescriptor ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

setIndex :: RWCtx m s => ThirdPartyCapDescriptor ('Mut s) -> Int -> List ('Mut s) (ThirdPartyCapDescriptor ('Mut s)) -> m () Source #

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (ThirdPartyCapDescriptor ('Mut s))) Source #

ListElem mut (ThirdPartyCapDescriptor mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (ThirdPartyCapDescriptor mut) Source #

MessageDefault (ThirdPartyCapDescriptor mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (ThirdPartyCapDescriptor mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (ThirdPartyCapDescriptor mut) 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 ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

FromPtr msg (Exception msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

Allocate s (Exception ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Exception ('Mut s)) Source #

MutListElem s (Exception ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Exception ('Mut s))) Source #

ListElem mut (Exception mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut (Exception mut) Source #

Methods

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

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

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

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

MessageDefault (Exception mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

HasMessage (Exception mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

message :: Exception mut -> Message mut Source #

newtype List mut (Exception mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

newtype List mut (Exception mut) = Exception'List_ (ListOf mut (Struct mut))

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 (Mut s))) => Exception (Mut s) -> Text (Mut s) -> m () Source #

new_Exception'reason :: RWCtx m s => Int -> Exception (Mut s) -> m (Text (Mut s)) 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 mut 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

Methods

cerialize :: RWCtx m s => Message ('Mut s) -> Exception'Type -> m (Cerial ('Mut s) Exception'Type) Source #

MutListElem s Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) Exception'Type) Source #

ListElem mut Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

Associated Types

data List mut 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.12.0.0-9jnlPOdOYzy7ssULfTgYnR" '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 mut Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc