Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- module Servant.JsonRpc
- 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
type RpcHandler a (m :: * -> *) Source #
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
module Servant.JsonRpc
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 handleAcceptH :: Proxy (JSON ': []) -> AcceptHeader -> PossibleContent a -> Maybe (ByteString, ByteString) # |
Orphan instances
(RouteJsonRpc api, HasContextEntry (context .++ DefaultErrorFormatters) ErrorFormatters) => HasServer (RawJsonRpc api :: Type) context Source # | |
type ServerT (RawJsonRpc api) m :: Type # route :: Proxy (RawJsonRpc api) -> Context context -> Delayed env (Server (RawJsonRpc api)) -> Router env # hoistServerWithContext :: Proxy (RawJsonRpc api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (RawJsonRpc api) m -> ServerT (RawJsonRpc api) n # |