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

Safe HaskellNone
LanguageHaskell98

Network.Haskoin.Wallet.Internals

Contents

Description

This module expose haskoin-wallet internals. No guarantee is made on the stability of the interface of these internal modules.

Synopsis

Documentation

Database Wallet

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

Database Accounts

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

renameAccount :: (MonadIO m, MonadThrow m, MonadBase IO m, MonadResource m) => Entity Account -> AccountName -> SqlPersistT m Account Source

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.

generateAddrs :: (MonadIO m, MonadThrow m, MonadBase IO m, MonadResource m) => Entity Account -> AddressType -> KeyIndex -> SqlPersistT m Int Source

Generate all the addresses up to certain index.

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.

Helpers

subSelectAddrCount :: Entity Account -> AddressType -> SqlExpr (Value KeyIndex) Source

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) 

accTxsFromBlock Source

Arguments

:: (MonadIO m, MonadThrow m) 
=> AccountId 
-> BlockHeight 
-> Word32

Block count (0 for all)

-> SqlPersistT m [WalletTx] 

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

killTxs :: MonadIO m => Maybe (TBMChan Notif) -> [TxHash] -> SqlPersistT m () Source

reviveTx :: MonadIO m => Maybe (TBMChan Notif) -> Tx -> SqlPersistT m () Source

getPendingTxs :: MonadIO m => Int -> SqlPersistT m [TxHash] Source

deleteTx :: (MonadIO m, MonadThrow m) => TxHash -> SqlPersistT m () 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

Helpers

cmdStart :: Handler () Source

cmdStop :: Handler () Source

cmdNewAcc :: Bool -> String -> [String] -> Handler () Source

cmdAddKey :: String -> Handler () Source

cmdSetGap :: String -> String -> Handler () Source

cmdAccount :: String -> Handler () Source

cmdRenameAcc :: String -> String -> Handler () Source

cmdAccounts :: [String] -> Handler () Source

cmdList :: String -> [String] -> Handler () Source

cmdUnused :: String -> [String] -> Handler () Source

cmdLabel :: String -> String -> String -> Handler () Source

cmdTxs :: String -> [String] -> Handler () Source

cmdAddrTxs :: String -> String -> [String] -> Handler () Source

cmdGenAddrs :: String -> String -> Handler () Source

cmdSend :: String -> String -> String -> Handler () Source

cmdSendMany :: String -> [String] -> Handler () Source

cmdImport :: String -> Handler () Source

cmdSign :: String -> String -> Handler () Source

cmdBalance :: String -> Handler () Source

cmdGetTx :: String -> String -> Handler () Source

cmdGetOffline :: String -> String -> Handler () Source

cmdSignOffline :: String -> String -> String -> Handler () Source

cmdRescan :: [String] -> Handler () Source

cmdDecodeTx :: Handler () Source

cmdVersion :: Handler () Source

cmdStatus :: Handler () Source

cmdMonitor :: [String] -> Handler () Source

cmdSync :: String -> String -> [String] -> Handler () Source

cmdKeyPair :: Handler () Source

cmdDeleteTx :: String -> Handler () Source

cmdPending :: String -> [String] -> Handler () Source

cmdDead :: String -> [String] -> Handler () Source

data HandlerSession Source

Constructors

HandlerSession 

Fields

handlerConfig :: !Config
 
handlerPool :: !ConnectionPool
 
handlerNodeState :: !(Maybe SharedNodeState)
 
handlerNotifChan :: !(TBMChan Notif)
 

runDB :: MonadBaseControl IO m => SqlPersistT m a -> Handler m a Source

runDBPool :: MonadBaseControl IO m => SqlPersistT m a -> ConnectionPool -> m a Source

tryDBPool :: MonadLoggerIO m => ConnectionPool -> SqlPersistM a -> m (Maybe a) Source

runNode :: MonadIO m => NodeT m a -> Handler m a Source

getAccountsR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadBase IO m, MonadThrow m, MonadResource m) => ListRequest -> Handler m (Maybe Value) Source

postAccountsR :: (MonadResource m, MonadThrow m, MonadLoggerIO m, MonadBaseControl IO m) => NewAccount -> Handler m (Maybe Value) Source

postAccountRenameR :: (MonadResource m, MonadThrow m, MonadLoggerIO m, MonadBaseControl IO m) => AccountName -> AccountName -> Handler m (Maybe Value) Source

getAccountR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadThrow m) => AccountName -> Handler m (Maybe Value) Source

postAccountKeysR :: (MonadResource m, MonadThrow m, MonadLoggerIO m, MonadBaseControl IO m) => AccountName -> [XPubKey] -> Handler m (Maybe Value) Source

