zenith/src/Zenith/RPC.hs

56 lines
1.6 KiB
Haskell
Raw Normal View History

2024-07-23 18:46:37 +00:00
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
module Zenith.RPC where
import Data.Aeson
import qualified Data.Text as T
import Servant
import ZcashHaskell.Types (RpcError(..), RpcResponse(..))
import Zenith.Types (RpcCall(..), ZenithMethod(..), ZenithParams(..))
type ZenithRPC
= "getinfo" :> Get '[ JSON] Value :<|> ReqBody '[ JSON] RpcCall :> Post
'[ JSON]
(RpcResponse Value)
zenithServer :: Server ZenithRPC
zenithServer = getinfo :<|> handleRPC
where
getinfo :: Handler Value
getinfo =
return $
object
[ "version" .= ("0.7.0.0-beta" :: String)
, "network" .= ("testnet" :: String)
]
handleRPC :: RpcCall -> Handler (RpcResponse Value)
handleRPC req =
case method req of
GetInfo ->
case parameters req of
GetInfoParams ->
return $
MakeRpcResponse
Nothing
(callId req)
(Just $ object ["data" .= ("Here's your info" :: String)])
_anyOtherParams ->
return $
MakeRpcResponse
(Just $ RpcError (-32602) "Invalid params")
(callId req)
Nothing
Test ->
case parameters req of
TestParams x ->
return $
MakeRpcResponse Nothing (callId req) (Just $ object ["data" .= x])
_anyOtherParams ->
return $
MakeRpcResponse
(Just $ RpcError (-32602) "Invalid params")
(callId req)
Nothing