{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
module Network.Ethereum.Api.Eth where
import Data.ByteArray.HexString (HexString)
import Data.Solidity.Prim.Address (Address)
import Data.Text (Text)
import Network.Ethereum.Api.Types (Block, BlockT, Call, Change,
DefaultBlock, Filter, Quantity,
SyncingState, Transaction, TxReceipt)
import Network.JsonRpc.TinyClient (JsonRpc (..))
protocolVersion :: JsonRpc m => m Text
{-# INLINE protocolVersion #-}
protocolVersion :: m Text
protocolVersion = Text -> m Text
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_protocolVersion"
syncing :: JsonRpc m => m SyncingState
{-# INLINE syncing #-}
syncing :: m SyncingState
syncing = Text -> m SyncingState
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_syncing"
coinbase :: JsonRpc m => m Address
{-# INLINE coinbase #-}
coinbase :: m Address
coinbase = Text -> m Address
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_coinbase"
mining :: JsonRpc m => m Bool
{-# INLINE mining #-}
mining :: m Bool
mining = Text -> m Bool
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_mining"
hashrate :: JsonRpc m => m Quantity
{-# INLINE hashrate #-}
hashrate :: m Quantity
hashrate = Text -> m Quantity
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_hashrate"
getStorageAt :: JsonRpc m => Address -> Quantity -> DefaultBlock -> m HexString
{-# INLINE getStorageAt #-}
getStorageAt :: Address -> Quantity -> DefaultBlock -> m HexString
getStorageAt = Text -> Address -> Quantity -> DefaultBlock -> m HexString
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getStorageAt"
getTransactionCount :: JsonRpc m => Address -> DefaultBlock -> m Quantity
{-# INLINE getTransactionCount #-}
getTransactionCount :: Address -> DefaultBlock -> m Quantity
getTransactionCount = Text -> Address -> DefaultBlock -> m Quantity
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getTransactionCount"
getBlockTransactionCountByHash :: JsonRpc m => HexString -> m Quantity
{-# INLINE getBlockTransactionCountByHash #-}
getBlockTransactionCountByHash :: HexString -> m Quantity
getBlockTransactionCountByHash = Text -> HexString -> m Quantity
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getBlockTransactionCountByHash"
getBlockTransactionCountByNumber :: JsonRpc m => Quantity -> m Quantity
{-# INLINE getBlockTransactionCountByNumber #-}
getBlockTransactionCountByNumber :: Quantity -> m Quantity
getBlockTransactionCountByNumber = Text -> Quantity -> m Quantity
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getBlockTransactionCountByNumber"
getUncleCountByBlockHash :: JsonRpc m => HexString -> m Quantity
{-# INLINE getUncleCountByBlockHash #-}
getUncleCountByBlockHash :: HexString -> m Quantity
getUncleCountByBlockHash = Text -> HexString -> m Quantity
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getUncleCountByBlockHash"
getUncleCountByBlockNumber :: JsonRpc m => Quantity -> m Quantity
{-# INLINE getUncleCountByBlockNumber #-}
getUncleCountByBlockNumber :: Quantity -> m Quantity
getUncleCountByBlockNumber = Text -> Quantity -> m Quantity
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getUncleCountByBlockNumber"
getCode :: JsonRpc m => Address -> DefaultBlock -> m HexString
{-# INLINE getCode #-}
getCode :: Address -> DefaultBlock -> m HexString
getCode = Text -> Address -> DefaultBlock -> m HexString
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getCode"
sign :: JsonRpc m => Address -> HexString -> m HexString
{-# INLINE sign #-}
sign :: Address -> HexString -> m HexString
sign = Text -> Address -> HexString -> m HexString
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_sign"
sendTransaction :: JsonRpc m => Call -> m HexString
{-# INLINE sendTransaction #-}
sendTransaction :: Call -> m HexString
sendTransaction = Text -> Call -> m HexString
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_sendTransaction"
sendRawTransaction :: JsonRpc m => HexString -> m HexString
{-# INLINE sendRawTransaction #-}
sendRawTransaction :: HexString -> m HexString
sendRawTransaction = Text -> HexString -> m HexString
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_sendRawTransaction"
getBalance :: JsonRpc m => Address -> DefaultBlock -> m Quantity
{-# INLINE getBalance #-}
getBalance :: Address -> DefaultBlock -> m Quantity
getBalance = Text -> Address -> DefaultBlock -> m Quantity
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getBalance"
newFilter :: JsonRpc m => Filter e -> m Quantity
{-# INLINE newFilter #-}
newFilter :: Filter e -> m Quantity
newFilter = Text -> Filter e -> m Quantity
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_newFilter"
getFilterChanges :: JsonRpc m => Quantity -> m [Change]
{-# INLINE getFilterChanges #-}
getFilterChanges :: Quantity -> m [Change]
getFilterChanges = Text -> Quantity -> m [Change]
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getFilterChanges"
uninstallFilter :: JsonRpc m => Quantity -> m Bool
{-# INLINE uninstallFilter #-}
uninstallFilter :: Quantity -> m Bool
uninstallFilter = Text -> Quantity -> m Bool
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_uninstallFilter"
getLogs :: JsonRpc m => Filter e -> m [Change]
{-# INLINE getLogs #-}
getLogs :: Filter e -> m [Change]
getLogs = Text -> Filter e -> m [Change]
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getLogs"
call :: JsonRpc m => Call -> DefaultBlock -> m HexString
{-# INLINE call #-}
call :: Call -> DefaultBlock -> m HexString
call = Text -> Call -> DefaultBlock -> m HexString
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_call"
estimateGas :: JsonRpc m => Call -> m Quantity
{-# INLINE estimateGas #-}
estimateGas :: Call -> m Quantity
estimateGas = Text -> Call -> m Quantity
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_estimateGas"
getBlockByHashLite :: JsonRpc m => HexString -> m (Maybe (BlockT HexString))
{-# INLINE getBlockByHashLite #-}
getBlockByHashLite :: HexString -> m (Maybe (BlockT HexString))
getBlockByHashLite = (HexString -> Bool -> m (Maybe (BlockT HexString)))
-> Bool -> HexString -> m (Maybe (BlockT HexString))
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Text -> HexString -> Bool -> m (Maybe (BlockT HexString))
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getBlockByHash") Bool
False
getBlockByNumberLite :: JsonRpc m => Quantity -> m (Maybe (BlockT HexString))
{-# INLINE getBlockByNumberLite #-}
getBlockByNumberLite :: Quantity -> m (Maybe (BlockT HexString))
getBlockByNumberLite = (Quantity -> Bool -> m (Maybe (BlockT HexString)))
-> Bool -> Quantity -> m (Maybe (BlockT HexString))
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Text -> Quantity -> Bool -> m (Maybe (BlockT HexString))
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getBlockByNumber") Bool
False
getBlockByHash :: JsonRpc m => HexString -> m (Maybe Block)
{-# INLINE getBlockByHash #-}
getBlockByHash :: HexString -> m (Maybe Block)
getBlockByHash = (HexString -> Bool -> m (Maybe Block))
-> Bool -> HexString -> m (Maybe Block)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Text -> HexString -> Bool -> m (Maybe Block)
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getBlockByHash") Bool
True
getBlockByNumber :: JsonRpc m => Quantity -> m (Maybe Block)
{-# INLINE getBlockByNumber #-}
getBlockByNumber :: Quantity -> m (Maybe Block)
getBlockByNumber = (Quantity -> Bool -> m (Maybe Block))
-> Bool -> Quantity -> m (Maybe Block)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Text -> Quantity -> Bool -> m (Maybe Block)
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getBlockByNumber") Bool
True
getTransactionByHash :: JsonRpc m => HexString -> m (Maybe Transaction)
{-# INLINE getTransactionByHash #-}
getTransactionByHash :: HexString -> m (Maybe Transaction)
getTransactionByHash = Text -> HexString -> m (Maybe Transaction)
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getTransactionByHash"
getTransactionByBlockHashAndIndex :: JsonRpc m => HexString -> Quantity -> m (Maybe Transaction)
{-# INLINE getTransactionByBlockHashAndIndex #-}
getTransactionByBlockHashAndIndex :: HexString -> Quantity -> m (Maybe Transaction)
getTransactionByBlockHashAndIndex = Text -> HexString -> Quantity -> m (Maybe Transaction)
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getTransactionByBlockHashAndIndex"
getTransactionByBlockNumberAndIndex :: JsonRpc m => DefaultBlock -> Quantity -> m (Maybe Transaction)
{-# INLINE getTransactionByBlockNumberAndIndex #-}
getTransactionByBlockNumberAndIndex :: DefaultBlock -> Quantity -> m (Maybe Transaction)
getTransactionByBlockNumberAndIndex = Text -> DefaultBlock -> Quantity -> m (Maybe Transaction)
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getTransactionByBlockNumberAndIndex"
getTransactionReceipt :: JsonRpc m => HexString -> m (Maybe TxReceipt)
{-# INLINE getTransactionReceipt #-}
getTransactionReceipt :: HexString -> m (Maybe TxReceipt)
getTransactionReceipt = Text -> HexString -> m (Maybe TxReceipt)
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getTransactionReceipt"
accounts :: JsonRpc m => m [Address]
{-# INLINE accounts #-}
accounts :: m [Address]
accounts = Text -> m [Address]
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_accounts"
newBlockFilter :: JsonRpc m => m Quantity
{-# INLINE newBlockFilter #-}
newBlockFilter :: m Quantity
newBlockFilter = Text -> m Quantity
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_newBlockFilter"
getBlockFilterChanges :: JsonRpc m => Quantity -> m [HexString]
{-# INLINE getBlockFilterChanges #-}
getBlockFilterChanges :: Quantity -> m [HexString]
getBlockFilterChanges = Text -> Quantity -> m [HexString]
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getFilterChanges"
blockNumber :: JsonRpc m => m Quantity
{-# INLINE blockNumber #-}
blockNumber :: m Quantity
blockNumber = Text -> m Quantity
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_blockNumber"
gasPrice :: JsonRpc m => m Quantity
{-# INLINE gasPrice #-}
gasPrice :: m Quantity
gasPrice = Text -> m Quantity
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_gasPrice"
getUncleByBlockHashAndIndex :: JsonRpc m => HexString -> Quantity -> m Block
{-# INLINE getUncleByBlockHashAndIndex #-}
getUncleByBlockHashAndIndex :: HexString -> Quantity -> m Block
getUncleByBlockHashAndIndex = Text -> HexString -> Quantity -> m Block
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getUncleByBlockHashAndIndex"
getUncleByBlockNumberAndIndex :: JsonRpc m => DefaultBlock -> Quantity -> m Block
{-# INLINE getUncleByBlockNumberAndIndex #-}
getUncleByBlockNumberAndIndex :: DefaultBlock -> Quantity -> m Block
getUncleByBlockNumberAndIndex = Text -> DefaultBlock -> Quantity -> m Block
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getUncleByBlockNumberAndIndex"
newPendingTransactionFilter :: JsonRpc m => m Quantity
{-# INLINE newPendingTransactionFilter #-}
newPendingTransactionFilter :: m Quantity
newPendingTransactionFilter = Text -> m Quantity
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_newPendingTransactionFilter"
getFilterLogs :: JsonRpc m => Quantity -> m [Change]
{-# INLINE getFilterLogs #-}
getFilterLogs :: Quantity -> m [Change]
getFilterLogs = Text -> Quantity -> m [Change]
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getFilterLogs"
getWork :: JsonRpc m => m [HexString]
{-# INLINE getWork #-}
getWork :: m [HexString]
getWork = Text -> m [HexString]
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_getWork"
submitWork :: JsonRpc m => HexString -> HexString -> HexString -> m Bool
{-# INLINE submitWork #-}
submitWork :: HexString -> HexString -> HexString -> m Bool
submitWork = Text -> HexString -> HexString -> HexString -> m Bool
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_submitWork"
submitHashrate :: JsonRpc m => HexString -> HexString -> m Bool
{-# INLINE submitHashrate #-}
submitHashrate :: HexString -> HexString -> m Bool
submitHashrate = Text -> HexString -> HexString -> m Bool
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"eth_submitHashrate"