capnp-0.5.0.0: Cap'n Proto for Haskell

Safe HaskellNone
LanguageHaskell2010

Capnp.Rpc

Contents

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
Default ConnConfig Source # 
Instance details

Defined in Capnp.Rpc.Untyped

Methods

def :: ConnConfig #

Calling methods

(?) :: InvokePureCtx m p r => MethodHandler m p r -> p -> m (Promise r) Source #

Handling method calls

data MethodHandler m p r Source #

a MethodHandler m p r handles a method call with parameters p and return type r, in monad m.

The library represents method handlers via an abstract type MethodHandler, parametrized over parameter (p) and return (r) types, and the monadic context in which it runs (m). This allows us to provide different strategies for actually handling methods; there are various helper functions which construct these handlers.

At some point we will likely additionally provide handlers affording:

  • Working directly with the low-level data types.
  • Replying to the method call asynchronously, allowing later method calls to be serviced before the current one is finished.

pureHandler :: (MonadCatch m, MonadSTM m, PrimMonad m, s ~ PrimState m, Decerialize p, FromPtr ConstMsg (Cerial ConstMsg p), Cerialize r, ToStruct (MutMsg s) (Cerial (MutMsg s) r)) => (cap -> p -> m r) -> cap -> MethodHandler m p r Source #

pureHandler f cap is a MethodHandler which calls a function f that accepts the receiver and the parameter type as exposed by the high-level API, and returns the high-level API representation of the return type.

rawHandler :: (MonadCatch m, MonadSTM m, PrimMonad m, s ~ PrimState m, Decerialize p, FromPtr ConstMsg (Cerial ConstMsg p), Decerialize r, ToStruct ConstMsg (Cerial ConstMsg r)) => (cap -> Cerial ConstMsg p -> m (Cerial ConstMsg r)) -> cap -> MethodHandler m p r Source #

Like pureHandler, except that the parameter and return value use the low-level representation.

rawAsyncHandler :: (MonadCatch m, MonadSTM m, PrimMonad m, s ~ PrimState m, Decerialize p, FromPtr ConstMsg (Cerial ConstMsg p), Decerialize r, ToStruct ConstMsg (Cerial ConstMsg r)) => (cap -> Cerial ConstMsg p -> Fulfiller (Cerial ConstMsg r) -> m ()) -> cap -> MethodHandler m p r Source #

Like rawHandler, except that it takes a fulfiller for the result, instead of returning it. This allows the result to be supplied some time after the method returns, making it possible to service other method calls before the result is available.

methodUnimplemented :: MonadIO m => MethodHandler m p r Source #

A MethodHandler which always throws an unimplemented exception.

methodThrow :: MonadIO m => Exception -> MethodHandler m p r Source #

methodThrow exn is a MethodHandler which always throws exn.

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
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

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.

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.

Supervisors

Misc.