Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type CallHandler = Map Word64 (Vector UntypedMethodHandler)
- type MethodHandler p r = Raw 'Const p -> Fulfiller (Raw 'Const r) -> IO ()
- type UntypedMethodHandler = MethodHandler AnyStruct AnyStruct
- class (IsCap i, HasTypeId i) => Export i where
- type Server i :: * -> Constraint
- methodHandlerTree :: Server i s => Proxy i -> s -> MethodHandlerTree
- export :: forall i s m. (MonadSTM m, Export i, Server i s, SomeServer s) => Supervisor -> s -> m (Client i)
- findMethod :: Word64 -> Word16 -> CallHandler -> Maybe UntypedMethodHandler
- class SomeServer a where
- handleParsed :: (Parse p pp, IsStruct p, Parse r rr, IsStruct r) => (pp -> IO rr) -> MethodHandler p r
- handleRaw :: (IsStruct p, IsStruct r) => (Raw 'Const p -> IO (Raw 'Const r)) -> MethodHandler p r
- methodUnimplemented :: MethodHandler p r
- toUntypedMethodHandler :: forall p r. (IsStruct p, IsStruct r) => MethodHandler p r -> UntypedMethodHandler
- data MethodHandlerTree = MethodHandlerTree {}
Documentation
type CallHandler = Map Word64 (Vector UntypedMethodHandler) Source #
A handler for arbitrary RPC calls. Maps (interfaceId, methodId) pairs to
UntypedMethodHandler
s.
type MethodHandler p r = Raw 'Const p -> Fulfiller (Raw 'Const r) -> IO () Source #
Type alias for a handler for a particular rpc method.
type UntypedMethodHandler = MethodHandler AnyStruct AnyStruct Source #
Type alias for a handler for an untyped RPC method.
class (IsCap i, HasTypeId i) => Export i where Source #
Generated interface types have instances of Export
, which allows a server
for that interface to be exported as a Client
.
type Server i :: * -> Constraint Source #
The constraint needed for a server to implement an interface;
if
is satisfied, Server
i ss
is a server for interface i
.
The code generator generates a type class for each interface, and
this will aways be an alias for that type class.
methodHandlerTree :: Server i s => Proxy i -> s -> MethodHandlerTree Source #
Convert the server to a MethodHandlerTree
populated with appropriate
MethodHandler
s for the interface. This is really only exported for use
by generated code; users of the library will generally prefer to use
export
.
Instances
(TypeParam sturdyRef, TypeParam owner) => Export (Persistent sturdyRef owner) Source # | |
Defined in Capnp.Gen.Capnp.Persistent.New type Server (Persistent sturdyRef owner) :: Type -> Constraint Source # methodHandlerTree :: Server (Persistent sturdyRef owner) s => Proxy (Persistent sturdyRef owner) -> s -> MethodHandlerTree Source # | |
(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => Export (RealmGateway internalRef externalRef internalOwner externalOwner) Source # | |
Defined in Capnp.Gen.Capnp.Persistent.New type Server (RealmGateway internalRef externalRef internalOwner externalOwner) :: Type -> Constraint Source # methodHandlerTree :: Server (RealmGateway internalRef externalRef internalOwner externalOwner) s => Proxy (RealmGateway internalRef externalRef internalOwner externalOwner) -> s -> MethodHandlerTree Source # |
export :: forall i s m. (MonadSTM m, Export i, Server i s, SomeServer s) => Supervisor -> s -> m (Client i) Source #
Export the server as a client for interface i
. Spawns a server thread
with its lifetime bound to the supervisor.
findMethod :: Word64 -> Word16 -> CallHandler -> Maybe UntypedMethodHandler Source #
Look up a particlar MethodHandler
in the CallHandler
.
class SomeServer a where Source #
Base class for things that can act as capnproto servers.
Nothing
shutdown :: a -> IO () 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.
Helpers for writing method handlers
handleParsed :: (Parse p pp, IsStruct p, Parse r rr, IsStruct r) => (pp -> IO rr) -> MethodHandler p r Source #
Handle a method, working with the parsed form of parameters and results.
handleRaw :: (IsStruct p, IsStruct r) => (Raw 'Const p -> IO (Raw 'Const r)) -> MethodHandler p r Source #
Handle a method, working with the raw (unparsed) form of parameters and results.
methodUnimplemented :: MethodHandler p r Source #
MethodHandler
that always throws unimplemented.
toUntypedMethodHandler :: forall p r. (IsStruct p, IsStruct r) => MethodHandler p r -> UntypedMethodHandler Source #
Convert a typed method handler to an untyped one. Mostly intended for use by generated code.
Internals; exposed only for use by generated code.
data MethodHandlerTree Source #
Lazily computed tree of the method handlers exposed by an interface. Only of interest to generated code.
MethodHandlerTree | |
|