Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Servant.JsonRpc
Description
Work with JSON-RPC protocol messages at both type and value level.
type Mul = JsonRpc "mul" (Int, Int) String Int req :: Request (Int, Int) req = Request "mul" (3, 5) (Just 0) rsp :: JsonRpcResponse String Int rsp = Result 0 15
Synopsis
- data RawJsonRpc ctype api
- data JsonRpc (method :: Symbol) p e r
- data JsonRpcNotification (method :: Symbol) p
- data JSONRPC
- data Request p = Request {}
- data JsonRpcResponse e r
- data JsonRpcErr e = JsonRpcErr {}
- parseErrorCode :: Int
- invalidRequestCode :: Int
- methodNotFoundCode :: Int
- invalidParamsCode :: Int
- internalErrorCode :: Int
- type family JsonRpcEndpoint ctype a where ...
API specification types
data RawJsonRpc ctype api Source #
A JSON RPC server handles any number of methods. Represent this at the type level using this type.
data JsonRpcNotification (method :: Symbol) p Source #
JSON-RPC endpoints which do not respond
The JSON-RPC content type
Instances
Accept JSONRPC Source # | |
Defined in Servant.JsonRpc | |
ToJSON a => MimeRender JSONRPC a Source # | |
Defined in Servant.JsonRpc Methods mimeRender :: Proxy JSONRPC -> a -> ByteString # | |
FromJSON a => MimeUnrender JSONRPC a Source # | |
Defined in Servant.JsonRpc Methods mimeUnrender :: Proxy JSONRPC -> ByteString -> Either String a # mimeUnrenderWithType :: Proxy JSONRPC -> MediaType -> ByteString -> Either String a # |
JSON-RPC messages
Client messages
Constructors
Request | |
data JsonRpcResponse e r Source #
Server messages. An Ack
is a message which refers to a Request
but
both its "errors" and "result" keys are null
Instances
data JsonRpcErr e Source #
Constructors
JsonRpcErr | |
Instances
Show e => Show (JsonRpcErr e) Source # | |
Defined in Servant.JsonRpc Methods showsPrec :: Int -> JsonRpcErr e -> ShowS # show :: JsonRpcErr e -> String # showList :: [JsonRpcErr e] -> ShowS # | |
Eq e => Eq (JsonRpcErr e) Source # | |
Defined in Servant.JsonRpc |
Standard error codes
parseErrorCode :: Int Source #
Type rewriting
type family JsonRpcEndpoint ctype a where ... Source #
Equations
JsonRpcEndpoint ctype (JsonRpc m p e r) = ReqBody '[ctype] (Request p) :> Post '[ctype] (JsonRpcResponse e r) | |
JsonRpcEndpoint ctype (JsonRpcNotification m p) = ReqBody '[ctype] (Request p) :> Post '[ctype] NoContent |