json-rpc-0.3.0.0: 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 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.

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.

Server Example

This JSON-RPC server returns the current time.

{-# LANGUAGE OverloadedStrings #-}
import Control.Applicative
import Data.Aeson.Types hiding (Error)
import Data.Conduit.Network
import Data.Time.Clock
import Data.Time.Format
import Network.JsonRpc
import System.Locale

data TimeReq = TimeReq
data TimeRes = TimeRes { timeRes :: UTCTime }

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

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

respond :: Respond TimeReq IO TimeRes
respond TimeReq = Right . TimeRes <$> getCurrentTime

main :: IO ()
main = jsonRpcTcpServer V2 (serverSettings 31337 "::1") respond dummySrv

Client Example

Corresponding TCP client to get time from server.

{-# LANGUAGE OverloadedStrings #-}
import Control.Concurrent
import Control.Concurrent.STM
import Control.Monad
import Control.Monad.Trans
import Data.Aeson
import Data.Aeson.Types hiding (Error)
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 { timeRes :: UTCTime }

instance ToRequest TimeReq where
    requestMethod TimeReq = "time"

instance ToJSON TimeReq where
    toJSON TimeReq = emptyArray

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

req :: JsonRpcT IO UTCTime
req = sendRequest TimeReq >>= liftIO . atomically >>= \ts -> case ts of
    Left e -> error $ fromError e
    Right (Just (TimeRes r)) -> return r
    _ -> error "Could not parse response"

main :: IO ()
main = jsonRpcTcpClient V2 (clientSettings 31337 "::1") dummyRespond .
    replicateM_ 4 $ req >>= liftIO . print >> liftIO (threadDelay 1000000)

Establish JSON-RPC context

type JsonRpcT = ReaderT Session Source

runJsonRpcT Source

Arguments

:: (FromRequest q, ToJSON r) 
=> Ver

JSON-RPC version

-> Respond q IO r

Respond to incoming requests

-> Sink ByteString IO ()

Sink to send messages

-> Source IO ByteString

Source of incoming messages

-> JsonRpcT IO a

JSON-RPC action

-> IO a

Output of action

Create JSON-RPC session around ByteString conduits from transport layer. When context exits, session stops existing.

Communicate with remote party

sendRequest :: (ToJSON q, ToRequest q, FromResponse r, MonadIO m) => q -> JsonRpcT m (STM (Either ErrorObj (Maybe r))) Source

Returns Right Nothing if could not parse response. Run output in STM monad. STM will block until response arrives.

sendNotif :: (ToJSON no, ToNotif no, Monad m) => no -> JsonRpcT m (STM ()) Source

Send notification. Run output in STM monad. Will not block.

receiveNotif :: (Monad m, FromNotif n) => JsonRpcT m (STM (Maybe (Either ErrorObj (Maybe n)))) Source

Receive notifications from peer. Returns Nothing if incoming channel is closed and empty. Result is Right Nothing if it failed to parse notification. Run output in STM monad. Will not block.

Transports

Client

jsonRpcTcpClient Source

Arguments

:: (FromRequest q, ToJSON r) 
=> Ver

JSON-RPC version

-> ClientSettings

Connection settings

-> Respond q IO r

Respond to incoming requests

-> JsonRpcT IO a

JSON-RPC action

-> IO a

Output of action

TCP client transport for JSON-RPC.

dummyRespond :: Monad m => Respond () m () Source

Respond function for systems that do not reply to requests, as usual in clients.

Server

jsonRpcTcpServer Source

Arguments

:: (FromRequest q, ToJSON r) 
=> Ver

JSON-RPC version

-> ServerSettings

Connection settings

-> Respond q IO r

Respond to incoming requests

-> JsonRpcT IO ()

Action to perform on connecting client thread

-> IO () 

TCP server transport for JSON-RPC.

dummySrv :: MonadIO m => JsonRpcT m () Source

Dummy server for servers not expecting client to send notifications, that is most cases.

Requests

Parsing

class FromRequest q where Source

Methods

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

Parser for params Value in JSON-RPC request.

Encoding

class ToRequest q where Source

Methods

requestMethod :: q -> Method Source

Method associated with request data to build a request object.

Instances

buildRequest Source

Arguments

:: (ToJSON q, ToRequest q) 
=> Ver

JSON-RPC version

-> q

Request data

-> Id 
-> Request 

Responses

Parsing

class FromResponse r where Source

Methods

parseResult :: Method -> Maybe (Value -> Parser r) Source

Parser for result Value in JSON-RPC response. Method corresponds to request to which this response answers.

Encoding

type Respond q m r = q -> m (Either ErrorObj r) Source

Notifications

Parsing

class FromNotif n where Source

Methods

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

Parser for notification params Value.

Instances

Encoding

class ToNotif n where Source

Methods

notifMethod :: n -> Method Source

Instances

buildNotif :: (ToJSON n, ToNotif n) => Ver -> n -> Notif Source

Errors

Error Messages

errorParse :: Value -> ErrorObj Source

Parse error.

errorInvalid :: Value -> ErrorObj Source

Invalid request.

errorParams :: Value -> ErrorObj Source

Invalid params.

errorMethod :: Method -> ErrorObj Source

Method not found.

errorId :: Id -> ErrorObj Source

Id not recognized.

Others

data Id Source

Constructors

IdInt 

Fields

getIdInt :: !Int
 
IdTxt 

Fields

getIdTxt :: !Text
 
IdNull 

data Ver Source

Constructors

V1

JSON-RPC 1.0

V2

JSON-RPC 2.0

Instances