Safe Haskell | None |
---|---|
Language | Haskell98 |
A Haskell binding to the bitcoind server.
Synopsis
- type Client = ByteString -> IO ByteString
- getClient :: String -> ByteString -> ByteString -> IO Client
- data BitcoinException
- type HexString = Text
- type TransactionID = HexString
- data Satoshi = Satoshi
- type BTC = Fixed Satoshi
- type Account = Text
- type Address = HexString
- data ScriptSig
- getBlockCount :: Client -> IO BlockHeight
- getDifficulty :: Client -> IO Integer
- setTransactionFee :: Client -> BTC -> IO ()
- getRawMemoryPool :: Client -> IO (Vector TransactionID)
- type BlockHash = HexString
- getBlockHash :: Client -> BlockHeight -> IO BlockHash
- data Block = Block {
- blockHash :: BlockHash
- blkConfirmations :: Integer
- blkSize :: Integer
- blkHeight :: BlockHeight
- blkVersion :: Integer
- merkleRoot :: BlockHash
- subTransactions :: Vector TransactionID
- blkTime :: Integer
- blkNonce :: Integer
- blkBits :: HexString
- blkDifficulty :: Double
- nextBlock :: Maybe BlockHash
- prevBlock :: Maybe BlockHash
- getBlock :: Client -> BlockHash -> IO Block
- data OutputSetInfo = OutputSetInfo {}
- getOutputSetInfo :: Client -> IO OutputSetInfo
- data OutputInfo = OutputInfo {}
- getOutputInfo :: Client -> TransactionID -> Integer -> IO (Maybe OutputInfo)
- importPrivateKey :: Client -> PrivateKey -> Maybe Account -> IO ()
- dumpPrivateKey :: Client -> Address -> IO PrivateKey
- generate :: Client -> Int -> Maybe Int -> IO [HexString]
- generateToAddress :: Client -> Int -> Address -> Maybe Int -> IO [HexString]
- getGenerate :: Client -> IO Bool
- setGenerate :: Client -> Bool -> Maybe Int -> IO (Maybe [HexString])
- getHashesPerSec :: Client -> IO Integer
- data MiningInfo = MiningInfo {}
- getMiningInfo :: Client -> IO MiningInfo
- data HashData = HashData {}
- getWork :: Client -> IO HashData
- solveBlock :: Client -> HexString -> IO Bool
- data Transaction = Transaction {}
- newtype CoinBaseAux = CoinBaseAux {}
- data BlockTemplate = BlockTemplate {
- blockVersion :: Integer
- previousBlockHash :: HexString
- transactionsToInclude :: Vector Transaction
- coinBaseAux :: CoinBaseAux
- coinBaseValue :: Integer
- btTarget :: HexString
- minTime :: Integer
- nonceRange :: HexString
- sigopLimit :: Integer
- sizeLimit :: Integer
- curTime :: Integer
- btBits :: HexString
- btHeight :: Integer
- getBlockTemplate :: Client -> IO BlockTemplate
- submitBlock :: Client -> HexString -> IO Bool
- getConnectionCount :: Client -> IO Integer
- data PeerInfo = PeerInfo {}
- getPeerInfo :: Client -> IO [PeerInfo]
- data AddNodeCommand
- addNode :: Client -> Text -> AddNodeCommand -> IO ()
- disconnectNode :: Client -> Maybe Text -> Maybe Int -> IO ()
- type RawTransaction = HexString
- getRawTransaction :: Client -> TransactionID -> IO RawTransaction
- data TxIn
- = TxCoinbase { }
- | TxIn { }
- data TxnOutputType
- data ScriptPubKey
- data TxOut = TxOut {}
- data BlockInfo
- = ConfirmedBlock { }
- | UnconfirmedBlock
- data RawTransactionInfo = RawTransactionInfo {}
- getRawTransactionInfo :: Client -> TransactionID -> IO RawTransactionInfo
- data UnspentTransaction = UnspentTransaction {}
- listUnspent :: Client -> Maybe Int -> Maybe Int -> Vector Address -> IO (Vector UnspentTransaction)
- createRawTransaction :: Client -> Vector UnspentTransaction -> Vector (Address, BTC) -> IO HexString
- data DecodedRawTransaction = DecodedRawTransaction {}
- decodeRawTransaction :: Client -> RawTransaction -> IO DecodedRawTransaction
- data WhoCanPay
- data RawSignedTransaction = RawSignedTransaction {}
- signRawTransaction :: Client -> RawTransaction -> Maybe (Vector UnspentTransaction) -> Maybe (Vector HexString) -> Maybe WhoCanPay -> IO RawSignedTransaction
- sendRawTransaction :: Client -> RawTransaction -> IO TransactionID
- data BitcoindInfo = BitcoindInfo {
- bitcoinVersion :: Integer
- protocolVersion :: Integer
- walletVersion :: Integer
- balance :: BTC
- numBlocks :: Integer
- numConnections :: Integer
- proxy :: Text
- generationDifficulty :: Double
- onTestNetwork :: Bool
- keyPoolOldest :: Integer
- keyPoolSize :: Integer
- transactionFeePaid :: BTC
- unlockedUntil :: Maybe Integer
- bitcoindErrors :: Text
- getBitcoindInfo :: Client -> IO BitcoindInfo
- getNewAddress :: Client -> Maybe Account -> IO Address
- getAccountAddress :: Client -> Account -> IO Address
- getAccount :: Client -> Address -> IO Account
- setAccount :: Client -> Address -> Account -> IO ()
- getAddressesByAccount :: Client -> Account -> IO (Vector Address)
- sendToAddress :: Client -> Address -> BTC -> Maybe Text -> Maybe Text -> IO TransactionID
- data AddressInfo = AddressInfo {}
- listAddressGroupings :: Client -> IO (Vector (Vector AddressInfo))
- type Signature = HexString
- signMessage :: Client -> Address -> Text -> IO Signature
- verifyMessage :: Client -> Address -> Signature -> Text -> IO Bool
- getReceivedByAddress :: Client -> Address -> IO BTC
- getReceivedByAddress' :: Client -> Address -> Int -> IO BTC
- getReceivedByAccount :: Client -> Account -> IO BTC
- getReceivedByAccount' :: Client -> Account -> Int -> IO BTC
- getBalance :: Client -> IO BTC
- getBalance' :: Client -> Account -> IO BTC
- getBalance'' :: Client -> Account -> Int -> IO BTC
- moveBitcoins :: Client -> Account -> Account -> BTC -> Text -> IO ()
- sendFromAccount :: Client -> Account -> Address -> BTC -> Maybe Text -> Maybe Text -> IO TransactionID
- sendMany :: Client -> Account -> Vector (Address, BTC) -> Maybe Text -> IO TransactionID
- data EstimationMode
- estimateSmartFee :: Client -> Word32 -> Maybe EstimationMode -> IO Double
- data ReceivedByAddress = ReceivedByAddress {}
- listReceivedByAddress :: Client -> IO (Vector ReceivedByAddress)
- listReceivedByAddress' :: Client -> Int -> Bool -> IO (Vector ReceivedByAddress)
- data ReceivedByAccount = ReceivedByAccount {}
- listReceivedByAccount :: Client -> IO (Vector ReceivedByAccount)
- listReceivedByAccount' :: Client -> Int -> Bool -> IO (Vector ReceivedByAccount)
- listTransactions :: Client -> Account -> Int -> Int -> IO (Vector SimpleTransaction)
- listTransactions' :: Client -> Maybe Account -> Maybe Int -> Maybe Int -> IO (Vector SimpleTransaction)
- listAccounts :: Client -> Maybe Int -> IO (HashMap Account BTC)
- importAddress :: Client -> Address -> Maybe Account -> Maybe Bool -> IO ()
- data SinceBlock = SinceBlock {}
- data SimpleTransaction = SimpleTransaction {
- stReceivingAccount :: Account
- stAddress :: Maybe Address
- stCategory :: TransactionCategory
- stFee :: Maybe BTC
- stAmount :: BTC
- stConfirmations :: Maybe Integer
- stBlockHash :: Maybe BlockHash
- stBlockIndex :: Maybe Integer
- stBlockTime :: Maybe POSIXTime
- stTransactionId :: Maybe TransactionID
- stWalletConflicts :: Maybe (Vector TransactionID)
- stTime :: POSIXTime
- stTimeReceived :: Maybe POSIXTime
- stComment :: Maybe Text
- stTo :: Maybe Text
- stOtherAccount :: Maybe Account
- data TransactionCategory
- listSinceBlock :: Client -> BlockHash -> Maybe Int -> IO SinceBlock
- listSinceBlock' :: Client -> Maybe BlockHash -> Maybe Int -> IO SinceBlock
- data DetailedTransaction = DetailedTransaction {
- dtAmount :: BTC
- dtFee :: Maybe BTC
- dtConfirmations :: Maybe Integer
- dtTransactionId :: Maybe TransactionID
- dtWalletConflicts :: Maybe (Vector TransactionID)
- dtTime :: POSIXTime
- dtTimeReceived :: Maybe POSIXTime
- dtComment :: Maybe Text
- dtTo :: Maybe Text
- dtDetails :: Vector DetailedTransactionDetails
- dtHex :: RawTransaction
- data DetailedTransactionDetails = DetailedTransactionDetails {}
- getTransaction :: Client -> TransactionID -> IO DetailedTransaction
- backupWallet :: Client -> FilePath -> IO ()
- keyPoolRefill :: Client -> IO ()
- unlockWallet :: Client -> Text -> Integer -> IO ()
- lockWallet :: Client -> IO ()
- changePassword :: Client -> Text -> Text -> IO ()
- encryptWallet :: Client -> Text -> IO ()
- isAddressValid :: Client -> Address -> IO Bool
Common Types
type Client = ByteString -> IO ByteString Source #
Client
describes authentication credentials and host info for
making API requests to the Bitcoin daemon.
getClient :: String -> ByteString -> ByteString -> IO Client Source #
getClient
takes a url, rpc username, and rpc password
and returns a Client that can be used to make API calls. Each
Client encloses a Manager (from http-client) that re-uses
connections for requests, so long as the same Client is
is used for each call.
data BitcoinException Source #
A BitcoinException
is thrown when 'callApi encounters an
error. The API error code is represented as an Int
, the message as
a String
.
It may also be thrown when the value returned by the bitcoin API wasn't what we expected.
WARNING: Any of the functions in this module's public API may throw this exception. You should plan on handling it.
BitcoinApiError Int Text | A |
BitcoinResultTypeError ByteString | The raw JSON returned, if we can't figure out what actually went wrong. |
Instances
Eq BitcoinException Source # | |
Defined in Network.Bitcoin.Types (==) :: BitcoinException -> BitcoinException -> Bool # (/=) :: BitcoinException -> BitcoinException -> Bool # | |
Ord BitcoinException Source # | |
Defined in Network.Bitcoin.Types compare :: BitcoinException -> BitcoinException -> Ordering # (<) :: BitcoinException -> BitcoinException -> Bool # (<=) :: BitcoinException -> BitcoinException -> Bool # (>) :: BitcoinException -> BitcoinException -> Bool # (>=) :: BitcoinException -> BitcoinException -> Bool # max :: BitcoinException -> BitcoinException -> BitcoinException # min :: BitcoinException -> BitcoinException -> BitcoinException # | |
Read BitcoinException Source # | |
Defined in Network.Bitcoin.Types | |
Show BitcoinException Source # | |
Defined in Network.Bitcoin.Types showsPrec :: Int -> BitcoinException -> ShowS # show :: BitcoinException -> String # showList :: [BitcoinException] -> ShowS # | |
Exception BitcoinException Source # | |
Defined in Network.Bitcoin.Types |
type HexString = Text Source #
A string returned by the bitcoind API, representing data as hex.
What that data represents depends on the API call, but should be dcumented accordingly.
type TransactionID = HexString Source #
A hexadecimal string representation of a 256-bit unsigned integer.
This integer is a unique transaction identifier.
A satoshi is the smallest subdivision of bitcoins. For the resolution,
use resolution
from Fixed
.
Instances
HasResolution Satoshi Source # | |
Defined in Network.Bitcoin.Types resolution :: p Satoshi -> Integer # |
An account on the wallet is just a label to easily specify private keys.
The default account is an empty string.
A script signature.
Block Chain Operations
getBlockCount :: Client -> IO BlockHeight Source #
Returns the number of blocks in the longest block chain.
getDifficulty :: Client -> IO Integer Source #
Returns the proof-of-work difficulty as a multiple of the minimum difficulty.
setTransactionFee :: Client -> BTC -> IO () Source #
Sets the transaction fee will will pay to the network. Values of 0 are rejected.
getRawMemoryPool :: Client -> IO (Vector TransactionID) Source #
Returns all transaction identifiers in the memory pool.
:: Client | |
-> BlockHeight | Block index. |
-> IO BlockHash |
Returns the hash of the block in best-block-chain at the given index.
Information about a given block in the block chain.
Block | |
|
getBlock :: Client -> BlockHash -> IO Block Source #
Returns details of a block with given block-hash.
data OutputSetInfo Source #
Information on the unspent transaction in the output set.
OutputSetInfo | |
|
Instances
getOutputSetInfo :: Client -> IO OutputSetInfo Source #
Returns statistics about the unspent transaction output set.
data OutputInfo Source #
Details about an unspent transaction output.
OutputInfo | |
|
Instances
:: Client | |
-> TransactionID | |
-> Integer | The index we're looking at. |
-> IO (Maybe OutputInfo) |
Returns details about an unspent transaction output.
Private Key Operations
:: Client | |
-> PrivateKey | |
-> Maybe Account | An optional label for the key. |
-> IO () |
Adds a private key (as returned by dumpprivkey) to your wallet.
dumpPrivateKey :: Client -> Address -> IO PrivateKey Source #
Reveals the private key corresponding to the given address.
Mining Operations
:: Client | |
-> Int | The number of blocks to generate. The RPC call will not return until all blocks have been generated or the maxium number of iterations has been reached |
-> Maybe Int | The maximum number of iterations that are tried to create the requested number of blocks. Default is 1000000 |
-> IO [HexString] | An array containing the block header hashes of the generated blocks (may be empty if used with generate 0) |
The generate RPC nearly instantly generates blocks. See https://bitcoin.org/en/developer-reference#generate for more details.
:: Client | |
-> Int | The number of blocks to generate. The RPC call will not return until all blocks have been generated or the maxium number of iterations has been reached |
-> Address | The address to send the newly generated Bitcoin to |
-> Maybe Int | The maximum number of iterations that are tried to create the requested number of blocks. Default is 1000000 |
-> IO [HexString] |
The generatetoaddress RPC mines blocks immediately to a specified address. See https://bitcoin.org/en/developer-reference#generatetoaddress for more details.
Returns whether or not bitcoind is generating bitcoins.
:: Client | bitcoind RPC client |
-> Bool | Turn it on, or turn it off? |
-> Maybe Int | Generation is limited to this number of processors. Set it to Nothing to keep the value at what it was before, Just -1 to use all available cores, and any other value to limit it. If bitcoind runs in regtest mode instead of the number of processors, this specifies the number of hashes to generate. |
-> IO (Maybe [HexString]) |
Controls whether or not bitcoind is generating bitcoins. If bitcoind runs in regtest mode the number of generated hashes is returned. See https://bitcoin.org/en/developer-reference#setgenerate for more details.
getHashesPerSec :: Client -> IO Integer Source #
Returns a recent hashes per second performance measurement while generating.
data MiningInfo Source #
Information related to the current bitcoind mining operation.
If a field is undocumented here, it's because I don't know what it means. If you DO know what it means, I'd love it if you would submit a patch to help complete this documentation.
MiningInfo | |
|
Instances
getMiningInfo :: Client -> IO MiningInfo Source #
Returns an object containing mining-related information.
The hash data returned from getWork
.
solveBlock :: Client -> HexString -> IO Bool Source #
Tries to solve the given block, and returns true if it was successful.
data Transaction Source #
A transaction to be included in the next block.
Instances
newtype CoinBaseAux Source #
Instances
data BlockTemplate Source #
A template for constructing a block to work on.
See https://en.bitcoin.it/wiki/BIP_0022 for the full specification.
BlockTemplate | |
|
Instances
getBlockTemplate :: Client -> IO BlockTemplate Source #
Returns data needed to construct a block to work on.
Attempts to submit a new block to the network.
Network Operations
getConnectionCount :: Client -> IO Integer Source #
Returns the number of connections to other nodes.
Information about a peer node of the Bitcoin network.
The documentation for this data structure is incomplete, as I honestly don't know what some of these fields are for. Patches are welcome!
PeerInfo | |
|
data AddNodeCommand Source #
Instances
Eq AddNodeCommand Source # | |
Defined in Network.Bitcoin.Net (==) :: AddNodeCommand -> AddNodeCommand -> Bool # (/=) :: AddNodeCommand -> AddNodeCommand -> Bool # | |
Read AddNodeCommand Source # | |
Defined in Network.Bitcoin.Net readsPrec :: Int -> ReadS AddNodeCommand # readList :: ReadS [AddNodeCommand] # | |
Show AddNodeCommand Source # | |
Defined in Network.Bitcoin.Net showsPrec :: Int -> AddNodeCommand -> ShowS # show :: AddNodeCommand -> String # showList :: [AddNodeCommand] -> ShowS # | |
ToJSON AddNodeCommand Source # | |
Defined in Network.Bitcoin.Net toJSON :: AddNodeCommand -> Value # toEncoding :: AddNodeCommand -> Encoding # toJSONList :: [AddNodeCommand] -> Value # toEncodingList :: [AddNodeCommand] -> Encoding # |
Raw Transaction Operations
type RawTransaction = HexString Source #
Just like most binary data retrieved from bitcoind, a raw transaction is represented by a hexstring.
This is a serialized, hex-encoded transaction.
getRawTransaction :: Client -> TransactionID -> IO RawTransaction Source #
Get a raw transaction from its unique ID.
A transaction into an account. This can either be a coinbase transaction, or a standard transaction with another account.
TxCoinbase | |
TxIn | |
|
data TxnOutputType Source #
The type of a transaction out.
More documentation is needed here. Submit a patch if you know what this is about!
TxnPubKey | JSON of "pubkey" received. |
TxnPubKeyHash | JSON of "pubkeyhash" received. |
TxnScriptHash | JSON of "scripthash" received. |
TxnMultisig | JSON of "multisig" received. |
Instances
data ScriptPubKey Source #
A public key of someone we sent money to.
NonStandardScriptPubKey | |
StandardScriptPubKey | |
|
Instances
A transaction out of an account.
TxOut | |
|
Information on a single block.
ConfirmedBlock | |
UnconfirmedBlock | An unconfirmed block is boring, but a possibility. |
data RawTransactionInfo Source #
The raw transaction info for a given transaction ID.
RawTransactionInfo | |
|
Instances
getRawTransactionInfo :: Client -> TransactionID -> IO RawTransactionInfo Source #
Get raw transaction info for a given transaction ID. The data structure returned is quite sprawling and undocumented, so any patches to help simplify things would be greatly appreciated.
data UnspentTransaction Source #
Instances
Eq UnspentTransaction Source # | |
Defined in Network.Bitcoin.RawTransaction (==) :: UnspentTransaction -> UnspentTransaction -> Bool # (/=) :: UnspentTransaction -> UnspentTransaction -> Bool # | |
Show UnspentTransaction Source # | |
Defined in Network.Bitcoin.RawTransaction showsPrec :: Int -> UnspentTransaction -> ShowS # show :: UnspentTransaction -> String # showList :: [UnspentTransaction] -> ShowS # | |
ToJSON UnspentTransaction Source # | |
Defined in Network.Bitcoin.RawTransaction toJSON :: UnspentTransaction -> Value # toEncoding :: UnspentTransaction -> Encoding # toJSONList :: [UnspentTransaction] -> Value # toEncodingList :: [UnspentTransaction] -> Encoding # | |
FromJSON UnspentTransaction Source # | |
Defined in Network.Bitcoin.RawTransaction parseJSON :: Value -> Parser UnspentTransaction # parseJSONList :: Value -> Parser [UnspentTransaction] # |
:: Client | |
-> Maybe Int | minconf. Defaults to 1 if |
-> Maybe Int | maxconf. Defaults to 9999999 if |
-> Vector Address | Use |
-> IO (Vector UnspentTransaction) |
Returns an array of unspent transaction outputs with between minconf and maxconf (inclusive) confirmations. If addresses are given, the result will be filtered to include only those addresses.
:: Client | |
-> Vector UnspentTransaction | The unspent transactions we'll be using as our output. |
-> Vector (Address, BTC) | The addresses we're sending money to, along with how much each of them gets. |
-> IO HexString |
Create a transaction spending given inputs, sending to given addresses.
Note that the transaction's inputs are not signed, and it is not stored in the wallet or transmitted to the network.
Also, there is no checking to see if it's possible to send that much to the targets specified. In the future, such a scenario might throw an exception.
data DecodedRawTransaction Source #
A successfully decoded raw transaction, from a given serialized, hex-encoded transaction.
DecodedRawTransaction | |
|
Instances
FromJSON DecodedRawTransaction Source # | |
Defined in Network.Bitcoin.RawTransaction parseJSON :: Value -> Parser DecodedRawTransaction # parseJSONList :: Value -> Parser [DecodedRawTransaction] # |
decodeRawTransaction :: Client -> RawTransaction -> IO DecodedRawTransaction Source #
Decodes a raw transaction into a more accessible data structure.
Who can pay for a given transaction.
data RawSignedTransaction Source #
A raw signed transaction contains the raw, signed hexstring and whether or not this transaction has a complete signature set.
Instances
FromJSON RawSignedTransaction Source # | |
Defined in Network.Bitcoin.RawTransaction parseJSON :: Value -> Parser RawSignedTransaction # parseJSONList :: Value -> Parser [RawSignedTransaction] # |
:: Client | |
-> RawTransaction | The raw transaction whose inputs we're signing. |
-> Maybe (Vector UnspentTransaction) | An optional list of previous transaction outputs that this transaction depends on but may not yet be in the block chain. |
-> Maybe (Vector HexString) | An array of base58-encoded private keys that, if given, will be the only keys used to sign the transaction. |
-> Maybe WhoCanPay | Who can pay for this transaction? |
-> IO RawSignedTransaction | Returns |
Sign inputs for a raw transaction.
sendRawTransaction :: Client -> RawTransaction -> IO TransactionID Source #
Wallet Operations
data BitcoindInfo Source #
A plethora of information about a bitcoind instance.
BitcoindInfo | |
|
Instances
getBitcoindInfo :: Client -> IO BitcoindInfo Source #
Returns an object containing various state info.
Availability: < 0.16
getNewAddress :: Client -> Maybe Account -> IO Address Source #
Returns a new bitcoin address for receiving payments.
If an account is specified (recommended), the new address is added to the address book so payments received with the address will be credited to the given account.
If no account is specified, the address will be credited to the account whose name is the empty string. i.e. the default account.
getAccountAddress :: Client -> Account -> IO Address Source #
Returns the current Bitcoin address for receiving payments to the given account.
getAccount :: Client -> Address -> IO Account Source #
Returns the account associated with the given address.
setAccount :: Client -> Address -> Account -> IO () Source #
Sets the account associated with the given address.
getAddressesByAccount :: Client -> Account -> IO (Vector Address) Source #
Returns the list of addresses for the given address.
:: Client | |
-> Address | Who we're sending to. |
-> BTC | The amount to send. |
-> Maybe Text | An optional comment for the transaction. |
-> Maybe Text | An optional comment-to (who did we sent this to?) for the transaction. |
-> IO TransactionID |
Sends some bitcoins to an address.
data AddressInfo Source #
Information on a given address.
Instances
listAddressGroupings :: Client -> IO (Vector (Vector AddressInfo)) Source #
Lists groups of addresses which have had their common ownership made public by common use as inputs or as the resulting change in past transactions.
:: Client | |
-> Address | The address whose private key we'll use. |
-> Text | The message to sign. |
-> IO Signature |
Sign a message with the private key of an address.
:: Client | |
-> Address | The address of the original signer. |
-> Signature | The message's signature. |
-> Text | The message. |
-> IO Bool | Was the signature valid? |
Verifies a signed message.
getReceivedByAddress :: Client -> Address -> IO BTC Source #
Returns the total amount received by the given address with at least one confirmation.
getReceivedByAddress' Source #
:: Client | |
-> Address | |
-> Int | The minimum number of confirmations needed for a transaction to to count towards the total. |
-> IO BTC |
Returns the total amount received by the given address, with at least the give number of confirmations.
getReceivedByAccount :: Client -> Account -> IO BTC Source #
Returns the total amount received by address with the given account.
getReceivedByAccount' Source #
:: Client | |
-> Account | The account in question. |
-> Int | The minimum number of confirmations needed for a transaction to count towards the total. |
-> IO BTC |
Returns the total amount received by addresses with the given account, counting only transactions with the given minimum number of confirmations.
getBalance' :: Client -> Account -> IO BTC Source #
Returns the balance in the given account, counting only transactions with at least one confirmation.
:: Client | |
-> Account | |
-> Int | The minimum number of confirmations needed for a transaction to count towards the total. |
-> IO BTC |
Returns the balance in the given account, counting only transactions with at least the given number of confirmations.
:: Client | |
-> Account | From. |
-> Account | To. |
-> BTC | The amount to transfer. |
-> Text | A comment to record for the transaction. |
-> IO () |
Move bitcoins from one account in your wallet to another.
If you want to send bitcoins to an address not in your wallet, use
sendFromAccount
.
:: Client | |
-> Account | The account to send from. |
-> Address | The address to send to. |
-> BTC | The amount to send. |
-> Maybe Text | An optional transaction comment. |
-> Maybe Text | An optional comment on who the money is going to. |
-> IO TransactionID |
Sends bitcoins from a given account in our wallet to a given address.
A transaction and sender comment may be optionally provided.
:: Client | |
-> Account | The account to send from. |
-> Vector (Address, BTC) | The address, and how much to send to each one. |
-> Maybe Text | An optional transaction comment. |
-> IO TransactionID |
Send to a whole bunch of address at once.
data EstimationMode Source #
Possible fee estimation modes
Instances
Eq EstimationMode Source # | |
Defined in Network.Bitcoin.Wallet (==) :: EstimationMode -> EstimationMode -> Bool # (/=) :: EstimationMode -> EstimationMode -> Bool # | |
ToJSON EstimationMode Source # | |
Defined in Network.Bitcoin.Wallet toJSON :: EstimationMode -> Value # toEncoding :: EstimationMode -> Encoding # toJSONList :: [EstimationMode] -> Value # toEncodingList :: [EstimationMode] -> Encoding # |
estimateSmartFee :: Client -> Word32 -> Maybe EstimationMode -> IO Double Source #
Estimate the fee per kb to send a transaction
data ReceivedByAddress Source #
Information on how much was received by a given address.
ReceivedByAddress | |
|
Instances
listReceivedByAddress :: Client -> IO (Vector ReceivedByAddress) Source #
Lists the amount received by each address which has received money at some point, counting only transactions with at least one confirmation.
listReceivedByAddress' Source #
:: Client | |
-> Int | The minimum number of confirmations before a transaction counts toward the total amount received. |
-> Bool | Should we include addresses with no money received? |
-> IO (Vector ReceivedByAddress) |
List the amount received by each of our addresses, counting only transactions with the given minimum number of confirmations.
data ReceivedByAccount Source #
ReceivedByAccount | |
|
Instances
listReceivedByAccount :: Client -> IO (Vector ReceivedByAccount) Source #
Lists the amount received by each account which has received money at some point, counting only transactions with at leaset one confirmation.
listReceivedByAccount' Source #
:: Client | |
-> Int | The minimum number of confirmations before a transaction counts toward the total received. |
-> Bool | Should we include the accounts with no money received? |
-> IO (Vector ReceivedByAccount) |
List the amount received by each of our accounts, counting only transactions with the given minimum number of confirmations.
:: Client | |
-> Account | Limits the |
-> Int | Limits the number of |
-> Int | Number of most recent transactions to skip. |
-> IO (Vector SimpleTransaction) |
Returns transactions from the blockchain.
:: Client | |
-> Maybe Account | Limits the |
-> Maybe Int | Limits the number of |
-> Maybe Int | Number of most recent transactions to skip. |
-> IO (Vector SimpleTransaction) |
Returns transactions from the blockchain.
:: Client | |
-> Maybe Int | Minimum number of confirmations required before payments are included in the balance. |
-> IO (HashMap Account BTC) |
List accounts and their current balance.
:: Client | |
-> Address | Address to import |
-> Maybe Account | Optional account, default "" |
-> Maybe Bool | Optional rescan the blockchain, default true |
-> IO () |
Import an address
data SinceBlock Source #
Instances
Eq SinceBlock Source # | |
Defined in Network.Bitcoin.Wallet (==) :: SinceBlock -> SinceBlock -> Bool # (/=) :: SinceBlock -> SinceBlock -> Bool # | |
Ord SinceBlock Source # | |
Defined in Network.Bitcoin.Wallet compare :: SinceBlock -> SinceBlock -> Ordering # (<) :: SinceBlock -> SinceBlock -> Bool # (<=) :: SinceBlock -> SinceBlock -> Bool # (>) :: SinceBlock -> SinceBlock -> Bool # (>=) :: SinceBlock -> SinceBlock -> Bool # max :: SinceBlock -> SinceBlock -> SinceBlock # min :: SinceBlock -> SinceBlock -> SinceBlock # | |
Show SinceBlock Source # | |
Defined in Network.Bitcoin.Wallet showsPrec :: Int -> SinceBlock -> ShowS # show :: SinceBlock -> String # showList :: [SinceBlock] -> ShowS # | |
FromJSON SinceBlock Source # | |
Defined in Network.Bitcoin.Wallet parseJSON :: Value -> Parser SinceBlock # parseJSONList :: Value -> Parser [SinceBlock] # |
data SimpleTransaction Source #
Data type for simple transactions. Rules involving Maybe
are
indications of the most probable value only when the transaction is
obtained from listTransactions
or listSinceBlock
are their associated
methods. They are never enforced on this side.
SimpleTransaction | |
|
Instances
data TransactionCategory Source #
Instances
:: Client | |
-> BlockHash | The hash of the first block to list. |
-> Maybe Int | The minimum number of confirmations before a
transaction can be returned as |
-> IO SinceBlock |
Gets all transactions in blocks since the given block.
:: Client | |
-> Maybe BlockHash | The hash of the first block to list. |
-> Maybe Int | The minimum number of confirmations before a
transaction can be returned as |
-> IO SinceBlock |
Gets all transactions in blocks since the given block, or all transactions if ommited.
data DetailedTransaction Source #
Data type for detailed transactions. Rules involving trCategory
are
indications of the most probable value only when the transaction is
obtained from listTransactions
or listSinceBlock
are their associated
methods.
DetailedTransaction | |
|
Instances
data DetailedTransactionDetails Source #
DetailedTransactionDetails | |
|
Instances
backupWallet :: Client -> FilePath -> IO () Source #
Safely copies wallet.dat to the given destination, which can be either a directory, or a path with filename.
keyPoolRefill :: Client -> IO () Source #
Fills the keypool.
:: Client | |
-> Text | The decryption key. |
-> Integer | How long to store the key in memory (in seconds). |
-> IO () |
Stores the wallet decryption key in memory for the given amount of time.
lockWallet :: Client -> IO () Source #
Removes the wallet encryption key from memory, locking the wallet.
After calling this function, you will need to call unlockWallet
again
before being able to call methods which require the wallet to be unlocked.
Note: In future releases, we might introduce an "unlocked" monad, so locking and unlocking is automatic.
Changes the wallet passphrase.