Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module exposes the most commonly used parts of the RPC subsystem.
Synopsis
- handleConn :: Transport -> ConnConfig -> IO ()
- data ConnConfig = ConnConfig {
- maxQuestions :: !Word32
- maxExports :: !Word32
- debugMode :: !Bool
- getBootstrap :: Supervisor -> STM (Maybe Client)
- withBootstrap :: Maybe (Supervisor -> Client -> IO ())
- (?) :: InvokePureCtx m p r => MethodHandler m p r -> p -> m (Promise r)
- class Monad m => Server m a | a -> m where
- data MethodHandler m p r
- pureHandler :: (MonadCatch m, MonadSTM m, PrimMonad m, s ~ PrimState m, Decerialize p, FromPtr ConstMsg (Cerial ConstMsg p), Cerialize s r, ToStruct (MutMsg s) (Cerial (MutMsg s) r)) => (cap -> p -> m r) -> cap -> MethodHandler m p r
- 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
- 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
- methodUnimplemented :: MonadIO m => MethodHandler m p r
- methodThrow :: MonadIO m => Exception -> MethodHandler m p r
- throwFailed :: MonadThrow m => Text -> m a
- data Transport = Transport {}
- socketTransport :: Socket -> WordCount -> Transport
- handleTransport :: Handle -> WordCount -> Transport
- tracingTransport :: (String -> IO ()) -> Transport -> Transport
- module Capnp.Rpc.Promise
- data Client
- class IsClient a where
- toClient :: a -> Client
- fromClient :: Client -> a
- newPromiseClient :: (MonadSTM m, IsClient c) => m (c, Fulfiller c)
- waitClient :: (IsClient c, MonadSTM m) => c -> m c
- unwrapServer :: (IsClient c, Typeable a) => c -> Maybe a
- module Supervisors
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.
ConnConfig | |
|
Instances
Default ConnConfig Source # | |
Defined in Capnp.Rpc.Untyped def :: ConnConfig # |
Calling methods
(?) :: InvokePureCtx m p r => MethodHandler m p r -> p -> m (Promise r) Source #
Alias for invokePurePromise
Handling method calls
class Monad m => Server m a | a -> m where Source #
Base class for things that can act as capnproto servers.
Nothing
shutdown :: a -> m () Source #
Called when the last live reference to a server is dropped.
unwrap :: Typeable b => a -> Maybe b Source #
Try to extract a value of a given type. The default implementation
always fails (returns Nothing
). If an instance chooses to implement
this, it will be possible to use "reflection" on clients that point
at local servers to dynamically unwrap the server value. A typical
implementation will just call Typeable's cast
method, but this
needn't be the case -- a server may wish to allow local peers to
unwrap some value that is not exactly the data the server has access
to.
Instances
Server IO (Persistent sturdyRef owner) Source # | |
Defined in Capnp.Gen.Capnp.Persistent.Pure | |
Server IO (RealmGateway internalRef externalRef internalOwner externalOwner) Source # | |
Defined in Capnp.Gen.Capnp.Persistent.Pure |
data MethodHandler m p r Source #
a
handles a method call with parameters MethodHandler
m p rp
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 s r, ToStruct (MutMsg s) (Cerial (MutMsg s) r)) => (cap -> p -> m r) -> cap -> MethodHandler m p r Source #
is a pureHandler
f capMethodHandler
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 #
is a methodThrow
exnMethodHandler
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
A
handles transmitting RPC messages.Transport
socketTransport :: Socket -> WordCount -> Transport Source #
is a transport which reads and writes
messages to/from a socket. It uses socketTransport
socket limitlimit
as the traversal limit when
reading messages and decoing.
handleTransport :: Handle -> WordCount -> Transport Source #
is a transport which reads and writes
messages from/to handleTransport
handle limithandle
. It uses limit
as the traversal limit when
reading messages and decoding.
tracingTransport :: (String -> IO ()) -> Transport -> Transport Source #
wraps another transport tracingTransport
log transtrans
, loging
messages when they are sent or received (using the log
function). This
can be useful for debugging.
Promises
module Capnp.Rpc.Promise
Clients
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.
class IsClient a where Source #
Types which may be converted to and from Client
s. Typically these
will be simple type wrappers for capabilities.
toClient :: a -> Client Source #
Convert a value to a client.
fromClient :: Client -> a Source #
Convert a client to a value.
Instances
IsClient Client Source # | |
IsClient (Persistent sturdyRef owner) Source # | |
Defined in Capnp.Gen.Capnp.Persistent.Pure toClient :: Persistent sturdyRef owner -> Client Source # fromClient :: Client -> Persistent sturdyRef owner Source # | |
IsClient (RealmGateway internalRef externalRef internalOwner externalOwner) Source # | |
Defined in Capnp.Gen.Capnp.Persistent.Pure toClient :: RealmGateway internalRef externalRef internalOwner externalOwner -> Client Source # fromClient :: Client -> RealmGateway internalRef externalRef internalOwner externalOwner Source # |
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 returnsNothing
for typea
.
Supervisors
module Supervisors