haskoin-wallet-0.3.1: Implementation of a Bitcoin SPV Wallet with BIP32 and multisig support.

Safe HaskellNone
LanguageHaskell98

Network.Haskoin.Wallet

Contents

Description

This package provides a command line application called hw (haskoin wallet). It is a lightweight bitcoin wallet featuring BIP32 key management, deterministic signatures (RFC-6979) and first order support for multisignature transactions. A library API for hw is also exposed.

Synopsis

Client

data Config Source

Constructors

Config 

Fields

configCount :: !Word32

Output size of commands

configMinConf :: !Word32

Minimum number of confirmations

configSignTx :: !Bool

Sign transactions

configFee :: !Word64

Fee to pay per 1000 bytes when creating new transactions

configRcptFee :: !Bool

Recipient pays fee (dangerous, no config file setting)

configAddrType :: !AddressType

Return internal instead of external addresses

configOffline :: !Bool

Display the balance including offline transactions

configReversePaging :: !Bool

Use reverse paging for displaying addresses and transactions

configPath :: !(Maybe HardPath)

Derivation path when creating account

configFormat :: !OutputFormat

How to format the command-line results

configConnect :: !String

ZeroMQ socket to connect to (location of the server)

configConnectNotif :: !String

ZeroMQ socket to connect for notifications

configDetach :: !Bool

Detach server when launched from command-line

configFile :: !FilePath

Configuration file

configTestnet :: !Bool

Use Testnet3 network

configDir :: !FilePath

Working directory

configBind :: !String

Bind address for the ZeroMQ socket

configBindNotif :: !String

Bind address for ZeroMQ notifications

configBTCNodes :: !(HashMap Text [BTCNode])

Trusted Bitcoin full nodes to connect to

configMode :: !SPVMode

Operation mode of the SPV node.

configBloomFP :: !Double

False positive rate for the bloom filter.

configDatabase :: !(HashMap Text DatabaseConfType)

Database configuration

configLogFile :: !FilePath

Log file

configPidFile :: !FilePath

PID File

configLogLevel :: !LogLevel

Log level

configVerbose :: !Bool

Verbose

configServerKey :: !(Maybe (Restricted Div5 ByteString))

Server key for authentication and encryption (server config)

configServerKeyPub :: !(Maybe (Restricted Div5 ByteString))

Server public key for authentication and encryption (client config)

configClientKey :: !(Maybe (Restricted Div5 ByteString))

Client key for authentication and encryption (client config)

configClientKeyPub :: !(Maybe (Restricted Div5 ByteString))

Client public key for authentication and encryption (client + server config)

Instances

FromJSON Config Source 
Default Config Source 

Server

API JSON Types

data JsonAddr Source

Constructors

JsonAddr 

Fields

jsonAddrAddress :: !Address
 
jsonAddrIndex :: !KeyIndex
 
jsonAddrType :: !AddressType
 
jsonAddrLabel :: !Text
 
jsonAddrRedeem :: !(Maybe ScriptOutput)
 
jsonAddrKey :: !(Maybe PubKeyC)
 
jsonAddrCreated :: !UTCTime
 
jsonAddrBalance :: !(Maybe BalanceInfo)
 

API Request Types

data CoinSignData Source

Constructors

CoinSignData 

Fields

coinSignOutPoint :: !OutPoint
 
coinSignScriptOutput :: !ScriptOutput
 
coinSignDeriv :: !SoftPath
 

data TxType Source

Constructors

TxIncoming 
TxOutgoing 
TxSelf 

Instances

API Response Types

data WalletResponse a Source

Constructors

ResponseError 

Fields

responseError :: !Text
 
ResponseValid 

Fields

responseResult :: !(Maybe a)
 

Instances

Eq a => Eq (WalletResponse a) Source 
Show a => Show (WalletResponse a) Source 
FromJSON a0 => FromJSON (WalletResponse a) Source 
ToJSON a0 => ToJSON (WalletResponse a) Source 

data ListResult a Source

Constructors

ListResult 

Instances

FromJSON a0 => FromJSON (ListResult a) Source 
ToJSON a0 => ToJSON (ListResult a) Source 

Database Accounts

initWallet :: MonadIO m => Double -> SqlPersistT m () Source

