network-bitcoin-1.5.2: An interface to bitcoind.

Safe HaskellNone

Network.Bitcoin

Contents

Description

A Haskell binding to the bitcoind server.

Synopsis

Common Types

data Auth Source

Auth describes authentication credentials for making API requests to the Bitcoin daemon.

Constructors

Auth 

Fields

rpcUrl :: Text

URL, with port, where bitcoind listens

rpcUser :: Text

same as bitcoind's rpcuser config

rpcPassword :: Text

same as bitcoind's rpcpassword config

Instances

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.

Constructors

BitcoinApiError Int Text

A BitcoinApiError has an error code error message, as returned by bitcoind's JSON-RPC response.

BitcoinResultTypeError ByteString

The raw JSON returned, if we can't figure out what actually went wrong.

type HexString = TextSource

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 = HexStringSource

A hexadecimal string representation of a 256-bit unsigned integer.

This integer is a unique transaction identifier.

data Satoshi Source

A satoshi is the smallest subdivision of bitcoins. For the resolution, use resolution from Fixed.

Constructors

Satoshi 

type BTC = Fixed SatoshiSource

The type of bitcoin money, represented with a fixed-point number.

type Account = TextSource

An account on the wallet is just a label to easily specify private keys.

The default account is an empty string.

type Address = HexStringSource

An address for sending or receiving money.

Block Chain Operations

getBlockCount :: Auth -> IO IntegerSource

Returns the number of blocks in the longest block chain.

getDifficulty :: Auth -> IO IntegerSource

Returns the proof-of-work difficulty as a multiple of the minimum difficulty.

setTransactionFee :: Auth -> BTC -> IO ()Source

Sets the transaction fee will will pay to the network. Values of 0 are rejected.

getRawMemoryPool :: Auth -> IO (Vector TransactionID)Source

Returns all transaction identifiers in the memory pool.

type BlockHash = HexStringSource

The hash of a given block.

getBlockHashSource

Arguments

:: Auth 
-> Integer

Block index.

-> IO BlockHash 

Returns the hash of the block in best-block-chain at the given index.

data Block Source

Information about a given block in the block chain.

Constructors

Block 

Fields

blockHash :: BlockHash
 
blkConfirmations :: Integer

The number of confirmations the block has.

blkSize :: Integer

The size of the block.

blkHeight :: Integer

The height of the block. TODO: Clarify this.

blkVersion :: Integer

The version of the block.

merkleRoot :: BlockHash

The hash of the block at the root of the merkle tree which this block belongs to.

subTransactions :: Vector TransactionID

Should this be a transaction, or transaction id?

blkTime :: Integer

The time it was mined.

blkNonce :: Integer

The block's nonce.

blkBits :: HexString
 
blkDifficulty :: Integer

How hard was this block to mine?

nextBlock :: Maybe BlockHash

A pointer to the next block in the chain.

prevBlock :: Maybe BlockHash

A pointer to the previous block in the chain.

getBlock :: Auth -> BlockHash -> IO BlockSource

Returns details of a block with given block-hash.

data OutputSetInfo Source

Information on the unspent transaction in the output set.

Constructors

OutputSetInfo 

Fields

osiBestBlock :: BlockHash
 
numTransactions :: Integer

The number of transactions in the output set.

transactionOutputs :: Integer

The number of outputs for the transactions.

serializedSize :: Integer

The serialized size of the output set.

getOutputSetInfo :: Auth -> IO OutputSetInfoSource

Returns statistics about the unspent transaction output set.

data OutputInfo Source

Details about an unspent transaction output.

Constructors

OutputInfo 

Fields

oiBestBlock :: BlockHash
 
oiConfirmations :: Integer

The number of times this transaction has been confirmed.

oiAmount :: BTC

The amount transferred.

oiScriptPubKey :: ScriptPubKey

The public key of the sender.

oiVersion :: Integer

The version of this transaction.

oiCoinBase :: Bool

Is this transaction part of the coin base?

getOutputInfoSource

Arguments

:: Auth 
-> TransactionID 
-> Integer

The index we're looking at.

-> IO OutputInfo 

Returns details about an unspent transaction output.

Private Key Operations

importPrivateKeySource

Arguments

:: Auth 
-> PrivateKey 
-> Maybe Account

An optional label for the key.

-> IO () 

Adds a private key (as returned by dumpprivkey) to your wallet.

dumpPrivateKey :: Auth -> Address -> IO PrivateKeySource

