Stability | experimental |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
We provide limited access to the bitcoin-core daemon RPC interface. RPC method descriptions come from the bitcoind RPC help pages.
Synopsis
- type BitcoindClient r = ReaderT BasicAuthData (ExceptT BitcoindException ClientM) r
- runBitcoind :: Manager -> String -> Int -> BasicAuthData -> BitcoindClient a -> IO (Either BitcoindException a)
- cookieClient :: Manager -> FilePath -> String -> Int -> BitcoindClient r -> IO (Either BitcoindException r)
- basicAuthFromCookie :: FilePath -> IO BasicAuthData
- mkBitcoindEnv :: Manager -> String -> Int -> ClientEnv
- data BitcoindException
- getTransaction :: TxHash -> Maybe BlockHash -> BitcoindClient Tx
- sendRawTransaction :: Text -> Maybe Double -> BitcoindClient TxHash
- sendTransaction :: Tx -> Maybe Double -> BitcoindClient TxHash
- testMempoolAccept :: [Tx] -> Maybe Double -> BitcoindClient [MempoolTestResult]
- getBlock :: BlockHash -> BitcoindClient Block
- getBlockFilter :: BlockHash -> BitcoindClient CompactFilter
- getBlockHeader :: BlockHash -> BitcoindClient BlockHeader
- getBlockHash :: BlockHeight -> BitcoindClient BlockHash
- getBlockCount :: BitcoindClient Word32
- getDifficulty :: BitcoindClient Scientific
- getBestBlockHash :: BitcoindClient BlockHash
- getBlockStats :: BlockHash -> BitcoindClient BlockStats
- getChainTips :: BitcoindClient [ChainTip]
- getChainTxStats :: Maybe Word32 -> Maybe BlockHash -> BitcoindClient ChainTxStats
- getMempoolInfo :: BitcoindClient MempoolInfo
- getMempoolAncestors :: TxHash -> BitcoindClient [TxHash]
- getMempoolDescendants :: TxHash -> BitcoindClient [TxHash]
- getRawMempool :: BitcoindClient [TxHash]
- getPeerInfo :: BitcoindClient [PeerInfo]
- getConnectionCount :: BitcoindClient Word16
- getNodeAddresses :: Maybe Word32 -> BitcoindClient [NodeAddress]
- getAddedNodeInfo :: Maybe Text -> BitcoindClient [NodeInfo]
- listBanned :: BitcoindClient [Text]
- getNetTotals :: BitcoindClient NetTotals
- stop :: BitcoindClient ()
- uptime :: BitcoindClient Word32
- data Command
- addNode :: Text -> Command -> BitcoindClient ()
- disconnectNode :: Text -> BitcoindClient ()
- clearBanned :: BitcoindClient ()
- generateToAddress :: Word32 -> Text -> Maybe Word32 -> BitcoindClient [BlockHash]
- module Bitcoin.Core.RPC.Responses
Interacting with bitcoind
type BitcoindClient r = ReaderT BasicAuthData (ExceptT BitcoindException ClientM) r Source #
:: Manager | |
-> String | host |
-> Int | port |
-> BasicAuthData | |
-> BitcoindClient a | |
-> IO (Either BitcoindException a) |
Convenience function for sending a RPC call to bitcoind
:: Manager | |
-> FilePath | path to the cookie file |
-> String | host |
-> Int | port |
-> BitcoindClient r | |
-> IO (Either BitcoindException r) |
Send a RPC call to bitcoind using credentials from a cookie file
:: FilePath | path to the cookie file |
-> IO BasicAuthData |
Parse a username and password from a file. The contents of the file should be exactly "username:password" (not base64 encoded).
Convenience function for connecting to bitcoind
data BitcoindException Source #
Exceptions resulting from interacting with bitcoind
RpcException String | The error message returned by bitcoind on failure |
ClientException ClientError | |
DecodingError String |
Instances
Show BitcoindException Source # | |
Defined in Servant.Bitcoind showsPrec :: Int -> BitcoindException -> ShowS # show :: BitcoindException -> String # showList :: [BitcoindException] -> ShowS # | |
Exception BitcoindException Source # | |
Defined in Servant.Bitcoind |
Transactions
getTransaction :: TxHash -> Maybe BlockHash -> BitcoindClient Tx Source #
By default this function only works for mempool transactions. When called with a blockhash argument, getrawtransaction will return the transaction if the specified block is available and the transaction is found in that block. When called without a blockhash argument, getrawtransaction will return the transaction if it is in the mempool, or if -txindex is enabled and the transaction is in a block in the blockchain.
sendRawTransaction :: Text -> Maybe Double -> BitcoindClient TxHash Source #
Submit a raw transaction (serialized, hex-encoded) to local node and network.
sendTransaction :: Tx -> Maybe Double -> BitcoindClient TxHash Source #
A version of sendRawTransaction
that handles serialization
testMempoolAccept :: [Tx] -> Maybe Double -> BitcoindClient [MempoolTestResult] Source #
Returns result of mempool acceptance tests indicating if the transactions would be accepted by mempool. This checks if the transaction violates the consensus or policy rules.
Blocks
getBlock :: BlockHash -> BitcoindClient Block Source #
Produce the block corresponding to the given BlockHash
if it exists.
getBlockFilter :: BlockHash -> BitcoindClient CompactFilter Source #
Retrieve a BIP 157 content filter for a particular block.
getBlockHeader :: BlockHash -> BitcoindClient BlockHeader Source #
Returns the header of the block corresponding to the given BlockHash
getBlockHash :: BlockHeight -> BitcoindClient BlockHash Source #
Returns hash of block in best-block-chain at height provided.
getBlockCount :: BitcoindClient Word32 Source #
Returns the height of the most-work fully-validated chain. The genesis block has height 0.
getDifficulty :: BitcoindClient Scientific Source #
Returns the proof-of-work difficulty as a multiple of the minimum difficulty.
getBestBlockHash :: BitcoindClient BlockHash Source #
Returns the hash of the best (tip) block in the most-work fully-validated chain.
getBlockStats :: BlockHash -> BitcoindClient BlockStats Source #
Compute per block statistics for a given window. All amounts are in satoshis. It won't work for some heights with pruning.
getChainTips :: BitcoindClient [ChainTip] Source #
Return information about all known tips in the block tree, including the main chain as well as orphaned branches.
getChainTxStats :: Maybe Word32 -> Maybe BlockHash -> BitcoindClient ChainTxStats Source #
Compute statistics about the total number and rate of transactions in the chain.
Mempool
getMempoolInfo :: BitcoindClient MempoolInfo Source #
Returns details on the active state of the TX memory pool.
getMempoolAncestors :: TxHash -> BitcoindClient [TxHash] Source #
If txid is in the mempool, returns all in-mempool ancestors.
getMempoolDescendants :: TxHash -> BitcoindClient [TxHash] Source #
If txid is in the mempool, returns all in-mempool descendants.
getRawMempool :: BitcoindClient [TxHash] Source #
Returns all transaction ids in memory pool.
Network
getPeerInfo :: BitcoindClient [PeerInfo] Source #
Returns data about each connected network node.
getConnectionCount :: BitcoindClient Word16 Source #
Returns the number of connections to other nodes.
getNodeAddresses :: Maybe Word32 -> BitcoindClient [NodeAddress] Source #
Return known addresses which can potentially be used to find new nodes in the network
:: Maybe Text | optionally specify a node by address |
-> BitcoindClient [NodeInfo] |
Returns information about the given added node, or all added nodes (note that onetry addnodes are not listed here)
listBanned :: BitcoindClient [Text] Source #
List all banned IPs/Subnets.
getNetTotals :: BitcoindClient NetTotals Source #
Returns information about network traffic, including bytes in, bytes out, and current time.
Control
stop :: BitcoindClient () Source #
Request a graceful shutdown of Bitcoin Core.
uptime :: BitcoindClient Word32 Source #
Returns the total uptime of the server (in seconds)
Commands as understood by addNode
Instances
Enum Command Source # | |
Eq Command Source # | |
Show Command Source # | |
ToJSON Command Source # | |
Defined in Bitcoin.Core.RPC.Network |
:: Text | node address |
-> Command | |
-> BitcoindClient () |
Attempts to add or remove a node from the addnode list; or try a connection to a node once. Nodes added using addnode are protected from DoS disconnection and are not required to be full nodes/support SegWit as other outbound peers are (though such peers will not be synced from).
:: Text | node address |
-> BitcoindClient () |
Immediately disconnects from the specified peer node.
clearBanned :: BitcoindClient () Source #
Clear all banned IPs.
:: Word32 | number of blocks to generate |
-> Text | address for the coinbase reward |
-> Maybe Word32 | how many iterations to try |
-> BitcoindClient [BlockHash] |
Generate blocks in regtest
mode
Response models
module Bitcoin.Core.RPC.Responses