haskoin-core-0.9.0: Bitcoin & Bitcoin Cash library for Haskell

CopyrightNo rights reserved
LicenseUNLICENSE
Maintainerxenog@protonmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Network.Haskoin.Transaction

Contents

Description

Transactions and related code.

Synopsis

Documentation

data Tx Source #

Data type representing a transaction.

Constructors

Tx 

Fields

Instances
Eq Tx Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

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

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

Ord Tx Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

compare :: Tx -> Tx -> Ordering #

(<) :: Tx -> Tx -> Bool #

(<=) :: Tx -> Tx -> Bool #

(>) :: Tx -> Tx -> Bool #

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

max :: Tx -> Tx -> Tx #

min :: Tx -> Tx -> Tx #

Read Tx Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Show Tx Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

showsPrec :: Int -> Tx -> ShowS #

show :: Tx -> String #

showList :: [Tx] -> ShowS #

IsString Tx Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

fromString :: String -> Tx #

Generic Tx Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Associated Types

type Rep Tx :: Type -> Type #

Methods

from :: Tx -> Rep Tx x #

to :: Rep Tx x -> Tx #

Hashable Tx Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

hashWithSalt :: Int -> Tx -> Int #

hash :: Tx -> Int #

ToJSON Tx Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

FromJSON Tx Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Serialize Tx Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

put :: Putter Tx #

get :: Get Tx #

type Rep Tx Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

data TxIn Source #

Data type representing a transaction input.

Constructors

TxIn 

Fields

Instances
Eq TxIn Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

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

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

Ord TxIn Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

compare :: TxIn -> TxIn -> Ordering #

(<) :: TxIn -> TxIn -> Bool #

(<=) :: TxIn -> TxIn -> Bool #

(>) :: TxIn -> TxIn -> Bool #

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

max :: TxIn -> TxIn -> TxIn #

min :: TxIn -> TxIn -> TxIn #

Read TxIn Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Show TxIn Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

showsPrec :: Int -> TxIn -> ShowS #

show :: TxIn -> String #

showList :: [TxIn] -> ShowS #

Generic TxIn Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Associated Types

type Rep TxIn :: Type -> Type #

Methods

from :: TxIn -> Rep TxIn x #

to :: Rep TxIn x -> TxIn #

Hashable TxIn Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

hashWithSalt :: Int -> TxIn -> Int #

hash :: TxIn -> Int #

Serialize TxIn Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

put :: Putter TxIn #

get :: Get TxIn #

type Rep TxIn Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

type Rep TxIn = D1 (MetaData "TxIn" "Network.Haskoin.Transaction.Common" "haskoin-core-0.9.0-9luCRjUjDcyCwjYBmjo0zV" False) (C1 (MetaCons "TxIn" PrefixI True) (S1 (MetaSel (Just "prevOutput") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 OutPoint) :*: (S1 (MetaSel (Just "scriptInput") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString) :*: S1 (MetaSel (Just "txInSequence") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word32))))

data TxOut Source #

Data type representing a transaction output.

Constructors

TxOut 

Fields

Instances
Eq TxOut Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

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

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

Ord TxOut Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

compare :: TxOut -> TxOut -> Ordering #

(<) :: TxOut -> TxOut -> Bool #

(<=) :: TxOut -> TxOut -> Bool #

(>) :: TxOut -> TxOut -> Bool #

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

max :: TxOut -> TxOut -> TxOut #

min :: TxOut -> TxOut -> TxOut #

Read TxOut Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Show TxOut Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

showsPrec :: Int -> TxOut -> ShowS #

show :: TxOut -> String #

showList :: [TxOut] -> ShowS #

Generic TxOut Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Associated Types

type Rep TxOut :: Type -> Type #

Methods

from :: TxOut -> Rep TxOut x #

to :: Rep TxOut x -> TxOut #

Hashable TxOut Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

hashWithSalt :: Int -> TxOut -> Int #

hash :: TxOut -> Int #

Serialize TxOut Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

put :: Putter TxOut #

get :: Get TxOut #

type Rep TxOut Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

