haskoin-0.0.2.1: Implementation of the Bitcoin protocol.

Safe HaskellNone

Network.Haskoin.Protocol

Contents

Description

This package provides all of the basic types used for the Bitcoin networking protocol together with Data.Binary instances for efficiently serializing and de-serializing them. More information on the bitcoin protocol is available here: http://en.bitcoin.it/wiki/Protocol_specification

Synopsis

Blocks

data Block Source

Data type describing a block in the bitcoin protocol. Blocks are sent in response to GetData messages that are requesting information from a block hash.

Constructors

Block 

Fields

blockHeader :: !BlockHeader

Header information for this block.

blockCoinbaseTx :: !CoinbaseTx

Coinbase transaction of this block.

blockTxns :: ![Tx]

List of transactions pertaining to this block.

Instances

data GetBlocks Source

Data type representing a GetBlocks message request. It is used in the bitcoin protocol to retrieve blocks from a peer by providing it a BlockLocator object. The BlockLocator is a sparse list of block hashes from the caller node with the purpose of informing the receiving node about the state of the caller's blockchain. The receiver node will detect a wrong branch in the caller's main chain and send the caller appropriate Blocks. The response to a GetBlocks message is an Inv message containing the list of block hashes pertaining to the request.

Constructors

GetBlocks 

Fields

getBlocksVersion :: !Word32

The protocol version

getBlocksLocator :: !BlockLocator

Block locator object. It is a list of block hashes from the most recent block back to the genesis block. The list is dense at first and sparse towards the end.

getBlocksHashStop :: !Hash256

Hash of the last desired block. If set to zero, the maximum number of block hashes is returned (500).

Block Headers

data BlockHeader Source

Data type recording information on a Block. The hash of a block is defined as the hash of this data structure. The block mining process involves finding a partial hash collision by varying the nonce in the BlockHeader and/or additional randomness in the CoinbaseTx of this Block. Variations in the CoinbaseTx will result in different merkle roots in the BlockHeader.

Constructors

BlockHeader 

Fields

blockVersion :: !Word32

Block version information, based on the version of the software creating this block.

prevBlock :: !Hash256

Hash of the previous block (parent) referenced by this block.

merkleRoot :: !Hash256

Root of the merkle tree of all transactions pertaining to this block.

blockTimestamp :: !Word32

Unix timestamp recording when this block was created

blockBits :: !Word32

The difficulty target being used for this block

bhNonce :: !Word32

A random nonce used to generate this block. Additional randomness is included in the coinbase transaction of this block.

data GetHeaders Source

Similar to the GetBlocks message type but for retrieving block headers only. The response to a GetHeaders request is a Headers message containing a list of block headers pertaining to the request. A maximum of 2000 block headers can be returned. GetHeaders is used by thin (SPV) clients to exclude block contents when synchronizing the blockchain.

Constructors

GetHeaders 

Fields

getHeadersVersion :: !Word32

The protocol version

getHeadersBL :: !BlockLocator

Block locator object. It is a list of block hashes from the most recent block back to the Genesis block. The list is dense at first and sparse towards the end.

getHeadersHashStop :: !Hash256

Hash of the last desired block header. When set to zero, the maximum number of block headers is returned (2000)

data Headers Source

The Headers type is used to return a list of block headers in response to a GetHeaders message.

Constructors

Headers 

Fields

headersList :: ![BlockHeaderCount]

List of block headers with respective transaction counts

type BlockHeaderCount = (BlockHeader, VarInt)Source

BlockHeader type with a transaction count as VarInt

blockid :: BlockHeader -> Hash256Source

Compute the hash of a block header

Requesting data

data GetData Source

The GetData type is used to retrieve information on a specific object (Block or Tx) identified by the objects hash. The payload of a GetData request is a list of InvVector which represent all the hashes for which a node wants to request information. The response to a GetBlock message wille be either a Block or a Tx message depending on the type of the object referenced by the hash. Usually, GetData messages are sent after a node receives an Inv message to obtain information on unknown object hashes.

Constructors

GetData 

Fields

getDataList :: ![InvVector]

List of object hashes

data Inv Source

Inv messages are used by nodes to advertise their knowledge of new objects by publishing a list of hashes. Inv messages can be sent unsolicited or in response to a GetBlocks message.

Constructors

Inv 

Fields

invList :: ![InvVector]

Inventory vectors

Instances

data InvVector Source

Invectory vectors represent hashes identifying objects such as a Block or a Tx. They are sent inside messages to notify other peers about new data or data they have requested.

Constructors

InvVector 

Fields

invType :: !InvType

Type of the object referenced by this inventory vector

invHash :: !Hash256

Hash of the object referenced by this inventory vector

data InvType Source

Data type identifying the type of an inventory vector.

Constructors

InvError

Error. Data containing this type can be ignored.

InvTx

InvVector hash is related to a transaction

InvBlock

InvVector hash is related to a block

InvMerkleBlock

InvVector has is related to a merkle block

data NotFound Source

