haskoin-node-0.9.5: Haskoin Node P2P library for Bitcoin and Bitcoin Cash

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

Network.Haskoin.Node.Common

Description

Common functions used by Haskoin Node.

Synopsis

Documentation

type HostPort = (Host, Port) Source #

Type alias for a combination of hostname and port.

type Host = String Source #

Type alias for a hostname.

type Port = Int Source #

Type alias for a port number.

data OnlinePeer Source #

Data structure representing an online peer.

Constructors

OnlinePeer 

Fields

type Peer = Mailbox PeerMessage Source #

Mailbox for a peer.

type Chain = Mailbox ChainMessage Source #

Mailbox for chain header syncing process.

type Manager = Mailbox ManagerMessage Source #

Mailbox for peer manager process.

data NodeConfig Source #

General node configuration.

Constructors

NodeConfig 

Fields

data ManagerConfig Source #

Peer manager configuration.

Constructors

ManagerConfig 

Fields

data ManagerMessage Source #

Messages that can be sent to the peer manager.

Constructors

ManagerConnect

try to connect to peers

ManagerGetPeers !(Listen [OnlinePeer])

get all connected peers

ManagerGetOnlinePeer !Peer !(Listen (Maybe OnlinePeer))

get a peer information

ManagerPurgePeers

delete all known peers

ManagerCheckPeer !Peer

check this peer

ManagerPeerMessage !Peer !Message

peer got a message that is forwarded to manager

ManagerPeerDied !Child !(Maybe SomeException)

child died

ManagerBestBlock !BlockHeight

set this as our best block

data ChainConfig Source #

Configuration for chain syncing process.

Constructors

ChainConfig 

Fields

data ChainMessage Source #

Messages that can be sent to the chain process.

Constructors

ChainGetBest !(Listen BlockNode)

get best block known

ChainHeaders !Peer ![BlockHeader] 
ChainGetAncestor !BlockHeight !BlockNode !(Listen (Maybe BlockNode))

get ancestor for BlockNode at BlockHeight

ChainGetSplit !BlockNode !BlockNode !(Listen BlockNode)

get highest common node

ChainGetBlock !BlockHash !(Listen (Maybe BlockNode))

get a block header

ChainIsSynced !(Listen Bool)

is chain in sync with network?

ChainPing

internal message for process housekeeping

ChainPeerConnected !Peer !SockAddr

internal message to notify that a peer has connected

ChainPeerDisconnected !Peer !SockAddr

internal message to notify that a peer has disconnected

data ChainEvent Source #

Events originating from chain syncing process.

Constructors

ChainBestBlock !BlockNode

chain has new best block

ChainSynced !BlockNode

chain is in sync with the network

Instances
Eq ChainEvent Source # 
Instance details

Defined in Network.Haskoin.Node.Common

Show ChainEvent Source # 
Instance details

Defined in Network.Haskoin.Node.Common

data NodeEvent Source #

Chain and peer events generated by the node.

Constructors

ChainEvent !ChainEvent

events from the chain syncing process

PeerEvent !PeerEvent

events from peers and peer manager

Instances
Eq NodeEvent Source # 
Instance details

Defined in Network.Haskoin.Node.Common

data PeerConfig Source #

Configuration for a particular peer.

Constructors

PeerConfig 

Fields

data PeerException Source #

Reasons why a peer may stop working.

Constructors

PeerMisbehaving !String

peer is being a naughty boy

DuplicateVersion

peer sent an extra version message

DecodeHeaderError

incoming message headers could not be decoded

CannotDecodePayload

incoming message payload could not be decoded

PeerIsMyself

nonce for peer matches ours

PayloadTooLarge !Word32

message payload too large

PeerAddressInvalid

peer address not valid

PeerSentBadHeaders

peer sent wrong headers

NotNetworkPeer

peer cannot serve block chain data

PeerNoSegWit

peer has no segwit support

PeerTimeout

request to peer timed out

PurgingPeer

peers are being purged

UnknownPeer

peer is unknown

data PeerEvent Source #

Events originating from peers and the peer manager.

Constructors

PeerConnected !Peer !SockAddr

new peer connected

PeerDisconnected !Peer !SockAddr

peer disconnected

PeerMessage !Peer !Message

peer sent a message

Instances
Eq PeerEvent Source # 
Instance details

Defined in Network.Haskoin.Node.Common

data PeerMessage Source #

