haskoin-core-0.19.0: Bitcoin & Bitcoin Cash library for Haskell
CopyrightNo rights reserved
LicenseMIT
Maintainerjprupp@protonmail.ch
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Haskoin.Block.Common

Contents

Description

Common data types and functions to handle blocks from the block chain.

Synopsis

Blocks

data Block Source #

Block header and transactions.

Constructors

Block 

Fields

Instances

Instances details
Eq Block Source # 
Instance details

Defined in Haskoin.Block.Common

Methods

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

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

Read Block Source # 
Instance details

Defined in Haskoin.Block.Common

Show Block Source # 
Instance details

Defined in Haskoin.Block.Common

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

Generic Block Source # 
Instance details

Defined in Haskoin.Block.Common

Associated Types

type Rep Block :: Type -> Type #

Methods

from :: Block -> Rep Block x #

to :: Rep Block x -> Block #

Hashable Block Source # 
Instance details

Defined in Haskoin.Block.Common

Methods

hashWithSalt :: Int -> Block -> Int #

hash :: Block -> Int #

ToJSON Block Source # 
Instance details

Defined in Haskoin.Block.Common

FromJSON Block Source # 
Instance details

Defined in Haskoin.Block.Common

Serialize Block Source # 
Instance details

Defined in Haskoin.Block.Common

Methods

put :: Putter Block #

get :: Get Block #

NFData Block Source # 
Instance details

Defined in Haskoin.Block.Common

Methods

rnf :: Block -> () #

type Rep Block Source # 
Instance details

Defined in Haskoin.Block.Common