Reveals the private key corresponding to the given address.

Mining Operations

getGenerateSource

Arguments

:: Auth

bitcoind RPC authorization

-> IO Bool 

Returns whether or not bitcoind is generating bitcoins.

setGenerateSource

Arguments

:: Auth

bitcoind RPC authorization

-> 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.

-> IO () 

Controls whether or not bitcoind is generating bitcoins.

getHashesPerSec :: Auth -> IO IntegerSource

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.

Constructors

MiningInfo 

Fields

nBlocks :: Integer

The number of blocks in our block-chain.

currentBlockSize :: Integer

The size of the current block we're mining.

currentBlockTransaction :: Integer
 
difficulty :: Double

How difficult mining currently is.

miningErrors :: Text

Any mining errors that may have come up.

isGenerating :: Bool

Are we currently generating bitcoins?

generationProcessorLimit :: Integer

How many processors have we limited bitcoin mining to?

hashesPerSecond :: Integer

How fast is the mining going?

pooledTransactions :: Integer
 
miningOnTestNetwork :: Bool

Are we on the bitcoin test network (as opposed to the real thing)?

getMiningInfo :: Auth -> IO MiningInfoSource

Returns an object containing mining-related information.

data HashData Source

The hash data returned from getWork.

Constructors

HashData 

Fields

blockData :: HexString
 
hdTarget :: HexString

Little-endian hash target, formatted as a hexadecimal string.

hash1 :: HexString
 
midstate :: HexString
 

getWork :: Auth -> IO HashDataSource

Returns formatted hash data to work on.

solveBlock :: Auth -> HexString -> IO BoolSource

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.

data BlockTemplate Source

A template for constructing a block to work on.

See https://en.bitcoin.it/wiki/BIP_0022 for the full specification.

Constructors

BlockTemplate 

Fields

blockVersion :: Integer
 
previousBlockHash :: HexString

Hash of current highest block.

transactionsToInclude :: Vector Transaction

Contents of non-coinbase transactions that should be included in the next block.

coinBaseAux :: CoinBaseAux

Data that should be included in coinbase.

coinBaseValue :: Integer

Maximum allowable input to coinbase transaction, including the generation award and transaction fees.

btTarget :: HexString

Hash target.

minTime :: Integer

Minimum timestamp appropriate for next block.

nonceRange :: HexString

Range of valid nonces.

sigopLimit :: Integer

Limit of sigops in blocks.

sizeLimit :: Integer

Limit of block size.

curTime :: Integer

Current timestamp.

btBits :: HexString

Compressed target of the next block.

btHeight :: Integer

Height of the next block.

getBlockTemplate :: Auth -> IO BlockTemplateSource

Returns data needed to construct a block to work on.

submitBlockSource

Arguments

:: Auth 
-> HexString

The block to submit.

-> IO Bool

Was the block accepted by the network?

Attempts to submit a new block to the network.

Network Operations

getConnectionCount :: Auth -> IO IntegerSource

Returns the number of connections to other nodes.

data PeerInfo Source

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!

Constructors

PeerInfo 

Fields

addressName :: Text

The IP:port of this peer, as a string.

services :: Text
 
lastSend :: Integer

Relative to the first time we conected with this peer (and in milliseconds), the last time we sent this peer any data.

lastRecv :: Integer

Relative to the first time we connected with this peer (and in milliseconds), the last time we sent this peer any data.

bytesSent :: Integer
 
bytesRecv :: Integer
 
connectionTime :: Integer

How long have we been connected to this peer (in milliseconds).

peerVersion :: Integer

The version of the Bitcion client the peer is running.

peerSubversion :: Text

The sub-version of the Bitcoin client the peer is running.

inbound :: Bool
 
startingHeight :: Integer
 
banScore :: Integer

How many times has this peer behaved badly?

getPeerInfo :: Auth -> IO [PeerInfo]Source

Returns data about all connected peer nodes.

Raw Transaction Operations

type RawTransaction = HexStringSource

Just like most binary data retrieved from bitcoind, a raw transaction is represented by a hexstring.

This is a serialized, hex-encoded transaction.

getRawTransaction :: Auth -> TransactionID -> IO RawTransactionSource

Get a raw transaction from its unique ID.

data TxIn Source

A transaction into an account. This can either be a coinbase transaction, or a standard transaction with another account.

Constructors

TxCoinbase 
TxIn 

Fields

txInId :: TransactionID

This transaction's ID.

