capnp-0.17.0.0: Cap'n Proto for Haskell
Safe HaskellSafe-Inferred
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.

  • maxCallWords :: !WordCount

    The maximum total size of outstanding call messages that will be accepted; if this limit is reached, the implementation will not read more messages from the connection until some calls have completed and freed up enough space.

    Defaults to 32MiB in words.

  • 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
Show Client Source # 
Instance details

Defined in Internal.Rpc.Breaker

IsClient Client Source # 
Instance details

Defined in Capnp.Rpc.Untyped

Eq Client Source # 
Instance details

Defined in Internal.Rpc.Breaker

Methods

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

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

Parse Capability Client Source # 
Instance details

Defined in Capnp.Basics

Methods

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

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

call :: MonadSTM m => CallInfo -> Client -> m (Promise 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

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 -> 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 (Parsed Exception)

The remote vat sent us an abort message.

SentAbort (Parsed Exception)

We sent an abort to the remote vat.

Instances

Instances details
Exception 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 #

Show RpcError Source # 
Instance details

Defined in Capnp.Rpc.Untyped

Eq 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.17.0.0-KnW61yXmCDxBdeB4uIxK8L" 'False) (C1 ('MetaCons "ReceivedAbort" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Parsed Exception))) :+: C1 ('MetaCons "SentAbort" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Parsed Exception))))

Shutting down the connection