postAccountGapR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadBase IO m, MonadThrow m, MonadResource m) => AccountName -> SetAccountGap -> Handler m (Maybe Value) Source

getAddressesR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadThrow m) => AccountName -> AddressType -> Word32 -> Bool -> ListRequest -> Handler m (Maybe Value) Source

getAddressesUnusedR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadThrow m) => AccountName -> AddressType -> ListRequest -> Handler m (Maybe Value) Source

getAddressR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadThrow m) => AccountName -> KeyIndex -> AddressType -> Word32 -> Bool -> Handler m (Maybe Value) Source

putAddressR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadThrow m) => AccountName -> KeyIndex -> AddressType -> AddressLabel -> Handler m (Maybe Value) Source

postAddressesR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadThrow m, MonadBase IO m, MonadResource m) => AccountName -> KeyIndex -> AddressType -> Handler m (Maybe Value) Source

getTxs :: (MonadLoggerIO m, MonadBaseControl IO m, MonadThrow m) => AccountName -> ListRequest -> String -> (AccountId -> ListRequest -> SqlPersistT m ([WalletTx], Word32)) -> Handler m (Maybe Value) Source

getTxsR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadThrow m) => AccountName -> ListRequest -> Handler m (Maybe Value) Source

getPendingR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadThrow m) => AccountName -> ListRequest -> Handler m (Maybe Value) Source

getDeadR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadThrow m) => AccountName -> ListRequest -> Handler m (Maybe Value) Source

getAddrTxsR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadThrow m) => AccountName -> KeyIndex -> AddressType -> ListRequest -> Handler m (Maybe Value) Source

postTxsR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadBase IO m, MonadThrow m, MonadResource m) => AccountName -> Maybe XPrvKey -> TxAction -> Handler m (Maybe Value) Source

getTxR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadThrow m) => AccountName -> TxHash -> Handler m (Maybe Value) Source

deleteTxIdR :: (MonadLoggerIO m, MonadThrow m, MonadBaseControl IO m) => TxHash -> Handler m (Maybe Value) Source

getBalanceR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadThrow m) => AccountName -> Word32 -> Bool -> Handler m (Maybe Value) Source

getOfflineTxR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadBase IO m, MonadThrow m, MonadResource m) => AccountName -> TxHash -> Handler m (Maybe Value) Source

postOfflineTxR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadBase IO m, MonadThrow m, MonadResource m) => AccountName -> Maybe XPrvKey -> Tx -> [CoinSignData] -> Handler m (Maybe Value) Source

postNodeR :: (MonadLoggerIO m, MonadBaseControl IO m, MonadThrow m) => NodeAction -> Handler m (Maybe Value) Source

getSyncR :: (MonadThrow m, MonadLoggerIO m, MonadBaseControl IO m) => AccountName -> Either BlockHeight BlockHash -> ListRequest -> Handler m (Maybe Value) Source

whenOnline :: Monad m => Handler m () -> Handler m () Source

updateNodeFilter :: (MonadBaseControl IO m, MonadLoggerIO m, MonadThrow m) => Handler m () Source

adjustFCTime :: Timestamp -> Timestamp Source

format :: String -> Text Source

type DatabaseConfType = SqliteConf Source

getDatabasePool :: (MonadLoggerIO m, MonadBaseControl IO m) => DatabaseConfType -> m ConnectionPool Source

type AccountName = Text Source

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)
 

data CoinSignData Source

Constructors

CoinSignData 

Fields

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

data TxType Source

Constructors

TxIncoming 
TxOutgoing 
TxSelf 

Instances

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 

data JsonBlock Source

Constructors

JsonBlock 

Fields

jsonBlockHash :: !BlockHash
 
jsonBlockHeight :: !BlockHeight
 
jsonBlockPrev :: !BlockHash
 

Helpers

splitSelect :: (SqlSelect a r, MonadIO m) => [t] -> ([t] -> SqlQuery a) -> SqlPersistT m [r] Source

splitUpdate :: (MonadIO m, PersistEntity val, PersistEntityBackend val ~ SqlBackend) => [t] -> ([t] -> SqlExpr (Entity val) -> SqlQuery ()) -> SqlPersistT m () Source

splitDelete :: MonadIO m => [t] -> ([t] -> SqlQuery ()) -> SqlPersistT m () Source

splitInsertMany_ :: (MonadIO m, PersistEntity val, PersistEntityBackend val ~ SqlBackend) => [val] -> SqlPersistT m () Source

join2 :: [SqlExpr (Value Bool)] -> SqlExpr (Value Bool) Source

limitOffset :: Word32 -> Word32 -> SqlQuery () Source