module Network.JsonRpc.Client (
Connection
, RpcResult
, Signature (..)
, (:::) (..)
, toFunction
, toFunction_
, Batch ()
, toBatchFunction
, toBatchFunction_
, voidBatch
, runBatch
, RpcError (..)
, clientCode
, ClientFunction
, ComposeMultiParam) where
import Network.JsonRpc.Server (RpcResult, RpcError (..), rpcError)
import qualified Data.Aeson as A
import Data.Aeson ((.=), (.:))
import Data.Text (Text (), pack)
import Data.ByteString.Lazy (ByteString)
import qualified Data.HashMap.Strict as H
import Data.Ord (comparing)
import Data.Maybe (catMaybes)
import qualified Data.Vector as V
import qualified Data.Vector.Algorithms.Intro as VA
import Control.Arrow ((&&&))
import Control.Monad (liftM)
import Control.Monad.Except (ExceptT (..), throwError, lift, (<=<))
import Control.Applicative (Alternative (..), (<|>))
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative (Applicative (..), (<$>), (<*>))
#endif
type Connection m = ByteString -> m (Maybe ByteString)
type Result = Either RpcError
data Signature ps r = Signature Text ps deriving Show
data p ::: ps = Text ::: ps deriving Show
infixr :::
toBatchFunction :: ClientFunction ps r f =>
Signature ps r
-> f
toBatchFunction s@(Signature name params) = _toBatch name params (resultType s) H.empty
toBatchFunction_ :: (ClientFunction ps r f, ComposeMultiParam (Batch r -> Batch ()) f g) =>
Signature ps r
-> g
toBatchFunction_ = composeWithBatch voidBatch
toFunction :: (Monad m, ClientFunction ps r f, ComposeMultiParam (Batch r -> RpcResult m r) f g) =>
Connection m
-> Signature ps r
-> g
toFunction = composeWithBatch . runBatch
toFunction_ :: (Monad m, ClientFunction ps r f, ComposeMultiParam (Batch r -> RpcResult m ()) f g) =>
Connection m
-> Signature ps r
-> g
toFunction_ server = composeWithBatch $ runBatch server . voidBatch
composeWithBatch :: (ClientFunction ps r g, ComposeMultiParam f g h) => f -> Signature ps r -> h
composeWithBatch f = _compose f . toBatchFunction
runBatch :: Monad m =>
Connection m
-> Batch r
-> RpcResult m r
runBatch server batch = liftResult . bToResult batch =<<
validate . sort =<<
processRqs server idRequests
where requests = bRequests batch
idRequests = V.zipWith assignId requests ids
where ids = V.postscanl' incId 0 requests
incId i rq = if rqIsNotification rq then i else i + 1
sort = V.modify $ VA.sortBy $ comparing rsId
liftResult = ExceptT . return
validate rsps = let (results, ids) = V.unzip $ V.map (rsResult &&& rsId) rsps
in if ids /= V.enumFromN 1 (bNonNotifications batch)
then throwError $ clientError $
"Invalid response IDs: " ++ show ids
else return results
assignId :: Request -> Int -> IdRequest
assignId rq i = IdRequest { idRqMethod = rqMethod rq
, idRqId = if rqIsNotification rq then Nothing else Just i
, idRqParams = rqParams rq }
processRqs :: Monad m =>
Connection m -> V.Vector IdRequest -> RpcResult m (V.Vector Response)
processRqs server requests | V.null requests = return V.empty
| V.length requests == 1 = process V.singleton $ V.head requests
| otherwise = process id requests
where decode rsp = case A.eitherDecode rsp of
Right r -> return r
Left msg -> throwError $ clientError $
"Client cannot parse JSON response: " ++ msg
process f rqs = maybe (return V.empty) (liftM f . decode) =<<
(lift . server . A.encode) rqs
voidBatch :: Batch r -> Batch ()
voidBatch batch = Batch { bNonNotifications = 0
, bRequests = V.map toNotification $ bRequests batch
, bToResult = const $ return () }
where toNotification rq = rq { rqIsNotification = True }
data Batch r = Batch { bNonNotifications :: Int
, bRequests :: V.Vector Request
, bToResult :: V.Vector (Result A.Value) -> Result r }
instance Functor Batch where
fmap f batch = batch { bToResult = fmap f . bToResult batch }
instance Applicative Batch where
pure x = empty { bToResult = const $ return x }
(<*>) = combine (<*>)
instance Alternative Batch where
empty = Batch { bNonNotifications = 0
, bRequests = V.empty
, bToResult = const $ throwError $ clientError "empty" }
(<|>) = combine (<||>)
where Right x <||> _ = Right x
_ <||> x = x
combine :: (Result a -> Result b -> Result c) -> Batch a -> Batch b -> Batch c
combine f (Batch n1 rqs1 g1) (Batch n2 rqs2 g2) =
Batch { bNonNotifications = n1 + n2
, bRequests = rqs1 V.++ rqs2
, bToResult = \rs -> let (rs1, rs2) = V.splitAt n1 rs
in g1 rs1 `f` g2 rs2 }
data ResultType r = ResultType
resultType :: Signature ps r -> ResultType r
resultType _ = ResultType
clientError :: String -> RpcError
clientError msg = rpcError clientCode $ pack msg
clientCode :: Int
clientCode = 31999
class ClientFunction ps r f | ps r -> f, f -> ps r where
_toBatch :: Text -> ps -> ResultType r -> A.Object -> f
instance A.FromJSON r => ClientFunction () r (Batch r) where
_toBatch name _ _ priorArgs = Batch { bNonNotifications = 1
, bRequests = V.singleton $
Request name False priorArgs
, bToResult = decode <=< V.head }
where decode result = case A.fromJSON result of
A.Success r -> Right r
A.Error msg -> throwError . clientError $
"Client received wrong result type: " ++ msg
instance (ClientFunction ps r f, A.ToJSON a) => ClientFunction (a ::: ps) r (a -> f) where
_toBatch name (p ::: ps) rt priorArgs a = let newArgs = H.insert p (A.toJSON a) priorArgs
in _toBatch name ps rt newArgs
class ComposeMultiParam f g h | f g -> h, g h -> f where
_compose :: f -> g -> h
instance ComposeMultiParam (Batch a -> b) (Batch a) b where
_compose = ($)
instance ComposeMultiParam f g h => ComposeMultiParam f (a -> g) (a -> h) where
_compose f g = _compose f . g
data Request = Request { rqMethod :: Text
, rqIsNotification :: Bool
, rqParams :: A.Object }
data IdRequest = IdRequest { idRqMethod :: Text
, idRqId :: Maybe Int
, idRqParams :: A.Object }
instance A.ToJSON IdRequest where
toJSON rq = A.object $ catMaybes [ Just $ "jsonrpc" .= A.String "2.0"
, Just $ "method" .= idRqMethod rq
, ("id" .=) <$> idRqId rq
, let params = idRqParams rq
in if H.null params
then Nothing
else Just $ "params" .= params ]
data Response = Response { rsResult :: Result A.Value
, rsId :: Int }
instance A.FromJSON Response where
parseJSON = A.withObject "JSON-RPC response object" $
\v -> Response <$>
(Right <$> v .: "result" <|> Left <$> v .: "error") <*>
v .: "id"