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

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

Network.Haskoin.Script

Description

This module provides functions for parsing and evaluating bitcoin transaction scripts. Data types are provided for building and deconstructing all of the standard input and output script types.

Synopsis

Documentation

data ScriptInput Source #

Standard input script high-level representation.

Constructors

RegularInput 

Fields

ScriptHashInput 

Fields

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

spend pay-to-public-key output

Fields

SpendPKHash

spend pay-to-public-key-hash output

Fields

SpendMulSig

spend multisig output

Fields

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.

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.

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.

scriptOpToInt :: ScriptOp -> Either String Int Source #

Decode ScriptOp [OP_1 .. OP_16] to integers [1 .. 16]. This functions fails for other values of ScriptOp

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.

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

Instances
Enum SigHash Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Eq SigHash Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Methods

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

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

Integral SigHash Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Num SigHash Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Ord SigHash Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Read SigHash Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Real SigHash Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Show SigHash Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Generic SigHash Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Associated Types

type Rep SigHash :: * -> * #

Methods

from :: SigHash -> Rep SigHash x #

to :: Rep SigHash x -> SigHash #

Hashable SigHash Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Methods

hashWithSalt :: Int -> SigHash -> Int #

hash :: SigHash -> Int #

ToJSON SigHash Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

FromJSON SigHash Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Bits SigHash Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

type Rep SigHash Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

type Rep SigHash = D1 (MetaData "SigHash" "Network.Haskoin.Script.SigHash" "haskoin-core-0.8.3-7QKDaQCnQgf2FaRKrwfsTk" 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
Enum SigHashFlag Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Eq SigHashFlag Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Ord SigHashFlag Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Read SigHashFlag Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Show SigHashFlag Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Generic SigHashFlag Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

Associated Types

type Rep SigHashFlag :: * -> * #

Hashable SigHashFlag Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

type Rep SigHashFlag Source # 
Instance details

Defined in Network.Haskoin.Script.SigHash

type Rep SigHashFlag = D1 (MetaData "SigHashFlag" "Network.Haskoin.Script.SigHash" "haskoin-core-0.8.3-7QKDaQCnQgf2FaRKrwfsTk" False) ((C1 (MetaCons "SIGHASH_ALL" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SIGHASH_NONE" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "SIGHASH_SINGLE" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "SIGHASH_FORKID" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SIGHASH_ANYONECANPAY" PrefixI False) (U1 :: * -> *))))

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

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

data ScriptOp Source #

Data type representing an operator allowed inside a Script.

Instances
Eq ScriptOp Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Read ScriptOp Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Show ScriptOp Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Generic ScriptOp Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Associated Types

type Rep ScriptOp :: * -> * #

Methods

from :: ScriptOp -> Rep ScriptOp x #

to :: Rep ScriptOp x -> ScriptOp #

Hashable ScriptOp Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Methods

hashWithSalt :: Int -> ScriptOp -> Int #

hash :: ScriptOp -> Int #

Serialize ScriptOp Source # 
Instance details

Defined in Network.Haskoin.Script.Common

type Rep ScriptOp Source # 
Instance details

Defined in Network.Haskoin.Script.Common

