| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Capnp.Rpc.Server
Description
The term server in this context refers to a thread that handles method calls for a particular capability (The capnproto rpc protocol itself has no concept of clients and servers).
Synopsis
- class Monad m => Server m a | a -> m where
 - data ServerOps m = ServerOps {
- handleCall :: Word64 -> Word16 -> MethodHandler m (Maybe (Ptr 'Const)) (Maybe (Ptr 'Const))
 - handleStop :: m ()
 - handleCast :: forall a. Typeable a => Maybe a
 
 - data CallInfo = CallInfo {}
 - runServer :: Q CallInfo -> ServerOps IO -> IO ()
 - data MethodHandler m p r
 - pureHandler :: (MonadCatch m, MonadSTM m, PrimMonad m, s ~ PrimState m, Decerialize p, FromPtr 'Const (Cerial 'Const p), Cerialize s r, ToStruct ('Mut s) (Cerial ('Mut s) r)) => (cap -> p -> m r) -> cap -> MethodHandler m p r
 - rawHandler :: (MonadCatch m, MonadSTM m, PrimMonad m, s ~ PrimState m, Decerialize p, FromPtr 'Const (Cerial 'Const p), Decerialize r, ToStruct 'Const (Cerial 'Const r)) => (cap -> Cerial 'Const p -> m (Cerial 'Const r)) -> cap -> MethodHandler m p r
 - rawAsyncHandler :: (MonadCatch m, MonadSTM m, PrimMonad m, s ~ PrimState m, Decerialize p, FromPtr 'Const (Cerial 'Const p), Decerialize r, ToStruct 'Const (Cerial 'Const r)) => (cap -> Cerial 'Const p -> Fulfiller (Cerial 'Const r) -> m ()) -> cap -> MethodHandler m p r
 - methodThrow :: MonadIO m => Exception -> MethodHandler m p r
 - methodUnimplemented :: MonadIO m => MethodHandler m p r
 - untypedHandler :: (Maybe (Ptr 'Const) -> Fulfiller (Maybe (Ptr 'Const)) -> m ()) -> MethodHandler m (Maybe (Ptr 'Const)) (Maybe (Ptr 'Const))
 - toUntypedHandler :: MethodHandler m p r -> MethodHandler m (Maybe (Ptr 'Const)) (Maybe (Ptr 'Const))
 - fromUntypedHandler :: MethodHandler m (Maybe (Ptr 'Const)) (Maybe (Ptr 'Const)) -> MethodHandler m p r
 - invoke :: MonadSTM m => MethodHandler m (Maybe (Ptr 'Const)) (Maybe (Ptr 'Const)) -> Maybe (Ptr 'Const) -> Fulfiller (Maybe (Ptr 'Const)) -> m ()
 
Documentation
class Monad m => Server m a | a -> m where Source #
Base class for things that can act as capnproto servers.
Minimal complete definition
Nothing
Methods
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  | |
The operations necessary to receive and handle method calls, i.e. to implement an object. It is parametrized over the monadic context in which methods are serviced.
Constructors
| ServerOps | |
Fields 
  | |
runServer :: Q CallInfo -> ServerOps IO -> IO () Source #
Handle incoming messages for a given object.
Accepts a queue of messages to handle, and ServerOps used to handle them.
 returns when it receives a Stop message.
Handling methods
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.
 
Using high-level representations
pureHandler :: (MonadCatch m, MonadSTM m, PrimMonad m, s ~ PrimState m, Decerialize p, FromPtr 'Const (Cerial 'Const p), Cerialize s r, ToStruct ('Mut s) (Cerial ('Mut 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.
Using low-level representations
rawHandler :: (MonadCatch m, MonadSTM m, PrimMonad m, s ~ PrimState m, Decerialize p, FromPtr 'Const (Cerial 'Const p), Decerialize r, ToStruct 'Const (Cerial 'Const r)) => (cap -> Cerial 'Const p -> m (Cerial 'Const 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 'Const (Cerial 'Const p), Decerialize r, ToStruct 'Const (Cerial 'Const r)) => (cap -> Cerial 'Const p -> Fulfiller (Cerial 'Const 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.
Always throwing exceptions
methodThrow :: MonadIO m => Exception -> MethodHandler m p r Source #
 is a methodThrow exnMethodHandler which always throws exn.
methodUnimplemented :: MonadIO m => MethodHandler m p r Source #
A MethodHandler which always throws an unimplemented exception.
Working with untyped data
untypedHandler :: (Maybe (Ptr 'Const) -> Fulfiller (Maybe (Ptr 'Const)) -> m ()) -> MethodHandler m (Maybe (Ptr 'Const)) (Maybe (Ptr 'Const)) Source #
Construct a method handler from a function accepting an untyped
 pointer for the method's parameter, and a Fulfiller which accepts
 an untyped pointer for the method's return value.
toUntypedHandler :: MethodHandler m p r -> MethodHandler m (Maybe (Ptr 'Const)) (Maybe (Ptr 'Const)) Source #
Convert a MethodHandler for any parameter and return types into
 one that deals with untyped pointers.
fromUntypedHandler :: MethodHandler m (Maybe (Ptr 'Const)) (Maybe (Ptr 'Const)) -> MethodHandler m p r Source #
Inverse of toUntypedHandler