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

Haskoin.Script.SigHash

Description

Transaction signatures and related functions.

Synopsis

Script Signatures

newtype SigHash Source #

Data type representing the different ways a transaction can be signed. When producing a signature, a hash of the transaction is used as the message to be signed. The SigHash parameter controls which parts of the transaction are used or ignored to produce the transaction hash. The idea is that if some part of a transaction is not used to produce the transaction hash, then you can change that part of the transaction after producing a signature without invalidating that signature.

If the SIGHASH_ANYONECANPAY flag is set (true), then only the current input is signed. Otherwise, all of the inputs of a transaction are signed. The default value for SIGHASH_ANYONECANPAY is unset (false).

Constructors

SigHash Word32 

Instances

Instances details
Enum SigHash Source # 
Instance details

Defined in Haskoin.Script.SigHash

Eq SigHash Source # 
Instance details

Defined in Haskoin.Script.SigHash

Methods

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

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

Integral SigHash Source # 
Instance details

Defined in Haskoin.Script.SigHash

Num SigHash Source # 
Instance details

Defined in Haskoin.Script.SigHash

Ord SigHash Source # 
Instance details

Defined in Haskoin.Script.SigHash

Read SigHash Source # 
Instance details

Defined in Haskoin.Script.SigHash

Real SigHash Source # 
Instance details

Defined in Haskoin.Script.SigHash

Show SigHash Source # 
Instance details

Defined in Haskoin.Script.SigHash

Generic SigHash Source # 
Instance details

Defined in Haskoin.Script.SigHash

Associated Types

type Rep SigHash :: Type -> Type #

Methods

from :: SigHash -> Rep SigHash x #

to :: Rep SigHash x -> SigHash #

Hashable SigHash Source # 
Instance details

Defined in Haskoin.Script.SigHash

Methods

hashWithSalt :: Int -> SigHash -> Int #

hash :: SigHash -> Int #

ToJSON SigHash Source # 
Instance details

Defined in Haskoin.Script.SigHash

FromJSON SigHash Source # 
Instance details

Defined in Haskoin.Script.SigHash

Bits SigHash Source # 
Instance details

Defined in Haskoin.Script.SigHash

NFData SigHash Source # 
Instance details

Defined in Haskoin.Script.SigHash

Methods

rnf :: SigHash -> () #

type Rep SigHash Source # 
Instance details

Defined in Haskoin.Script.SigHash

