capnp-0.1.0.0: Cap'n Proto for Haskell

Safe HaskellNone
LanguageHaskell2010

Capnp.Capnp.Rpc

Description

This module is the generated code for capnp/rpc.capnp, for the low-level api.

Documentation

newtype Accept msg Source #

Constructors

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

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Accept msg -> Struct msg Source #

FromStruct msg (Accept msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (Accept msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (Accept msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (Accept msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Accept msg Source #

HasMessage (Accept msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Accept msg -> msg Source #

data List msg (Accept msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (Accept msg) = List_Accept (ListOf msg (Struct msg))

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

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

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

newtype Bootstrap msg Source #

Constructors

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

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Bootstrap msg -> Struct msg Source #

FromStruct msg (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (Bootstrap msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Bootstrap msg Source #

HasMessage (Bootstrap msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Bootstrap msg -> msg Source #

data List msg (Bootstrap msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (Bootstrap msg) = List_Bootstrap (ListOf msg (Struct msg))

newtype Call msg Source #

Constructors

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

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Call msg -> Struct msg Source #

FromStruct msg (Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (Call msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Call msg Source #

HasMessage (Call msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Call msg -> msg Source #

data List msg (Call msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (Call msg) = List_Call (ListOf msg (Struct msg))

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

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

has_Call'methodId :: 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 => Call msg -> m (Payload msg) Source #

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

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

newtype CapDescriptor msg Source #

Constructors

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

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: CapDescriptor msg -> Struct msg Source #

FromStruct msg (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (CapDescriptor msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> CapDescriptor msg Source #

HasMessage (CapDescriptor msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: CapDescriptor msg -> msg Source #

data List msg (CapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (CapDescriptor msg) = List_CapDescriptor (ListOf msg (Struct msg))

newtype Disembargo msg Source #

Constructors

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

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Disembargo msg -> Struct msg Source #

FromStruct msg (Disembargo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (Disembargo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (Disembargo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (Disembargo msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Disembargo msg Source #

HasMessage (Disembargo msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Disembargo msg -> msg Source #

data List msg (Disembargo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (Disembargo msg) = List_Disembargo (ListOf msg (Struct msg))

newtype Exception msg Source #

Constructors

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

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Exception msg -> Struct msg Source #

FromStruct msg (Exception msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (Exception msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (Exception msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (Exception msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Exception msg Source #

HasMessage (Exception msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Exception msg -> msg Source #

data List msg (Exception msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (Exception msg) = List_Exception (ListOf msg (Struct msg))

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

newtype Finish msg Source #

Constructors

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

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Finish msg -> Struct msg Source #

FromStruct msg (Finish msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (Finish msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (Finish msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (Finish msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Finish msg Source #

HasMessage (Finish msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Finish msg -> msg Source #

data List msg (Finish msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (Finish msg) = List_Finish (ListOf msg (Struct msg))

newtype Join msg Source #

Constructors

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

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Join msg -> Struct msg Source #

FromStruct msg (Join msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (Join msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (Join msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (Join msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Join msg Source #

HasMessage (Join msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Join msg -> msg Source #

data List msg (Join msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (Join msg) = List_Join (ListOf msg (Struct msg))

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

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

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

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

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

newtype Message msg Source #

Constructors

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

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Message msg -> Struct msg Source #

FromStruct msg (Message msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (Message msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (Message msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (Message msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Message msg Source #

HasMessage (Message msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Message msg -> msg Source #

data List msg (Message msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (Message msg) = List_Message (ListOf msg (Struct msg))

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

has_Message' :: ReadCtx m msg => Message msg -> m Bool Source #

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

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

newtype MessageTarget msg Source #

Constructors

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

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: MessageTarget msg -> Struct msg Source #

FromStruct msg (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (MessageTarget msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> MessageTarget msg Source #

HasMessage (MessageTarget msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: MessageTarget msg -> msg Source #

data List msg (MessageTarget msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (MessageTarget msg) = List_MessageTarget (ListOf msg (Struct msg))

newtype Payload msg Source #

Constructors

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

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Payload msg -> Struct msg Source #

FromStruct msg (Payload msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (Payload msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (Payload msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (Payload msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Payload msg Source #

HasMessage (Payload msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Payload msg -> msg Source #

data List msg (Payload msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (Payload msg) = List_Payload (ListOf msg (Struct msg))

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

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

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

newtype PromisedAnswer msg Source #

Constructors

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

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: PromisedAnswer msg -> Struct msg Source #

FromStruct msg (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (PromisedAnswer msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> PromisedAnswer msg Source #

HasMessage (PromisedAnswer msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: PromisedAnswer msg -> msg Source #

data List msg (PromisedAnswer msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (PromisedAnswer msg) = List_PromisedAnswer (ListOf msg (Struct msg))

newtype Provide msg Source #

Constructors

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

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Provide msg -> Struct msg Source #

FromStruct msg (Provide msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (Provide msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (Provide msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (Provide msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Provide msg Source #

HasMessage (Provide msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Provide msg -> msg Source #

data List msg (Provide msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (Provide msg) = List_Provide (ListOf msg (Struct msg))

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

newtype Release msg Source #

Constructors

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

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Release msg -> Struct msg Source #

FromStruct msg (Release msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (Release msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (Release msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (Release msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Release msg Source #

HasMessage (Release msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Release msg -> msg Source #

data List msg (Release msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (Release msg) = List_Release (ListOf msg (Struct msg))

has_Release'id :: ReadCtx m msg => Release msg -> m Bool Source #

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

newtype Resolve msg Source #

Constructors

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

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Resolve msg -> Struct msg Source #

FromStruct msg (Resolve msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (Resolve msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (Resolve msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (Resolve msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Resolve msg Source #

HasMessage (Resolve msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Resolve msg -> msg Source #

data List msg (Resolve msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (Resolve msg) = List_Resolve (ListOf msg (Struct msg))

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

newtype Return msg Source #

Constructors

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

Defined in Capnp.Capnp.Rpc

Methods

toStruct :: Return msg -> Struct msg Source #

FromStruct msg (Return msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (Return msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (Return msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (Return msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Return msg Source #

HasMessage (Return msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Return msg -> msg Source #

data List msg (Return msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (Return msg) = List_Return (ListOf msg (Struct msg))

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

newtype ThirdPartyCapDescriptor msg Source #

Instances
ToStruct msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

FromStruct msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

ListElem msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (ThirdPartyCapDescriptor msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

HasMessage (ThirdPartyCapDescriptor msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data List msg (ThirdPartyCapDescriptor msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

newtype Call'sendResultsTo msg Source #

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

Defined in Capnp.Capnp.Rpc

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

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

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

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

Defined in Capnp.Capnp.Rpc

Methods

message :: Call'sendResultsTo msg -> msg Source #

data List msg (Call'sendResultsTo msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

newtype Disembargo'context msg Source #

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

Defined in Capnp.Capnp.Rpc

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

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

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

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

Defined in Capnp.Capnp.Rpc

Methods

message :: Disembargo'context msg -> msg Source #

data List msg (Disembargo'context msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

data Exception'Type Source #

Instances
Enum Exception'Type Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Eq Exception'Type Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Read Exception'Type Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Show Exception'Type Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Generic Exception'Type Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

IsWord Exception'Type Source # 
Instance details

Defined in Capnp.Capnp.Rpc

MutListElem s Exception'Type Source # 
Instance details

Defined in Capnp.Capnp.Rpc

ListElem msg Exception'Type Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

data List msg Exception'Type :: * Source #

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

type Rep Exception'Type Source # 
Instance details

Defined in Capnp.Capnp.Rpc

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

Defined in Capnp.Capnp.Rpc

newtype PromisedAnswer'Op msg Source #

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

Defined in Capnp.Capnp.Rpc

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

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

Defined in Capnp.Capnp.Rpc

Methods

message :: PromisedAnswer'Op msg -> msg Source #

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

Defined in Capnp.Capnp.Rpc

newtype Resolve' msg Source #

Constructors

Resolve'_newtype_ (Struct msg) 
Instances
ToStruct msg (Resolve' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

FromStruct msg (Resolve' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (Resolve' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (Resolve' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (Resolve' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Resolve' msg Source #

HasMessage (Resolve' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Resolve' msg -> msg Source #

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

Defined in Capnp.Capnp.Rpc

data List msg (Resolve' msg) = List_Resolve' (ListOf msg (Struct msg))

data Resolve'' msg Source #

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

has_Resolve'' :: ReadCtx m msg => Resolve' msg -> m Bool Source #

newtype Return' msg Source #

Constructors

Return'_newtype_ (Struct msg) 
Instances
ToStruct msg (Return' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

FromStruct msg (Return' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

IsPtr msg (Return' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

ListElem msg (Return' msg) Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.Rpc

Methods

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

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

MessageDefault (Return' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

messageDefault :: msg -> Return' msg Source #

HasMessage (Return' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Rpc

Methods

message :: Return' msg -> msg Source #

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

Defined in Capnp.Capnp.Rpc

data List msg (Return' msg) = List_Return' (ListOf msg (Struct msg))

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

has_Return'' :: ReadCtx m msg => Return' msg -> m Bool Source #