bitcoin-hs-0.0.1: Partial implementation of the Bitcoin protocol (as of 2013)

Safe HaskellNone
LanguageHaskell98

Bitcoin.RPC.API

Contents

Description

bitcoind API access (via JSON-RPC over HTTP calls)

See https://en.bitcoin.it/wiki/Original_Bitcoin_client/API_calls_list

Synopsis

Documentation

type Account = String Source #

An account in the Satoshi client wallet

type Node = String Source #

A network node

type TxId = Hash256 Source #

A transaction id

type Key = Either PubKey Address Source #

A public key

type MinConf = Maybe Int Source #

Minimum number of confirmations (default is usually 1)

type RedeemScript = RawScript Source #

A redeem script for a multi-sig address

client info

getClientInfo :: Call ClientInfo Source #

Returns an object containing various state info.

getConnectionCount :: Call Int Source #

Returns the number of connections to other nodes

stopClient :: Call () Source #

Stops the bitcoin client

blockchain info

getDifficulty :: Call Double Source #

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

getBlockCount :: Call Int Source #

Returns the number of blocks in the longest block chain.

getBlockHash :: Int -> Call Hash256 Source #

Returns hash of block in best-block-chain at <index> transaction info

getBlockInfo :: Hash256 -> Call BlockInfo Source #

Returns information about the given block hash.

transaction info

getWalletTransaction :: TxId -> Call TxInfo Source #

Returns an object about the given transaction. Note: this only works for the transaction in the wallet. For transactions out in the blockchain, use "getRawTransaction" or "getTransactionInfo"

data ScriptSigVerbose Source #

A scriptSig as returned by "getrawtransaction" (verbose=1) API call

Constructors

ScriptSigVerbose 

Fields

data TxVIn Source #

A transaction input as returned by "getrawtransaction" (verbose=1) API call

Constructors

TxVIn 

Fields

Instances

Eq TxVIn Source # 

Methods

(==) :: TxVIn -> TxVIn -> Bool #

(/=) :: TxVIn -> TxVIn -> Bool #

Show TxVIn Source # 

Methods

showsPrec :: Int -> TxVIn -> ShowS #

show :: TxVIn -> String #

showList :: [TxVIn] -> ShowS #

data ScriptPubKeyVerbose Source #

A scriptPubKey as returned by "getrawtransaction" (verbose=1) API call

Constructors

ScriptPubKeyVerbose 

Fields

data TxVOut Source #

A transaction output as returned by "getrawtransaction" (verbose=1) API call

Instances

data TxVerbose Source #

A transaction as decoded by the "decoderawtransaction" API call

Constructors

TxVerbose 

Fields

data TxVerboseEx Source #

A transaction as reported by the "getrawtransaction" (verbose=1) API call

Constructors

TxVerboseEx 

Fields

getRawTransaction :: TxId -> Call RawTx Source #

"getrawtransaction", verbose=0. Version 0.7. Returns raw transaction representation for given transaction id.

WARNING! Important note from the version 0.8 readme:

"This release no longer maintains a full index of historical transaction ids by default, so looking up an arbitrary transaction using the getrawtransaction RPC call will not work. If you need that functionality, you must run once with -txindex=1 -reindex=1 to rebuild block-chain indices (see below for more details)."

getTransactionInfo :: TxId -> Call TxVerboseEx Source #

"getrawtransaction", verbose=1. Version 0.7. Returns transaction representation for given transaction id, in human-understandable format.

wallet info

dumpPrivKeyWIF :: Address -> Call WIF Source #

Reveals the private key corresponding to <bitcoinaddress>. NOTE: Wallet needs to be unlocked!

dumpPrivPubKey :: Address -> Call (PrivKey, PubKey) Source #

We decode the WIF and also compute the corresponding public key for convenience.

getBalance :: Maybe Account -> MinConf -> Call Amount Source #

If [account] is not specified, returns the server's total available balance. MinConf = Maybe Int is the number of minimum confirmations (default is 1)

getAccountAddress :: Account -> Call Address Source #

Returns the current bitcoin address for receiving payments to this account.

getAddressesByAccount :: Account -> Call [Address] Source #

Returns the list of addresses for the given account.

getAccount :: Address -> Call Account Source #

Returns the account associated with the given address.

listAccounts :: MinConf -> Call [(Account, Amount)] Source #

Returns a list of pairs that has account names as keys, account balances as values. Maybe Int is number of minimal confirmations (default is 1)

listAddressGroupings :: Call JSValue Source #

version 0.7 Returns all addresses in the wallet and info used for coincontrol.

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.

