json-rpc-server-0.2.4.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

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.

data Method m Source

A JSON-RPC method.

toMethod :: MethodParams f p m r => Text -> f -> p -> Method m Source

Creates a method from a name, function, and parameter descriptions. The parameter names must be unique.

call Source

Arguments

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

Handles one JSON-RPC request. The method names must be unique.

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

Instances

(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

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.

Deprecated

type Methods m = [Method m] Source

Deprecated: Use [Method m].

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

Deprecated: Use call directly.