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

Haskoin.Script.Standard

Description

Standard scripts like pay-to-public-key, pay-to-public-key-hash, pay-to-script-hash, pay-to-multisig and corresponding SegWit variants.

Synopsis

Standard Script Outputs

data ScriptOutput Source #

Data type describing standard transaction output scripts. Output scripts provide the conditions that must be fulfilled for someone to spend the funds in a transaction output.

Constructors

PayPK

pay to public key

PayPKHash

pay to public key hash

PayMulSig

multisig

PayScriptHash

pay to a script hash

PayWitnessPKHash

pay to witness public key hash

PayWitnessScriptHash

pay to witness script hash

PayWitness

another pay to witness address

DataCarrier

provably unspendable data carrier

Instances

Instances details
Eq ScriptOutput Source # 
Instance details

Defined in Haskoin.Script.Standard

Read ScriptOutput Source # 
Instance details

Defined in Haskoin.Script.Standard

Show ScriptOutput Source # 
Instance details

Defined in Haskoin.Script.Standard

Generic ScriptOutput Source # 
Instance details

Defined in Haskoin.Script.Standard

Associated Types

type Rep ScriptOutput :: Type -> Type #

Hashable ScriptOutput Source # 
Instance details

Defined in Haskoin.Script.Standard

ToJSON ScriptOutput Source # 
Instance details

Defined in Haskoin.Script.Standard

FromJSON ScriptOutput Source # 
Instance details

Defined in Haskoin.Script.Standard

NFData ScriptOutput Source # 
Instance details

Defined in Haskoin.Script.Standard

Methods

rnf :: ScriptOutput -> () #

type Rep ScriptOutput Source # 
Instance details

Defined in Haskoin.Script.Standard

type Rep ScriptOutput = D1 ('MetaData "ScriptOutput" "Haskoin.Script.Standard" "haskoin-core-0.21.2-inplace" 'False) (((C1 ('MetaCons "PayPK" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOutputPubKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PubKeyI)) :+: C1 ('MetaCons "PayPKHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOutputHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Hash160))) :+: (C1 ('MetaCons "PayMulSig" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOutputMulSigKeys") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [PubKeyI]) :*: S1 ('MetaSel ('Just "getOutputMulSigRequired") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "PayScriptHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOutputHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Hash160)))) :+: ((C1 ('MetaCons "PayWitnessPKHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOutputHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Hash160)) :+: C1 ('MetaCons "PayWitnessScriptHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "getScriptHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Hash256))) :+: (C1 ('MetaCons "PayWitness" 'PrefixI 'True) (S1 ('MetaSel ('Just "getWitnessVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8) :*: S1 ('MetaSel ('Just "getWitnessData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "DataCarrier" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOutputData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)))))

type RedeemScript = ScriptOutput Source #

A redeem script is the output script serialized into the spending input script. It must be included in inputs that spend pay-to-script-hash outputs.

isPayPK :: ScriptOutput -> Bool Source #

Is script a pay-to-public-key output?

isPayPKHash :: ScriptOutput -> Bool Source #

Is script a pay-to-pub-key-hash output?

isPayMulSig :: ScriptOutput -> Bool Source #

Is script a pay-to-multi-sig output?

isPayScriptHash :: ScriptOutput -> Bool Source #

Is script a pay-to-script-hash output?

isPayWitness :: ScriptOutput -> Bool Source #

Is script paying to a different type of witness address?

isPayWitnessPKHash :: ScriptOutput -> Bool Source #

Is script a pay-to-witness-pub-key-hash output?

isPayWitnessScriptHash :: ScriptOutput -> Bool Source #

Is script a pay-to-witness-script-hash output?

isDataCarrier :: ScriptOutput -> Bool Source #

Is script a data carrier output?

encodeOutput :: ScriptOutput -> Script Source #

Computes a Script from a standard ScriptOutput.

encodeOutputBS :: ScriptOutput -> ByteString Source #

Similar to encodeOutput but encodes to a ByteString

decodeOutput :: Script -> Either String ScriptOutput Source #

Tries to decode a ScriptOutput from a Script. This can fail if the script is not recognized as any of the standard output types.

toP2SH :: Script -> ScriptOutput Source #

