Stability | experimental |
---|---|
Maintainer | gershomb@gmail.com |
Safe Haskell | None |
The jmacro-rpc library provides an implementation of the JSON-RPC 2.0 protocol in Haskell (http:www.jsonrpc.org/), using typeclass based induction to automatically wrap arbitrary Haskell functions up as exposed RPCs, and to generate Haskell functions to call those RPCs on a remote server. Facilities are also included to expose RPCs in javascript on generated HTML pages, and to manage page-local (i.e. conversation) state on these pages. This package provides all core functionality and APIs. Additional backend-specific packages are provided for wiring these functions up to existing HTTP server packages.
- type JRequest = [Value]
- type JResult = Either String Value
- data JsonRPC m s = JsonRPC String (s -> JRequest -> m JResult)
- retErr :: Monad m => a -> m (Either a b)
- class Monad m => ToJsonRPC a m | a -> m where
- toJsonRPC_ :: a -> [Value] -> m JResult
- toJsonRPC :: ToJsonRPC a m => String -> a -> JsonRPC m ()
- toJsonConvRPC :: ToJsonRPC a m => String -> (s -> a) -> JsonRPC m s
- class ToJsonRPCCall a b | a -> b where
- toJsonRPCCall_ :: [Value] -> a -> b
- toJsonRPCCall :: ToJsonRPCCall a b => a -> b
- mkJsonRPCPair :: (ToJsonRPC a m, ToJsonRPCCall a t) => String -> (s -> a) -> (t, JsonRPC m s)
- invokeRPCLib :: JStat
- asIO :: IO a -> IO a
- handleRpcs :: (Functor m, Monad m) => (Int -> m s) -> [JsonRPC m s] -> ByteString -> m ByteString
- mkConversationPageGen :: (MonadIO m1, MonadIO m) => IO timestamp -> (IntMap (timestamp, s) -> IO (IntMap (timestamp, s))) -> ((Int -> m s) -> [JsonRPC m s] -> m1 resp) -> (JStat -> m1 resp) -> IO s -> [JsonRPC m s] -> IO (m1 resp, m1 resp)
- jsonRPCToDecl :: JsonRPC a m -> JStat
- type JState a = MVar (Either String a)
- type JStateAsync a = MVar (Either (Int, String) (JState a))
Documentation
A JsonRPC is a named function that takes a handle to some state, and yields a function from request to result in some monad. It is a representation of the server side of an RPC call.
class Monad m => ToJsonRPC a m | a -> m whereSource
This class should not be used directly.
toJsonRPC_ :: a -> [Value] -> m JResultSource
toJsonRPC :: ToJsonRPC a m => String -> a -> JsonRPC m ()Source
Takes a compatible function to a JsonRPC.
toJsonConvRPC :: ToJsonRPC a m => String -> (s -> a) -> JsonRPC m sSource
Takes a compatible function to a JsonRPC making use of state (i.e. a conversation).
class ToJsonRPCCall a b | a -> b whereSource
This class should not be used directly.
toJsonRPCCall_ :: [Value] -> a -> bSource
FromJSON b => ToJsonRPCCall (IO (Either String b)) ((ByteString -> IO (Either String ByteString)) -> Value -> String -> IO (Either String b)) | |
(ToJSON a, ToJsonRPCCall b c) => ToJsonRPCCall (a -> b) (a -> c) |
toJsonRPCCall :: ToJsonRPCCall a b => a -> bSource
Send a function on Jsonable values to a function of the same signature whose logic is invokable on a remote server. This function operates on the type of its argument. The body can remain undefined.
mkJsonRPCPair :: (ToJsonRPC a m, ToJsonRPCCall a t) => String -> (s -> a) -> (t, JsonRPC m s)Source
Takes a name and a function and yields both the server-side JsonRPC and the client-side stub.
JMacro Javascript stub to invoke json-rpc calls from web browsers.
handleRpcs :: (Functor m, Monad m) => (Int -> m s) -> [JsonRPC m s] -> ByteString -> m ByteStringSource
Given a function for managing local state, and a list of JsonRPCs over that local state, produce a function from Bytestring to Bytestring mapping json-rpc requests to responses.
mkConversationPageGen :: (MonadIO m1, MonadIO m) => IO timestamp -> (IntMap (timestamp, s) -> IO (IntMap (timestamp, s))) -> ((Int -> m s) -> [JsonRPC m s] -> m1 resp) -> (JStat -> m1 resp) -> IO s -> [JsonRPC m s] -> IO (m1 resp, m1 resp)Source
Used for creating server backends. Yes, this type is confusing. But unless you are creating a server backend, you can ignore it. Takes a function to generate some time identifier, a function to cull page state, a rpc handler, a function for creating a single page, a function to initialize a page state, and a bunch of rpcs, and creates a pair of handler functions (one for POST and one for GET) such that individual clients first pull a page with an embedded ID, along with client-side rpc functions. Those functions in turn interact with state local to that invocation of a page when they make json-rpc requests to the server. The cull function is in IO so it has access to whatever notion of time it desires, including the opportunity to not run at all. Note that the POST page should be served from the same url as the get page, but with an additional /jrpcs directory guard.
jsonRPCToDecl :: JsonRPC a m -> JStatSource
Converts a json rpc to a javascript declaration of the appropriate function.