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

Capnp.Rpc.Untyped

Description

This module does not deal with schema-level concepts; all capabilities, methods etc. as used here are untyped.

Synopsis

Connections to other vats

data ConnConfig Source #

Configuration information for a connection.

Constructors

ConnConfig 

Fields

  • maxQuestions :: !Word32

    The maximum number of simultanious outstanding requests to the peer vat. Once this limit is reached, further questsions will block until some of the existing questions have been answered.

    Defaults to 128.

  • maxExports :: !Word32

    The maximum number of objects which may be exported on this connection.

    Defaults to 8192.

  • debugMode :: !Bool

    In debug mode, errors reported by the RPC system to its peers will contain extra information. This should not be used in production, as it is possible for these messages to contain sensitive information, but it can be useful for debugging.

    Defaults to False.

  • getBootstrap :: Supervisor -> STM (Maybe Client)

    Get the bootstrap interface we should serve for this connection. the argument is a supervisor whose lifetime is bound to the connection. If $sel:getBootstrap:ConnConfig returns Nothing, we will respond to bootstrap messages with an exception.

    The default always returns Nothing.

    $sel:getBootstrap:ConnConfig MUST NOT block; the connection will not be serviced and $sel:withBootstrap:ConnConfig will not be run until this returns. If you need to supply the bootstrap interface later, use newPromiseClient.

  • withBootstrap :: Maybe (Supervisor -> Client -> IO ())

    An action to perform with access to the remote vat's bootstrap interface. The supervisor argument is bound to the lifetime of the connection. If this is Nothing (the default), the bootstrap interface will not be requested.

Instances

Instances details
Default ConnConfig Source # 
Instance details

Defined in Capnp.Rpc.Untyped

Methods

def :: ConnConfig #

handleConn :: Transport -> ConnConfig -> IO () Source #

Handle a connection to another vat. Returns when the connection is closed.

Clients for capabilities

data Client Source #

A reference to a capability, which may be live either in the current vat or elsewhere. Holding a client affords making method calls on a capability or modifying the local vat's reference count to it.

Instances

Instances details
Eq Client Source # 
Instance details

Defined in Capnp.Rpc.Untyped

Methods

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

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

Show Client Source # 
Instance details

Defined in Capnp.Rpc.Untyped

IsClient Client Source # 
Instance details

Defined in Capnp.Rpc.Untyped

Parse Capability Client Source # 
Instance details

Defined in Capnp.New.Basics

Methods

parse :: ReadCtx m 'Const => Raw 'Const Capability -> m Client Source #

encode :: RWCtx m s => Message ('Mut s) -> Client -> m (Raw ('Mut s) Capability) Source #

call :: MonadSTM m => CallInfo -> Client -> m Pipeline Source #

Queue a call on a client.

nullClient :: Client Source #

A null client. This is the only client value that can be represented statically. Throws exceptions in response to all method calls.

newPromiseClient :: (MonadSTM m, IsClient c) => m (c, Fulfiller c) Source #

Create a new client based on a promise. The fulfiller can be used to supply the final client.

class IsClient a where Source #

Types which may be converted to and from Clients. Typically these will be simple type wrappers for capabilities.

Methods

toClient :: a -> Client Source #

Convert a value to a client.

fromClient :: Client -> a Source #

Convert a client to a value.

Instances

Instances details
IsClient Client Source # 
Instance details

Defined in Capnp.Rpc.Untyped

ReprFor a ~ 'Ptr ('Just 'Cap) => IsClient (Client a) Source # 
Instance details

Defined in Capnp.Repr.Methods

