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

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

Network.Haskoin.Network

Contents

Description

This module provides basic types used for the Bitcoin networking protocol together with Serialize instances for efficiently serializing and de-serializing them.

Synopsis

Network Data Types

newtype Addr Source #

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

Constructors

Addr 
Instances
Eq Addr Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

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

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

Show Addr Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

showsPrec :: Int -> Addr -> ShowS #

show :: Addr -> String #

showList :: [Addr] -> ShowS #

Serialize Addr Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

put :: Putter Addr #

get :: Get Addr #

type NetworkAddressTime = (Word32, NetworkAddress) Source #

Network address with a timestamp.

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

Instances
Eq Alert Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

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

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

Read Alert Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Show Alert Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

showsPrec :: Int -> Alert -> ShowS #

show :: Alert -> String #

showList :: [Alert] -> ShowS #

Serialize Alert Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

put :: Putter Alert #

get :: Get Alert #

newtype 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 of objects that a node wants. The response to a GetBlock message will 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 that contains unknown object hashes.

Constructors

GetData 

Fields

Instances
Eq GetData Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

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

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

Show GetData Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Serialize GetData Source # 
Instance details

Defined in Network.Haskoin.Network.Common

newtype Inv Source #

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

Constructors

Inv 

Fields

Instances
Eq Inv Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

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

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

Show Inv Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

showsPrec :: Int -> Inv -> ShowS #

show :: Inv -> String #

showList :: [Inv] -> ShowS #

Serialize Inv Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

put :: Putter Inv #

get :: Get Inv #

data InvVector Source #

Invectory vectors represent hashes identifying objects such as a Block or a Tx. They notify other peers about new data or data they have otherwise requested.

Constructors

InvVector 

Fields

data InvType Source #

Data type identifying the type of an inventory vector. SegWit types are only used in GetData messages, not Inv.

Constructors

InvError

error

InvTx

transaction

InvBlock

block

InvMerkleBlock

filtered block

InvWitnessTx

segwit transaction

InvWitnessBlock

segwit block

InvWitnessMerkleBlock

segwit filtere block

data NetworkAddress Source #

Data type describing a bitcoin network address. Addresses are stored in IPv6 format. IPv4 addresses are mapped to IPv6 using IPv4 mapped IPv6 addresses: http://en.wikipedia.org/wiki/IPv6#IPv4-mapped_IPv6_addresses.

Constructors

NetworkAddress 

Fields

newtype 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

Instances
Eq NotFound Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Show NotFound Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Serialize NotFound Source # 
Instance details

Defined in Network.Haskoin.Network.Common

newtype Ping Source #

A Ping message is sent to bitcoin peers to check if a connection is still open.

Constructors

Ping 

Fields

  • pingNonce :: Word64

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

Instances
Eq Ping Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

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

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

Read Ping Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Show Ping Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

showsPrec :: Int -> Ping -> ShowS #

show :: Ping -> String #

showList :: [Ping] -> ShowS #

Serialize Ping Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

put :: Putter Ping #

get :: Get Ping #

newtype Pong Source #

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

Constructors

Pong 

Fields

Instances
Eq Pong Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

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

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

Read Pong Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Show Pong Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

showsPrec :: Int -> Pong -> ShowS #

show :: Pong -> String #

showList :: [Pong] -> ShowS #

Serialize Pong Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

put :: Putter Pong #

get :: Get Pong #

data Reject Source #

The Reject message is sent when messages are rejected by a peer.

Constructors

Reject 

Fields

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

newtype VarString Source #

Data type for serialization of variable-length strings.

Constructors

VarString 

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

Instances
Eq Version Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Methods

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

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

Show Version Source # 
Instance details

Defined in Network.Haskoin.Network.Common

Serialize Version Source # 
Instance details

Defined in Network.Haskoin.Network.Common

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.

Useful Functions

reject :: MessageCommand -> RejectCode -> ByteString -> Reject Source #

Convenience function to build a Reject message.

nodeNone :: Word64 Source #

Node offers no services.

nodeNetwork :: Word64 Source #

Services indicate node is a full node that can serve full blocks.

nodeGetUTXO :: Word64 Source #

Services indicate node allows to request UTXO set.

nodeBloom :: Word64 Source #

Services indicate node accepts bloom filters.

nodeWitness :: Word64 Source #

Services indicate SegWit-capable node.

nodeXThin :: Word64 Source #

Services indicate Xtreme Thinblocks compatibility.

commandToString :: MessageCommand -> ByteString Source #

Convert a MessageCommand to its string representation.

stringToCommand :: ByteString -> Maybe MessageCommand Source #

Read a MessageCommand from its string representation.

Network Message

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.

Instances
Eq Message Source # 
Instance details

Defined in Network.Haskoin.Network.Message

Methods

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

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

Show Message Source # 
Instance details

Defined in Network.Haskoin.Network.Message

data MessageHeader Source #

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

Constructors

MessageHeader 

Fields

msgType :: Message -> MessageCommand Source #

Get MessageCommand assocated with a message.

putMessage :: Network -> Putter Message Source #

Serializer for network messages.

getMessage :: Network -> Get Message Source #

Deserializer for network messages.

Bloom Filters

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

auto-update on pay-to-pubkey or pay-to-multisig (default)

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 can have false positives but not false negatives. 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

newtype FilterAdd Source #

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

Constructors

FilterAdd 

bloomCreate Source #

Arguments

:: Int

number of elements

-> Double

false positive rate

-> Word32

random nonce (tweak) for the hash function

-> BloomFlags

bloom filter flags

-> BloomFilter

bloom filter

Build a bloom filter that will provide the given false positive rate when the given number of elements have been inserted.

bloomInsert Source #

Arguments

:: BloomFilter

Original bloom filter

-> ByteString

New data to insert

-> BloomFilter

Bloom filter containing the new data

Insert arbitrary data into a bloom filter. Returns the new bloom filter containing the new data.

bloomContains Source #

Arguments

:: BloomFilter

Bloom filter

-> ByteString

Data that will be checked against the given bloom filter

-> Bool

Returns True if the data matches the filter

Tests if some arbitrary data matches the filter. This can be either because the data was inserted into the filter or because it is a false positive.

isBloomValid Source #

Arguments

:: BloomFilter

Bloom filter to test

-> Bool

True if the given filter is valid

Tests if a given bloom filter is valid.

isBloomEmpty :: BloomFilter -> Bool Source #

Returns True if the filter is empty (all bytes set to 0x00)

isBloomFull :: BloomFilter -> Bool Source #

Returns True if the filter is full (all bytes set to 0xff)

acceptsFilters :: Word64 -> Bool Source #

Does the peer with these version services accept bloom filters?