remote-json: Remote Monad implementation of the JSON RPC protocol
JSON RPC, where you can using monads and applicative functors to bundle JSON RPC methods and notifications.
{-# LANGUAGE GADTs, OverloadedStrings, TypeOperators #-}
module Main where
import Control.Natural ((:~>), nat)
import Control.Remote.Monad.JSON
import Control.Remote.Monad.JSON.Router(transport,router,Call(..),methodNotFound)
import Data.Aeson
import Data.Text(Text)
-- Our small DSL
say :: Text -> RPC ()
say msg = notification "say" (List [String msg])
temperature :: RPC Int
temperature = method "temperature" None
-- Our remote program
main :: IO ()
main = do
let s = weakSession network
t <- send s $ do
say "Hello, "
say "World!"
temperature
print t
-- Simulate the JSON-RPC server
network :: SendAPI :~> IO
network = transport $ router sequence $ nat remote
where
remote :: Call a -> IO a
remote (CallMethod "temperature" _) = return $ Number 42
remote (CallNotification "say" (List [String msg])) = print msg
remote _ = methodNotFound
[Skip to Readme]
Modules
[Index]
Downloads
- remote-json-0.2.tar.gz [browse] (Cabal source package)
- Package description (as included in the package)
Maintainer's Corner
For package maintainers and hackage trustees
Candidates
| Versions [RSS] | 0.2 |
|---|---|
| Dependencies | aeson (>=0.8 && <0.12), base (>=4 && <5), exceptions (>=0.8 && <0.9), fail, natural-transformation (>=0.3.1 && <0.4), remote-monad (==0.2), text (>=1.2 && <1.3), transformers (>=0.4 && <0.6), unordered-containers (>=0.2.5 && <0.2.7), vector (>=0.11 && <0.12) [details] |
| Tested with | ghc ==7.10.3 |
| License | BSD-3-Clause |
| Copyright | (c) 2016 The University of Kansas |
| Author | Justin Dawson and Andy Gill |
| Maintainer | JDawson@ku.edu |
| Category | Network |
| Source repo | head: git clone git://github.com/ku-fpg/remote-json |
| Uploaded | by AndyGill at 2016-02-09T20:03:21Z |
| Distributions | |
| Reverse Dependencies | 4 direct, 1 indirect [details] |
| Downloads | 922 total (4 in the last 30 days) |
| Rating | (no votes yet) [estimated by Bayesian average] |
| Your Rating | |
| Status | Docs uploaded by user Build status unknown [no reports yet] |