Encode script as pay-to-script-hash script

toP2WSH :: Script -> ScriptOutput Source #

Encode script as a pay-to-witness-script-hash script

sortMulSig :: ScriptOutput -> ScriptOutput Source #

Sort the public keys of a multisig output in ascending order by comparing their compressed serialized representations. Refer to BIP-67.

Standard Script Inputs

data ScriptInput Source #

Standard input script high-level representation.

Constructors

RegularInput 

Fields

ScriptHashInput 

Fields

Instances

Instances details
Eq ScriptInput Source # 
Instance details

Defined in Haskoin.Script.Standard

Show ScriptInput Source # 
Instance details

Defined in Haskoin.Script.Standard

Generic ScriptInput Source # 
Instance details

Defined in Haskoin.Script.Standard

Associated Types

type Rep ScriptInput :: Type -> Type #

NFData ScriptInput Source # 
Instance details

Defined in Haskoin.Script.Standard

Methods

rnf :: ScriptInput -> () #

type Rep ScriptInput Source # 
Instance details

Defined in Haskoin.Script.Standard

type Rep ScriptInput = D1 ('MetaData "ScriptInput" "Haskoin.Script.Standard" "haskoin-core-0.21.2-inplace" 'False) (C1 ('MetaCons "RegularInput" 'PrefixI 'True) (S1 ('MetaSel ('Just "getRegularInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SimpleInput)) :+: C1 ('MetaCons "ScriptHashInput" 'PrefixI 'True) (S1 ('MetaSel ('Just "getScriptHashInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SimpleInput) :*: S1 ('MetaSel ('Just "getScriptHashRedeem") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RedeemScript)))

data SimpleInput Source #

Data type describing standard transaction input scripts. Input scripts provide the signing data required to unlock the coins of the output they are trying to spend, except in pay-to-witness-public-key-hash and pay-to-script-hash transactions.

Constructors

SpendPK 

Fields

SpendPKHash 

Fields

SpendMulSig 

Fields

Instances

Instances details
Eq SimpleInput Source # 
Instance details

Defined in Haskoin.Script.Standard

Show SimpleInput Source # 
Instance details

Defined in Haskoin.Script.Standard

Generic SimpleInput Source # 
Instance details

Defined in Haskoin.Script.Standard

Associated Types

type Rep SimpleInput :: Type -> Type #

NFData SimpleInput Source # 
Instance details

Defined in Haskoin.Script.Standard

Methods

rnf :: SimpleInput -> () #

type Rep SimpleInput Source # 
Instance details

Defined in Haskoin.Script.Standard

type Rep SimpleInput = D1 ('MetaData "SimpleInput" "Haskoin.Script.Standard" "haskoin-core-0.21.2-inplace" 'False) (C1 ('MetaCons "SpendPK" 'PrefixI 'True) (S1 ('MetaSel ('Just "getInputSig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxSignature)) :+: (C1 ('MetaCons "SpendPKHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "getInputSig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxSignature) :*: S1 ('MetaSel ('Just "getInputKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PubKeyI)) :+: C1 ('MetaCons "SpendMulSig" 'PrefixI 'True) (S1 ('MetaSel ('Just "getInputMulSigKeys") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [TxSignature]))))

encodeInput :: ScriptInput -> Script Source #

Encode a standard input into a script.

encodeInputBS :: ScriptInput -> ByteString Source #

Similar to encodeInput but encodes directly to a serialized script ByteString.

decodeInput :: Network -> Script -> Either String ScriptInput Source #

Heuristic to decode a ScriptInput from a Script. This function fails if the script can not be parsed as a standard script input.

decodeInputBS :: Network -> ByteString -> Either String ScriptInput Source #

Like decodeInput but decodes directly from a serialized script ByteString.

isSpendPK :: ScriptInput -> Bool Source #

Returns true if the input script is spending from a pay-to-public-key output.

isSpendPKHash :: ScriptInput -> Bool Source #

Returns true if the input script is spending from a pay-to-public-key-hash output.

isSpendMulSig :: ScriptInput -> Bool Source #

Returns true if the input script is spending a multisig output.

isScriptHashInput :: ScriptInput -> Bool Source #

Returns true if the input script is spending a pay-to-script-hash output.