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

Haskoin.Network.Common

Description

Common functions and data types related to peer-to-peer network.

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

Instances details
Eq Addr Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

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

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

Show Addr Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

showsPrec :: Int -> Addr -> ShowS #

show :: Addr -> String #

showList :: [Addr] -> ShowS #

Generic Addr Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep Addr :: Type -> Type #

Methods

from :: Addr -> Rep Addr x #

to :: Rep Addr x -> Addr #

Binary Addr Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

put :: Addr -> Put #

get :: Get Addr #

putList :: [Addr] -> Put #

Serial Addr Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

serialize :: MonadPut m => Addr -> m () #

deserialize :: MonadGet m => m Addr #

Serialize Addr Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

put :: Putter Addr #

get :: Get Addr #

NFData Addr Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: Addr -> () #

type Rep Addr Source # 
Instance details

Defined in Haskoin.Network.Common

type Rep Addr = D1 ('MetaData "Addr" "Haskoin.Network.Common" "haskoin-core-0.20.5-inplace" 'True) (C1 ('MetaCons "Addr" 'PrefixI 'True) (S1 ('MetaSel ('Just "addrList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [NetworkAddressTime])))

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

Instances details
Eq Alert Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

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

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

Read Alert Source # 
Instance details

Defined in Haskoin.Network.Common

Show Alert Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

showsPrec :: Int -> Alert -> ShowS #

show :: Alert -> String #

showList :: [Alert] -> ShowS #

Generic Alert Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep Alert :: Type -> Type #

Methods

from :: Alert -> Rep Alert x #

to :: Rep Alert x -> Alert #

Binary Alert Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

put :: Alert -> Put #

get :: Get Alert #

putList :: [Alert] -> Put #

Serial Alert Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

serialize :: MonadPut m => Alert -> m () #

deserialize :: MonadGet m => m Alert #

Serialize Alert Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

put :: Putter Alert #

get :: Get Alert #

NFData Alert Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: Alert -> () #

type Rep Alert Source # 
Instance details

Defined in Haskoin.Network.Common

type Rep Alert = D1 ('MetaData "Alert" "Haskoin.Network.Common" "haskoin-core-0.20.5-inplace" 'False) (C1 ('MetaCons "Alert" 'PrefixI 'True) (S1 ('MetaSel ('Just "alertPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarString) :*: S1 ('MetaSel ('Just "alertSignature") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarString)))

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

Instances details
Eq GetData Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

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

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

Show GetData Source # 
Instance details

Defined in Haskoin.Network.Common

Generic GetData Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep GetData :: Type -> Type #

Methods

from :: GetData -> Rep GetData x #

to :: Rep GetData x -> GetData #

Binary GetData Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

put :: GetData -> Put #

get :: Get GetData #

putList :: [GetData] -> Put #

Serial GetData Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

serialize :: MonadPut m => GetData -> m () #

deserialize :: MonadGet m => m GetData #

Serialize GetData Source # 
Instance details

Defined in Haskoin.Network.Common

NFData GetData Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: GetData -> () #

type Rep GetData Source # 
Instance details

Defined in Haskoin.Network.Common

type Rep GetData = D1 ('MetaData "GetData" "Haskoin.Network.Common" "haskoin-core-0.20.5-inplace" 'True) (C1 ('MetaCons "GetData" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDataList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [InvVector])))

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

Instances details
Eq Inv Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

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

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

Show Inv Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

showsPrec :: Int -> Inv -> ShowS #

show :: Inv -> String #

showList :: [Inv] -> ShowS #

Generic Inv Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep Inv :: Type -> Type #

Methods

from :: Inv -> Rep Inv x #

to :: Rep Inv x -> Inv #

Binary Inv Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

put :: Inv -> Put #

get :: Get Inv #

putList :: [Inv] -> Put #

Serial Inv Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

serialize :: MonadPut m => Inv -> m () #

deserialize :: MonadGet m => m Inv #

Serialize Inv Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

put :: Putter Inv #

get :: Get Inv #

NFData Inv Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: Inv -> () #

type Rep Inv Source # 
Instance details

Defined in Haskoin.Network.Common

type Rep Inv = D1 ('MetaData "Inv" "Haskoin.Network.Common" "haskoin-core-0.20.5-inplace" 'True) (C1 ('MetaCons "Inv" 'PrefixI 'True) (S1 ('MetaSel ('Just "invList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [InvVector])))

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

Instances

Instances details
Eq InvVector Source # 
Instance details

Defined in Haskoin.Network.Common

Show InvVector Source # 
Instance details

Defined in Haskoin.Network.Common

Generic InvVector Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep InvVector :: Type -> Type #

Binary InvVector Source # 
Instance details

Defined in Haskoin.Network.Common

Serial InvVector Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

serialize :: MonadPut m => InvVector -> m () #

deserialize :: MonadGet m => m InvVector #

Serialize InvVector Source # 
Instance details

Defined in Haskoin.Network.Common

NFData InvVector Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: InvVector -> () #

type Rep InvVector Source # 
Instance details

Defined in Haskoin.Network.Common

type Rep InvVector = D1 ('MetaData "InvVector" "Haskoin.Network.Common" "haskoin-core-0.20.5-inplace" 'False) (C1 ('MetaCons "InvVector" 'PrefixI 'True) (S1 ('MetaSel ('Just "invType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 InvType) :*: S1 ('MetaSel ('Just "invHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Hash256)))

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 filtered block

InvType Word32

unknown inv type

Instances

Instances details
Eq InvType Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

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

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

Read InvType Source # 
Instance details

Defined in Haskoin.Network.Common

Show InvType Source # 
Instance details

Defined in Haskoin.Network.Common

Generic InvType Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep InvType :: Type -> Type #

Methods

from :: InvType -> Rep InvType x #

to :: Rep InvType x -> InvType #

Binary InvType Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

put :: InvType -> Put #

get :: Get InvType #

putList :: [InvType] -> Put #

Serial InvType Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

serialize :: MonadPut m => InvType -> m () #

deserialize :: MonadGet m => m InvType #

Serialize InvType Source # 
Instance details

Defined in Haskoin.Network.Common

NFData InvType Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: InvType -> () #

type Rep InvType Source # 
Instance details

Defined in Haskoin.Network.Common

type Rep InvType = D1 ('MetaData "InvType" "Haskoin.Network.Common" "haskoin-core-0.20.5-inplace" 'False) (((C1 ('MetaCons "InvError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvTx" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "InvBlock" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvMerkleBlock" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "InvWitnessTx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvWitnessBlock" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "InvWitnessMerkleBlock" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InvType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))))

data HostAddress Source #

Instances

Instances details
Eq HostAddress Source # 
Instance details

Defined in Haskoin.Network.Common

Ord HostAddress Source # 
Instance details

Defined in Haskoin.Network.Common

Show HostAddress Source # 
Instance details

Defined in Haskoin.Network.Common

Generic HostAddress Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep HostAddress :: Type -> Type #

Binary HostAddress Source # 
Instance details

Defined in Haskoin.Network.Common

Serial HostAddress Source # 
Instance details

Defined in Haskoin.Network.Common

Serialize HostAddress Source # 
Instance details

Defined in Haskoin.Network.Common

NFData HostAddress Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: HostAddress -> () #

type Rep HostAddress Source # 
Instance details

Defined in Haskoin.Network.Common

type Rep HostAddress = D1 ('MetaData "HostAddress" "Haskoin.Network.Common" "haskoin-core-0.20.5-inplace" 'True) (C1 ('MetaCons "HostAddress" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

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

Instances

Instances details
Eq NetworkAddress Source # 
Instance details

Defined in Haskoin.Network.Common

Show NetworkAddress Source # 
Instance details

Defined in Haskoin.Network.Common

Generic NetworkAddress Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep NetworkAddress :: Type -> Type #

Binary NetworkAddress Source # 
Instance details

Defined in Haskoin.Network.Common

Serial NetworkAddress Source # 
Instance details

Defined in Haskoin.Network.Common

Serialize NetworkAddress Source # 
Instance details

Defined in Haskoin.Network.Common

NFData NetworkAddress Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: NetworkAddress -> () #

type Rep NetworkAddress Source # 
Instance details

Defined in Haskoin.Network.Common

type Rep NetworkAddress = D1 ('MetaData "NetworkAddress" "Haskoin.Network.Common" "haskoin-core-0.20.5-inplace" 'False) (C1 ('MetaCons "NetworkAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "naServices") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "naAddress") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HostAddress)))

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

Instances details
Eq NotFound Source # 
Instance details

Defined in Haskoin.Network.Common

Show NotFound Source # 
Instance details

Defined in Haskoin.Network.Common

Generic NotFound Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep NotFound :: Type -> Type #

Methods

from :: NotFound -> Rep NotFound x #

to :: Rep NotFound x -> NotFound #

Binary NotFound Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

put :: NotFound -> Put #

get :: Get NotFound #

putList :: [NotFound] -> Put #

Serial NotFound Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

serialize :: MonadPut m => NotFound -> m () #

deserialize :: MonadGet m => m NotFound #

Serialize NotFound Source # 
Instance details

Defined in Haskoin.Network.Common

NFData NotFound Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: NotFound -> () #

type Rep NotFound Source # 
Instance details

Defined in Haskoin.Network.Common

type Rep NotFound = D1 ('MetaData "NotFound" "Haskoin.Network.Common" "haskoin-core-0.20.5-inplace" 'True) (C1 ('MetaCons "NotFound" 'PrefixI 'True) (S1 ('MetaSel ('Just "notFoundList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [InvVector])))

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

Instances details
Eq Ping Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

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

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

Read Ping Source # 
Instance details

Defined in Haskoin.Network.Common

Show Ping Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

showsPrec :: Int -> Ping -> ShowS #

show :: Ping -> String #

showList :: [Ping] -> ShowS #

Generic Ping Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep Ping :: Type -> Type #

Methods

from :: Ping -> Rep Ping x #

to :: Rep Ping x -> Ping #

Binary Ping Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

put :: Ping -> Put #

get :: Get Ping #

putList :: [Ping] -> Put #

Serial Ping Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

serialize :: MonadPut m => Ping -> m () #

deserialize :: MonadGet m => m Ping #

Serialize Ping Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

put :: Putter Ping #

get :: Get Ping #

NFData Ping Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: Ping -> () #

type Rep Ping Source # 
Instance details

Defined in Haskoin.Network.Common

type Rep Ping = D1 ('MetaData "Ping" "Haskoin.Network.Common" "haskoin-core-0.20.5-inplace" 'True) (C1 ('MetaCons "Ping" 'PrefixI 'True) (S1 ('MetaSel ('Just "pingNonce") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

newtype Pong Source #

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

Constructors

Pong 

Fields

Instances

Instances details
Eq Pong Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

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

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

Read Pong Source # 
Instance details

Defined in Haskoin.Network.Common

Show Pong Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

showsPrec :: Int -> Pong -> ShowS #

show :: Pong -> String #

showList :: [Pong] -> ShowS #

Generic Pong Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep Pong :: Type -> Type #

Methods

from :: Pong -> Rep Pong x #

to :: Rep Pong x -> Pong #

Binary Pong Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

put :: Pong -> Put #

get :: Get Pong #

putList :: [Pong] -> Put #

Serial Pong Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

serialize :: MonadPut m => Pong -> m () #

deserialize :: MonadGet m => m Pong #

Serialize Pong Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

put :: Putter Pong #

get :: Get Pong #

NFData Pong Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: Pong -> () #

type Rep Pong Source # 
Instance details

Defined in Haskoin.Network.Common

type Rep Pong = D1 ('MetaData "Pong" "Haskoin.Network.Common" "haskoin-core-0.20.5-inplace" 'True) (C1 ('MetaCons "Pong" 'PrefixI 'True) (S1 ('MetaSel ('Just "pongNonce") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

data Reject Source #

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

Constructors

Reject 

Fields

Instances

Instances details
Eq Reject Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

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

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

Read Reject Source # 
Instance details

Defined in Haskoin.Network.Common

Show Reject Source # 
Instance details

Defined in Haskoin.Network.Common

Generic Reject Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep Reject :: Type -> Type #

Methods

from :: Reject -> Rep Reject x #

to :: Rep Reject x -> Reject #

Binary Reject Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

put :: Reject -> Put #

get :: Get Reject #

putList :: [Reject] -> Put #

Serial Reject Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

serialize :: MonadPut m => Reject -> m () #

deserialize :: MonadGet m => m Reject #

Serialize Reject Source # 
Instance details

Defined in Haskoin.Network.Common

NFData Reject Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: Reject -> () #

type Rep Reject Source # 
Instance details

Defined in Haskoin.Network.Common

type Rep Reject = D1 ('MetaData "Reject" "Haskoin.Network.Common" "haskoin-core-0.20.5-inplace" 'False) (C1 ('MetaCons "Reject" 'PrefixI 'True) ((S1 ('MetaSel ('Just "rejectMessage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MessageCommand) :*: S1 ('MetaSel ('Just "rejectCode") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RejectCode)) :*: (S1 ('MetaSel ('Just "rejectReason") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarString) :*: S1 ('MetaSel ('Just "rejectData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString))))

data RejectCode Source #

Rejection code associated to the Reject message.

Instances

Instances details
Eq RejectCode Source # 
Instance details

Defined in Haskoin.Network.Common

Read RejectCode Source # 
Instance details

Defined in Haskoin.Network.Common

Show RejectCode Source # 
Instance details

Defined in Haskoin.Network.Common

Generic RejectCode Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep RejectCode :: Type -> Type #

Binary RejectCode Source # 
Instance details

Defined in Haskoin.Network.Common

Serial RejectCode Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

serialize :: MonadPut m => RejectCode -> m () #

deserialize :: MonadGet m => m RejectCode #

Serialize RejectCode Source # 
Instance details

Defined in Haskoin.Network.Common

NFData RejectCode Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: RejectCode -> () #

type Rep RejectCode Source # 
Instance details

Defined in Haskoin.Network.Common

type Rep RejectCode = D1 ('MetaData "RejectCode" "Haskoin.Network.Common" "haskoin-core-0.20.5-inplace" 'False) (((C1 ('MetaCons "RejectMalformed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RejectInvalid" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RejectObsolete" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RejectDuplicate" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "RejectNonStandard" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RejectDust" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RejectInsufficientFee" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RejectCheckpoint" 'PrefixI 'False) (U1 :: Type -> Type))))

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

Instances

Instances details
Eq VarInt Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

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

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

Read VarInt Source # 
Instance details

Defined in Haskoin.Network.Common

Show VarInt Source # 
Instance details

Defined in Haskoin.Network.Common

Generic VarInt Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep VarInt :: Type -> Type #

Methods

from :: VarInt -> Rep VarInt x #

to :: Rep VarInt x -> VarInt #

Binary VarInt Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

put :: VarInt -> Put #

get :: Get VarInt #

putList :: [VarInt] -> Put #

Serial VarInt Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

serialize :: MonadPut m => VarInt -> m () #

deserialize :: MonadGet m => m VarInt #

Serialize VarInt Source # 
Instance details

Defined in Haskoin.Network.Common

NFData VarInt Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: VarInt -> () #

type Rep VarInt Source # 
Instance details

Defined in Haskoin.Network.Common

type Rep VarInt = D1 ('MetaData "VarInt" "Haskoin.Network.Common" "haskoin-core-0.20.5-inplace" 'True) (C1 ('MetaCons "VarInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "getVarInt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

newtype VarString Source #

Data type for serialization of variable-length strings.

Constructors

VarString 

Instances

Instances details
Eq VarString Source # 
Instance details

Defined in Haskoin.Network.Common

Read VarString Source # 
Instance details

Defined in Haskoin.Network.Common

Show VarString Source # 
Instance details

Defined in Haskoin.Network.Common

Generic VarString Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep VarString :: Type -> Type #

Binary VarString Source # 
Instance details

Defined in Haskoin.Network.Common

Serial VarString Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

serialize :: MonadPut m => VarString -> m () #

deserialize :: MonadGet m => m VarString #

Serialize VarString Source # 
Instance details

Defined in Haskoin.Network.Common

NFData VarString Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: VarString -> () #

type Rep VarString Source # 
Instance details

Defined in Haskoin.Network.Common

type Rep VarString = D1 ('MetaData "VarString" "Haskoin.Network.Common" "haskoin-core-0.20.5-inplace" 'True) (C1 ('MetaCons "VarString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getVarString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

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

Instances details
Eq Version Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

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

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

Show Version Source # 
Instance details

Defined in Haskoin.Network.Common

Generic Version Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Binary Version Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

put :: Version -> Put #

get :: Get Version #

putList :: [Version] -> Put #

Serial Version Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

serialize :: MonadPut m => Version -> m () #

deserialize :: MonadGet m => m Version #

Serialize Version Source # 
Instance details

Defined in Haskoin.Network.Common

NFData Version Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: Version -> () #

type Rep Version Source # 
Instance details

Defined in 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.

Instances

Instances details
Eq MessageCommand Source # 
Instance details

Defined in Haskoin.Network.Common

Read MessageCommand Source # 
Instance details

Defined in Haskoin.Network.Common

Show MessageCommand Source # 
Instance details

Defined in Haskoin.Network.Common

IsString MessageCommand Source # 
Instance details

Defined in Haskoin.Network.Common

Generic MessageCommand Source # 
Instance details

Defined in Haskoin.Network.Common

Associated Types

type Rep MessageCommand :: Type -> Type #

Binary MessageCommand Source # 
Instance details

Defined in Haskoin.Network.Common

Serial MessageCommand Source # 
Instance details

Defined in Haskoin.Network.Common

Serialize MessageCommand Source # 
Instance details

Defined in Haskoin.Network.Common

NFData MessageCommand Source # 
Instance details

Defined in Haskoin.Network.Common

Methods

rnf :: MessageCommand -> () #

type Rep MessageCommand Source # 
Instance details

Defined in Haskoin.Network.Common

type Rep MessageCommand = D1 ('MetaData "MessageCommand" "Haskoin.Network.Common" "haskoin-core-0.20.5-inplace" 'False) ((((C1 ('MetaCons "MCVersion" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MCVerAck" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MCAddr" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MCInv" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MCGetData" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "MCNotFound" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MCGetBlocks" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MCGetHeaders" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "MCTx" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MCBlock" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MCMerkleBlock" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "MCHeaders" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MCGetAddr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MCFilterLoad" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "MCFilterAdd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MCFilterClear" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MCPing" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "MCPong" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MCAlert" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MCMempool" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "MCReject" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MCSendHeaders" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MCOther" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))))))

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 -> MessageCommand Source #

Read a MessageCommand from its string representation.

putVarInt :: (MonadPut m, Integral a) => a -> m () Source #