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

Haskoin.Script.Common

Contents

Description

Common script-related functions and data types.

Synopsis

Scripts

data ScriptOp Source #

Data type representing an operator allowed inside a Script.

Instances

Instances details
Eq ScriptOp Source # 
Instance details

Defined in Haskoin.Script.Common

Read ScriptOp Source # 
Instance details

Defined in Haskoin.Script.Common

Show ScriptOp Source # 
Instance details

Defined in Haskoin.Script.Common

Generic ScriptOp Source # 
Instance details

Defined in Haskoin.Script.Common

Associated Types

type Rep ScriptOp :: Type -> Type #

Methods

from :: ScriptOp -> Rep ScriptOp x #

to :: Rep ScriptOp x -> ScriptOp #

Hashable ScriptOp Source # 
Instance details

Defined in Haskoin.Script.Common

Methods

hashWithSalt :: Int -> ScriptOp -> Int #

hash :: ScriptOp -> Int #

Binary ScriptOp Source # 
Instance details

Defined in Haskoin.Script.Common

Methods

put :: ScriptOp -> Put #

get :: Get ScriptOp #

putList :: [ScriptOp] -> Put #

Serial ScriptOp Source # 
Instance details

Defined in Haskoin.Script.Common

Methods

serialize :: MonadPut m => ScriptOp -> m () #

deserialize :: MonadGet m => m ScriptOp #

Serialize ScriptOp Source # 
Instance details

Defined in Haskoin.Script.Common

NFData ScriptOp Source # 
Instance details

Defined in Haskoin.Script.Common

Methods

rnf :: ScriptOp -> () #

type Rep ScriptOp Source # 
Instance details

Defined in Haskoin.Script.Common

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

Instances details
Eq Script Source # 
Instance details

Defined in Haskoin.Script.Common

Methods

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

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

Read Script Source # 
Instance details

Defined in Haskoin.Script.Common

Show Script Source # 
Instance details

Defined in Haskoin.Script.Common

Generic Script Source # 
Instance details

Defined in Haskoin.Script.Common

Associated Types

type Rep Script :: Type -> Type #

Methods

from :: Script -> Rep Script x #

to :: Rep Script x -> Script #

Hashable Script Source # 
Instance details

Defined in Haskoin.Script.Common

Methods

hashWithSalt :: Int -> Script -> Int #

hash :: Script -> Int #

Binary Script Source # 
Instance details

Defined in Haskoin.Script.Common

Methods

put :: Script -> Put #

get :: Get Script #

putList :: [Script] -> Put #

Serial Script Source # 
Instance details

Defined in Haskoin.Script.Common

Methods

serialize :: MonadPut m => Script -> m () #

deserialize :: MonadGet m => m Script #

Serialize Script Source # 
Instance details

Defined in Haskoin.Script.Common

NFData Script Source # 
Instance details

Defined in Haskoin.Script.Common

Methods

rnf :: Script -> () #

type Rep Script Source # 
Instance details

Defined in Haskoin.Script.Common

type Rep Script = D1 ('MetaData "Script" "Haskoin.Script.Common" "haskoin-core-0.20.0-inplace" '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

Instances details
Eq PushDataType Source # 
Instance details

Defined in Haskoin.Script.Common

Read PushDataType Source # 
Instance details

Defined in Haskoin.Script.Common

Show PushDataType Source # 
Instance details

Defined in Haskoin.Script.Common

Generic PushDataType Source # 
Instance details

Defined in Haskoin.Script.Common

Associated Types

type Rep PushDataType :: Type -> Type #

Hashable PushDataType Source # 
Instance details

Defined in Haskoin.Script.Common

NFData PushDataType Source # 
Instance details

Defined in Haskoin.Script.Common

Methods

rnf :: PushDataType -> () #

type Rep PushDataType Source # 
Instance details

Defined in Haskoin.Script.Common

type Rep PushDataType = D1 ('MetaData "PushDataType" "Haskoin.Script.Common" "haskoin-core-0.20.0-inplace" 'False) ((C1 ('MetaCons "OPCODE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OPDATA1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OPDATA2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OPDATA4" 'PrefixI 'False) (U1 :: Type -> Type)))

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