accounts :: (MonadIO m, MonadThrow m, MonadBase IO m, MonadResource m) => ListRequest -> SqlPersistT m ([Account], Word32) Source

Fetch all accounts

newAccount :: (MonadIO m, MonadThrow m, MonadBase IO m, MonadResource m) => NewAccount -> SqlPersistT m (Entity Account, Maybe Mnemonic) Source

Create a new account

addAccountKeys Source

Arguments

:: (MonadIO m, MonadThrow m, MonadBase IO m, MonadResource m) 
=> Entity Account

Account Entity

-> [XPubKey]

Thirdparty public keys to add

-> SqlPersistT m Account

Account information

Add new thirdparty keys to a multisignature account. This function can fail if the multisignature account already has all required keys.

getAccount :: (MonadIO m, MonadThrow m) => AccountName -> SqlPersistT m (Entity Account) Source

Database Addresses

getAddress Source

Arguments

:: (MonadIO m, MonadThrow m) 
=> Entity Account

Account Entity

-> AddressType

Address type

-> KeyIndex

Derivation index (key)

-> SqlPersistT m (Entity WalletAddr)

Address

Get an address if it exists, or throw an exception otherwise. Fetching addresses in the hidden gap will also throw an exception.

addressesAll :: (MonadIO m, MonadThrow m, MonadBase IO m, MonadResource m) => SqlPersistT m [WalletAddr] Source

All addresses in the wallet, including hidden gap addresses. This is useful for building a bloom filter.

addresses Source

Arguments

:: (MonadIO m, MonadThrow m, MonadBase IO m, MonadResource m) 
=> Entity Account

Account Entity

-> AddressType

Address Type

-> SqlPersistT m [WalletAddr]

Addresses

All addresses in one account excluding hidden gap.

addressList Source

Arguments

:: MonadIO m 
=> Entity Account

Account Entity

-> AddressType

Address type

-> ListRequest

List request

-> SqlPersistT m ([WalletAddr], Word32)

List result

Get address list.

unusedAddresses Source

Arguments

:: MonadIO m 
=> Entity Account

Account ID

-> AddressType

Address type

-> ListRequest 
-> SqlPersistT m ([WalletAddr], Word32)

Unused addresses

Get a list of all unused addresses.

addressCount Source

Arguments

:: MonadIO m 
=> Entity Account

Account Entity

-> AddressType

Address type

-> SqlPersistT m Word32

Address Count

Get a count of all the addresses in an account

setAddrLabel Source

Arguments

:: (MonadIO m, MonadThrow m) 
=> Entity Account

Account ID

-> KeyIndex

Derivation index

-> AddressType

Address type

-> Text

New label

-> SqlPersistT m WalletAddr 

Add a label to an address.

addressPrvKey Source

Arguments

:: (MonadIO m, MonadThrow m) 
=> Entity Account

Account Entity

-> Maybe XPrvKey

If not in account

-> KeyIndex

Derivation index of the address

-> AddressType

Address type

-> SqlPersistT m PrvKeyC

Private key

Returns the private key of an address.

useAddress :: (MonadIO m, MonadThrow m, MonadBase IO m, MonadResource m) => WalletAddr -> SqlPersistT m [WalletAddr] Source

Use an address and make sure we have enough gap addresses after it. Returns the new addresses that have been created.

setAccountGap Source

Arguments

:: (MonadIO m, MonadThrow m, MonadBase IO m, MonadResource m) 
=> Entity Account

Account Entity

-> Word32

New gap value

-> SqlPersistT m (Entity Account) 

Set the address gap of an account to a new value. This will create new internal and external addresses as required. The gap can only be increased, not decreased in size.

firstAddrTime :: MonadIO m => SqlPersistT m (Maybe Timestamp) Source

getPathRedeem :: Account -> SoftPath -> RedeemScript Source

getPathPubKey :: Account -> SoftPath -> PubKeyC Source

Database Bloom Filter

getBloomFilter :: (MonadIO m, MonadThrow m) => SqlPersistT m (BloomFilter, Int, Double) Source

Returns a bloom filter containing all the addresses in this wallet. This includes internal and external addresses. The bloom filter can be set on a peer connection to filter the transactions received by that peer.

Database transactions

txs Source

Arguments

:: MonadIO m 
=> Maybe TxConfidence 
-> AccountId

Account ID

-> ListRequest