listReceivedByAccount :: MinConf -> Bool -> Call [Received] Source #

Bool is "includeempty". Returns an array of objects containing: "account", "amount", "confirmations"

listReceivedByAddress :: MinConf -> Bool -> Call [Received] Source #

Returns an array of objects containing: "address", "account", "amount", "confirmations".

To get a list of accounts on the system, execute bitcoind listreceivedbyaddress 0 true

data Unspent Source #

An unspent transactions as returned by the "listunspent" API call

Constructors

Unspent 

Fields

listUnspent :: MinConf -> MaxConf -> Call [Unspent] Source #

Returns an array of unspent transaction outputs in the wallet that have between minconf and maxconf (inclusive) confirmations. Each output is a 5-element object with keys: txid, output, scriptPubKey, amount, confirmations. txid is the hexadecimal transaction id, output is which output of that transaction, scriptPubKey is the hexadecimal-encoded CScript for that output, amount is the value of that output and confirmations is the transaction's depth in the chain.

Minimum confirmations default is 1 and maximum confirmation default is 999999.

network info

getRawMemPool :: Call [TxId] Source #

version 0.7: Returns all transaction ids in memory pool

multi-sig

addMultiSigAddress :: Int -> [Key] -> Maybe Account -> Call Address Source #

Add a n-required-to-sign multisignature address to the wallet. Each key is a bitcoin address or hex-encoded public key. If [account] is specified, assign address to [account].

createMultiSig :: Int -> [Key] -> Call (Address, RedeemScript) Source #

Creates a multi-signature address and returns a json object.

sending coins

sendFrom :: Account -> Address -> Amount -> MinConf -> Maybe String -> Maybe String -> Call TxId Source #

Send coins from an account to an address

<fromaccount> <tobitcoinaddress> <amount> [minconf=1] [comment] [comment-to]. 

Will send the given amount to the given address, ensuring the account has a valid balance using [minconf] confirmations. Returns the transaction ID if successful (not in JSON object). NOTE: Wallet needs to be unlocked!

"comment" is the transaction comment, and "comment-to" is a local comment: a reminder that who did we sent the coins to? (?)

sendMany :: Account -> [(Address, Amount)] -> MinConf -> Maybe String -> Call TxId Source #

Send coins from an account to many addresses NOTE: Wallet needs to be unlocked!

sendRawTransaction :: RawTx -> Call () Source #

version 0.7. Submits raw transaction (serialized, hex-encoded) to local node and network.

sendToAddress :: Address -> Amount -> Maybe String -> Maybe String -> Call TxId Source #

<bitcoinaddress> <amount> [comment] [comment-to]

moveCoins :: Account -> Account -> Amount -> MinConf -> Maybe String -> Call () Source #

Move from one account in your wallet to another

<fromaccount> <toaccount> <amount> [minconf=1] [comment]. 

setTxFee :: Amount -> Call () Source #

Sets the transaction fee

wallet operations

importPrivKey :: (PubKeyFormat, PrivKey) -> Maybe String -> Bool -> Call () Source #

Adds a private key (as returned by dumpprivkey) to your wallet. The second argument is an optional label (account???). This may take a while, as a rescan is done, looking for existing transactions. Optional [rescan] parameter added in 0.8.0. NOTE: Wallet needs to be unlocked!

importPrivKeyWIF :: WIF -> Maybe String -> Bool -> Call () Source #

Imports a private key given as WIF (Wallet Import Format).

getNewAddress :: Maybe Account -> Call Address Source #

Returns a new bitcoin address for receiving payments. If [account] is specified (recommended), it is added to the address book so payments received with the address will be credited to [account].

setAccount :: Address -> Account -> Call () Source #

Sets the account associated with the given address. Assigning address that is already assigned to the same account will create a new address associated with that account.

keyPoolRefill :: Call () Source #

Fills the keypool, requires wallet passphrase to be set. NOTE: Wallet needs to be unlocked!

backupWallet :: FilePath -> Call () Source #

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

walletLock :: Call () Source #

Removes the wallet encryption key from memory, locking the wallet. After calling this method, you will need to call walletpassphrase again before being able to call any methods which require the wallet to be unlocked.

walletPassPhrase :: PassPhrase -> Int -> Call () Source #

Stores the wallet decryption key in memory for <timeout> seconds.

walletPassPhraseChange :: PassPhrase -> PassPhrase -> Call () Source #

Changes the wallet passphrase from <oldpassphrase> to <newpassphrase>.

encryptWallet :: PassPhrase -> Call () Source #

Encrypts the wallet with <passphrase>.