Safe Haskell | None |
---|---|
Language | Haskell98 |
Functions for implementing the server side of JSON-RPC 2.0. See http://www.jsonrpc.org/specification.
- type RpcResult m r = ExceptT RpcError m r
- data Method m
- toMethod :: (MethodParams f p m r, ToJSON r, Monad m) => Text -> f -> p -> Method m
- call :: Monad m => [Method m] -> ByteString -> m (Maybe ByteString)
- callWithBatchStrategy :: Monad m => (forall a. NFData a => [m a] -> m [a]) -> [Method m] -> ByteString -> m (Maybe ByteString)
- data Parameter a
- data a :+: ps = (Parameter a) :+: ps
- class (Monad m, ToJSON r) => MethodParams f p m r | f -> p m r, p m r -> f
- data RpcError = RpcError {}
- rpcError :: Int -> Text -> RpcError
- rpcErrorWithData :: ToJSON a => Int -> Text -> a -> RpcError
- type Methods m = [Method m]
- toMethods :: [Method m] -> Methods m
Instructions
- Create methods by calling
toMethod
and providing the method names, lists of parameters, and functions to be called. - Process a request by calling
call
orcallWithBatchStrategy
on theMethod
s and inputByteString
.
Requests
This library handles by-name and by-position arguments, batch and single requests, and notifications. It also allows each parameter of a method to be either optional (with a default value) or required. The function is called as long as all required arguments are present. A request providing more positional arguments than the total number of optional and required parameters to a function results in an error. However, additional by-name arguments are ignored.
Example
Here is an example with three JSON-RPC methods that all have
access to an MVar
counter. The program reads requests from
stdin and writes responses to stdout. Compile it with the build
flag demo
.
{-# LANGUAGE OverloadedStrings #-} module Main (main) where import Network.JsonRpc.Server import System.IO (BufferMode (LineBuffering), hSetBuffering, stdout) import qualified Data.ByteString.Lazy.Char8 as B import Data.List (intercalate) import Data.Maybe (fromMaybe) import Control.Monad (forM_, when) import Control.Monad.Trans (liftIO) import Control.Monad.Except (throwError) import Control.Monad.Reader (ReaderT, ask, runReaderT) import Control.Concurrent.MVar (MVar, newMVar, modifyMVar) main = do hSetBuffering stdout LineBuffering contents <- B.getContents count <- newMVar 0 forM_ (B.lines contents) $ \request -> do response <- runReaderT (call methods request) count B.putStrLn $ fromMaybe "" response type Server = ReaderT (MVar Integer) IO methods :: [Method Server] methods = [add, printSequence, increment] add = toMethod "add" f (Required "x" :+: Required "y" :+: ()) where f :: Double -> Double -> RpcResult Server Double f x y = liftIO $ return (x + y) printSequence = toMethod "print_sequence" f params where params = Required "string" :+: Optional "count" 1 :+: Optional "separator" ',' :+: () f :: String -> Int -> Char -> RpcResult Server () f str count sep = do when (count < 0) $ throwError negativeCount liftIO $ print $ intercalate [sep] $ replicate count str negativeCount = rpcError (-32000) "negative count" increment = toMethod "increment_and_get_count" f () where f :: RpcResult Server Integer f = ask >>= \count -> liftIO $ modifyMVar count inc where inc x = return (x + 1, x + 1)
Methods
type RpcResult m r = ExceptT RpcError m r Source
Return type of a method. A method call can either fail with an RpcError
or succeed with a result of type r
.
toMethod :: (MethodParams f p m r, ToJSON r, Monad m) => Text -> f -> p -> Method m Source
Creates a method from a name, function, and parameter descriptions. The parameter names must be unique.
:: Monad m | |
=> [Method m] | Choice of methods to call. |
-> ByteString | JSON-RPC request. |
-> m (Maybe ByteString) | The response wrapped in |
Handles one JSON-RPC request. It is the same as
callWithBatchStrategy sequence
.
:: Monad m | |
=> (forall a. NFData a => [m a] -> m [a]) | Function specifying the evaluation strategy. |
-> [Method m] | Choice of methods to call. |
-> ByteString | JSON-RPC request. |
-> m (Maybe ByteString) | The response wrapped in |
Handles one JSON-RPC request. The method names must be unique.
Parameter expected by a method.
A node in a type-level linked list of Parameter
types. It is right associative.
(FromJSON a, MethodParams f p m r) => MethodParams (a -> f) ((:+:) a p) m r Source |
class (Monad m, ToJSON r) => MethodParams f p m r | f -> p m r, p m r -> f Source
Relationship between a method's function (f
), parameters (p
),
monad (m
), and return type (r
). p
has one Parameter
for
every argument of f
and is terminated by ()
. The return type
of f
is RpcResult m r
. This class is treated as closed.
(Monad m, ToJSON r) => MethodParams (RpcResult m r) () m r Source | |
(FromJSON a, MethodParams f p m r) => MethodParams (a -> f) ((:+:) a p) m r Source |
Errors
JSON-RPC error.
rpcError :: Int -> Text -> RpcError Source
Creates an RpcError
with the given error code and message.
According to the specification, server error codes should be
in the range -32099 to -32000, and application defined errors
should be outside the range -32768 to -32000.