Copyright | No rights reserved |
---|---|
License | UNLICENSE |
Maintainer | xenog@protonmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Block chain header synchronization and proof-of-work consensus functions.
Synopsis
- data BlockNode
- = BlockNode {
- nodeHeader :: !BlockHeader
- nodeHeight :: !BlockHeight
- nodeWork :: !BlockWork
- nodeSkip :: !BlockHash
- | GenesisNode {
- nodeHeader :: !BlockHeader
- nodeHeight :: !BlockHeight
- nodeWork :: !BlockWork
- = BlockNode {
- class Monad m => BlockHeaders m where
- type BlockWork = Integer
- genesisNode :: Network -> BlockNode
- genesisBlock :: Network -> Block
- isGenesis :: BlockNode -> Bool
- chooseBest :: BlockNode -> BlockNode -> BlockNode
- parentBlock :: BlockHeaders m => BlockHeader -> m (Maybe BlockNode)
- getParents :: BlockHeaders m => Int -> BlockNode -> m [BlockNode]
- getAncestor :: BlockHeaders m => BlockHeight -> BlockNode -> m (Maybe BlockNode)
- splitPoint :: BlockHeaders m => BlockNode -> BlockNode -> m BlockNode
- connectBlocks :: BlockHeaders m => Network -> Timestamp -> [BlockHeader] -> m (Either String [BlockNode])
- connectBlock :: BlockHeaders m => Network -> Timestamp -> BlockHeader -> m (Either String BlockNode)
- blockLocator :: BlockHeaders m => BlockNode -> m BlockLocator
- data HeaderMemory = HeaderMemory {}
- type ShortBlockHash = Word64
- type BlockMap = HashMap ShortBlockHash ShortByteString
- shortBlockHash :: BlockHash -> ShortBlockHash
- initialChain :: Network -> HeaderMemory
- genesisMap :: Network -> BlockMap
- appendBlocks :: Network -> Word32 -> BlockHeader -> Int -> [BlockHeader]
- validBlock :: Network -> Timestamp -> BlockNode -> BlockNode -> [BlockNode] -> BlockHeader -> BlockNode -> Either String BlockNode
- validCP :: Network -> BlockHeight -> BlockHash -> Bool
- afterLastCP :: Network -> BlockHeight -> BlockHeight -> Bool
- bip34 :: Network -> BlockHeight -> BlockHash -> Bool
- validVersion :: Network -> BlockHeight -> Word32 -> Bool
- lastNoMinDiff :: BlockHeaders m => Network -> BlockNode -> m BlockNode
- nextWorkRequired :: BlockHeaders m => Network -> BlockNode -> BlockHeader -> m Word32
- nextEdaWorkRequired :: BlockHeaders m => Network -> BlockNode -> BlockHeader -> m Word32
- nextDaaWorkRequired :: BlockHeaders m => Network -> BlockNode -> BlockHeader -> m Word32
- computeTarget :: Network -> BlockNode -> BlockNode -> Integer
- getSuitableBlock :: BlockHeaders m => BlockNode -> m BlockNode
- nextPowWorkRequired :: BlockHeaders m => Network -> BlockNode -> BlockHeader -> m Word32
- calcNextWork :: Network -> BlockHeader -> Timestamp -> Word32
- isValidPOW :: Network -> BlockHeader -> Bool
- blockPOW :: BlockHash -> Integer
- headerWork :: BlockHeader -> Integer
- diffInterval :: Network -> Word32
- blockLocatorNodes :: BlockHeaders m => BlockNode -> m [BlockNode]
- mineBlock :: Network -> Word32 -> BlockHeader -> BlockHeader
Documentation
Data structure representing a block header and its position in the block chain.
BlockNode | non-Genesis block header |
| |
GenesisNode | Genesis block header |
|
Instances
class Monad m => BlockHeaders m where Source #
Typeclass for block header chain storage monad.
addBlockHeader :: BlockNode -> m () Source #
Add a new BlockNode
to the chain. Does not validate.
getBlockHeader :: BlockHash -> m (Maybe BlockNode) Source #
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.
Instances
Monad m => BlockHeaders (StateT HeaderMemory m) Source # | |
Defined in Network.Haskoin.Block.Headers addBlockHeader :: BlockNode -> StateT HeaderMemory m () Source # getBlockHeader :: BlockHash -> StateT HeaderMemory m (Maybe BlockNode) Source # getBestBlockHeader :: StateT HeaderMemory m BlockNode Source # setBestBlockHeader :: BlockNode -> StateT HeaderMemory m () Source # addBlockHeaders :: [BlockNode] -> StateT HeaderMemory m () Source # |
Header Chain Storage Functions
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.
:: BlockHeaders m | |
=> Int | |
-> BlockNode | |
-> m [BlockNode] | starts from immediate parent |
Get a number of parents for the provided block.
getAncestor :: BlockHeaders m => BlockHeight -> BlockNode -> m (Maybe BlockNode) Source #
Get the ancestor of the provided BlockNode
at the specified
BlockHeight
.
splitPoint :: BlockHeaders m => BlockNode -> BlockNode -> m BlockNode Source #
Find the last common block ancestor between provided block headers.
:: BlockHeaders m | |
=> Network | |
-> Timestamp | current time |
-> [BlockHeader] | |
-> m (Either String [BlockNode]) |
Validate a list of continuous block headers and import them to the
block chain. Return Left
on failure with error information.
:: BlockHeaders m | |
=> Network | |
-> Timestamp | current time |
-> BlockHeader | |
-> m (Either String BlockNode) |
Validate and connect single block header to the block chain. Return Left
if fails
to be validated.
blockLocator :: BlockHeaders m => BlockNode -> m BlockLocator Source #
Get block locator.
In-Memory Header Chain Store
data HeaderMemory Source #
Memory-based header tree.
Instances
type ShortBlockHash = Word64 Source #
Short version of the block hash. Uses the good end of the hash (the part that doesn't have a long string of zeroes).
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.
shortBlockHash :: BlockHash -> ShortBlockHash Source #
Calculate short block hash taking eight non-zero bytes from the 16-byte hash. This function will take the bytes that are not on the zero-side of the hash, making colissions between short block hashes difficult.
initialChain :: Network -> HeaderMemory Source #
Initialize memory-based chain.
genesisMap :: Network -> BlockMap Source #
Initialize map for memory-based chain.
Helper Functions
:: Network | |
-> Word32 | random seed |
-> BlockHeader | |
-> Int | |
-> [BlockHeader] |
Generate and append new blocks (mining). Only practical in regtest network.
:: Network | |
-> Timestamp | current time |
-> BlockNode | best block |
-> BlockNode | immediate parent |
-> [BlockNode] | 10 parents above |
-> BlockHeader | header to validate |
-> BlockNode | skip node (black magic) |
-> Either String BlockNode |
Validate this block header. Build a BlockNode
if successful.
:: Network | |
-> BlockHeight | new child height |
-> BlockHash | new child hash |
-> Bool |
Verify that checkpoint location is valid.
:: Network | |
-> BlockHeight | best height |
-> BlockHeight | new imported block height |
-> Bool |
New block height above the last checkpoint imported. Used to prevent a reorg below the highest checkpoint that was already imported.
:: Network | |
-> BlockHeight | new child height |
-> BlockHash | new child hash |
-> Bool |
This block should be at least version 2 (BIP34). Block height must be included in the coinbase transaction to prevent non-unique transaction hashes.
:: Network | |
-> BlockHeight | new child height |
-> Word32 | new child version |
-> Bool |
Check if the provided block height and version are valid.
lastNoMinDiff :: BlockHeaders m => Network -> BlockNode -> m BlockNode Source #
Find last block with normal, as opposed to minimum difficulty (for test networks).
nextWorkRequired :: BlockHeaders m => Network -> BlockNode -> BlockHeader -> m Word32 Source #
Returns the work required on a block header given the previous block. This
coresponds to bitcoind
function GetNextWorkRequired
in main.cpp
.
nextEdaWorkRequired :: BlockHeaders m => Network -> BlockNode -> BlockHeader -> m Word32 Source #
Find out the next amount of work required according to the Emergency Difficulty Adjustment (EDA) algorithm from Bitcoin Cash.
nextDaaWorkRequired :: BlockHeaders m => Network -> BlockNode -> BlockHeader -> m Word32 Source #
Find the next amount of work required according to the Difficulty Adjustment Algorithm (DAA) from Bitcoin Cash.
computeTarget :: Network -> BlockNode -> BlockNode -> Integer Source #
Compute Bitcoin Cash DAA target for a new block.
getSuitableBlock :: BlockHeaders m => BlockNode -> m BlockNode Source #
Get suitable block for Bitcoin Cash DAA computation.
nextPowWorkRequired :: BlockHeaders m => Network -> BlockNode -> BlockHeader -> m Word32 Source #
Returns the work required on a block header given the previous block. This coresponds to bitcoind function GetNextWorkRequired in main.cpp.
:: Network | |
-> BlockHeader | last block in previous retarget (parent) |
-> Timestamp | timestamp of first block in previous retarget |
-> Word32 |
Computes the work required for the first block in a new retarget period.
isValidPOW :: Network -> BlockHeader -> Bool Source #
Returns True if the difficulty target (bits) of the header is valid and the
proof of work of the header matches the advertised difficulty target. This
function corresponds to the function CheckProofOfWork
from bitcoind
in
main.cpp
.
blockPOW :: BlockHash -> Integer Source #
Returns the proof of work of a block header hash as an Integer
number.
headerWork :: BlockHeader -> Integer Source #
Returns the work represented by this block. Work is defined as the number of tries needed to solve a block in the average case with respect to the target.
diffInterval :: Network -> Word32 Source #
Number of blocks on average between difficulty cycles (2016 blocks).
blockLocatorNodes :: BlockHeaders m => BlockNode -> m [BlockNode] Source #
Get list of blocks for a block locator.
mineBlock :: Network -> Word32 -> BlockHeader -> BlockHeader Source #
Become rich beyond your wildest dreams.