type Rep TxOut = D1 (MetaData "TxOut" "Network.Haskoin.Transaction.Common" "haskoin-core-0.9.0-9luCRjUjDcyCwjYBmjo0zV" False) (C1 (MetaCons "TxOut" PrefixI True) (S1 (MetaSel (Just "outValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word64) :*: S1 (MetaSel (Just "scriptOutput") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString)))

data OutPoint Source #

The OutPoint refers to a transaction output being spent.

Constructors

OutPoint 

Fields

Instances
Eq OutPoint Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Ord OutPoint Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Read OutPoint Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Show OutPoint Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Generic OutPoint Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Associated Types

type Rep OutPoint :: Type -> Type #

Methods

from :: OutPoint -> Rep OutPoint x #

to :: Rep OutPoint x -> OutPoint #

Hashable OutPoint Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

hashWithSalt :: Int -> OutPoint -> Int #

hash :: OutPoint -> Int #

ToJSON OutPoint Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

FromJSON OutPoint Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Serialize OutPoint Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

type Rep OutPoint Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

type Rep OutPoint = D1 (MetaData "OutPoint" "Network.Haskoin.Transaction.Common" "haskoin-core-0.9.0-9luCRjUjDcyCwjYBmjo0zV" False) (C1 (MetaCons "OutPoint" PrefixI True) (S1 (MetaSel (Just "outPointHash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TxHash) :*: S1 (MetaSel (Just "outPointIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word32)))

newtype TxHash Source #

Transaction id: hash of transaction excluding witness data.

Constructors

TxHash 

Fields

Instances
Eq TxHash Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

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

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

Ord TxHash Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Read TxHash Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Show TxHash Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

IsString TxHash Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

fromString :: String -> TxHash #

Generic TxHash Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Associated Types

type Rep TxHash :: Type -> Type #

Methods

from :: TxHash -> Rep TxHash x #

to :: Rep TxHash x -> TxHash #

Hashable TxHash Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Methods

hashWithSalt :: Int -> TxHash -> Int #

hash :: TxHash -> Int #

ToJSON TxHash Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

FromJSON TxHash Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

Serialize TxHash Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

type Rep TxHash Source # 
Instance details

Defined in Network.Haskoin.Transaction.Common

type Rep TxHash = D1 (MetaData "TxHash" "Network.Haskoin.Transaction.Common" "haskoin-core-0.9.0-9luCRjUjDcyCwjYBmjo0zV" True) (C1 (MetaCons "TxHash" PrefixI True) (S1 (MetaSel (Just "getTxHash") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Hash256)))

type WitnessData = [WitnessStack] Source #

Witness stack for SegWit transactions.

type WitnessStack = [WitnessStackItem] Source #

Witness stack for SegWit transactions.

type WitnessStackItem = ByteString Source #

Witness stack item for SegWit transactions.

txHash :: Tx -> TxHash Source #

Compute transaction hash.

hexToTxHash :: Text -> Maybe TxHash Source #

Convert transaction hash from hex, reversing bytes.

txHashToHex :: TxHash -> Text Source #

Convert transaction hash to hex form, reversing bytes.

nosigTxHash :: Tx -> TxHash Source #

Transaction hash excluding signatures.

nullOutPoint :: OutPoint Source #

Outpoint used in coinbase transactions.

genesisTx :: Tx Source #

Transaction from Genesis block.

Transaction Creation & Signing

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)] -> Either String 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
Eq SigInput Source # 
Instance details

Defined in Network.Haskoin.Transaction.Builder

Read SigInput Source # 
Instance details

Defined in Network.Haskoin.Transaction.Builder

Show SigInput Source # 
Instance details

Defined in Network.Haskoin.Transaction.Builder

Generic SigInput Source # 
Instance details

Defined in Network.Haskoin.Transaction.Builder

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 Network.Haskoin.Transaction.Builder

Methods

hashWithSalt :: Int -> SigInput -> Int #

hash :: SigInput -> Int #

ToJSON SigInput Source # 
Instance details

Defined in Network.Haskoin.Transaction.Builder

FromJSON SigInput Source # 
Instance details

Defined in Network.Haskoin.Transaction.Builder

type Rep SigInput Source # 
Instance details

Defined in Network.Haskoin.Transaction.Builder

type Rep SigInput = D1 (MetaData "SigInput" "Network.Haskoin.Transaction.Builder" "haskoin-core-0.9.0-9luCRjUjDcyCwjYBmjo0zV" 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 parametres and a list of private keys. The signature is computed deterministically as defined in RFC-6979.

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

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

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.

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.

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
Coin TestCoin Source # 
Instance details

Defined in Network.Haskoin.Test.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.