type Rep ScriptOp = D1 (MetaData "ScriptOp" "Network.Haskoin.Script.Common" "haskoin-core-0.8.3-7QKDaQCnQgf2FaRKrwfsTk" False) ((((((C1 (MetaCons "OP_PUSHDATA" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PushDataType)) :+: (C1 (MetaCons "OP_0" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_1NEGATE" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "OP_RESERVED" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_1" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_2" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_3" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "OP_4" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OP_5" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_6" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "OP_7" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_8" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_9" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_10" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "OP_11" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OP_12" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_13" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "OP_14" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_15" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_16" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_NOP" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "OP_VER" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OP_IF" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_NOTIF" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "OP_VERIF" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_VERNOTIF" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_ELSE" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_ENDIF" PrefixI False) (U1 :: * -> *)))))) :+: ((((C1 (MetaCons "OP_VERIFY" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OP_RETURN" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_TOALTSTACK" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "OP_FROMALTSTACK" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_IFDUP" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_DEPTH" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_DROP" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "OP_DUP" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OP_NIP" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_OVER" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "OP_PICK" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_ROLL" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_ROT" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_SWAP" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "OP_TUCK" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OP_2DROP" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_2DUP" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "OP_3DUP" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_2OVER" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_2ROT" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_2SWAP" PrefixI False) (U1 :: * -> *)))) :+: (((C1 (MetaCons "OP_CAT" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_SUBSTR" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_LEFT" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_RIGHT" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "OP_SIZE" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_INVERT" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_AND" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_OR" PrefixI False) (U1 :: * -> *))))))) :+: (((((C1 (MetaCons "OP_XOR" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OP_EQUAL" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_EQUALVERIFY" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "OP_RESERVED1" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_RESERVED2" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_1ADD" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_1SUB" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "OP_2MUL" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OP_2DIV" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_NEGATE" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "OP_ABS" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_NOT" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_0NOTEQUAL" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_ADD" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "OP_SUB" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OP_MUL" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_DIV" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "OP_MOD" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_LSHIFT" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_RSHIFT" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_BOOLAND" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "OP_BOOLOR" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OP_NUMEQUAL" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_NUMEQUALVERIFY" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "OP_NUMNOTEQUAL" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_LESSTHAN" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_GREATERTHAN" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_LESSTHANOREQUAL" PrefixI False) (U1 :: * -> *)))))) :+: ((((C1 (MetaCons "OP_GREATERTHANOREQUAL" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OP_MIN" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_MAX" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "OP_WITHIN" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_RIPEMD160" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_SHA1" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_SHA256" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "OP_HASH160" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OP_HASH256" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_CODESEPARATOR" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "OP_CHECKSIG" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_CHECKSIGVERIFY" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_CHECKMULTISIG" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_CHECKMULTISIGVERIFY" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "OP_NOP1" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OP_NOP2" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_NOP3" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "OP_NOP4" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_NOP5" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_NOP6" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_NOP7" PrefixI False) (U1 :: * -> *)))) :+: (((C1 (MetaCons "OP_NOP8" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_NOP9" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_NOP10" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_CHECKDATASIG" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "OP_CHECKDATASIGVERIFY" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_PUBKEYHASH" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OP_PUBKEY" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OP_INVALIDOPCODE" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word8)))))))))

newtype Script Source #

Data type representing a transaction script. Scripts are defined as lists of script operators ScriptOp. Scripts are used to:

  • Define the spending conditions in the output of a transaction.
  • Provide signatures in the input of a transaction (except SegWit).

SigWit only: the segregated witness data structure, and not the input script, contains signatures and redeem script for pay-to-witness-script and pay-to-witness-public-key-hash transactions.

Constructors

Script 

Fields

Instances
Eq Script Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Methods

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

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

Read Script Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Show Script Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Generic Script Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Associated Types

type Rep Script :: * -> * #

Methods

from :: Script -> Rep Script x #

to :: Rep Script x -> Script #

Hashable Script Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Methods

hashWithSalt :: Int -> Script -> Int #

hash :: Script -> Int #

Serialize Script Source # 
Instance details

Defined in Network.Haskoin.Script.Common

type Rep Script Source # 
Instance details

Defined in Network.Haskoin.Script.Common

type Rep Script = D1 (MetaData "Script" "Network.Haskoin.Script.Common" "haskoin-core-0.8.3-7QKDaQCnQgf2FaRKrwfsTk" True) (C1 (MetaCons "Script" PrefixI True) (S1 (MetaSel (Just "scriptOps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ScriptOp])))

data PushDataType Source #

Data type representing the type of an OP_PUSHDATA opcode.

Constructors

OPCODE

next opcode bytes is data to be pushed

OPDATA1

next byte contains number of bytes of data to be pushed

OPDATA2

next two bytes contains number of bytes to be pushed

OPDATA4

next four bytes contains the number of bytes to be pushed

Instances
Eq PushDataType Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Read PushDataType Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Show PushDataType Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Generic PushDataType Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Associated Types

type Rep PushDataType :: * -> * #

Hashable PushDataType Source # 
Instance details

Defined in Network.Haskoin.Script.Common

type Rep PushDataType Source # 
Instance details

Defined in Network.Haskoin.Script.Common

type Rep PushDataType = D1 (MetaData "PushDataType" "Network.Haskoin.Script.Common" "haskoin-core-0.8.3-7QKDaQCnQgf2FaRKrwfsTk" False) ((C1 (MetaCons "OPCODE" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OPDATA1" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OPDATA2" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OPDATA4" PrefixI False) (U1 :: * -> *)))

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

DataCarrier

provably unspendable data carrier

Instances
Eq ScriptOutput Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Read ScriptOutput Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Show ScriptOutput Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Generic ScriptOutput Source # 
Instance details

Defined in Network.Haskoin.Script.Common

Associated Types

type Rep ScriptOutput :: * -> * #

Hashable ScriptOutput Source # 
Instance details

Defined in Network.Haskoin.Script.Common

ToJSON ScriptOutput Source # 
Instance details

Defined in Network.Haskoin.Script.Common

FromJSON ScriptOutput Source # 
Instance details

Defined in Network.Haskoin.Script.Common

type Rep ScriptOutput Source # 
Instance details

Defined in Network.Haskoin.Script.Common

type Rep ScriptOutput = D1 (MetaData "ScriptOutput" "Network.Haskoin.Script.Common" "haskoin-core-0.8.3-7QKDaQCnQgf2FaRKrwfsTk" 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 "DataCarrier" PrefixI True) (S1 (MetaSel (Just "getOutputData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString)))))

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?

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

isPushOp :: ScriptOp -> Bool Source #

Check whether opcode is only data.

opPushData :: ByteString -> ScriptOp Source #

Optimally encode data using one of the 4 types of data pushing opcodes.

intToScriptOp :: Int -> ScriptOp Source #

Transforms integers [1 .. 16] to ScriptOp [OP_1 .. OP_16].

scriptOpToInt :: ScriptOp -> Either String Int Source #

Decode ScriptOp [OP_1 .. OP_16] to integers [1 .. 16]. This functions fails for other values of ScriptOp