json-rpc-0.2.0.2: Fully-featured JSON-RPC 2.0 library

Safe HaskellNone
LanguageHaskell2010

Network.JsonRpc

Contents

Synopsis

Introduction

This JSON-RPC library is fully-compatible with JSON-RPC 2.0 and partially-compatible with JSON-RPC 1.0. It provides an interface that combines a JSON-RPC client and server. It can set and keep track of request ids to parse responses. There is support for sending and receiving notifications. You may use any underlying transport. Basic TCP client and server provided.

The recommended interface to this library is provided as conduits that encode outgoing messages, and decode incoming messages. Incoming messages are delivered as an IncomingMsg data structure, while outgoing messages are sent in a Message data structure. The former packs responses and errors with their corresponding request, and has a separate constructor for decoding errors.

A JSON-RPC application using this interface is considered to be peer-to-peer, as it can send and receive all types of JSON-RPC message independent of whether it originated the connection.

Type classes ToRequest, ToNotif are for data that can be converted into JSON-RPC requests and notifications respectively. An instance of aeson's ToJSON class is also required to serialize these data structures. Make sure that they serialize as a structured JSON value (array or object) that can go into the params field of the JSON-RPC object. Type classes FromRequest, FromNotif and FromResult are for deserializing JSON-RPC messages.

Errors are deserialized to the ErrorObj data type. Only a string is supported as contents inside a JSON-RPC 1.0 error. JSON-RPC 2.0 errors also have a code, and possibly additional data as an aeson Value.

Server Example

This server returns the current time.