type Rep SigHash = D1 ('MetaData "SigHash" "Haskoin.Script.SigHash" "haskoin-core-0.20.5-inplace" 'True) (C1 ('MetaCons "SigHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

data SigHashFlag Source #

Constant representing a SIGHASH flag that controls what is being signed.

Constructors

SIGHASH_ALL

sign all outputs

SIGHASH_NONE

sign no outputs

SIGHASH_SINGLE

sign the output index corresponding to the input

SIGHASH_FORKID

replay protection for Bitcoin Cash transactions

SIGHASH_ANYONECANPAY

new inputs can be added

Instances

Instances details
Enum SigHashFlag Source # 
Instance details

Defined in Haskoin.Script.SigHash

Eq SigHashFlag Source # 
Instance details

Defined in Haskoin.Script.SigHash

Ord SigHashFlag Source # 
Instance details

Defined in Haskoin.Script.SigHash

Read SigHashFlag Source # 
Instance details

Defined in Haskoin.Script.SigHash

Show SigHashFlag Source # 
Instance details

Defined in Haskoin.Script.SigHash

Generic SigHashFlag Source # 
Instance details

Defined in Haskoin.Script.SigHash

Associated Types

type Rep SigHashFlag :: Type -> Type #

Hashable SigHashFlag Source # 
Instance details

Defined in Haskoin.Script.SigHash

NFData SigHashFlag Source # 
Instance details

Defined in Haskoin.Script.SigHash

Methods

rnf :: SigHashFlag -> () #

type Rep SigHashFlag Source # 
Instance details

Defined in Haskoin.Script.SigHash

type Rep SigHashFlag = D1 ('MetaData "SigHashFlag" "Haskoin.Script.SigHash" "haskoin-core-0.20.5-inplace" 'False) ((C1 ('MetaCons "SIGHASH_ALL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SIGHASH_NONE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SIGHASH_SINGLE" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SIGHASH_FORKID" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SIGHASH_ANYONECANPAY" 'PrefixI 'False) (U1 :: Type -> Type))))

sigHashAll :: SigHash Source #

SIGHASH_ALL as a byte.

sigHashNone :: SigHash Source #

SIGHASH_NONE as a byte.

sigHashSingle :: SigHash Source #

SIGHASH_SINGLE as a byte.

hasAnyoneCanPayFlag :: SigHash -> Bool Source #

Is the SIGHASH_ANYONECANPAY flag set?

hasForkIdFlag :: SigHash -> Bool Source #

Is the SIGHASH_FORKID flag set?

setAnyoneCanPayFlag :: SigHash -> SigHash Source #

Set SIGHASH_ANYONECANPAY flag.

setForkIdFlag :: SigHash -> SigHash Source #

Set SIGHASH_FORKID flag.

isSigHashAll :: SigHash -> Bool Source #

Returns True if the SigHash has the value SIGHASH_ALL.

isSigHashNone :: SigHash -> Bool Source #

Returns True if the SigHash has the value SIGHASH_NONE.

isSigHashSingle :: SigHash -> Bool Source #

Returns True if the SigHash has the value SIGHASH_SINGLE.

isSigHashUnknown :: SigHash -> Bool Source #

Returns True if the SigHash has the value SIGHASH_UNKNOWN.

sigHashAddForkId :: SigHash -> Word32 -> SigHash Source #

Add a fork id to a SigHash.

sigHashAddNetworkId :: Network -> SigHash -> SigHash Source #

Add fork id of a particular network to a SigHash.

txSigHash Source #

Arguments

:: Network 
-> Tx

transaction to sign

-> Script

script from output being spent

-> Word64

value of output being spent

-> Int

index of input being signed

-> SigHash

what to sign

-> Hash256

hash to be signed

Computes the hash that will be used for signing a transaction.

txSigHashForkId Source #

Arguments

:: Network 
-> Tx

transaction to sign

-> Script

script from output being spent

-> Word64

value of output being spent

-> Int

index of input being signed

-> SigHash

what to sign

-> Hash256

hash to be signed

Compute the hash that will be used for signing a transaction. This function is used when the SIGHASH_FORKID flag is set.

data TxSignature Source #

Data type representing a signature together with a SigHash. The SigHash is serialized as one byte at the end of an ECDSA Sig. All signatures in transaction inputs are of type TxSignature.

Instances

Instances details
Eq TxSignature Source # 
Instance details

Defined in Haskoin.Script.SigHash

Show TxSignature Source # 
Instance details

Defined in Haskoin.Script.SigHash

Generic TxSignature Source # 
Instance details

Defined in Haskoin.Script.SigHash

Associated Types

type Rep TxSignature :: Type -> Type #

NFData TxSignature Source # 
Instance details

Defined in Haskoin.Script.SigHash

Methods

rnf :: TxSignature -> () #

type Rep TxSignature Source # 
Instance details

Defined in Haskoin.Script.SigHash

type Rep TxSignature = D1 ('MetaData "TxSignature" "Haskoin.Script.SigHash" "haskoin-core-0.20.5-inplace" 'False) (C1 ('MetaCons "TxSignature" 'PrefixI 'True) (S1 ('MetaSel ('Just "txSignature") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Sig) :*: S1 ('MetaSel ('Just "txSignatureSigHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SigHash)) :+: C1 ('MetaCons "TxSignatureEmpty" 'PrefixI 'False) (U1 :: Type -> Type))