bitcoin-hs-0.0.1: Partial implementation of the Bitcoin protocol (as of 2013)

Safe HaskellNone
LanguageHaskell98

Bitcoin.Script.Run

Contents

Description

Bitcoin script interpreter

Synopsis

types

type Entry = ByteString Source #

Stack entry

data InterpreterConfig Source #

Constructors

Cfg 

Fields

  • _newTx :: !(Tx RawScript RawScript)

    the new tx we are running (containing the scriptSigs which are combined with the previous tx's pubKeyScripts)

  • _curTxInIdx :: !Int

    the index of the current transaction input (within the new tx) we are checking

data InterpreterState Source #

Two stacks, an opcode stream (the latter necessary for the somewhat convoluted IF parsing, and also for OP_CHECKSIG)

Constructors

St 

Fields

high level functions

checkTransaction :: forall a. Tx (Tx a RawScript, RawScript) RawScript -> Either String Bool Source #

Given a transaction together with its inputs, we check if it is valid or not. This is done by combining the input scripts of this transaction with the output scripts of the previous transactions, and running the resulting scripts

If any of the scripts fails, the cause of failure is returned; if the scripts runs correctly, the result is returned (which should be True for valid transactions)

medium level functions

initialState :: InterpreterState Source #

Empty stacks, empty script

executeScript :: [Opcode] -> ScriptMonad () Source #

Executes a list of opcodes

scriptStep :: ScriptMonad Bool Source #

Execute a single (except in case of conditionals) opcode

"The stacks hold byte vectors. Byte vectors are interpreted as little-endian variable-length integers with the most significant bit determining the sign of the integer. Thus 0x81 represents -1. 0x80 is another representation of zero (so called negative 0). Byte vectors are interpreted as Booleans where False is represented by any representation of zero, and True is represented by any representation of non-zero."

Returns True if the script finished.

internal types

data Stream Source #

An opcode stream consist of a zipper of opcodes, and a Context which describes (possibly recursively) what is on the left and right side of this zipper. This is used for executing (possibly nested) OP_IF blocks.

This may be overly complicated :)

Instances

data Context Source #

A context of opcodes and (nested) if blocks

Constructors

CtxEmpty

we are the full opcode stream

CtxHole Context [Opcode] IfType Hole [Opcode]

a hole has an outer context, opcodes on the left and right, and an if block in the middle

Instances

data Hole Source #

Constructors

HoleThen

we are in the "then" branch

Fields

HoleElse

we are in the "else" branch (which may not physically exists - this is important when reconstructing)

Fields

Instances

data IfBranch Source #

Constructors

IfBranch

"if-then"

ElseBranch

"else"

data IfType Source #

Constructors

If

OP_IF

NotIf

OP_NOTIF

Instances

data IfBlock Source #

Constructors

IfBlock 

Instances

some internal functions

streamMoveRight :: Stream -> Either Stream (Opcode, Stream) Source #

Even where there is nothing on the right, we can change the stream itself during the discovery of this fact!

fetchOpcode :: ScriptMonad (Maybe Opcode) Source #

Fetches an opcode, possibly exiting the current context

fetchOpcodeWithinContext :: ScriptMonad (Maybe Opcode) Source #

Fetches an opcode, but does not exit the current context

fetchIfBlock :: IfType -> IfBranch -> ScriptMonad IfBlock Source #

We fetch an if block *and* take the given branch (second argument)

Note: if blocks can be nested...

script monad

push/pop

parsing (should be elsewhere)

parseTxScripts :: Tx RawScript RawScript -> Either String (Tx Script Script) Source #

Tries to parse all scripts, both input and output. Since the output scripts can fail to parse (see below), this may also fail.

parseTxInScripts :: Tx RawScript a -> Either String (Tx Script a) Source #

Tries to parse all input scripts. This shouldn't fail for a valid transaction.

parseTxOutScripts :: Tx a RawScript -> Either String (Tx a Script) Source #

Tries to parse all output scripts. This may fail because invalid output scripts are allowed, just unspendable... :(

parseSingleTxOutScript :: Int -> Tx a RawScript -> Either String (Tx a (Either RawScript Script)) Source #

Parses only a single output script, leaves the rest (reason: tx validation shouldn't fail just because there are other invalid scripts in the prev tx unrelated to this one).