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

Haskoin.Transaction.Builder.Sign

Description

Types and logic for signing transactions.

Synopsis

Documentation

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.0-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))))))

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

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

makeSigHash :: Network -> Tx -> Int -> ScriptOutput -> Word64 -> SigHash -> Maybe RedeemScript -> Hash256 Source #

A function which selects the digest algorithm and parameters as appropriate

Since: 0.11.0.0

signTx Source #

Arguments

:: Network 
-> Tx

transaction to sign

-> [(SigInput, Bool)]

signing parameters, with nesting flag

-> [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.

findInputIndex Source #

Arguments

:: (a -> OutPoint)

extract an outpoint

-> [a]

input list

-> [TxIn]

reference list of inputs

-> [(a, Int)] 

Associate an input index to each value in a list

signInput Source #

Arguments

:: Network 
-> Tx 
-> Int 
-> (SigInput, Bool)

boolean flag: nest input

-> SecKeyI 
-> Either String Tx 

Sign a single input in a transaction deterministically (RFC-6979). The nesting flag only affects the behavior of segwit inputs.

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.

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.