Safe Haskell | None |
---|---|
Language | Haskell2010 |
Network.JSONRPC
Contents
Synopsis
- data Session = Session {}
- type JSONRPCT = ReaderT Session
- runJSONRPCT :: (MonadLoggerIO m, MonadUnliftIO m) => Ver -> Bool -> ConduitT ByteString Void m () -> ConduitT () ByteString m () -> JSONRPCT m a -> m a
- decodeConduit :: forall (m :: Type -> Type). MonadLogger m => Ver -> ConduitT ByteString (Either Response Value) m ()
- encodeConduit :: forall j (m :: Type -> Type). (ToJSON j, MonadLogger m) => ConduitT j ByteString m ()
- receiveRequest :: forall (m :: Type -> Type). MonadLoggerIO m => JSONRPCT m (Maybe Request)
- receiveBatchRequest :: forall (m :: Type -> Type). MonadLoggerIO m => JSONRPCT m (Maybe BatchRequest)
- sendResponse :: forall (m :: Type -> Type). MonadLoggerIO m => Response -> JSONRPCT m ()
- sendBatchResponse :: forall (m :: Type -> Type). MonadLoggerIO m => BatchResponse -> JSONRPCT m ()
- sendRequest :: forall (m :: Type -> Type) q r. (MonadLoggerIO m, ToJSON q, ToRequest q, FromResponse r) => q -> JSONRPCT m (Maybe (Either ErrorObj r))
- sendBatchRequest :: forall (m :: Type -> Type) q r. (MonadLoggerIO m, ToJSON q, ToRequest q, FromResponse r) => [q] -> JSONRPCT m [Maybe (Either ErrorObj r)]
- jsonrpcTCPClient :: (MonadLoggerIO m, MonadUnliftIO m) => Ver -> Bool -> ClientSettings -> JSONRPCT m a -> m a
- jsonrpcTCPServer :: (MonadLoggerIO m, MonadUnliftIO m) => Ver -> Bool -> ServerSettings -> JSONRPCT m () -> m a
- type SentRequests = HashMap Id (TMVar (Maybe Response))
- initSession :: Ver -> Bool -> STM Session
- processIncoming :: forall (m :: Type -> Type). (Functor m, MonadLoggerIO m) => JSONRPCT m ()
- sendMessage :: forall (m :: Type -> Type). MonadLoggerIO m => Message -> JSONRPCT m ()
- data Ver
- data Message
- = MsgRequest {
- getMsgRequest :: !Request
- | MsgResponse { }
- | MsgBatch { }
- = MsgRequest {
- data Id
- type Method = Text
- data Request
- = Request {
- getReqVer :: !Ver
- getReqMethod :: !Method
- getReqParams :: !Value
- getReqId :: !Id
- | Notif {
- getReqVer :: !Ver
- getReqMethod :: !Method
- getReqParams :: !Value
- = Request {
- data BatchRequest
- = BatchRequest {
- getBatchRequest :: ![Request]
- | SingleRequest { }
- = BatchRequest {
- class FromRequest q where
- parseParams :: Method -> Maybe (Value -> Parser q)
- fromRequest :: FromRequest q => Request -> Either ErrorObj q
- class ToRequest q where
- requestMethod :: q -> Method
- requestIsNotif :: q -> Bool
- buildRequest :: (ToJSON q, ToRequest q) => Ver -> q -> Id -> Request
- data Response
- data BatchResponse
- = BatchResponse {
- getBatchResponse :: ![Response]
- | SingleResponse { }
- = BatchResponse {
- class FromResponse r where
- parseResult :: Method -> Maybe (Value -> Parser r)
- fromResponse :: FromResponse r => Method -> Response -> Maybe r
- type Respond q (m :: Type -> Type) r = q -> m (Either ErrorObj r)
- buildResponse :: (Monad m, FromRequest q, ToJSON r) => Respond q m r -> Request -> m (Maybe Response)
- data ErrorObj
- = ErrorObj {
- getErrMsg :: !String
- getErrCode :: !Int
- getErrData :: !Value
- | ErrorVal {
- getErrData :: !Value
- = ErrorObj {
- fromError :: ErrorObj -> String
- errorParse :: ByteString -> ErrorObj
- errorInvalid :: Value -> ErrorObj
- errorParams :: Value -> String -> ErrorObj
- errorMethod :: Method -> ErrorObj
- errorId :: Id -> ErrorObj
- fromId :: Id -> String
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.
Arguments
:: (MonadLoggerIO m, MonadUnliftIO m) | |
=> Ver | JSON-RPC version |
-> Bool | Ignore incoming requests/notifs |
-> ConduitT ByteString Void m () | Sink to send messages |
-> ConduitT () ByteString m () | Source to receive messages from |
-> JSONRPCT m a | JSON-RPC action |
-> m a | Output of action |
Create JSON-RPC session around conduits from transport layer. When context exits session disappears.
decodeConduit :: forall (m :: Type -> Type). MonadLogger m => Ver -> ConduitT ByteString (Either Response Value) m () Source #
Conduit to decode incoming messages. Left Response indicates a response to send back to sender if parsing JSON fails.
encodeConduit :: forall j (m :: Type -> Type). (ToJSON j, MonadLogger m) => ConduitT j ByteString m () Source #
receiveRequest :: forall (m :: Type -> Type). MonadLoggerIO m => JSONRPCT m (Maybe Request) Source #
Receive requests from remote endpoint. Returns Nothing if incoming channel is closed or has never been opened. Will reject incoming request if sent in a batch.
receiveBatchRequest :: forall (m :: Type -> Type). MonadLoggerIO m => JSONRPCT m (Maybe BatchRequest) Source #
Receive batch of requests. Will also accept single requests.
sendResponse :: forall (m :: Type -> Type). MonadLoggerIO m => Response -> JSONRPCT m () Source #
Send response message. Do not use to respond to a batch of requests.
sendBatchResponse :: forall (m :: Type -> Type). MonadLoggerIO m => BatchResponse -> JSONRPCT m () Source #
Send batch of responses. Use to respond to a batch of requests.
sendRequest :: forall (m :: Type -> Type) q r. (MonadLoggerIO m, ToJSON q, ToRequest q, FromResponse r) => q -> JSONRPCT m (Maybe (Either ErrorObj r)) Source #
Returns Nothing if did not receive response, could not parse it, or request is a notification. Just Left contains the error object returned by server if any. Just Right means response was received just right.
sendBatchRequest :: forall (m :: Type -> Type) q r. (MonadLoggerIO m, ToJSON q, ToRequest q, FromResponse r) => [q] -> JSONRPCT m [Maybe (Either ErrorObj r)] Source #
Send multiple requests in a batch. If only a single request, do not put it in a batch.
Arguments
:: (MonadLoggerIO m, MonadUnliftIO m) | |
=> Ver | JSON-RPC version |
-> Bool | Ignore incoming requests or notifications |
-> ClientSettings | Connection settings |
-> JSONRPCT m a | JSON-RPC action |
-> m a | Output of action |
TCP client transport for JSON-RPC.
Arguments
:: (MonadLoggerIO m, MonadUnliftIO m) | |
=> Ver | JSON-RPC version |
-> Bool | Ignore incoming requests or notifications |
-> ServerSettings | Connection settings |
-> JSONRPCT m () | Action to perform on connecting client thread |
-> m a |
TCP server transport for JSON-RPC.
processIncoming :: forall (m :: Type -> Type). (Functor m, MonadLoggerIO m) => JSONRPCT m () Source #
Process incoming messages. Do not use this directly unless you know what you are doing. This is an internal function.
sendMessage :: forall (m :: Type -> Type). MonadLoggerIO m => Message -> JSONRPCT m () Source #
Send any message. Do not use this. Use the other high-level functions instead. Will not track request ids. Incoming responses to requests sent using this method will be ignored.
JSON-RPC version.
Constructors
MsgRequest | |
Fields
| |
MsgResponse | |
Fields | |
MsgBatch | |
Instances
Instances
Arbitrary Id Source # | |||||
FromJSON Id Source # | |||||
Defined in Network.JSONRPC.Data | |||||
ToJSON Id Source # | |||||
Enum Id Source # | |||||
Generic Id Source # | |||||
Defined in Network.JSONRPC.Data Associated Types
| |||||
Read Id Source # | |||||
Show Id Source # | |||||
NFData Id Source # | |||||
Defined in Network.JSONRPC.Data | |||||
Eq Id Source # | |||||
Hashable Id Source # | |||||
Defined in Network.JSONRPC.Data | |||||
type Rep Id Source # | |||||
Defined in Network.JSONRPC.Data type Rep Id = D1 ('MetaData "Id" "Network.JSONRPC.Data" "json-rpc-1.1.2-684ncyg3Rc88KoeoDxJyo3" 'False) (C1 ('MetaCons "IdInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "getIdInt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "IdTxt" 'PrefixI 'True) (S1 ('MetaSel ('Just "getIdTxt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) |
Constructors
Request | |
Fields
| |
Notif | |
Fields
|
Instances
Arbitrary Request Source # | |||||
FromJSON Request Source # | |||||
Defined in Network.JSONRPC.Data | |||||
ToJSON Request Source # | |||||
Generic Request Source # | |||||
Defined in Network.JSONRPC.Data Associated Types
| |||||
Show Request Source # | |||||
NFData Request Source # | |||||
Defined in Network.JSONRPC.Data | |||||
Eq Request Source # | |||||
type Rep Request Source # | |||||
Defined in Network.JSONRPC.Data type Rep Request = D1 ('MetaData "Request" "Network.JSONRPC.Data" "json-rpc-1.1.2-684ncyg3Rc88KoeoDxJyo3" 'False) (C1 ('MetaCons "Request" 'PrefixI 'True) ((S1 ('MetaSel ('Just "getReqVer") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Ver) :*: S1 ('MetaSel ('Just "getReqMethod") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Method)) :*: (S1 ('MetaSel ('Just "getReqParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Value) :*: S1 ('MetaSel ('Just "getReqId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Id))) :+: C1 ('MetaCons "Notif" 'PrefixI 'True) (S1 ('MetaSel ('Just "getReqVer") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Ver) :*: (S1 ('MetaSel ('Just "getReqMethod") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Method) :*: S1 ('MetaSel ('Just "getReqParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Value)))) |
data BatchRequest Source #
Constructors
BatchRequest | |
Fields
| |
SingleRequest | |
Fields |
Instances
Arbitrary BatchRequest Source # | |||||
Defined in Network.JSONRPC.Arbitrary | |||||
FromJSON BatchRequest Source # | |||||
Defined in Network.JSONRPC.Data | |||||
ToJSON BatchRequest Source # | |||||
Defined in Network.JSONRPC.Data Methods toJSON :: BatchRequest -> Value # toEncoding :: BatchRequest -> Encoding # toJSONList :: [BatchRequest] -> Value # toEncodingList :: [BatchRequest] -> Encoding # omitField :: BatchRequest -> Bool # | |||||
Generic BatchRequest Source # | |||||
Defined in Network.JSONRPC.Data Associated Types
| |||||
Show BatchRequest Source # | |||||
Defined in Network.JSONRPC.Data Methods showsPrec :: Int -> BatchRequest -> ShowS # show :: BatchRequest -> String # showList :: [BatchRequest] -> ShowS # | |||||
NFData BatchRequest Source # | |||||
Defined in Network.JSONRPC.Data Methods rnf :: BatchRequest -> () # | |||||
Eq BatchRequest Source # | |||||
Defined in Network.JSONRPC.Data | |||||
type Rep BatchRequest Source # | |||||
Defined in Network.JSONRPC.Data type Rep BatchRequest = D1 ('MetaData "BatchRequest" "Network.JSONRPC.Data" "json-rpc-1.1.2-684ncyg3Rc88KoeoDxJyo3" 'False) (C1 ('MetaCons "BatchRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "getBatchRequest") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Request])) :+: C1 ('MetaCons "SingleRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSingleRequest") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Request))) |
class FromRequest q where Source #
Methods
parseParams :: Method -> Maybe (Value -> Parser q) Source #
Parser for params Value in JSON-RPC request.
Instances
FromRequest Value Source # | |
Defined in Network.JSONRPC.Data | |
FromRequest () Source # | |
Defined in Network.JSONRPC.Data |
fromRequest :: FromRequest q => Request -> Either ErrorObj q Source #
class ToRequest q where Source #
Methods
requestMethod :: q -> Method Source #
Method associated with request data to build a request object.
requestIsNotif :: q -> Bool Source #
Is this request to be sent as a notification (no id, no response)?
Instances
ToRequest Value Source # | |
Defined in Network.JSONRPC.Data | |
ToRequest () Source # | |
Defined in Network.JSONRPC.Data |
Constructors
Response | |
ResponseError | |
OrphanError | |
Instances
Arbitrary Response Source # | |||||
FromJSON Response Source # | |||||
Defined in Network.JSONRPC.Data | |||||
ToJSON Response Source # | |||||
Generic Response Source # | |||||
Defined in Network.JSONRPC.Data Associated Types
| |||||
Show Response Source # | |||||
NFData Response Source # | |||||
Defined in Network.JSONRPC.Data | |||||
Eq Response Source # | |||||
type Rep Response Source # | |||||
Defined in Network.JSONRPC.Data type Rep Response = D1 ('MetaData "Response" "Network.JSONRPC.Data" "json-rpc-1.1.2-684ncyg3Rc88KoeoDxJyo3" 'False) (C1 ('MetaCons "Response" 'PrefixI 'True) (S1 ('MetaSel ('Just "getResVer") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Ver) :*: (S1 ('MetaSel ('Just "getResult") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Value) :*: S1 ('MetaSel ('Just "getResId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Id))) :+: (C1 ('MetaCons "ResponseError" 'PrefixI 'True) (S1 ('MetaSel ('Just "getResVer") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Ver) :*: (S1 ('MetaSel ('Just "getError") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ErrorObj) :*: S1 ('MetaSel ('Just "getResId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Id))) :+: C1 ('MetaCons "OrphanError" 'PrefixI 'True) (S1 ('MetaSel ('Just "getResVer") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Ver) :*: S1 ('MetaSel ('Just "getError") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ErrorObj)))) |
data BatchResponse Source #
Constructors
BatchResponse | |
Fields
| |
SingleResponse | |
Fields |
Instances
Arbitrary BatchResponse Source # | |||||
Defined in Network.JSONRPC.Arbitrary | |||||
FromJSON BatchResponse Source # | |||||
Defined in Network.JSONRPC.Data Methods parseJSON :: Value -> Parser BatchResponse # parseJSONList :: Value -> Parser [BatchResponse] # | |||||
ToJSON BatchResponse Source # | |||||
Defined in Network.JSONRPC.Data Methods toJSON :: BatchResponse -> Value # toEncoding :: BatchResponse -> Encoding # toJSONList :: [BatchResponse] -> Value # toEncodingList :: [BatchResponse] -> Encoding # omitField :: BatchResponse -> Bool # | |||||
Generic BatchResponse Source # | |||||
Defined in Network.JSONRPC.Data Associated Types
| |||||
Show BatchResponse Source # | |||||
Defined in Network.JSONRPC.Data Methods showsPrec :: Int -> BatchResponse -> ShowS # show :: BatchResponse -> String # showList :: [BatchResponse] -> ShowS # | |||||
NFData BatchResponse Source # | |||||
Defined in Network.JSONRPC.Data Methods rnf :: BatchResponse -> () # | |||||
Eq BatchResponse Source # | |||||
Defined in Network.JSONRPC.Data Methods (==) :: BatchResponse -> BatchResponse -> Bool # (/=) :: BatchResponse -> BatchResponse -> Bool # | |||||
type Rep BatchResponse Source # | |||||
Defined in Network.JSONRPC.Data type Rep BatchResponse = D1 ('MetaData "BatchResponse" "Network.JSONRPC.Data" "json-rpc-1.1.2-684ncyg3Rc88KoeoDxJyo3" 'False) (C1 ('MetaCons "BatchResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "getBatchResponse") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Response])) :+: C1 ('MetaCons "SingleResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSingleResponse") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Response))) |
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.
Instances
FromResponse Value Source # | |
Defined in Network.JSONRPC.Data | |
FromResponse () Source # | |
Defined in Network.JSONRPC.Data |
fromResponse :: FromResponse r => Method -> Response -> Maybe r Source #
Parse a response knowing the method of the corresponding request.
type Respond q (m :: Type -> Type) r = q -> m (Either ErrorObj r) Source #
Type of function to make it easy to create a response from a request. Meant to be used in servers.
buildResponse :: (Monad m, FromRequest q, ToJSON r) => Respond q m r -> Request -> m (Maybe Response) Source #
Create a response from a request. Use in servers.
Error object from JSON-RPC 2.0. ErrorVal for backwards compatibility.
Constructors
ErrorObj | |
Fields
| |
ErrorVal | |
Fields
|
Instances
Arbitrary ErrorObj Source # | |||||
FromJSON ErrorObj Source # | |||||
Defined in Network.JSONRPC.Data | |||||
ToJSON ErrorObj Source # | |||||
Generic ErrorObj Source # | |||||
Defined in Network.JSONRPC.Data Associated Types
| |||||
Show ErrorObj Source # | |||||
NFData ErrorObj Source # | |||||
Defined in Network.JSONRPC.Data | |||||
Eq ErrorObj Source # | |||||
type Rep ErrorObj Source # | |||||
Defined in Network.JSONRPC.Data type Rep ErrorObj = D1 ('MetaData "ErrorObj" "Network.JSONRPC.Data" "json-rpc-1.1.2-684ncyg3Rc88KoeoDxJyo3" 'False) (C1 ('MetaCons "ErrorObj" 'PrefixI 'True) (S1 ('MetaSel ('Just "getErrMsg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String) :*: (S1 ('MetaSel ('Just "getErrCode") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "getErrData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Value))) :+: C1 ('MetaCons "ErrorVal" 'PrefixI 'True) (S1 ('MetaSel ('Just "getErrData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Value))) |
errorParse :: ByteString -> ErrorObj Source #
Parse error.
errorInvalid :: Value -> ErrorObj Source #
Invalid request.
errorMethod :: Method -> ErrorObj Source #
Method not found.