haskoin-wallet-0.4.2: 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 OutputFormat Source #

Instances

ToJSON OutputFormat Source # 

Methods

toJSON :: OutputFormat -> Value

toEncoding :: OutputFormat -> Encoding

toJSONList :: [OutputFormat] -> Value

toEncodingList :: [OutputFormat] -> Encoding

FromJSON OutputFormat Source # 

Methods

parseJSON :: Value -> Parser OutputFormat

parseJSONList :: Value -> Parser [OutputFormat]

data Config Source #

Constructors

Config 

Fields

Instances

FromJSON Config Source # 

Methods

parseJSON :: Value -> Parser Config

parseJSONList :: Value -> Parser [Config]

Default Config Source # 

Methods

def :: Config

Server

data SPVMode Source #

Constructors

SPVOnline 
SPVOffline 

Instances

Eq SPVMode Source # 

Methods

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

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

Read SPVMode Source # 
Show SPVMode Source # 
ToJSON SPVMode Source # 

Methods

toJSON :: SPVMode -> Value

toEncoding :: SPVMode -> Encoding

toJSONList :: [SPVMode] -> Value

toEncodingList :: [SPVMode] -> Encoding

FromJSON SPVMode Source # 

Methods

parseJSON :: Value -> Parser SPVMode

parseJSONList :: Value -> Parser [SPVMode]

API JSON Types

data JsonAddr Source #

Constructors

JsonAddr 

Fields

Instances

API Request Types

data WalletRequest Source #

data OfflineTxData Source #

Instances

ToJSON OfflineTxData Source # 

Methods

toJSON :: OfflineTxData -> Value

toEncoding :: OfflineTxData -> Encoding

toJSONList :: [OfflineTxData] -> Value

toEncodingList :: [OfflineTxData] -> Encoding

FromJSON OfflineTxData Source # 

Methods

parseJSON :: Value -> Parser OfflineTxData

parseJSONList :: Value -> Parser [OfflineTxData]

data CoinSignData Source #

Constructors

CoinSignData 

Fields

data TxAction Source #

Instances

Eq TxAction Source # 
Show TxAction Source # 
ToJSON TxAction Source # 

Methods

toJSON :: TxAction -> Value

toEncoding :: TxAction -> Encoding

toJSONList :: [TxAction] -> Value

toEncodingList :: [TxAction] -> Encoding

FromJSON TxAction Source # 

Methods

parseJSON :: Value -> Parser TxAction

parseJSONList :: Value -> Parser [TxAction]

data TxType Source #

Constructors

TxIncoming 
TxOutgoing 
TxSelf 

Instances

Eq TxType Source # 

Methods

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

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

Read TxType Source # 
Show TxType Source # 
NFData TxType Source # 

Methods

rnf :: TxType -> () #

ToJSON TxType Source # 

Methods

toJSON :: TxType -> Value

toEncoding :: TxType -> Encoding

toJSONList :: [TxType] -> Value

toEncodingList :: [TxType] -> Encoding

FromJSON TxType Source # 

Methods

parseJSON :: Value -> Parser TxType

parseJSONList :: Value -> Parser [TxType]

PersistField TxType Source # 

Methods

toPersistValue :: TxType -> PersistValue

fromPersistValue :: PersistValue -> Either Text TxType

PersistFieldSql TxType Source # 

Methods

sqlType :: Proxy * TxType -> SqlType

data AddressInfo Source #

Instances

Eq AddressInfo Source # 
Read AddressInfo Source # 
Show AddressInfo Source # 
Generic AddressInfo Source # 

Associated Types

type Rep AddressInfo :: * -> * #

NFData AddressInfo Source # 

Methods

rnf :: AddressInfo -> () #

ToJSON AddressInfo Source # 

Methods

toJSON :: AddressInfo -> Value

toEncoding :: AddressInfo -> Encoding

toJSONList :: [AddressInfo] -> Value

toEncodingList :: [AddressInfo] -> Encoding

FromJSON AddressInfo Source # 

Methods

parseJSON :: Value -> Parser AddressInfo

parseJSONList :: Value -> Parser [AddressInfo]

Serialize AddressInfo Source # 

Methods

put :: Putter AddressInfo

get :: Get AddressInfo

PersistField [AddressInfo] Source # 

Methods

toPersistValue :: [AddressInfo] -> PersistValue

fromPersistValue :: PersistValue -> Either Text [AddressInfo]

PersistFieldSql [AddressInfo] Source # 

Methods

sqlType :: Proxy * [AddressInfo] -> SqlType

type Rep AddressInfo Source # 
type Rep AddressInfo = D1 (MetaData "AddressInfo" "Network.Haskoin.Wallet.Types" "haskoin-wallet-0.4.2-GGNJxNbZENWKcZl6t1mkyY" False) (C1 (MetaCons "AddressInfo" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "addressInfoAddress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Address)) ((:*:) (S1 (MetaSel (Just Symbol "addressInfoValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Word64))) (S1 (MetaSel (Just Symbol "addressInfoIsLocal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)))))

API Response Types

data WalletResponse a Source #

Constructors

ResponseError 

Fields

ResponseValid 

Fields

Instances

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

Methods

toJSON :: WalletResponse a0 -> Value

toEncoding :: WalletResponse a0 -> Encoding

toJSONList :: [WalletResponse a0] -> Value

toEncodingList :: [WalletResponse a0] -> Encoding

FromJSON a0 => FromJSON (WalletResponse a0) Source # 

Methods

parseJSON :: Value -> Parser (WalletResponse a0)

parseJSONList :: Value -> Parser [WalletResponse a0]

data ListResult a Source #

Constructors

ListResult 

Instances

ToJSON a0 => ToJSON (ListResult a0) Source # 

Methods

toJSON :: ListResult a0 -> Value

toEncoding :: ListResult a0 -> Encoding

toJSONList :: [ListResult a0] -> Value

toEncodingList :: [ListResult a0] -> Encoding

FromJSON a0 => FromJSON (ListResult a0) Source # 

Methods

parseJSON :: Value -> Parser (ListResult a0)

parseJSONList :: Value -> Parser [ListResult a0]

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 #

createWalletTx 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 #