numOut :: Integer
 
scriptSig :: ScriptSig
 
txSequence :: Integer

A transaction sequence number.

data TxnOutputType Source

The type of a transaction out.

More documentation is needed here. Submit a patch if you know what this is about!

Constructors

TxnPubKey

JSON of pubkey received.

TxnPubKeyHash

JSON of pubkeyhash received.

TxnScriptHash

JSON of scripthash received.

TxnMultisig

JSON of multisig received.

data ScriptPubKey Source

A public key of someone we sent money to.

Constructors

NonStandardScriptPubKey 

Fields

nspkAsm :: HexString

The JSON asm field.

nspkHex :: HexString

The JSON hex field.

StandardScriptPubKey 

Fields

sspkAsm :: HexString

The JSON asm field.

sspkHex :: HexString

The JSON hex field.

requiredSigs :: Integer

The number of required signatures.

sspkType :: TxnOutputType

The type of the transaction.

sspkAddresses :: Vector Address

The addresses associated with this key.

data TxOut Source

A transaction out of an account.

Constructors

TxOut 

Fields

txoutVal :: BTC

The amount of bitcoin transferred out.

scriptPubKey :: ScriptPubKey

The public key of the account we sent the money to.

data BlockInfo Source

Information on a single block.

Constructors

ConfirmedBlock 

Fields

confirmations :: Integer

The number of confirmations a block has. This will always be >= 1.

cbTime :: Integer
 
blockTime :: Integer

The JSON blocktime field.

UnconfirmedBlock

An unconfirmed block is boring, but a possibility.

data RawTransactionInfo Source

The raw transaction info for a given transaction ID.

Constructors

RawTransactionInfo 

Fields

raw :: RawTransaction

The raw transaction.

txnVersion :: Integer

The transaction version number.

txnLockTime :: Integer
 
vin :: Vector TxIn

The vector of transactions in.

vout :: Vector TxOut

The vector of transactions out.

rawTxBlockHash :: HexString

The hash of the block that was used for this transaction.

rawBlockInfo :: BlockInfo

The transaction's block's info.

getRawTransactionInfo :: Auth -> TransactionID -> IO RawTransactionInfoSource

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.

listUnspentSource

Arguments

:: Auth 
-> Maybe Int

minconf. Defaults to 1 if Nothing.

-> Maybe Int

maxconf. Defaults to 9999999 if Nothing.

-> Vector Address

Use empty for no filtering.

-> 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.

createRawTransactionSource

Arguments

:: Auth 
-> 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.

Constructors

DecodedRawTransaction 

Fields

decRaw :: RawTransaction

The raw transaction.

decTxnVersion :: Integer

The transaction version number.

decTxnLockTime :: Integer
 
decVin :: Vector TxIn

The vector of transactions in.

decVout :: Vector TxOut

The vector of transactions out.

decodeRawTransaction :: Auth -> RawTransaction -> IO DecodedRawTransactionSource

Decodes a raw transaction into a more accessible data structure.

data WhoCanPay Source

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.

signRawTransactionSource

Arguments

:: Auth 
-> 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? All by default.

-> IO RawSignedTransaction

Returns Nothing if the transaction has a complete set of signatures, and the raw signed transa

Sign inputs for a raw transaction.

Wallet Operations

data BitcoindInfo Source

A plethora of information about a bitcoind instance.

Constructors

BitcoindInfo 

Fields

bitcoinVersion :: Integer

What version of bitcoind are we running?

protocolVersion :: Integer

What is bitcoind's current protocol number?

walletVersion :: Integer

What version is the wallet?

balance :: BTC

How much money is currently in the wallet?

numBlocks :: Integer

The number of blocks in our chain.

numConnections :: Integer

How many peers are we connected to?

proxy :: Text

A blank string if we're not using a proxy.

generationDifficulty :: Double

The difficulty multiplier for bitcoin mining operations.

onTestNetwork :: Bool

Are we on the test network (as opposed to the primary bitcoin network)?

keyPoolOldest :: Integer

The timestamp of the oldest key in the key pool.

keyPoolSize :: Integer

The size of the key pool.

transactionFeePaid :: BTC

How much do we currently pay as a transaction fee?

unlockedUntil :: Maybe Integer

If the wallet is unlocked, the number of seconds until a re-lock is needed.

bitcoindErrors :: Text

Any alerts will show up here. This should normally be an empty string.

getBitcoindInfo :: Auth -> IO BitcoindInfoSource

