servant-jsonrpc-client-1.2.0: Generate JSON-RPC servant clients
Safe HaskellSafe-Inferred
LanguageHaskell2010

Servant.Client.JsonRpc

Description

This module provides support for generating JSON-RPC clients in the Servant framework.

type Mul = JsonRpc "mul" (Int, Int) String Int
mul :: (Int, Int) -> ClientM (JsonRpcResponse String Int)
mul = client $ Proxy @Mul

Note: This client implementation runs over HTTP and the semantics of HTTP remove the need for the message id.

Documentation

Orphan instances

(RunClient m, HasClient m (RawJsonRpc ctype apiL), HasClient m (RawJsonRpc ctype apiR)) => HasClient m (RawJsonRpc ctype (apiL :<|> apiR)) Source #

The RawJsonRpc construct is completely transparent to clients

Instance details

Associated Types

type Client m (RawJsonRpc ctype (apiL :<|> apiR)) #

Methods

clientWithRoute :: Proxy m -> Proxy (RawJsonRpc ctype (apiL :<|> apiR)) -> Request -> Client m (RawJsonRpc ctype (apiL :<|> apiR)) #

hoistClientMonad :: Proxy m -> Proxy (RawJsonRpc ctype (apiL :<|> apiR)) -> (forall x. mon x -> mon' x) -> Client mon (RawJsonRpc ctype (apiL :<|> apiR)) -> Client mon' (RawJsonRpc ctype (apiL :<|> apiR)) #

(RunClient m, KnownSymbol method, MimeRender ctype (Request p), MimeUnrender ctype (JsonRpcResponse e r)) => HasClient m (RawJsonRpc ctype (JsonRpc method p e r)) Source # 
Instance details

Associated Types

type Client m (RawJsonRpc ctype (JsonRpc method p e r)) #

Methods

clientWithRoute :: Proxy m -> Proxy (RawJsonRpc ctype (JsonRpc method p e r)) -> Request -> Client m (RawJsonRpc ctype (JsonRpc method p e r)) #

hoistClientMonad :: Proxy m -> Proxy (RawJsonRpc ctype (JsonRpc method p e r)) -> (forall x. mon x -> mon' x) -> Client mon (RawJsonRpc ctype (JsonRpc method p e r)) -> Client mon' (RawJsonRpc ctype (JsonRpc method p e r)) #

(RunClient m, KnownSymbol method, MimeRender ctype (Request p)) => HasClient m (RawJsonRpc ctype (JsonRpcNotification method p)) Source # 
Instance details

Associated Types

type Client m (RawJsonRpc ctype (JsonRpcNotification method p)) #

Methods

clientWithRoute :: Proxy m -> Proxy (RawJsonRpc ctype (JsonRpcNotification method p)) -> Request -> Client m (RawJsonRpc ctype (JsonRpcNotification method p)) #

hoistClientMonad :: Proxy m -> Proxy (RawJsonRpc ctype (JsonRpcNotification method p)) -> (forall x. mon x -> mon' x) -> Client mon (RawJsonRpc ctype (JsonRpcNotification method p)) -> Client mon' (RawJsonRpc ctype (JsonRpcNotification method p)) #