{-# LANGUAGE OverloadedStrings #-}
import Data.Aeson.Types
import Data.Conduit
import qualified Data.Conduit.List as CL
import Data.Conduit.Network
import Data.Time.Clock
import Data.Time.Format
import Network.JsonRpc
import System.Locale

data TimeReq = TimeReq
data TimeRes = TimeRes UTCTime

instance FromRequest TimeReq where
    paramsParser "time" = Just $ const $ return TimeReq 
    paramsParser _ = Nothing

instance ToJSON TimeRes where
    toJSON (TimeRes t) = toJSON $ formatTime defaultTimeLocale "%c" t

srv :: AppConduits () () TimeRes TimeReq () () IO -> IO ()
srv (src, snk) = src $= CL.mapM respond $$ snk

respond :: IncomingMsg () TimeReq () ()
        -> IO (Message () () TimeRes)
respond (IncomingMsg (MsgRequest (Request ver _ TimeReq i)) Nothing) = do    
    t <- getCurrentTime
    return $ MsgResponse (Response ver (TimeRes t) i)

respond (IncomingError e) = return $ MsgError e
respond (IncomingMsg (MsgError e) _) = return $ MsgError $ e
respond _ = undefined

main :: IO ()
main = tcpServer V2 (serverSettings 31337 "127.0.0.1") srv

Client Example

Corresponding TCP client to get time from server.

{-# LANGUAGE OverloadedStrings #-}
import Data.Aeson.Types hiding (Error)
import Data.Conduit
import qualified Data.Conduit.List as CL
import Data.Conduit.Network
import qualified Data.Text as T
import Data.Time.Clock
import Data.Time.Format
import Network.JsonRpc
import System.Locale

data TimeReq = TimeReq
data TimeRes = TimeRes UTCTime

instance ToRequest TimeReq where
    requestMethod TimeReq = "time"

instance ToJSON TimeReq where
    toJSON TimeReq = emptyArray

instance FromResponse TimeRes where
    parseResult "time" = withText "time" $ \t -> case f t of
        Nothing -> fail "Could not parse time"
        Just t' -> return $ TimeRes t'
      where
        f t = parseTime defaultTimeLocale "%c" (T.unpack t)

cli :: AppConduits TimeReq () () () () TimeRes IO
    -> IO UTCTime
cli (src, snk) = do
    CL.sourceList [MsgRequest $ buildRequest V2 TimeReq] $$ snk
    ts <- src $$ CL.consume
    case ts of
        [] -> error "No response received"
        [IncomingError (ErrorObj _ m _ _ _)] -> error $ "Unknown: " ++ m
        [IncomingMsg (MsgError (ErrorObj _ m _ _ _)) _] -> error m
        [IncomingMsg (MsgResponse (Response _ (TimeRes t) _)) _] -> return t
        _ -> undefined

main :: IO ()
main = tcpClient V2 True (clientSettings 31337 "127.0.0.1") cli >>= print

Conduits

High-Level

type AppConduits qo no ro qi ni ri m = (Source m (IncomingMsg qo qi ni ri), Sink (Message qo no ro) m ()) Source

Conduits of sending and receiving JSON-RPC messages.

data IncomingMsg qo qi ni ri Source

Incoming messages. Responses and corresponding requests go together. IncomingError is for problems decoding incoming messages. These should be sent to the remote party.

Constructors

IncomingMsg 

Fields

incomingMsg :: !(Message qi ni ri)
 
matchingReq :: !(Maybe (Request qo))
 
IncomingError 

Instances

(Eq qo, Eq qi, Eq ni, Eq ri) => Eq (IncomingMsg qo qi ni ri) 
(Show qo, Show qi, Show ni, Show ri) => Show (IncomingMsg qo qi ni ri) 
(NFData qo, NFData qi, NFData ni, NFData ri) => NFData (IncomingMsg qo qi ni ri) 

runConduits Source

Arguments

:: (FromRequest qi, FromNotif ni, FromResponse ri, ToJSON qo, ToJSON no, ToJSON ro) 
=> Ver

JSON-RPC version

-> Bool

Disconnect on last response

-> Sink ByteString IO ()

Sink to send messages

-> Source IO ByteString

Source of incoming messages

-> (AppConduits qo no ro qi ni ri IO -> IO a)

JSON-RPC action

-> IO a

Output of action

tcpClient Source

Arguments

:: (FromRequest qi, FromNotif ni, FromResponse ri, ToJSON qo, ToJSON no, ToJSON ro) 
=> Ver

JSON-RPC version

-> Bool

Disconnect on last response

-> ClientSettings

Connection settings

-> (AppConduits qo no ro qi ni ri IO -> IO a)

JSON-RPC action

-> IO a

Output of action

tcpServer Source

Arguments

:: (FromRequest qi, FromNotif ni, FromResponse ri, ToJSON qo, ToJSON no, ToJSON ro) 
=> Ver

JSON-RPC version

-> ServerSettings

Connection settings

-> (AppConduits qo no ro qi ni ri IO -> IO ())

JSON-RPC action to perform on connecting client thread

-> IO () 

query Source

Arguments

:: (ToJSON qo, ToRequest qo, FromResponse ri) 
=> Ver

JSON-RPC version

-> [qo]

List of requests

-> AppConduits qo () () () () ri IO

Message conduits

-> IO [IncomingMsg qo () () ri]

Incoming messages

Send requests and get responses (or errors).

Example:

tcpClient V2 True (clientSettings 31337 "127.0.0.1") (query V2 [TimeReq])

Low-Level

data Session qo Source

JSON-RPC session mutable data.

Constructors

Session 

Fields

lastId :: TVar Id

Last generated id

sentRequests :: TVar (SentRequests qo)

Map of ids to requests

isLast :: TQueue Bool

For each sent request, write a False, when sink closes, write a True

type SentRequests qo = HashMap Id (Request qo) Source

Map of ids to sent requests.

initSession :: STM (Session qo) Source

Initialize JSON-RPC session.

encodeConduit :: (ToJSON a, Monad m) => Conduit a m ByteString Source

Conduit that serializes JSON documents for sending to the network.

msgConduit Source

Arguments

:: MonadIO m 
=> Bool

Set to true if decodeConduit must disconnect on last response

-> Session qo 
-> Conduit (Message qo no ro) m (Message qo no ro) 

Conduit for outgoing JSON-RPC messages. Adds an id to requests whose id is IdNull. Tracks all sent requests to match corresponding responses.

decodeConduit Source

Arguments

:: (FromRequest qi, FromNotif ni, FromResponse ri, MonadIO m) 
=> Ver

JSON-RPC version

-> Bool

Close on last response

-> Session qo

JSON-RPC session

-> Conduit ByteString m (IncomingMsg qo qi ni ri)

Decoded incoming messages

Conduit to decode incoming JSON-RPC messages. An error in the decoding operation will output an IncomingError, which should be relayed to the remote party.

Requests

data Request q Source

Constructors

Request 

Fields

getReqVer :: !Ver
 
getReqMethod :: !Method
 
getReqParams :: !q
 
getReqId :: !Id
 

Instances

Eq q => Eq (Request q) 
Read q => Read (Request q) 
Show q => Show (Request q) 
ToJSON q => ToJSON (Request q) 
NFData q => NFData (Request q) 

Parsing

class FromRequest q where Source

Class for data that can be received in JSON-RPC requests.

Methods

paramsParser :: Method -> Maybe (Value -> Parser q) Source

Parser for params field.

parseRequest :: FromRequest q => Value -> Parser (Either ErrorObj (Request q)) Source

Parse JSON-RPC request.

Encoding

class ToRequest q where Source

Class for data that can be sent as JSON-RPC requests. Define a method name for each request.

Methods

requestMethod :: q -> Method Source

Instances

buildRequest Source

Arguments

:: ToRequest q 
=> Ver

JSON-RPC version

-> q

Request data

-> Request q 

Responses

data Response r Source

JSON-RPC response data type

Constructors

Response 

Fields

getResVer :: !Ver

Version

getResult :: !r

Result

getResId :: !Id

Id

Instances

Eq r => Eq (Response r) 
Read r => Read (Response r) 
Show r => Show (Response r) 
ToJSON r => ToJSON (Response r) 
NFData r => NFData (Response r) 

Parsing

class FromResponse r where Source

Class for data that can be received inside JSON-RPC responses.

Methods

parseResult :: Method -> Value -> Parser r Source

Parse result field from JSON-RPC response.

parseResponse :: FromResponse r => Request q -> Value -> Parser (Either ErrorObj (Response r)) Source

Parse JSON-RPC response.

Notifications

data Notif n Source

Class for JSON-RPC notifications.

Constructors

Notif 

Fields

getNotifVer :: !Ver

Version

getNotifMethod :: !Method

Method

getNotifParams :: !n

Params

Instances

Eq n => Eq (Notif n) 
Read n => Read (Notif n) 
Show n => Show (Notif n) 
ToJSON n => ToJSON (Notif n) 
NFData n => NFData (Notif n) 

Parsing

class FromNotif n where Source

Class for data that can be received in JSON-RPC notifications.

Methods

notifParamsParser :: Method -> Maybe (Value -> Parser n) Source

Parser for notification params field

Instances

parseNotif :: FromNotif n => Value -> Parser (Either ErrorObj (Notif n)) Source

Parse notifications.

Encoding

class ToNotif n where Source

Methods

notifMethod :: n -> Method Source

Instances

buildNotif Source

Arguments

:: ToNotif n 
=> Ver

Version

-> n

Notification data

-> Notif n 

Build notifications.

Errors

data ErrorObj Source

JSON-RPC errors.

Constructors

ErrorObj 

Fields

getErrVer :: !Ver

Version

getErrMsg :: !String

Message

getErrCode :: !Int

Error code (2.0)

getErrData :: !Value

Error data (2.0)

getErrId :: !Id

Error id

Error Messages

errorParse :: Ver -> Value -> ErrorObj Source

Parse error.

errorInvalid :: Ver -> Value -> ErrorObj Source

Invalid request.

errorParams :: Ver -> Value -> Id -> ErrorObj Source

Invalid params.

errorMethod :: Ver -> Method -> Id -> ErrorObj Source

Method not found.

errorId :: Ver -> Id -> ErrorObj Source

Id not recognized.

Others

data Message q n r Source

Class for any JSON-RPC message.

Constructors

MsgRequest 

Fields

getMsgRequest :: !(Request q)
 
MsgNotif 

Fields

getMsgNotif :: !(Notif n)
 
MsgResponse 

Fields

getMsgResponse :: !(Response r)
 
MsgError 

Fields

getMsgError :: !ErrorObj
 

Instances

(Eq q, Eq n, Eq r) => Eq (Message q n r) 
(Show q, Show n, Show r) => Show (Message q n r) 
(ToJSON q, ToJSON n, ToJSON r) => ToJSON (Message q n r) 
(NFData q, NFData n, NFData r) => NFData (Message q n r) 

type Method = Text Source

JSON-RPC methods in requests and notifications.

data Id Source

JSON-RPC message id.

Constructors

IdInt 

Fields

getIdInt :: !Int
 
IdTxt 

Fields

getIdTxt :: !Text
 
IdNull 

data Ver Source

JSON-RPC version

Constructors

V1

JSON-RPC 1.0

V2

JSON-RPC 2.0

Instances