type Rep Block = D1 ('MetaData "Block" "Haskoin.Block.Common" "haskoin-core-0.19.0-inplace" 'False) (C1 ('MetaCons "Block" 'PrefixI 'True) (S1 ('MetaSel ('Just "blockHeader") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockHeader) :*: S1 ('MetaSel ('Just "blockTxns") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Tx])))

type BlockHeight = Word32 Source #

Height of a block in the block chain, 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

Instances

Instances details
Eq BlockHeader Source # 
Instance details

Defined in Haskoin.Block.Common

Ord BlockHeader Source # 
Instance details

Defined in Haskoin.Block.Common

Read BlockHeader Source # 
Instance details

Defined in Haskoin.Block.Common

Show BlockHeader Source # 
Instance details

Defined in Haskoin.Block.Common

Generic BlockHeader Source # 
Instance details

Defined in Haskoin.Block.Common

Associated Types

type Rep BlockHeader :: Type -> Type #

Hashable BlockHeader Source # 
Instance details

Defined in Haskoin.Block.Common

ToJSON BlockHeader Source # 
Instance details

Defined in Haskoin.Block.Common

FromJSON BlockHeader Source # 
Instance details

Defined in Haskoin.Block.Common

Serialize BlockHeader Source # 
Instance details

Defined in Haskoin.Block.Common

NFData BlockHeader Source # 
Instance details

Defined in Haskoin.Block.Common

Methods

rnf :: BlockHeader -> () #

type Rep BlockHeader Source # 
Instance details

Defined in Haskoin.Block.Common

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

Instances details
Eq GetBlocks Source # 
Instance details

Defined in Haskoin.Block.Common

Read GetBlocks Source # 
Instance details

Defined in Haskoin.Block.Common

Show GetBlocks Source # 
Instance details

Defined in Haskoin.Block.Common

Generic GetBlocks Source # 
Instance details

Defined in Haskoin.Block.Common

Associated Types

type Rep GetBlocks :: Type -> Type #

Serialize GetBlocks Source # 
Instance details

Defined in Haskoin.Block.Common

NFData GetBlocks Source # 
Instance details

Defined in Haskoin.Block.Common

Methods

rnf :: GetBlocks -> () #

type Rep GetBlocks Source # 
Instance details

Defined in Haskoin.Block.Common

type Rep GetBlocks = D1 ('MetaData "GetBlocks" "Haskoin.Block.Common" "haskoin-core-0.19.0-inplace" 'False) (C1 ('MetaCons "GetBlocks" 'PrefixI 'True) (S1 ('MetaSel ('Just "getBlocksVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "getBlocksLocator") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockLocator) :*: S1 ('MetaSel ('Just "getBlocksHashStop") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockHash))))

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 block chain.

Constructors

GetHeaders 

Fields

Instances

Instances details
Eq GetHeaders Source # 
Instance details

Defined in Haskoin.Block.Common

Read GetHeaders Source # 
Instance details

Defined in Haskoin.Block.Common

Show GetHeaders Source # 
Instance details

Defined in Haskoin.Block.Common

Generic GetHeaders Source # 
Instance details

Defined in Haskoin.Block.Common

Associated Types

type Rep GetHeaders :: Type -> Type #

Serialize GetHeaders Source # 
Instance details

Defined in Haskoin.Block.Common

NFData GetHeaders Source # 
Instance details

Defined in Haskoin.Block.Common

Methods

rnf :: GetHeaders -> () #

type Rep GetHeaders Source # 
Instance details

Defined in Haskoin.Block.Common

type Rep GetHeaders = D1 ('MetaData "GetHeaders" "Haskoin.Block.Common" "haskoin-core-0.19.0-inplace" 'False) (C1 ('MetaCons "GetHeaders" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHeadersVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "getHeadersBL") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockLocator) :*: S1 ('MetaSel ('Just "getHeadersHashStop") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockHash))))

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

Instances details
Eq BlockHash Source # 
Instance details

Defined in Haskoin.Block.Common

Ord BlockHash Source # 
Instance details

Defined in Haskoin.Block.Common

Read BlockHash Source # 
Instance details

Defined in Haskoin.Block.Common

Show BlockHash Source # 
Instance details

Defined in Haskoin.Block.Common

IsString BlockHash Source # 
Instance details

Defined in Haskoin.Block.Common

Generic BlockHash Source # 
Instance details

Defined in Haskoin.Block.Common

Associated Types

type Rep BlockHash :: Type -> Type #

Hashable BlockHash Source # 
Instance details

Defined in Haskoin.Block.Common

ToJSON BlockHash Source # 
Instance details

Defined in Haskoin.Block.Common

FromJSON BlockHash Source # 
Instance details

Defined in Haskoin.Block.Common

Serialize BlockHash Source # 
Instance details

Defined in Haskoin.Block.Common

NFData BlockHash Source # 
Instance details

Defined in Haskoin.Block.Common

Methods

rnf :: BlockHash -> () #

type Rep BlockHash Source # 
Instance details

Defined in Haskoin.Block.Common

type Rep BlockHash = D1 ('MetaData "BlockHash" "Haskoin.Block.Common" "haskoin-core-0.19.0-inplace" 'True) (C1 ('MetaCons "BlockHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "getBlockHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Hash256)))

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

Instances details
Eq Headers Source # 
Instance details

Defined in Haskoin.Block.Common

Methods

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

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

Read Headers Source # 
Instance details

Defined in Haskoin.Block.Common

Show Headers Source # 
Instance details

Defined in Haskoin.Block.Common

Generic Headers Source # 
Instance details

Defined in Haskoin.Block.Common

Associated Types

type Rep Headers :: Type -> Type #

Methods

from :: Headers -> Rep Headers x #

to :: Rep Headers x -> Headers #

Serialize Headers Source # 
Instance details

Defined in Haskoin.Block.Common

NFData Headers Source # 
Instance details

Defined in Haskoin.Block.Common

Methods

rnf :: Headers -> () #

type Rep Headers Source # 
Instance details

Defined in Haskoin.Block.Common

type Rep Headers = D1 ('MetaData "Headers" "Haskoin.Block.Common" "haskoin-core-0.19.0-inplace" 'True) (C1 ('MetaCons "Headers" 'PrefixI 'True) (S1 ('MetaSel ('Just "headersList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BlockHeaderCount])))

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.