Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 JsonRpc (method :: Symbol) p e r
- data JsonRpcNotification (method :: Symbol) p
- data Request p = Request {}
- data JsonRpcResponse e r
- data JsonRpcErr e = JsonRpcErr {}
- type family JsonRpcEndpoint a where ...
API specification types
data JsonRpcNotification (method :: Symbol) p Source #
JSON-RPC endpoints which do not respond
JSON-RPC messages
Client messages
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
(Eq r, Eq e) => Eq (JsonRpcResponse e r) Source # | |
Defined in Servant.JsonRpc (==) :: JsonRpcResponse e r -> JsonRpcResponse e r -> Bool # (/=) :: JsonRpcResponse e r -> JsonRpcResponse e r -> Bool # | |
(Show r, Show e) => Show (JsonRpcResponse e r) Source # | |
Defined in Servant.JsonRpc showsPrec :: Int -> JsonRpcResponse e r -> ShowS # show :: JsonRpcResponse e r -> String # showList :: [JsonRpcResponse e r] -> ShowS # | |
(ToJSON e, ToJSON r) => ToJSON (JsonRpcResponse e r) Source # | |
Defined in Servant.JsonRpc toJSON :: JsonRpcResponse e r -> Value # toEncoding :: JsonRpcResponse e r -> Encoding # toJSONList :: [JsonRpcResponse e r] -> Value # toEncodingList :: [JsonRpcResponse e r] -> Encoding # | |
(FromJSON e, FromJSON r) => FromJSON (JsonRpcResponse e r) Source # | |
Defined in Servant.JsonRpc parseJSON :: Value -> Parser (JsonRpcResponse e r) # parseJSONList :: Value -> Parser [JsonRpcResponse e r] # |
data JsonRpcErr e Source #
Instances
Eq e => Eq (JsonRpcErr e) Source # | |
Defined in Servant.JsonRpc (==) :: JsonRpcErr e -> JsonRpcErr e -> Bool # (/=) :: JsonRpcErr e -> JsonRpcErr e -> Bool # | |
Show e => Show (JsonRpcErr e) Source # | |
Defined in Servant.JsonRpc showsPrec :: Int -> JsonRpcErr e -> ShowS # show :: JsonRpcErr e -> String # showList :: [JsonRpcErr e] -> ShowS # |
Type rewriting
type family JsonRpcEndpoint a where ... Source #
JsonRpcEndpoint (JsonRpc m p e r) = ReqBody '[JSON] (Request p) :> Post '[JSON] (JsonRpcResponse e r) | |
JsonRpcEndpoint (JsonRpcNotification m p) = ReqBody '[JSON] (Request p) :> Post '[JSON] NoContent |