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 = ErrorT RpcError m r
- data Method m
- toMethod :: (MethodParams f p m r, ToJSON r, Monad m) => Text -> f -> p -> Method m
- data Methods m
- toMethods :: [Method m] -> Methods m
- call :: Monad m => Methods m -> ByteString -> m (Maybe ByteString)
- callWithBatchStrategy :: Monad m => (forall a. [m a] -> m [a]) -> Methods m -> ByteString -> m (Maybe ByteString)
- data Parameter a
- data a :+: ps = (Parameter a) :+: ps
- class (Monad m, Functor m, ToJSON r) => MethodParams f p m r | f -> p m r
- data RpcError
- rpcError :: Int -> Text -> RpcError
- rpcErrorWithData :: ToJSON a => Int -> Text -> a -> RpcError
Instructions
- Create methods by calling
toMethod
and providing the method names, lists of parameters, and functions to be called. - Create a set of methods by calling
toMethods
. - Process a request by calling
call
orcallWithBatchStrategy
on theMethods
and inputByteString
.
Unnamed and Optional Arguments
RPC methods can have any mix of required and optional parameters. When a request uses unnamed arguments, the function is applied to the arguments in order. The function will be called as long as all required arguments are specified, and the number of arguments provided is not greater than the total number of required and optional parameters.
Example
Here is an example of a simple Happstack server with three methods.
Compile it with the build flag demo
.
{-# LANGUAGE OverloadedStrings #-} module Main (main) where import Network.JsonRpc.Server import Happstack.Server.SimpleHTTP( ServerPartT, simpleHTTP, nullConf , askRq, rqBody, unBody, toResponse) import Data.List (intercalate) import Data.Maybe (fromMaybe) import Control.Monad (when) import Control.Monad.Trans (liftIO) import Control.Monad.Error (throwError) import Control.Monad.Reader (ReaderT, ask, runReaderT) import Control.Concurrent.MVar (MVar, newMVar, readMVar, modifyMVar) main :: IO () main = newMVar 0 >>= \count -> simpleHTTP nullConf $ do request <- askRq body <- liftIO $ getBody request result <- runReaderT (call methods body) count let resultStr = fromMaybe "" result return $ toResponse resultStr where getBody r = unBody `fmap` readMVar (rqBody r) type Server = ReaderT (MVar Integer) (ServerPartT IO) methods :: Methods Server methods = toMethods [printSequence, getCount, add] printSequence, getCount, add :: Method Server printSequence = toMethod "print" 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" getCount = toMethod "get_count" f () where f :: RpcResult Server Integer f = ask >>= \count -> liftIO $ modifyMVar count inc where inc x = return (x + 1, x + 1) add = toMethod "add" f (Required "x" :+: Required "y" :+: ()) where f :: Double -> Double -> RpcResult Server Double f x y = liftIO $ return (x + y)
Methods
type RpcResult m r = ErrorT 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.
toMethods :: [Method m] -> Methods m Source
Creates a set of methods to be called by name. The names must be unique.
:: Monad m | |
=> Methods 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. [m a] -> m [a]) | Function specifying the evaluation strategy. |
-> Methods m | Choice of methods to call. |
-> ByteString | JSON RPC request. |
-> m (Maybe ByteString) | The response wrapped in |
Handles one JSON RPC request.
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 |
class (Monad m, Functor m, ToJSON r) => MethodParams f p m r | f -> p m r 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.
apply
(Monad m, Functor m, ToJSON r) => MethodParams (RpcResult m r) () m r | |
(FromJSON a, MethodParams f p m r) => MethodParams (a -> f) ((:+:) a p) m r |
Errors
Error to be returned to the client.