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

Capnp.Gen.Capnp.RpcTwoparty

Documentation

data Side Source #

Instances

Instances details
Enum Side Source # 
Instance details

Defined in Capnp.Gen.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.Gen.Capnp.RpcTwoparty

Methods

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

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

Read Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Show Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

showsPrec :: Int -> Side -> ShowS #

show :: Side -> String #

showList :: [Side] -> ShowS #

Generic Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

type Rep Side :: Type -> Type #

Methods

from :: Side -> Rep Side x #

to :: Rep Side x -> Side #

Decerialize Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.Pure

Associated Types

type Cerial msg Side Source #

IsWord Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Cerialize s Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Side -> m (Cerial (MutMsg s) Side) Source #

MutListElem s Side Source # 
Instance details

Defined in Capnp.Gen.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.Gen.Capnp.RpcTwoparty

Associated Types

data List msg Side Source #

Methods

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

toUntypedList :: List msg Side -> List msg Source #

length :: List msg Side -> Int Source #

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

Cerialize s (Vector (Vector (Vector (Vector (Vector (Vector Side)))))) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.Pure

Cerialize s (Vector (Vector (Vector (Vector (Vector Side))))) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.Pure

Cerialize s (Vector (Vector (Vector (Vector Side)))) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.Pure

Cerialize s (Vector (Vector (Vector Side))) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Vector (Vector (Vector Side)) -> m (Cerial (MutMsg s) (Vector (Vector (Vector Side)))) Source #

Cerialize s (Vector (Vector Side)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Vector (Vector Side) -> m (Cerial (MutMsg s) (Vector (Vector Side))) Source #

Cerialize s (Vector Side) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.Pure

Methods

cerialize :: RWCtx m s => MutMsg s -> Vector Side -> m (Cerial (MutMsg s) (Vector Side)) Source #

type Rep Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

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

Defined in Capnp.Gen.Capnp.RpcTwoparty.Pure

type Cerial msg Side = Side
newtype List msg Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

newtype List msg Side = Side'List_ (ListOf msg Word16)

newtype VatId msg Source #

Constructors

VatId'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

toStruct :: VatId msg -> Struct msg Source #

FromStruct msg (VatId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

FromPtr msg (VatId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.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.Gen.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.Gen.Capnp.RpcTwoparty

Associated Types

data List msg (VatId msg) Source #

Methods

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

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

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

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

MessageDefault (VatId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

HasMessage (VatId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

type InMessage (VatId msg) Source #

Methods

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

newtype List msg (VatId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

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

Defined in Capnp.Gen.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 #

newtype ProvisionId msg Source #

Constructors

ProvisionId'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

toStruct :: ProvisionId msg -> Struct msg Source #

FromStruct msg (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

FromPtr msg (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.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.Gen.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.Gen.Capnp.RpcTwoparty

Associated Types

data List msg (ProvisionId msg) Source #

Methods

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

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

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

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

MessageDefault (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

HasMessage (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

type InMessage (ProvisionId msg) Source #

newtype List msg (ProvisionId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

type InMessage (ProvisionId msg) = msg

newtype RecipientId msg Source #

Constructors

RecipientId'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

toStruct :: RecipientId msg -> Struct msg Source #

FromStruct msg (RecipientId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

FromPtr msg (RecipientId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

ListElem msg (RecipientId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

data List msg (RecipientId msg) Source #

Methods

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

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

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

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

MessageDefault (RecipientId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

HasMessage (RecipientId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

type InMessage (RecipientId msg) Source #

newtype List msg (RecipientId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

type InMessage (RecipientId msg) = msg

newtype ThirdPartyCapId msg Source #

Constructors

ThirdPartyCapId'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

toStruct :: ThirdPartyCapId msg -> Struct msg Source #

FromStruct msg (ThirdPartyCapId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

FromPtr msg (ThirdPartyCapId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

ListElem msg (ThirdPartyCapId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

data List msg (ThirdPartyCapId msg) Source #

Methods

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

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

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

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

MessageDefault (ThirdPartyCapId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

HasMessage (ThirdPartyCapId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

type InMessage (ThirdPartyCapId msg) Source #

newtype List msg (ThirdPartyCapId msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

type InMessage (ThirdPartyCapId msg) = msg

newtype JoinKeyPart msg Source #

Constructors

JoinKeyPart'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

toStruct :: JoinKeyPart msg -> Struct msg Source #

FromStruct msg (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

FromPtr msg (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.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.Gen.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.Gen.Capnp.RpcTwoparty

Associated Types

data List msg (JoinKeyPart msg) Source #

Methods

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

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

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

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

MessageDefault (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

HasMessage (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

type InMessage (JoinKeyPart msg) Source #

newtype List msg (JoinKeyPart msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

type InMessage (JoinKeyPart msg) = msg

newtype JoinResult msg Source #

Constructors

JoinResult'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

toStruct :: JoinResult msg -> Struct msg Source #

FromStruct msg (JoinResult msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

FromPtr msg (JoinResult msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Methods

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

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

Defined in Capnp.Gen.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.Gen.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.Gen.Capnp.RpcTwoparty

Associated Types

data List msg (JoinResult msg) Source #

Methods

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

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

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

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

MessageDefault (JoinResult msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

HasMessage (JoinResult msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

Associated Types

type InMessage (JoinResult msg) Source #

newtype List msg (JoinResult msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

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

Defined in Capnp.Gen.Capnp.RpcTwoparty

type InMessage (JoinResult msg) = msg

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

set_JoinResult'cap :: (RWCtx m s, ToPtr s (Maybe (Ptr (MutMsg s)))) => JoinResult (MutMsg s) -> Maybe (Ptr (MutMsg s)) -> m () Source #