Returns an object containing various state info.

getNewAddress :: Auth -> Maybe Account -> IO AddressSource

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 :: Auth -> Account -> IO AddressSource

Returns the current Bitcoin address for receiving payments to the given account.

getAccount :: Auth -> Address -> IO AccountSource

Returns the account associated with the given address.

setAccount :: Auth -> Address -> Account -> IO ()Source

Sets the account associated with the given address.

getAddressesByAccount :: Auth -> Account -> IO (Vector Address)Source

Returns the list of addresses for the given address.

sendToAddressSource

Arguments

:: Auth 
-> 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.

Constructors

AddressInfo 

Fields

aiAddress :: Address

The address in question.

aiAmount :: BTC

The address' balance.

aiAccount :: Maybe Account

The address' linked account.

listAddressGroupings :: Auth -> 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.

type Signature = HexStringSource

A signature is a base-64 encoded string.

signMessageSource

Arguments

:: Auth 
-> 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.

verifyMessageSource

Arguments

:: Auth 
-> 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 :: Auth -> Address -> IO BTCSource

Returns the total amount received by the given address with at least one confirmation.

getReceivedByAddress'Source

Arguments

:: Auth 
-> 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 :: Auth -> Account -> IO BTCSource

Returns the total amount received by address with the given account.

getReceivedByAccount'Source

Arguments

:: Auth 
-> 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 :: Auth -> IO BTCSource

Returns the server's total available balance.

getBalance' :: Auth -> Account -> IO BTCSource

Returns the balance in the given account, counting only transactions with at least one confirmation.

getBalance''Source

Arguments

:: Auth 
-> 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.

moveBitcoinsSource

Arguments

:: Auth 
-> 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.

sendFromAccountSource

Arguments

:: Auth 
-> 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.

sendManySource

Arguments

:: Auth 
-> 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 ReceivedByAddress Source

Information on how much was received by a given address.

Constructors

ReceivedByAddress 

Fields

recvAddress :: Address

The address which the money was deposited to.

recvAccount :: Account

The account which this address belongs to.

recvAmount :: BTC

The amount received.

recvNumConfirmations :: Integer

The number of confirmations of the most recent included transaction.

listReceivedByAddress :: Auth -> 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

Arguments

:: Auth 
-> 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

Constructors

ReceivedByAccount 

Fields

raccAccount :: Account

The account we received into.

raccAmount :: BTC

The mount received. ^ The number of confirmations of the most recent included transaction.

raccNumConfirmations :: Integer
 

listReceivedByAccount :: Auth -> 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

Arguments

:: Auth 
-> 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.

data SinceBlockTransaction Source

Constructors

SinceBlockTransaction 

Fields

sbtReceivingAccount :: Account

The account associated with the receiving address.

sbtAddress :: Address

The receiving address of the transaction.

sbtCategory :: TransactionCategory

The category of the transaction (As of 0.8.6 this field can be send,orphan,immature,generate,receive,move).

sbtAmountBitcoin :: BTC

The amount of bitcoins transferred.

sbtConfirmations :: Integer

The number of confirmation of the transaction.

sbtBlockHash :: BlockHash

The hash of the block containing the transaction.

sbtBlockIndex :: Integer
 
sbtBlockTime :: Double
 
sbtTransactionId :: TransactionID
 
sbtWalletConflicts :: Vector TransactionID

The list of transaction ids containing the same data as the original transaction (See ID-malleation bug).

sbtTime :: Integer
 
sbtTimeReceived :: Integer
 

listSinceBlockSource

Arguments

:: Auth 
-> BlockHash 
-> Maybe Int

The minimum number of confirmations before a transaction counts toward the total received.

-> IO SinceBlock 

backupWallet :: Auth -> FilePath -> IO ()Source

Safely copies wallet.dat to the given destination, which can be either a directory, or a path with filename.

keyPoolRefill :: Auth -> IO ()Source

Fills the keypool.

unlockWalletSource

Arguments

:: Auth 
-> 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 :: Auth -> 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.

changePasswordSource

Arguments

:: Auth 
-> Text

The old password.

-> Text

The new password.

-> IO () 

Changes the wallet passphrase.

encryptWallet :: Auth -> Text -> IO ()Source

Encrypts the wallet with the given passphrase.

WARNING: bitcoind will shut down after calling this method. Don't say I didn't warn you.

isAddressValid :: Auth -> Address -> IO BoolSource

Checks if a given address is a valid one.