Skip to content

Instantly share code, notes, and snippets.

@i-v-s
Created May 6, 2021 19:08
Show Gist options
  • Save i-v-s/782aae0ed56e2182cfed4d0eab3149e7 to your computer and use it in GitHub Desktop.
Save i-v-s/782aae0ed56e2182cfed4d0eab3149e7 to your computer and use it in GitHub Desktop.
Ethereum JSON-RPC query example on Haskell
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Numeric (showHex)
import Data.Text (pack)
import Control.Monad.IO.Class
import Data.Aeson
import Network.HTTP.Req
data Request = BlockNumberReq | BlockByNumberReq Int Bool
{-| Decode
>>> decode "{\"jsonrpc\":\"2.0\",\"result\":\"0xb27398\",\"id\":1}" :: Maybe Response
-}
data Response = Response {id :: Int, jsonrpc :: String, result :: String} deriving (Show)
instance FromJSON Response where
parseJSON (Object o) =
Response <$>
o .: "id" <*>
o .: "jsonrpc" <*>
o .: "result"
buildRequest :: Request -> Int -> ReqBodyJson Value
buildRequest BlockNumberReq id = buildRPC "eth_blockNumber" [] id
buildRequest (BlockByNumberReq num full) id = buildRPC "eth_getBlockByNumber" [String $ pack $ "0x" ++ showHex num "", Bool full] id
buildRPC :: String -> [Value] -> Int -> ReqBodyJson Value
buildRPC method params id =
ReqBodyJson $ object ["method" .= method, "params" .= params, "id" .= id, "jsonrpc" .= String "2.0"]
main :: IO ()
-- You can either make your monad an instance of 'MonadHttp', or use
-- 'runReq' in any IO-enabled monad without defining new instances.
main = runReq defaultHttpConfig $ do
-- One function—full power and flexibility, automatic retrying on timeouts
-- and such, automatic connection sharing.
r <-
req
POST -- method
(http "localhost") -- safe by construction URL
(buildRequest BlockNumberReq 1) -- use built-in options or add your own
jsonResponse -- specify how to interpret response
(port 8545) -- query params, headers, explicit port number, etc.
liftIO $ print (responseBody r :: Response)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment