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

Safe HaskellNone
LanguageHaskell2010

Network.Haskoin.Block

Contents

Synopsis

Documentation

data Block Source #

Block header and transactions.

Constructors

Block 

Fields

Instances
Eq Block Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Methods

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

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

Read Block Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Show Block Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

Serialize Block Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Methods

put :: Putter Block #

get :: Get Block #

NFData Block Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Methods

rnf :: Block -> () #

type BlockHeight = Word32 Source #

Height of a block in the blockchain, starting at 0 for Genesis.

type Timestamp = Word32 Source #

Block timestamp as Unix time (seconds since 1970-01-01 00:00 UTC).

data BlockHeader Source #

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

Constructors

BlockHeader 

Fields

type BlockLocator = [BlockHash] Source #

A block locator is a set of block headers, denser towards the best block and sparser towards the genesis block. It starts at the highest block known. It is used by a node to synchronize against the network. When the locator is provided to a peer, it will send back block hashes starting from the first block in the locator that it recognizes.

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 response to a GetBlocks message is an Inv message containing a list of block hashes that the peer believes this node is missing. The number of block hashes in that inv message will end at the stop block hash, at at the tip of the chain, or after 500 entries, whichever comes earlier.

Constructors

GetBlocks 

Fields

Instances
Eq GetBlocks Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Show GetBlocks Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Serialize GetBlocks Source # 
Instance details

Defined in Network.Haskoin.Block.Common

NFData GetBlocks Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Methods

rnf :: GetBlocks -> () #

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. A maximum of 2000 block headers can be returned. GetHeaders is used by simplified payment verification (SPV) clients to exclude block contents when synchronizing the blockchain.

Constructors

GetHeaders 

Fields

type BlockHeaderCount = (BlockHeader, VarInt) Source #

BlockHeader type with a transaction count as VarInt

newtype BlockHash Source #

Block header hash. To be serialized reversed for display purposes.

Constructors

BlockHash 
Instances
Eq BlockHash Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Ord BlockHash Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Read BlockHash Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Show BlockHash Source # 
Instance details

Defined in Network.Haskoin.Block.Common

IsString BlockHash Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Hashable BlockHash Source # 
Instance details

Defined in Network.Haskoin.Block.Common

ToJSON BlockHash Source # 
Instance details

Defined in Network.Haskoin.Block.Common

FromJSON BlockHash Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Serialize BlockHash Source # 
Instance details

Defined in Network.Haskoin.Block.Common

NFData BlockHash Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Methods

rnf :: BlockHash -> () #

blockHashToHex :: BlockHash -> Text Source #

Block hashes are reversed with respect to the in-memory byte order in a block hash when displayed.

hexToBlockHash :: Text -> Maybe BlockHash Source #

Convert a human-readable hex block hash into a BlockHash. Bytes are reversed as normal.

newtype Headers Source #

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

Constructors

Headers 

Fields

Instances
Eq Headers Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Methods

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

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

Show Headers Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Serialize Headers Source # 
Instance details

Defined in Network.Haskoin.Block.Common

NFData Headers Source # 
Instance details

Defined in Network.Haskoin.Block.Common

Methods

rnf :: Headers -> () #

decodeCompact Source #

Arguments

:: Word32 
-> (Integer, Bool)

true means overflow

Decode the compact number used in the difficulty target of a block.

The compact format is a representation of a whole number \(N\) using an unsigned 32-bit number similar to a floating point format. The most significant 8 bits are the unsigned exponent of base 256. This exponent can be thought of as the number of bytes of \(N\). The lower 23 bits are the mantissa. Bit number 24 represents the sign of \(N\).

\[ N = -1^{sign} \times mantissa \times 256^{exponent-3} \]

encodeCompact :: Integer -> Word32 Source #

Encode an Integer to the compact number format used in the difficulty target of a block.

Block Header Chain

type BlockWork = Integer Source #

Represents accumulated work in the blockchain so far.

class Monad m => BlockHeaders m where Source #

