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

Capnp.Rpc

Description

This module exposes the most commonly used parts of the RPC subsystem.

Synopsis

Establishing connections

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

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

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 #

throwing errors

throwFailed :: MonadThrow m => Text -> m a Source #

Throw an exception with a type field of Exception'Type'failed and the argument as a reason.

Transmitting messages

data Transport Source #

A Transport handles transmitting RPC messages.

Constructors

Transport 

Fields

socketTransport :: Socket -> WordCount -> Transport Source #

socketTransport socket limit is a transport which reads and writes messages to/from a socket. It uses limit as the traversal limit when reading messages and decoing.

handleTransport :: Handle -> WordCount -> Transport Source #

handleTransport handle limit is a transport which reads and writes messages from/to handle. It uses limit as the traversal limit when reading messages and decoding.

tracingTransport :: (String -> IO ()) -> Transport -> Transport Source #

tracingTransport log trans wraps another transport trans, loging messages when they are sent or received (using the log function). This can be useful for debugging.

Promises

Clients

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 #

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

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.

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.

Reflection

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.

Supervisors

Misc.