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

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

Network.Haskoin.Block.Merkle

Contents

Description

Function to deal with Merkle trees inside blocks.

Synopsis

Documentation

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

Instances
Eq MerkleBlock Source # 
Instance details

Defined in Network.Haskoin.Block.Merkle

Read MerkleBlock Source # 
Instance details

Defined in Network.Haskoin.Block.Merkle

Show MerkleBlock Source # 
Instance details

Defined in Network.Haskoin.Block.Merkle

Generic MerkleBlock Source # 
Instance details

Defined in Network.Haskoin.Block.Merkle

Associated Types

type Rep MerkleBlock :: * -> * #

Hashable MerkleBlock Source # 
Instance details

Defined in Network.Haskoin.Block.Merkle

Serialize MerkleBlock Source # 
Instance details

Defined in Network.Haskoin.Block.Merkle

type Rep MerkleBlock Source # 
Instance details

Defined in Network.Haskoin.Block.Merkle

type Rep MerkleBlock = D1 (MetaData "MerkleBlock" "Network.Haskoin.Block.Merkle" "haskoin-core-0.8.4-AWaCExKDMsg51o0OUGuqyW" False) (C1 (MetaCons "MerkleBlock" PrefixI True) ((S1 (MetaSel (Just "merkleHeader") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 BlockHeader) :*: S1 (MetaSel (Just "merkleTotalTxns") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word32)) :*: (S1 (MetaSel (Just "mHashes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PartialMerkleTree) :*: S1 (MetaSel (Just "mFlags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FlagBits))))

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.

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.

Helper functions

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.

decodeMerkleFlags :: [Word8] -> FlagBits Source #

Unpack Merkle flags into FlagBits structure.

encodeMerkleFlags :: FlagBits -> [Word8] Source #

Pack Merkle flags from FlagBits.

calcTreeHeight Source #

Arguments

:: Int

number of transactions (leaf nodes)

-> Int

height of the merkle tree

Computes the height of a Merkle tree.

calcTreeWidth Source #

Arguments

:: Int

number of transactions (leaf nodes)

-> Int

height at which we want to compute the width

-> Int

width of the Merkle tree

Computes the width of a Merkle tree at a specific height. The transactions are at height 0.

hash2 :: Hash256 -> Hash256 -> Hash256 Source #

Concatenate and compute double SHA256.

calcHash Source #

Arguments

:: Int

height of the node

-> Int

position of the node (0 for the leftmost node)

-> [TxHash]

transaction hashes (leaf nodes)

-> Hash256

hash of the node at the specified position

Computes the hash of a specific node in a Merkle tree.

traverseAndBuild :: Int -> Int -> [(TxHash, Bool)] -> (FlagBits, PartialMerkleTree) Source #

Helper function to build partial Merkle tree. Used by buildPartialMerkle above.

traverseAndExtract :: Int -> Int -> Int -> FlagBits -> PartialMerkleTree -> Maybe (MerkleRoot, [TxHash], Int, Int) Source #

Helper function to extract transaction hashes from partial Merkle tree.

extractMatches Source #

Arguments

:: Network 
-> FlagBits 
-> PartialMerkleTree 
-> Int

number of transaction at height 0 (leaf nodes)

-> Either String (MerkleRoot, [TxHash])

Merkle root and list of matching transaction hashes

Extracts the matching hashes from a partial merkle tree. This will return the list of transaction hashes that have been included (set to true) in a call to buildPartialMerkle.

splitIn :: Int -> [a] -> [[a]] Source #

Helper function to split a list in chunks Int length. Last chunk may be smaller.

boolsToWord8 :: [Bool] -> Word8 Source #

Pack up to eight bools in a byte.