| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Servant.Server.JsonRpc
Contents
Description
This module provides support for writing handlers for JSON-RPC endpoints
type Mul = JsonRpc "mul" (Int, Int) String Int mulHandler :: (Int, Int) -> Handler (Either (JsonRpcErr String) Int) mulHandler = _
type Add = JsonRpc "add" (Int, Int) String Int addHandler :: (Int, Int) -> Handler (Either (JsonRpcErr String) Int) addHandler = _
type API = Add :<|> Mul server :: Application server = serve (Proxy @(RawJsonRpc API)) $ addHandler :<|> mulHandler
Synopsis
- serveJsonRpc :: (Monad m, RouteJsonRpc a) => Proxy a -> Proxy m -> RpcHandler a m -> Request Value -> m PossibleJsonRpcResponse
- class RouteJsonRpc a where
- type RpcHandler a (m :: * -> *)
- jsonRpcRouter :: Monad m => Proxy a -> Proxy m -> RpcHandler a m -> Map String (Value -> m (PossibleContent (Either (JsonRpcErr Value) Value)))
- hoistRpcRouter :: Proxy a -> (forall x. m x -> n x) -> RpcHandler a m -> RpcHandler a n
- data PossibleContent a
- type PossibleJsonRpcResponse = PossibleContent (JsonRpcResponse Value Value)
Documentation
serveJsonRpc :: (Monad m, RouteJsonRpc a) => Proxy a -> Proxy m -> RpcHandler a m -> Request Value -> m PossibleJsonRpcResponse Source #
This function is the glue required to convert a collection of
handlers in servant standard style to the handler that RawJsonRpc
expects.
class RouteJsonRpc a where Source #
This internal class is how we accumulate a map of handlers for dispatch
Associated Types
type RpcHandler a (m :: * -> *) Source #
Methods
jsonRpcRouter :: Monad m => Proxy a -> Proxy m -> RpcHandler a m -> Map String (Value -> m (PossibleContent (Either (JsonRpcErr Value) Value))) Source #
hoistRpcRouter :: Proxy a -> (forall x. m x -> n x) -> RpcHandler a m -> RpcHandler a n Source #
Instances
| (RouteJsonRpc a, RouteJsonRpc b) => RouteJsonRpc (a :<|> b) Source # | |
Defined in Servant.Server.JsonRpc Associated Types type RpcHandler (a :<|> b) m :: Type Source # Methods jsonRpcRouter :: Monad m => Proxy (a :<|> b) -> Proxy m -> RpcHandler (a :<|> b) m -> Map String (Value -> m (PossibleContent (Either (JsonRpcErr Value) Value))) Source # hoistRpcRouter :: Proxy (a :<|> b) -> (forall x. m x -> n x) -> RpcHandler (a :<|> b) m -> RpcHandler (a :<|> b) n Source # | |
| (KnownSymbol method, FromJSON p) => RouteJsonRpc (JsonRpcNotification method p) Source # | |
Defined in Servant.Server.JsonRpc Associated Types type RpcHandler (JsonRpcNotification method p) m :: Type Source # Methods jsonRpcRouter :: Monad m => Proxy (JsonRpcNotification method p) -> Proxy m -> RpcHandler (JsonRpcNotification method p) m -> Map String (Value -> m (PossibleContent (Either (JsonRpcErr Value) Value))) Source # hoistRpcRouter :: Proxy (JsonRpcNotification method p) -> (forall x. m x -> n x) -> RpcHandler (JsonRpcNotification method p) m -> RpcHandler (JsonRpcNotification method p) n Source # | |
| (KnownSymbol method, FromJSON p, ToJSON e, ToJSON r) => RouteJsonRpc (JsonRpc method p e r) Source # | |
Defined in Servant.Server.JsonRpc Associated Types type RpcHandler (JsonRpc method p e r) m :: Type Source # Methods jsonRpcRouter :: Monad m => Proxy (JsonRpc method p e r) -> Proxy m -> RpcHandler (JsonRpc method p e r) m -> Map String (Value -> m (PossibleContent (Either (JsonRpcErr Value) Value))) Source # hoistRpcRouter :: Proxy (JsonRpc method p e r) -> (forall x. m x -> n x) -> RpcHandler (JsonRpc method p e r) m -> RpcHandler (JsonRpc method p e r) n Source # | |
data PossibleContent a Source #
Since we collapse an entire JSON RPC api down to a single Servant endpoint, we need a type that can return content but might not.
Instances
| ToJSON a => AllCTRender (JSON ': ([] :: [Type])) (PossibleContent a) Source # | |
Defined in Servant.Server.JsonRpc Methods handleAcceptH :: Proxy (JSON ': []) -> AcceptHeader -> PossibleContent a -> Maybe (ByteString, ByteString) # | |
type PossibleJsonRpcResponse = PossibleContent (JsonRpcResponse Value Value) Source #
Orphan instances
| RouteJsonRpc api => HasServer (RawJsonRpc api :: Type) context Source # | |