Incoming messages that a peer accepts.

toSockAddr :: MonadUnliftIO m => HostPort -> m [SockAddr] Source #

Resolve a host and port to a list of SockAddr. May make use DNS resolver.

fromSockAddr :: MonadUnliftIO m => SockAddr -> m (Maybe HostPort) Source #

Convert a SockAddr to a a numeric host and port.

myVersion :: Word32 Source #

Our protocol version.

managerPeerMessage :: MonadIO m => Peer -> Message -> Manager -> m () Source #

Internal function used by peer to send a message to the peer manager.

managerGetPeers :: MonadIO m => Manager -> m [OnlinePeer] Source #

Get list of connected peers from manager.

managerGetPeer :: MonadIO m => Peer -> Manager -> m (Maybe OnlinePeer) Source #

Get information for an online peer from manager.

killPeer :: MonadIO m => PeerException -> Peer -> m () Source #

Kill a peer with the provided exception.

managerCheck :: MonadIO m => Peer -> Manager -> m () Source #

Internal function used by manager to check peers periodically.

managerConnect :: MonadIO m => Manager -> m () Source #

Internal function used to ask manager to connect to a new peer.

managerSetBest :: MonadIO m => BlockHeight -> Manager -> m () Source #

Set the best block that the manager knows about.

sendMessage :: MonadIO m => Message -> Peer -> m () Source #

Send a network message to peer.

peerGetPublisher :: MonadUnliftIO m => Int -> Peer -> m (Maybe (Publisher Message)) Source #

Get a publisher associated to a peer. Must provide timeout as peer may disconnect and become unresponsive.

peerGetBlocks :: MonadUnliftIO m => Network -> Int -> Peer -> [BlockHash] -> m (Maybe [Block]) Source #

Request full blocks from peer. Will return Nothing if the list of blocks returned by the peer is incomplete, comes out of order, or a timeout is reached.

peerGetTxs :: MonadUnliftIO m => Network -> Int -> Peer -> [TxHash] -> m (Maybe [Tx]) Source #

Request transactions from peer. Will return Nothing if the list of transactions returned by the peer is incomplete, comes out of order, or a timeout is reached.

peerGetData :: MonadUnliftIO m => Int -> Peer -> GetData -> m (Maybe [Either Tx Block]) Source #

Request transactions and/or blocks from peer. Return maybe if any single inventory fails to be retrieved, if they come out of order, or if timeout is reached.

peerPing :: MonadUnliftIO m => Int -> Peer -> m Bool Source #

Ping a peer and await response. Return False if response not received before timeout.

buildVersion :: Network -> Word64 -> BlockHeight -> NetworkAddress -> NetworkAddress -> Word64 -> Version Source #

Create version data structure.

chainGetBlock :: MonadIO m => BlockHash -> Chain -> m (Maybe BlockNode) Source #

Get a block header from Chain process.

chainGetBest :: MonadIO m => Chain -> m BlockNode Source #

Get best block header from chain process.

chainGetAncestor :: MonadIO m => BlockHeight -> BlockNode -> Chain -> m (Maybe BlockNode) Source #

Get ancestor of BlockNode at BlockHeight from chain process.

chainGetParents :: MonadIO m => BlockHeight -> BlockNode -> Chain -> m [BlockNode] Source #

Get parents of BlockNode starting at BlockHeight from chain process.

chainGetSplitBlock :: MonadIO m => BlockNode -> BlockNode -> Chain -> m BlockNode Source #

Get last common block from chain process.

chainPeerConnected :: MonadIO m => Peer -> SockAddr -> Chain -> m () Source #

Notify chain that a new peer is connected.

chainPeerDisconnected :: MonadIO m => Peer -> SockAddr -> Chain -> m () Source #

Notify chain that a peer has disconnected.

chainBlockMain :: MonadIO m => BlockHash -> Chain -> m Bool Source #

Is given BlockHash in the main chain?

chainIsSynced :: MonadIO m => Chain -> m Bool Source #

Is chain in sync with network?

chainHeaders :: MonadIO m => Peer -> [BlockHeader] -> Chain -> m () Source #

Peer sends a bunch of headers to the chain process.

withConnection :: MonadUnliftIO m => SockAddr -> (AppData -> m a) -> m a Source #

Connect to a socket via TCP.

median :: Fractional a => [a] -> Maybe a Source #

Calculate the median value from a list. The list must not be empty.