json-rpc-client-0.2.5.0: JSON-RPC 2.0 on the client side.

Safe HaskellNone
LanguageHaskell2010

Network.JsonRpc.Client

Contents

Description

Functions for implementing the client side of JSON-RPC 2.0. See http://www.jsonrpc.org/specification.

Synopsis

Summary

Demo

The demo folder contains a client and server that communicate using a shared set of Signatures. The client runs the server as a subprocess, sending requests to stdin and receiving responses from stdout. Compile both programs with the demo flag. Then run the client by passing it a command to run the server (e.g., demo-client demo-server).

Types

type Connection m = ByteString -> m (Maybe ByteString) Source #

Function used to send requests to the server. Nothing represents no response, as when a JSON-RPC server receives only notifications.

type RpcResult m r = ExceptT RpcError m r #

Return type of a method. A method call can either fail with an RpcError or succeed with a result of type r.

Signatures

data Signature ps r Source #

Signature specifying the name, parameter names and types (ps), and return type (r) of a method.

Constructors

Signature Text ps 

Instances

Show ps => Show (Signature ps r) Source # 

Methods

showsPrec :: Int -> Signature ps r -> ShowS #

show :: Signature ps r -> String #

showList :: [Signature ps r] -> ShowS #

data p ::: ps infixr 9 Source #

A node in a linked list specifying parameter names and types. It is right associative.

Constructors

Text ::: ps infixr 9 

Instances

Show ps => Show ((:::) p ps) Source # 

Methods

showsPrec :: Int -> (p ::: ps) -> ShowS #

show :: (p ::: ps) -> String #

showList :: [p ::: ps] -> ShowS #

(ClientFunction ps r f, ToJSON a) => ClientFunction ((:::) a ps) r (a -> f) Source # 

Methods

_toBatch :: Text -> (a ::: ps) -> ResultType r -> Object -> a -> f

ConvertParams ps1 ps2 => ConvertParams ((:::) p ps1) ((:+:) p ps2) Source # 

Methods

_toServerParams :: (p ::: ps1) -> p :+: ps2

Single Requests

toFunction Source #

Arguments

:: (Monad m, ClientFunction ps r f, ComposeMultiParam (Batch r -> RpcResult m r) f g) 
=> Connection m

Function for sending requests to the server.

-> Signature ps r

Method signature.

-> g

Client-side function with a return type of RpcResult m r.

Creates a function for calling a JSON-RPC method on the server.

toFunction_ Source #

Arguments

:: (Monad m, ClientFunction ps r f, ComposeMultiParam (Batch r -> RpcResult m ()) f g) 
=> Connection m

Function for sending requests to the server.

-> Signature ps r

Method signature.

-> g

Client-side function with a return type of RpcResult m ().

Creates a function for calling a JSON-RPC method on the server as a notification.

Batch Requests

data Batch r Source #

A batch call. Batch multiple requests by combining values of this type using its Applicative and Alternative instances before running them with runBatch.

Instances

Functor Batch Source # 

Methods

fmap :: (a -> b) -> Batch a -> Batch b #

(<$) :: a -> Batch b -> Batch a #

Applicative Batch Source # 

Methods

pure :: a -> Batch a #

(<*>) :: Batch (a -> b) -> Batch a -> Batch b #

(*>) :: Batch a -> Batch b -> Batch b #

(<*) :: Batch a -> Batch b -> Batch a #

Alternative Batch Source # 

Methods

empty :: Batch a #

(<|>) :: Batch a -> Batch a -> Batch a #

some :: Batch a -> Batch [a] #

many :: Batch a -> Batch [a] #

FromJSON r => ClientFunction () r (Batch r) Source # 

Methods

_toBatch :: Text -> () -> ResultType r -> Object -> Batch r

ComposeMultiParam (Batch a -> b) (Batch a) b Source # 

Methods

_compose :: (Batch a -> b) -> Batch a -> b

toBatchFunction Source #

Arguments

:: ClientFunction ps r f 
=> Signature ps r

Method signature.

-> f

Client-side function with a return type of Batch r.

Creates a function for calling a JSON-RPC method as part of a batch request.

toBatchFunction_ Source #

Arguments

:: (ClientFunction ps r f, ComposeMultiParam (Batch r -> Batch ()) f g) 
=> Signature ps r

Method signature.

-> g

Client-side function with a return type of Batch ().

Creates a function for calling a JSON-RPC method as a notification and as part of a batch request.

voidBatch :: Batch r -> Batch () Source #

Converts all requests in a batch to notifications.

runBatch Source #

Arguments

:: Monad m 
=> Connection m

Function for sending requests to the server.

-> Batch r

Batch to be evaluated.

-> RpcResult m r

Result.

Evaluates a batch. The process depends on its size:

  1. If the batch is empty, the server function is not called.
  2. If the batch has exactly one request, it is sent as a request object.
  3. If the batch has multiple requests, they are sent as an array of request objects.

Errors

RpcError is used for all server-side errors, as described in the specification. Additionally, the error code -31999 is used for any errors that occur while parsing the server's response.

data RpcError :: * #

JSON-RPC error.

Constructors

RpcError 

Fields

clientCode :: Int Source #

Code used for all client-side errors. It is -31999.

Type Classes

class ClientFunction ps r f | ps r -> f, f -> ps r Source #

Relationship between the parameters (ps), return type (r), and client-side batch function (f) of a JSON-RPC method.

Instances

FromJSON r => ClientFunction () r (Batch r) Source # 

Methods

_toBatch :: Text -> () -> ResultType r -> Object -> Batch r

(ClientFunction ps r f, ToJSON a) => ClientFunction ((:::) a ps) r (a -> f) Source # 

Methods

_toBatch :: Text -> (a ::: ps) -> ResultType r -> Object -> a -> f

class ComposeMultiParam f g h | f g -> h, g h -> f Source #

Relationship between a function (g) taking any number of arguments and yielding a Batch a, a function (f) taking a Batch a, and the function (h) that applies g to all of its arguments and then applies f to the result.

Instances

ComposeMultiParam f g h => ComposeMultiParam f (a -> g) (a -> h) Source # 

Methods

_compose :: f -> (a -> g) -> a -> h

ComposeMultiParam (Batch a -> b) (Batch a) b Source # 

Methods

_compose :: (Batch a -> b) -> Batch a -> b