haskoin-core-0.20.4: Bitcoin & Bitcoin Cash library for Haskell
CopyrightNo rights reserved
LicenseMIT
Maintainerjprupp@protonmail.ch
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Haskoin.Transaction.Builder

Description

Code to simplify transaction creation, signing, fee calculation and coin selection.

Synopsis

Transaction Builder

buildAddrTx :: Network -> [OutPoint] -> [(Text, Word64)] -> Either String Tx Source #

Build a transaction by providing a list of outpoints as inputs and a list of recipient addresses and amounts as outputs.

buildTx :: [OutPoint] -> [(ScriptOutput, Word64)] -> Tx Source #

Build a transaction by providing a list of outpoints as inputs and a list of ScriptOutput and amounts as outputs.

buildInput Source #

Arguments

:: Network 
-> Tx

transaction where input will be added

-> Int

input index where signature will go

-> ScriptOutput

output script being spent

-> Word64

amount of previous output

-> Maybe RedeemScript

redeem script if pay-to-script-hash

-> TxSignature 
-> PubKeyI 
-> Either String ScriptInput 

Construct an input for a transaction given a signature, public key and data about the previous output.

data SigInput Source #

Data type used to specify the signing parameters of a transaction input. To sign an input, the previous output script, outpoint and sighash are required. When signing a pay to script hash output, an additional redeem script is required.

Constructors

SigInput 

Fields

Instances

Instances details
Eq SigInput Source # 
Instance details

Defined in Haskoin.Transaction.Builder.Sign

Read SigInput Source # 
Instance details

Defined in Haskoin.Transaction.Builder.Sign

Show SigInput Source # 
Instance details

Defined in Haskoin.Transaction.Builder.Sign

Generic SigInput Source # 
Instance details

Defined in Haskoin.Transaction.Builder.Sign

Associated Types

type Rep SigInput :: Type -> Type #

Methods

from :: SigInput -> Rep SigInput x #

to :: Rep SigInput x -> SigInput #

Hashable SigInput Source # 
Instance details

Defined in Haskoin.Transaction.Builder.Sign

Methods

hashWithSalt :: Int -> SigInput -> Int #

hash :: SigInput -> Int #

ToJSON SigInput Source # 
Instance details

Defined in Haskoin.Transaction.Builder.Sign

FromJSON SigInput Source # 
Instance details

Defined in Haskoin.Transaction.Builder.Sign

NFData SigInput Source # 
Instance details

Defined in Haskoin.Transaction.Builder.Sign

Methods

rnf :: SigInput -> () #

type Rep SigInput Source # 
Instance details

Defined in Haskoin.Transaction.Builder.Sign