A NotFound message is returned as a response to a GetData message whe one of the requested objects could not be retrieved. This could happen, for example, if a tranasaction was requested and was not available in the memory pool of the receiving node.

Constructors

NotFound 

Fields

notFoundList :: ![InvVector]

Inventory vectors related to this request

Scripts

More informations on scripts is available here: http://en.bitcoin.it/wiki/Script

data 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 the spending signatures in the input of a transaction

Constructors

Script 

Fields

scriptOps :: [ScriptOp]

List of script operators defining this script

data PushDataType Source

Data type representing the type of an OP_PUSHDATA opcode.

Constructors

OPCODE

The next opcode bytes is data to be pushed onto the stack

OPDATA1

The next byte contains the number of bytes to be pushed onto the stack

OPDATA2

The next two bytes contains the number of bytes to be pushed onto the stack

OPDATA4

The next four bytes contains the number of bytes to be pushed onto the stack

opPushData :: ByteString -> ScriptOpSource

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

getScriptOps :: Get [ScriptOp]Source

Deserialize a list of ScriptOp inside the Get monad. This deserialization does not take into account the length of the script.

putScriptOps :: [ScriptOp] -> PutSource

Serialize a list of ScriptOp inside the Put monad. This serialization does not take into account the length of the script.

decodeScriptOps :: ByteString -> Either String ScriptSource

Decode a Script from a ByteString by omiting the length of the script. This is used to produce scripthash addresses.

encodeScriptOps :: Script -> ByteStringSource

Encode a Script into a ByteString by omiting the length of the script. This is used to produce scripthash addresses.

Transactions

data Tx Source

Data type representing a bitcoin transaction

Constructors

Tx 

Fields

txVersion :: !Word32

Transaction data format version

txIn :: ![TxIn]

List of transaction inputs

txOut :: ![TxOut]

List of transaction outputs

txLockTime :: !Word32

The block number of timestamp at which this transaction is locked

Instances

txid :: Tx -> Hash256Source

Computes the hash of a transaction.

cbid :: CoinbaseTx -> Hash256Source

Computes the hash of a coinbase transaction.

data CoinbaseTx Source

Data type representing the coinbase transaction of a Block. Coinbase transactions are special types of transactions which are created by miners when they find a new block. Coinbase transactions have no inputs. They have outputs sending the newly generated bitcoins together with all the block's fees to a bitcoin address (usually the miners address). Data can be embedded in a Coinbase transaction which can be chosen by the miner of a block. This data also typically contains some randomness which is used, together with the nonce, to find a partial hash collision on the block's hash.

Constructors

CoinbaseTx 

Fields

cbVersion :: !Word32

Transaction data format version.

cbPrevOutput :: !OutPoint

Previous outpoint. This is ignored for coinbase transactions but preserved for computing the correct txid.

cbData :: !ByteString

Data embedded inside the coinbase transaction.

cbInSequence :: !Word32

Transaction sequence number. This is ignored for coinbase transactions but preserved for computing the correct txid.

cbOut :: ![TxOut]

List of transaction outputs.

cbLockTime :: !Word32

The block number of timestamp at which this transaction is locked.

data TxIn Source

Data type representing a transaction input.

Constructors

TxIn 

Fields

prevOutput :: !OutPoint

Reference the previous transaction output (hash + position)

scriptInput :: !Script

Script providing the requirements of the previous transaction output to spend those coins.

txInSequence :: !Word32

Transaction version as defined by the sender of the transaction. The intended use is for replacing transactions with new information before the transaction is included in a block.

data TxOut Source

Data type representing a transaction output.

Constructors

TxOut 

Fields

outValue :: !Word64

Transaction output value.

scriptOutput :: !Script

Script specifying the conditions to spend this output.

data OutPoint Source

The OutPoint is used inside a transaction input to reference the previous transaction output that it is spending.

Constructors

OutPoint 

Fields

outPointHash :: !Hash256

The hash of the referenced transaction.

outPointIndex :: !Word32

The position of the specific output in the transaction. The first output position is 0.

encodeTxid :: Hash256 -> StringSource

Encodes a transaction hash as little endian in HEX format. This is mostly used for displaying transaction ids. Internally, these ids are handled as big endian but are transformed to little endian when displaying them.

decodeTxid :: String -> Maybe Hash256Source

Decodes a little endian transaction hash in HEX format.

Merkle trees and bloom filters

data MerkleBlock Source

Constructors

MerkleBlock 

Fields

merkleHeader :: !BlockHeader

Header information for this merkle block.

merkleTotalTxns :: !Word32

Number of transactions in the block (including unmatched transactions).

mHashes :: [Hash256]

Hashes in depth-first order. They are used to rebuild a partial merkle tree.

mFlags :: [Bool]

Flag bits, packed per 8 in a byte. Least significant bit first. Flag bits are used to rebuild a partial merkle tree.

Bloom Filter

data BloomFlags Source

The bloom flags are used to tell the remote peer how to auto-update the provided bloom filter.

Constructors

