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