| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Capnp.Rpc.Untyped
Contents
Description
This module does not deal with schema-level concepts; all capabilities, methods etc. as used here are untyped.
Synopsis
- data ConnConfig = ConnConfig {- maxQuestions :: !Word32
- maxExports :: !Word32
- debugMode :: !Bool
- getBootstrap :: Supervisor -> STM (Maybe Client)
- withBootstrap :: Maybe (Supervisor -> Client -> IO ())
 
- handleConn :: Transport -> ConnConfig -> IO ()
- data Client
- call :: MonadSTM m => CallInfo -> Client -> m ()
- nullClient :: Client
- newPromiseClient :: (MonadSTM m, IsClient c) => m (c, Fulfiller c)
- class IsClient a where- toClient :: a -> Client
- fromClient :: Client -> a
 
- export :: MonadSTM m => Supervisor -> ServerOps IO -> m Client
- clientMethodHandler :: Word64 -> Word16 -> Client -> MethodHandler IO p r
- unwrapServer :: (IsClient c, Typeable a) => c -> Maybe a
- data RpcError
- data Exception = Exception {}
- data Exception'Type
Connections to other vats
data ConnConfig Source #
Configuration information for a connection.
Constructors
| ConnConfig | |
| Fields 
 | |
Instances
| Default ConnConfig Source # | |
| 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
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.
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
| IsClient Client Source # | |
| IsClient RealmGateway Source # | |
| Defined in Capnp.Gen.Capnp.Persistent.Pure | |
| IsClient Persistent Source # | |
| Defined in Capnp.Gen.Capnp.Persistent.Pure | |
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).
clientMethodHandler :: Word64 -> Word16 -> Client -> MethodHandler IO p r Source #
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 unwrapmethod returnsNothingfor typea.
Errors
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
| Eq RpcError Source # | |
| Show RpcError Source # | |
| Generic RpcError Source # | |
| Exception RpcError Source # | |
| Defined in Capnp.Rpc.Untyped Methods toException :: RpcError -> SomeException # fromException :: SomeException -> Maybe RpcError # displayException :: RpcError -> String # | |
| type Rep RpcError Source # | |
| Defined in Capnp.Rpc.Untyped type Rep RpcError = D1 (MetaData "RpcError" "Capnp.Rpc.Untyped" "capnp-0.6.0.0-kmuWJKkOwSDLq91ugTnNR" 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))) | |
Constructors
| Exception | |
| Fields | |
Instances
data Exception'Type Source #
Constructors
| Exception'Type'failed | |
| Exception'Type'overloaded | |
| Exception'Type'disconnected | |
| Exception'Type'unimplemented | |
| Exception'Type'unknown' Word16 |