capnp-0.3.0.0: Cap'n Proto for Haskell

Safe HaskellNone
LanguageHaskell2010

Capnp.Capnp.RpcTwoparty

Description

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

Documentation

newtype JoinKeyPart msg Source #

Constructors

JoinKeyPart_newtype_ (Struct msg) 
Instances
ToStruct msg (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

toStruct :: JoinKeyPart msg -> Struct msg Source #

FromStruct msg (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

IsPtr msg (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

ListElem msg (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

MessageDefault (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

HasMessage (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

type InMessage (JoinKeyPart msg) :: * Source #

data List msg (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

data List msg (JoinKeyPart msg) = List_JoinKeyPart (ListOf msg (Struct msg))
type InMessage (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

type InMessage (JoinKeyPart msg) = msg

newtype JoinResult msg Source #

Constructors

JoinResult_newtype_ (Struct msg) 
Instances
ToStruct msg (JoinResult msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

toStruct :: JoinResult msg -> Struct msg Source #

FromStruct msg (JoinResult msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

IsPtr msg (JoinResult msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

ListElem msg (JoinResult msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

MessageDefault (JoinResult msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

HasMessage (JoinResult msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

type InMessage (JoinResult msg) :: * Source #

data List msg (JoinResult msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

data List msg (JoinResult msg) = List_JoinResult (ListOf msg (Struct msg))
type InMessage (JoinResult msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

type InMessage (JoinResult msg) = msg

get_JoinResult'cap :: ReadCtx m msg => JoinResult msg -> m (Maybe (Ptr msg)) Source #

newtype ProvisionId msg Source #

Constructors

ProvisionId_newtype_ (Struct msg) 
Instances
ToStruct msg (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

toStruct :: ProvisionId msg -> Struct msg Source #

FromStruct msg (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

IsPtr msg (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

ListElem msg (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

MessageDefault (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

HasMessage (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

type InMessage (ProvisionId msg) :: * Source #

data List msg (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

data List msg (ProvisionId msg) = List_ProvisionId (ListOf msg (Struct msg))
type InMessage (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

type InMessage (ProvisionId msg) = msg

data Side Source #

Instances
Enum Side Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

succ :: Side -> Side #

pred :: Side -> Side #

toEnum :: Int -> Side #

fromEnum :: Side -> Int #

enumFrom :: Side -> [Side] #

enumFromThen :: Side -> Side -> [Side] #

enumFromTo :: Side -> Side -> [Side] #

enumFromThenTo :: Side -> Side -> Side -> [Side] #

Eq Side Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

(==) :: Side -> Side -> Bool #

(/=) :: Side -> Side -> Bool #

Read Side Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Show Side Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

showsPrec :: Int -> Side -> ShowS #

show :: Side -> String #

showList :: [Side] -> ShowS #

Generic Side Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

type Rep Side :: * -> * #

Methods

from :: Side -> Rep Side x #

to :: Rep Side x -> Side #

IsWord Side Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

MutListElem s Side Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

ListElem msg Side Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

data List msg Side :: * Source #

Methods

length :: List msg Side -> Int Source #

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

IsPtr msg (List msg Side) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

type Rep Side Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

type Rep Side = D1 (MetaData "Side" "Capnp.Capnp.RpcTwoparty" "capnp-0.3.0.0-KeQ8qWCAauTAd8VLAv8qve" False) (C1 (MetaCons "Side'server" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Side'client" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Side'unknown'" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word16))))
data List msg Side Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

data List msg Side = List_Side (ListOf msg Word16)

newtype VatId msg Source #

Constructors

VatId_newtype_ (Struct msg) 
Instances
ToStruct msg (VatId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

toStruct :: VatId msg -> Struct msg Source #

FromStruct msg (VatId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

IsPtr msg (VatId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

ListElem msg (VatId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

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

Methods

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

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

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

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

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

MessageDefault (VatId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Methods

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

HasMessage (VatId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

Associated Types

type InMessage (VatId msg) :: * Source #

Methods

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

data List msg (VatId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

data List msg (VatId msg) = List_VatId (ListOf msg (Struct msg))
type InMessage (VatId msg) Source # 
Instance details

Defined in Capnp.Capnp.RpcTwoparty

type InMessage (VatId msg) = msg

get_VatId'side :: ReadCtx m msg => VatId msg -> m Side Source #

set_VatId'side :: RWCtx m s => VatId (MutMsg s) -> Side -> m () Source #