BloomUpdateNone

Never update

BloomUpdateAll

Auto-update on all outputs

BloomUpdateP2PubKeyOnly

Only auto-update on outputs that are pay-to-pubkey or pay-to-multisig. This is the default setting.

data BloomFilter Source

A bloom filter is a probabilistic data structure that SPV clients send to other peers to filter the set of transactions received from them. Bloom filters are probabilistic and have a false positive rate. Some transactions that pass the filter may not be relevant to the receiving peer. By controlling the false positive rate, SPV nodes can trade off bandwidth versus privacy.

Constructors

BloomFilter 

Fields

bloomData :: Seq Word8

Bloom filter data

bloomFull :: Bool

Flag indicating if the filter is full (bloomData is all 0x00)

bloomEmpty :: Bool

Flag indicating if the filter is empty (bloomData is all 0xff)

bloomHashFuncs :: Word32

Number of hash functions for this filter

bloomTweak :: Word32

Hash function random nonce

bloomFlags :: BloomFlags

Bloom filter auto-update flags

newtype FilterLoad Source

Set a new bloom filter on the peer connection.

Constructors

FilterLoad 

newtype FilterAdd Source

Add the given data element to the connections current filter without requiring a completely new one to be set.

Constructors

FilterAdd 

Network types

newtype VarInt Source

Data type representing a variable length integer. The VarInt type usually precedes an array or a string that can vary in length.

Constructors

VarInt 

Fields

getVarInt :: Word64
 

newtype VarString Source

Data type for variable length strings. Variable length strings are serialized as a VarInt followed by a bytestring.

Constructors

VarString 

data NetworkAddress Source

Data type describing a bitcoin network address. Addresses are stored in IPv6. IPv4 addresses are mapped to IPv6 using IPv4 mapped IPv6 addresses: http://en.wikipedia.org/wiki/IPv6#IPv4-mapped_IPv6_addresses. Sometimes, timestamps are sent together with the NetworkAddress such as in the Addr data type.

Constructors

NetworkAddress 

Fields

naServices :: !Word64

Bitmask of services available for this address

naAddress :: !(Word64, Word64)

IPv6 address serialized as big endian

naPort :: !Word16

Port number serialized as big endian

data Addr Source

Provides information on known nodes in the bitcoin network. An Addr type is sent inside a Message as a response to a GetAddr message.

Constructors

Addr 

type NetworkAddressTime = (Word32, NetworkAddress)Source

Network address with a timestamp

data Version Source

When a bitcoin node creates an outgoing connection to another node, the first message it will send is a Version message. The other node will similarly respond with it's own Version message.

Constructors

Version 

Fields

version :: !Word32

Protocol version being used by the node.

services :: !Word64

Bitmask of features to enable for this connection.

timestamp :: !Word64

UNIX timestamp

addrRecv :: !NetworkAddress

Network address of the node receiving this message.

addrSend :: !NetworkAddress

Network address of the node sending this message.

verNonce :: !Word64

Randomly generated identifying sent with every version message. This nonce is used to detect connection to self.

userAgent :: !VarString

User agent

startHeight :: !Word32

The height of the last block received by the sending node.

relay :: !Bool

Wether the remote peer should announce relaying transactions or not. This feature is enabled since version >= 70001. See BIP37 for more details.

newtype Ping Source

A Ping message is sent to bitcoin peers to check if a TCP/IP connection is still valid.

Constructors

Ping 

Fields

pingNonce :: Word64

A random nonce used to identify the recipient of the ping request once a Pong response is received.

newtype Pong Source

A Pong message is sent as a response to a ping message.

Constructors

Pong 

Fields

pongNonce :: Word64

When responding to a Ping request, the nonce from the Ping is copied in the Pong response.

data Alert Source

Data type describing signed messages that can be sent between bitcoin nodes to display important notifications to end users about the health of the network.

Constructors

Alert 

Fields

alertPayload :: !VarString

Alert payload.

alertSignature :: !VarString

ECDSA signature of the payload

Messages

data Message Source

The Message type is used to identify all the valid messages that can be sent between bitcoin peers. Only values of type Message will be accepted by other bitcoin peers as bitcoin protocol messages need to be correctly serialized with message headers. Serializing a Message value will include the MessageHeader with the correct checksum value automatically. No need to add the MessageHeader separately.

data MessageHeader Source

Data type representing the header of a Message. All messages sent between nodes contain a message header.

Constructors

MessageHeader 

Fields

headMagic :: !Word32

Network magic bytes. It is used to differentiate messages meant for different bitcoin networks, such as prodnet and testnet.

headCmd :: !MessageCommand

Message command identifying the type of message. included in the payload.

headPayloadSize :: !Word32

Byte length of the payload.

headChecksum :: !CheckSum32

Checksum of the payload.

data MessageCommand Source

A MessageCommand is included in a MessageHeader in order to identify the type of message present in the payload. This allows the message de-serialization code to know how to decode a particular message payload. Every valid Message constructor has a corresponding MessageCommand constructor.