json-rpc-server-0.1.2.0: JSON RPC 2.0 on the server side.

Safe HaskellNone
LanguageHaskell98

Network.JsonRpc.Server

Contents

Description

Functions for implementing the server side of JSON RPC 2.0. See http://www.jsonrpc.org/specification.

Synopsis

Instructions

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.

data Method m Source

Single method.

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.

data Methods m Source

Multiple methods.

toMethods :: [Method m] -> Methods m Source

Creates a set of methods to be called by name. The names must be unique.

call Source

Arguments

:: Monad m 
=> Methods m

Choice of methods to call.

-> ByteString

JSON RPC request.

-> m (Maybe ByteString)

The response wrapped in Just, or Nothing in the case of a notification, all wrapped in the given monad.

Handles one JSON RPC request. It is the same as callWithBatchStrategy sequence.

callWithBatchStrategy Source

Arguments

:: 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 Just, or Nothing in the case of a notification, all wrapped in the given monad.

Handles one JSON RPC request.

data Parameter a Source

Parameter expected by a method.

Constructors

Required Text

Required parameter with a name.

Optional Text a

Optional parameter with a name and default value.

data a :+: ps infixr 9 Source

A node in a type-level linked list of Parameter types. It is right associative.

Constructors

(Parameter a) :+: ps infixr 9 

Instances

(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.

Minimal complete definition

apply

Instances

(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

data RpcError Source

Error to be returned to the client.

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.

rpcErrorWithData :: ToJSON a => Int -> Text -> a -> RpcError Source

Creates an RpcError with the given code, message, and additional data. See rpcError for the recommended error code ranges.