IsClient (Persistent sturdyRef owner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.Pure

Methods

toClient :: Persistent sturdyRef owner -> Client Source #

fromClient :: Client -> Persistent sturdyRef owner Source #

IsClient (RealmGateway internalRef externalRef internalOwner externalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.Pure

Methods

toClient :: RealmGateway internalRef externalRef internalOwner externalOwner -> Client Source #

fromClient :: Client -> RealmGateway internalRef externalRef internalOwner externalOwner Source #

Promise pipelining

data Pipeline Source #

A Pipeline is a reference to a value within a message that has not yet arrived.

walkPipelinePtr :: Pipeline -> Word16 -> Pipeline Source #

walkPipleinePtr follows a pointer starting from the object referred to by the Pipeline. The Pipeline must refer to a struct, and the pointer is referred to by its index into the struct's pointer section.

pipelineClient :: MonadSTM m => Pipeline -> m Client Source #

Convert a Pipeline into a Client, which can be used to send messages to the referant of the Pipeline, using promise pipelining.

waitPipeline :: MonadSTM m => Pipeline -> m RawMPtr Source #

Wait for the pipeline's target to resolve, and return the corresponding pointer.

Exporting local objects

export :: MonadSTM m => Supervisor -> ServerOps IO -> m Client Source #

Spawn a local server with its lifetime bound to the supervisor, and return a client for it. When the client is garbage collected, the server will be stopped (if it is still running).

Unwrapping local clients

unwrapServer :: (IsClient c, Typeable a) => c -> Maybe a Source #

Attempt to unwrap a client, to get at an underlying value from the server. Returns Nothing on failure.

This shells out to the underlying server's implementation of unwrap. It will fail with Nothing if any of these are true:

  • The client is a promise.
  • The client points to an object in a remote vat.
  • The underlying Server's unwrap method returns Nothing for type a.

Waiting for resolution

waitClient :: (IsClient c, MonadSTM m) => c -> m c Source #

Wait for the client to be fully resolved, and then return a client pointing directly to the destination.

If the argument is null, a local client, or a (permanent) remote client, this returns the argument immediately. If the argument is a promise client, then this waits for the promise to resolve and returns the result of the resolution. If the promise resolves to *another* promise, then this waits for that promise to also resolve.

If the promise is rejected, then this throws the corresponding exception.

Errors

data RpcError Source #

Errors which can be thrown by the rpc system.

Constructors

ReceivedAbort Exception

The remote vat sent us an abort message.

SentAbort Exception

We sent an abort to the remote vat.

Instances

Instances details
Eq RpcError Source # 
Instance details

Defined in Capnp.Rpc.Untyped

Show RpcError Source # 
Instance details

Defined in Capnp.Rpc.Untyped

Generic RpcError Source # 
Instance details

Defined in Capnp.Rpc.Untyped

Associated Types

type Rep RpcError :: Type -> Type #

Methods

from :: RpcError -> Rep RpcError x #

to :: Rep RpcError x -> RpcError #

Exception RpcError Source # 
Instance details

Defined in Capnp.Rpc.Untyped

type Rep RpcError Source # 
Instance details

Defined in Capnp.Rpc.Untyped

type Rep RpcError = D1 ('MetaData "RpcError" "Capnp.Rpc.Untyped" "capnp-0.11.0.0-50ovYl0NjrHDYHPSniP5DX" 'False) (C1 ('MetaCons "ReceivedAbort" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exception)) :+: C1 ('MetaCons "SentAbort" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exception)))

data Exception Source #

Instances

Instances details
Eq Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

Show Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

Generic Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

Associated Types

type Rep Exception :: Type -> Type #

Exception Exception Source # 
Instance details

Defined in Capnp.Rpc.Errors

Default Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

Methods

def :: Exception #

Decerialize Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

Associated Types

type Cerial mut Exception Source #

FromStruct 'Const Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

Cerialize s Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

Methods

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

Marshal s Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

Methods

marshalInto :: RWCtx m s => Cerial ('Mut s) Exception -> Exception -> m () Source #

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

Defined in Capnp.Gen.Capnp.Rpc.Pure

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

Defined in Capnp.Gen.Capnp.Rpc.Pure

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

Defined in Capnp.Gen.Capnp.Rpc.Pure

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

Defined in Capnp.Gen.Capnp.Rpc.Pure

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

Defined in Capnp.Gen.Capnp.Rpc.Pure

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

Defined in Capnp.Gen.Capnp.Rpc.Pure

Methods

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

Cerialize s (Vector Exception) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

Methods

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

type Rep Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

type Rep Exception = D1 ('MetaData "Exception" "Capnp.Gen.Capnp.Rpc.Pure" "capnp-0.11.0.0-50ovYl0NjrHDYHPSniP5DX" 'False) (C1 ('MetaCons "Exception" 'PrefixI 'True) ((S1 ('MetaSel ('Just "reason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "obsoleteIsCallersFault") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "obsoleteDurability") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16) :*: S1 ('MetaSel ('Just "type_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exception'Type))))
type Cerial msg Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.Pure

type Cerial msg Exception = Exception msg

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.11.0.0-50ovYl0NjrHDYHPSniP5DX" '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

Shutting down the connection