List request

-> SqlPersistT m ([WalletTx], Word32)

List result

Get transactions.

addrTxs Source

Arguments

:: MonadIO m 
=> Entity Account

Account entity

-> Entity WalletAddr

Address entity

-> ListRequest

List request

-> SqlPersistT m ([WalletTx], Word32) 

getTx :: MonadIO m => TxHash -> SqlPersistT m (Maybe Tx) Source

getAccountTx :: MonadIO m => AccountId -> TxHash -> SqlPersistT m WalletTx Source

importTx Source

Arguments

:: (MonadIO m, MonadThrow m, MonadBase IO m, MonadResource m) 
=> Tx

Transaction to import

-> Maybe (TBMChan Notif) 
-> AccountId

Account ID

-> SqlPersistT m ([WalletTx], [WalletAddr])

New transactions and addresses created

Import a transaction into the wallet from an unknown source. If the transaction is standard, valid, all inputs are known and all inputs can be spent, then the transaction will be imported as a network transaction. Otherwise, the transaction will be imported into the local account as an offline transaction.

importNetTx Source

Arguments

:: (MonadIO m, MonadThrow m, MonadBase IO m, MonadResource m) 
=> Tx 
-> Maybe (TBMChan Notif) 
-> SqlPersistT m ([WalletTx], [WalletAddr])

Returns the new transactions and addresses created

Import a transaction from the network into the wallet. This function assumes transactions are imported in-order (parents first). It also assumes that the confirmations always arrive after the transaction imports. This function is idempotent.

When re-importing an existing transaction, this function will recompute the inputs, outputs and transaction details for each account. A non-dead transaction could be set to dead due to new inputs being double spent. However, we do not allow dead transactions to be revived by reimporting them. Transactions can only be revived if they make it into the main chain.

This function returns the network confidence of the imported transaction.

signAccountTx :: (MonadIO m, MonadThrow m, MonadBase IO m, MonadResource m) => Entity Account -> Maybe (TBMChan Notif) -> Maybe XPrvKey -> TxHash -> SqlPersistT m ([WalletTx], [WalletAddr]) Source

createTx Source

Arguments

:: (MonadIO m, MonadThrow m, MonadBase IO m, MonadResource m) 
=> Entity Account

Account Entity

-> Maybe (TBMChan Notif)

Notification channel

-> Maybe XPrvKey

Key if not provided by account

-> [(Address, Word64)]

List of recipient addresses and amounts

-> Word64

Fee per 1000 bytes

-> Word32

Minimum confirmations

-> Bool

Should fee be paid by recipient

-> Bool

Should the transaction be signed

-> SqlPersistT m (WalletTx, [WalletAddr])

(New transaction hash, Completed flag)

Create a transaction sending some coins to a list of recipient addresses.

signOfflineTx Source

Arguments

:: Account

Account used for signing

-> Maybe XPrvKey

Key if not provided in account

-> Tx

Transaction to sign

-> [CoinSignData]

Input signing data

-> Tx 

getOfflineTxData :: (MonadIO m, MonadThrow m, MonadBase IO m, MonadResource m) => AccountId -> TxHash -> SqlPersistT m (OfflineTxData, [InCoinData]) Source

Database blocks

importMerkles :: MonadIO m => BlockChainAction -> [MerkleTxs] -> Maybe (TBMChan Notif) -> SqlPersistT m () Source

walletBestBlock :: MonadIO m => SqlPersistT m (BlockHash, Word32) Source

Database coins and balances

spendableCoins Source

Arguments

:: (MonadIO m, MonadThrow m, MonadBase IO m, MonadResource m) 
=> AccountId

Account key

-> Word32

Minimum confirmations

-> (SqlExpr (Entity WalletCoin) -> SqlExpr (Entity WalletTx) -> [SqlExpr OrderBy])

Coin ordering policy

-> SqlPersistT m [InCoinData]

Spendable coins

accountBalance :: MonadIO m => AccountId -> Word32 -> Bool -> SqlPersistT m Word64 Source

addressBalances :: MonadIO m => Entity Account -> KeyIndex -> KeyIndex -> AddressType -> Word32 -> Bool -> SqlPersistT m [(KeyIndex, BalanceInfo)] Source

Rescan

resetRescan :: MonadIO m => SqlPersistT m () Source