servant-jsonrpc-server-2.1.0: JSON-RPC servant servers

Safe HaskellNone
LanguageHaskell2010

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

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 # 
Instance details

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 # 
Instance details

Defined in Servant.Server.JsonRpc

Associated Types

type RpcHandler (JsonRpcNotification method p) m :: Type Source #

(KnownSymbol method, FromJSON p, ToJSON e, ToJSON r) => RouteJsonRpc (JsonRpc method p e r) Source # 
Instance details

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 # 
Instance details

Defined in Servant.Server.JsonRpc

Orphan instances

(RouteJsonRpc api, HasContextEntry (context .++ DefaultErrorFormatters) ErrorFormatters) => HasServer (RawJsonRpc api :: Type) context Source # 
Instance details

Associated Types

type ServerT (RawJsonRpc api) m :: Type #

Methods

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 #