type Rep SigInput = D1 ('MetaData "SigInput" "Haskoin.Transaction.Builder.Sign" "haskoin-core-0.20.4-inplace" 'False) (C1 ('MetaCons "SigInput" 'PrefixI 'True) ((S1 ('MetaSel ('Just "sigInputScript") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ScriptOutput) :*: S1 ('MetaSel ('Just "sigInputValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64)) :*: (S1 ('MetaSel ('Just "sigInputOP") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OutPoint) :*: (S1 ('MetaSel ('Just "sigInputSH") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SigHash) :*: S1 ('MetaSel ('Just "sigInputRedeem") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe RedeemScript))))))

signTx Source #

Arguments

:: Network 
-> Tx

transaction to sign

-> [SigInput]

signing parameters

-> [SecKey]

private keys to sign with

-> Either String Tx

signed transaction

Sign a transaction by providing the SigInput signing parameters and a list of private keys. The signature is computed deterministically as defined in RFC-6979.

Example: P2SH-P2WKH

sigIn = SigInput (PayWitnessPKHash h) 100000 op sigHashAll Nothing
signedTx = signTx btc unsignedTx [sigIn] [key]

Example: P2SH-P2WSH multisig

sigIn = SigInput (PayWitnessScriptHash h) 100000 op sigHashAll (Just $ PayMulSig [p1,p2,p3] 2)
signedTx = signTx btc unsignedTx [sigIn] [k1,k3]

signNestedWitnessTx Source #

Arguments

:: Network 
-> Tx

transaction to sign

-> [SigInput]

signing parameters

-> [SecKey]

private keys to sign with

-> Either String Tx

signed transaction

This function differs from signTx by assuming all segwit inputs are P2SH-nested. Use the same signing parameters for segwit inputs as in signTx.

makeSignature :: Network -> Tx -> Int -> SigInput -> SecKeyI -> TxSignature Source #

Produce a structured representation of a deterministic (RFC-6979) signature over an input.

signInput :: Network -> Tx -> Int -> SigInput -> SecKeyI -> Either String Tx Source #

Sign a single input in a transaction deterministically (RFC-6979).

signNestedInput :: Network -> Tx -> Int -> SigInput -> SecKeyI -> Either String Tx Source #

Like signInput but treat segwit inputs as nested

verifyStdTx :: Network -> Tx -> [(ScriptOutput, Word64, OutPoint)] -> Bool Source #

Verify if a transaction is valid and all of its inputs are standard.

mergeTxs :: Network -> [Tx] -> [(ScriptOutput, Word64, OutPoint)] -> Either String Tx Source #

Merge partially-signed multisig transactions. This function does not support segwit and P2SH-segwit inputs. Use PSBTs to merge transactions with segwit inputs.

sigKeys :: ScriptOutput -> Maybe RedeemScript -> [SecKey] -> Either String [SecKeyI] Source #

Find from the list of provided private keys which one is required to sign the ScriptOutput.

mergeTxInput :: Network -> [Tx] -> Tx -> ((ScriptOutput, Word64), Int) -> Either String Tx Source #

Merge input from partially-signed multisig transactions. This function does not support segwit and P2SH-segwit inputs.

findSigInput :: [SigInput] -> [TxIn] -> [(SigInput, Int)] Source #

Order the SigInput with respect to the transaction inputs. This allows the user to provide the SigInput in any order. Users can also provide only a partial set of SigInput entries.

verifyStdInput :: Network -> Tx -> Int -> ScriptOutput -> Word64 -> Bool Source #

Verify if a transaction input is valid and standard.

Coin Selection

class Coin c where Source #

Any type can be used as a Coin if it can provide a value in Satoshi. The value is used in coin selection algorithms.

Methods

coinValue :: c -> Word64 Source #

Instances

Instances details
Coin TestCoin Source # 
Instance details

Defined in Haskoin.Util.Arbitrary.Transaction

chooseCoins Source #

Arguments

:: Coin c 
=> Word64

value to send

-> Word64

fee per byte

-> Int

number of outputs (including change)

-> Bool

try to find better solutions

-> [c]

list of ordered coins to choose from

-> Either String ([c], Word64)

coin selection and change

Coin selection algorithm for normal (non-multisig) transactions. This function returns the selected coins together with the amount of change to send back to yourself, taking the fee into account.

chooseCoinsSink Source #

Arguments

:: (Monad m, Coin c) 
=> Word64

value to send

-> Word64

fee per byte

-> Int

number of outputs (including change)

-> Bool

try to find better solution

-> ConduitT c Void m (Either String ([c], Word64))

coin selection and change

Coin selection algorithm for normal (non-multisig) transactions. This function returns the selected coins together with the amount of change to send back to yourself, taking the fee into account. This version uses a Sink for conduit-based coin selection.

chooseMSCoins Source #

Arguments

:: Coin c 
=> Word64

value to send

-> Word64

fee per byte

-> (Int, Int)

m of n multisig

-> Int

number of outputs (including change)

-> Bool

try to find better solution

-> [c] 
-> Either String ([c], Word64)

coin selection change amount

Coin selection algorithm for multisig transactions. This function returns the selected coins together with the amount of change to send back to yourself, taking the fee into account. This function assumes all the coins are script hash outputs that send funds to a multisignature address.

chooseMSCoinsSink Source #

Arguments

:: (Monad m, Coin c) 
=> Word64

value to send

-> Word64

fee per byte

-> (Int, Int)

m of n multisig

-> Int

number of outputs (including change)

-> Bool

try to find better solution

-> ConduitT c Void m (Either String ([c], Word64))

coin selection and change

Coin selection algorithm for multisig transactions. This function returns the selected coins together with the amount of change to send back to yourself, taking the fee into account. This function assumes all the coins are script hash outputs that send funds to a multisignature address. This version uses a Sink if you need conduit-based coin selection.

countMulSig :: Network -> Tx -> Script -> Word64 -> Int -> [PubKey] -> [TxSignature] -> Int Source #

Count the number of valid signatures for a multi-signature transaction.

greedyAddSink Source #

Arguments

:: (Monad m, Coin c) 
=> Word64

value to send

-> (Int -> Word64)

coin count to fee function

-> Bool

try to find better solutions

-> ConduitT c Void m (Maybe ([c], Word64))

coin selection and change

Select coins greedily by starting from an empty solution. If the continue flag is set, the algorithm will try to find a better solution in the stream after a solution is found. If the next solution found is not strictly better than the previously found solution, the algorithm stops and returns the previous solution. If the continue flag is not set, the algorithm will return the first solution it finds in the stream.

guessTxFee :: Word64 -> Int -> Int -> Word64 Source #

Estimate tranasction fee to pay based on transaction size estimation.

guessMSTxFee :: Word64 -> (Int, Int) -> Int -> Int -> Word64 Source #

Same as guessTxFee but for multisig transactions.

guessTxSize Source #

Arguments

:: Int

number of regular transaction inputs

-> [(Int, Int)]

multisig m of n for each input

-> Int

number of P2PKH outputs

-> Int

number of P2SH outputs

-> Int

upper bound on transaction size

Computes an upper bound on the size of a transaction based on some known properties of the transaction.

guessMSSize :: (Int, Int) -> Int Source #

Size of a multisig P2SH input.