Typeclass for block header chain storage monad.

Methods

addBlockHeader :: BlockNode -> m () Source #

Add a new BlockNode to the chain. Does not validate.

getBlockHeader :: BlockHash -> m (Maybe BlockNode) Source #

Get a BlockNode associated with a BlockHash.

getBestBlockHeader :: m BlockNode Source #

Locate the BlockNode for the highest block in the chain

setBestBlockHeader :: BlockNode -> m () Source #

Set the highest block in the chain.

addBlockHeaders :: [BlockNode] -> m () Source #

Add a continuous bunch of block headers the chain. Does not validate.

data BlockNode Source #

Data structure representing a block header and its position in the blockchain.

Constructors

BlockNode

non-Genesis block header

Fields

GenesisNode

Genesis block header

Fields

type BlockMap = HashMap ShortBlockHash ShortByteString Source #

Memory-based map to a serialized BlockNode data structure. ShortByteString is used to avoid memory fragmentation and make the data structure compact.

getAncestor :: BlockHeaders m => BlockHeight -> BlockNode -> m (Maybe BlockNode) Source #

Get the ancestor of the provided BlockNode at the specified BlockHeight.

isGenesis :: BlockNode -> Bool Source #

Is the provided BlockNode the Genesis block?

initialChain :: Network -> HeaderMemory Source #

Initialize memory-based chain.

genesisMap :: Network -> BlockMap Source #

Initialize map for memory-based chain.

genesisNode :: Network -> BlockNode Source #

Build the genesis BlockNode for the supplied Network.

genesisBlock :: Network -> Block Source #

Generate the entire Genesis block for Network.

connectBlocks Source #

Arguments

:: BlockHeaders m 
=> Network 
-> Timestamp

current time

-> [BlockHeader] 
-> m (Either String [BlockNode]) 

Validate a list of continuous block headers and import them to the blockchain. Return Left on failure with error information.

connectBlock Source #

Arguments

:: BlockHeaders m 
=> Network 
-> Timestamp

current time

-> BlockHeader 
-> m (Either String BlockNode) 

Validate and connect single block header to the blockchain. Return Left if fails to be validated.

parentBlock :: BlockHeaders m => BlockHeader -> m (Maybe BlockNode) Source #

Block's parent. If the block header is in the store, its parent must also be there. No block header get deleted or pruned from the store.

splitPoint :: BlockHeaders m => BlockNode -> BlockNode -> m BlockNode Source #

Find the last common block ancestor between provided block headers.

blockLocator :: BlockHeaders m => BlockNode -> m BlockLocator Source #

Get block locator.

Merkle Blocks

data MerkleBlock Source #

Filtered block: a block with a partial Merkle tree that only includes the transactions that pass a bloom filter that was negotiated.

Constructors

MerkleBlock 

Fields

type MerkleRoot = Hash256 Source #

Hash of the block's Merkle root.

type FlagBits = [Bool] Source #

Bits that are used to rebuild partial merkle tree transaction hash list.

type PartialMerkleTree = [Hash256] Source #

Partial Merkle tree for a filtered block.

buildMerkleRoot Source #

Arguments

:: [TxHash]

transaction hashes (leaf nodes)

-> MerkleRoot

root of the Merkle tree

Computes the root of a Merkle tree from a list of leaf node hashes.

buildPartialMerkle Source #

Arguments

:: [(TxHash, Bool)]

transaction hash and whether to include

-> (FlagBits, PartialMerkleTree)

flag bits and partial Merkle tree

Build a partial Merkle tree. Provide a list of tuples with all transaction hashes in the block, and whether the transaction is to be included in the partial tree. Returns a flag bits structure and the computed partial Merkle tree.

merkleBlockTxs :: Network -> MerkleBlock -> Either String [TxHash] Source #

Get matching transactions from Merkle block.

testMerkleRoot :: Network -> MerkleBlock -> Bool Source #

Check if Merkle block root is valid against the block header.