{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Network.JsonRpc.TinyClient
(
JsonRpc(..)
, MethodName
, JsonRpcClient(..)
, defaultSettings
, JsonRpcException(..)
, RpcError(..)
) where
import Control.Applicative ((<|>))
import Control.Exception (Exception)
import Control.Monad ((<=<))
import Control.Monad.Catch (MonadThrow (..))
import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.State (MonadState, get)
import Crypto.Number.Generate (generateMax)
import Data.Aeson (FromJSON (..), ToJSON (..),
Value (String), eitherDecode, encode,
object, withObject, (.:), (.:?), (.=))
import Data.ByteString.Lazy (ByteString)
import Data.Text (Text, unpack)
import Network.HTTP.Client (Manager, RequestBody (RequestBodyLBS),
httpLbs, method, newManager,
parseRequest, requestBody,
requestHeaders, responseBody)
import Network.HTTP.Client.TLS (tlsManagerSettings)
import qualified Network.WebSockets as WS (Connection, receiveData,
sendTextData)
type JsonRpcM m = (MonadIO m, MonadThrow m, MonadState JsonRpcClient m)
data JsonRpcClient = JsonRpcHttpClient
{ jsonRpcManager :: Manager
, jsonRpcServer :: String
}
| JsonRpcWsClient
{ jsonRpcWsConnection :: WS.Connection
}
defaultSettings :: MonadIO m
=> String
-> m JsonRpcClient
defaultSettings srv = liftIO $ JsonRpcHttpClient
<$> newManager tlsManagerSettings
<*> pure srv
instance Show JsonRpcClient where
show JsonRpcHttpClient{..} = "<JSON-RPC HTTP Client>"
show JsonRpcWsClient{..} = "<JSON-RPC WebSocket Client>"
data Request = Request
{ rqMethod :: !Text
, rqId :: !Int
, rqParams :: !Value
}
deriving (Eq, Show)
instance ToJSON Request where
toJSON rq = object [ "jsonrpc" .= String "2.0"
, "method" .= rqMethod rq
, "params" .= rqParams rq
, "id" .= rqId rq
]
data Response = Response
{ rsResult :: !(Either RpcError Value)
}
deriving (Eq, Show)
instance FromJSON Response where
parseJSON =
withObject "JSON-RPC response object" $
\v -> Response <$>
(Right <$> v .: "result" <|> Left <$> v .: "error")
data RpcError = RpcError
{ errCode :: !Int
, errMessage :: !Text
, errData :: !(Maybe Value)
}
deriving Eq
instance Show RpcError where
show (RpcError code msg dat) =
"JSON-RPC error " ++ show code ++ ": " ++ unpack msg
++ ". Data: " ++ show dat
instance FromJSON RpcError where
parseJSON = withObject "JSON-RPC error object" $
\v -> RpcError <$> v .: "code"
<*> v .: "message"
<*> v .:? "data"
data JsonRpcException = ParsingException String
| CallException RpcError
deriving (Show, Eq)
instance Exception JsonRpcException
class JsonRpcM m => Remote m a | a -> m where
remote' :: ([Value] -> m ByteString) -> a
instance (ToJSON a, Remote m b) => Remote m (a -> b) where
remote' f x = remote' (\xs -> f (toJSON x : xs))
instance {-# INCOHERENT #-} (JsonRpcM m, FromJSON b) => Remote m (m b) where
remote' f = decodeResponse =<< f []
type MethodName = Text
class JsonRpcM m => JsonRpc m where
remote :: Remote m a => MethodName -> a
{-# INLINE remote #-}
remote = remote' . call
call :: JsonRpcM m
=> MethodName
-> [Value]
-> m ByteString
call m r = do
rid <- liftIO $ generateMax maxInt
connection . encode $ Request m (fromInteger rid) (toJSON r)
where
maxInt = toInteger (maxBound :: Int)
connection body = do
jsonRpcInstance <- get
case jsonRpcInstance of
JsonRpcHttpClient{..} -> do
request <- parseRequest jsonRpcServer
let request' = request {
requestBody = RequestBodyLBS body
, requestHeaders = [("Content-Type", "application/json")]
, method = "POST"
}
responseBody <$> liftIO (httpLbs request' jsonRpcManager)
JsonRpcWsClient{..} -> liftIO $ do
WS.sendTextData jsonRpcWsConnection body
WS.receiveData jsonRpcWsConnection
decodeResponse :: (MonadThrow m, FromJSON a)
=> ByteString
-> m a
decodeResponse = (tryParse . eitherDecode . encode)
<=< tryResult . rsResult
<=< tryParse . eitherDecode
where
tryParse = either (throwM . ParsingException) return
tryResult = either (throwM . CallException) return