| Copyright | No rights reserved |
|---|---|
| License | MIT |
| Maintainer | jprupp@protonmail.ch |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Haskoin.Network.Common
Contents
Description
Common functions and data types related to peer-to-peer network.
Synopsis
- newtype Addr = Addr {
- list :: [NetworkAddressTime]
- type NetworkAddressTime = (Word32, NetworkAddress)
- data Alert = Alert {}
- newtype GetData = GetData {}
- newtype Inv = Inv {}
- data InvVector = InvVector {}
- data InvType
- data HostAddress
- hostToSockAddr :: HostAddress -> SockAddr
- sockToHostAddress :: SockAddr -> HostAddress
- data NetworkAddress = NetworkAddress {
- services :: !Word64
- address :: !HostAddress
- newtype NotFound = NotFound {}
- newtype Ping = Ping {}
- newtype Pong = Pong {}
- data Reject = Reject {
- message :: !MessageCommand
- code :: !RejectCode
- reason :: !VarString
- extra :: !ByteString
- data RejectCode
- newtype VarInt = VarInt {}
- newtype VarString = VarString {
- get :: ByteString
- data Version = Version {}
- data MessageCommand
- reject :: MessageCommand -> RejectCode -> ByteString -> Reject
- nodeNone :: Word64
- nodeNetwork :: Word64
- nodeGetUTXO :: Word64
- nodeBloom :: Word64
- nodeWitness :: Word64
- nodeXThin :: Word64
- commandToString :: MessageCommand -> ByteString
- stringToCommand :: ByteString -> MessageCommand
- putVarInt :: (MonadPut m, Integral a) => a -> m ()
Network Data Types
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 | |
Fields
| |
Instances
| Generic Addr Source # | |
| Show Addr Source # | |
| Binary Addr Source # | |
| Serial Addr Source # | |
Defined in Haskoin.Network.Common | |
| Serialize Addr Source # | |
| NFData Addr Source # | |
Defined in Haskoin.Network.Common | |
| Eq Addr Source # | |
| type Rep Addr Source # | |
Defined in Haskoin.Network.Common type Rep Addr = D1 ('MetaData "Addr" "Haskoin.Network.Common" "haskoin-core-1.1.0-EPeWWz60EKPlWai44F9WC" 'True) (C1 ('MetaCons "Addr" 'PrefixI 'True) (S1 ('MetaSel ('Just "list") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [NetworkAddressTime]))) | |
type NetworkAddressTime = (Word32, NetworkAddress) Source #
Network address with a timestamp.
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 | |
Instances
| Generic Alert Source # | |
| Read Alert Source # | |
| Show Alert Source # | |
| Binary Alert Source # | |
| Serial Alert Source # | |
Defined in Haskoin.Network.Common | |
| Serialize Alert Source # | |
| NFData Alert Source # | |
Defined in Haskoin.Network.Common | |
| Eq Alert Source # | |
| type Rep Alert Source # | |
Defined in Haskoin.Network.Common type Rep Alert = D1 ('MetaData "Alert" "Haskoin.Network.Common" "haskoin-core-1.1.0-EPeWWz60EKPlWai44F9WC" 'False) (C1 ('MetaCons "Alert" 'PrefixI 'True) (S1 ('MetaSel ('Just "payload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarString) :*: S1 ('MetaSel ('Just "signature") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarString))) | |
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.
Instances
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.
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 | |
Instances
| Generic InvVector Source # | |
| Show InvVector Source # | |
| Binary InvVector Source # | |
| Serial InvVector Source # | |
Defined in Haskoin.Network.Common | |
| Serialize InvVector Source # | |
| NFData InvVector Source # | |
Defined in Haskoin.Network.Common | |
| Eq InvVector Source # | |
| type Rep InvVector Source # | |
Defined in Haskoin.Network.Common type Rep InvVector = D1 ('MetaData "InvVector" "Haskoin.Network.Common" "haskoin-core-1.1.0-EPeWWz60EKPlWai44F9WC" '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 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
data HostAddress Source #
Instances
hostToSockAddr :: HostAddress -> SockAddr Source #
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
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.
Instances
| Generic NotFound Source # | |
| Show NotFound Source # | |
| Binary NotFound Source # | |
| Serial NotFound Source # | |
Defined in Haskoin.Network.Common | |
| Serialize NotFound Source # | |
| NFData NotFound Source # | |
Defined in Haskoin.Network.Common | |
| Eq NotFound Source # | |
| type Rep NotFound Source # | |
Defined in Haskoin.Network.Common | |
A Ping message is sent to bitcoin peers to check if a connection is still
open.
Constructors
| Ping | |
A Pong message is sent as a response to a ping message.
The Reject message is sent when messages are rejected by a peer.
Constructors
| Reject | |
Fields
| |
Instances
| Generic Reject Source # | |
| Read Reject Source # | |
| Show Reject Source # | |
| Binary Reject Source # | |
| Serial Reject Source # | |
Defined in Haskoin.Network.Common | |
| Serialize Reject Source # | |
| NFData Reject Source # | |
Defined in Haskoin.Network.Common | |
| Eq Reject Source # | |
| type Rep Reject Source # | |
Defined in Haskoin.Network.Common type Rep Reject = D1 ('MetaData "Reject" "Haskoin.Network.Common" "haskoin-core-1.1.0-EPeWWz60EKPlWai44F9WC" 'False) (C1 ('MetaCons "Reject" 'PrefixI 'True) ((S1 ('MetaSel ('Just "message") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MessageCommand) :*: S1 ('MetaSel ('Just "code") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RejectCode)) :*: (S1 ('MetaSel ('Just "reason") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarString) :*: S1 ('MetaSel ('Just "extra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)))) | |
data RejectCode Source #
Rejection code associated to the Reject message.
Constructors
| RejectMalformed | |
| RejectInvalid | |
| RejectObsolete | |
| RejectDuplicate | |
| RejectNonStandard | |
| RejectDust | |
| RejectInsufficientFee | |
| RejectCheckpoint |
Instances
Data type representing a variable-length integer. The VarInt type
usually precedes an array or a string that can vary in length.
Instances
| Generic VarInt Source # | |
| Read VarInt Source # | |
| Show VarInt Source # | |
| Binary VarInt Source # | |
| Serial VarInt Source # | |
Defined in Haskoin.Network.Common | |
| Serialize VarInt Source # | |
| NFData VarInt Source # | |
Defined in Haskoin.Network.Common | |
| Eq VarInt Source # | |
| type Rep VarInt Source # | |
Defined in Haskoin.Network.Common | |
Data type for serialization of variable-length strings.
Constructors
| VarString | |
Fields
| |
Instances
| Generic VarString Source # | |
| Read VarString Source # | |
| Show VarString Source # | |
| Binary VarString Source # | |
| Serial VarString Source # | |
Defined in Haskoin.Network.Common | |
| Serialize VarString Source # | |
| NFData VarString Source # | |
Defined in Haskoin.Network.Common | |
| Eq VarString Source # | |
| type Rep VarString Source # | |
Defined in Haskoin.Network.Common type Rep VarString = D1 ('MetaData "VarString" "Haskoin.Network.Common" "haskoin-core-1.1.0-EPeWWz60EKPlWai44F9WC" 'True) (C1 ('MetaCons "VarString" 'PrefixI 'True) (S1 ('MetaSel ('Just "get") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) | |
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
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.
Constructors
Instances
reject :: MessageCommand -> RejectCode -> ByteString -> Reject Source #
Convenience function to build a Reject message.
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.
nodeWitness :: Word64 Source #
Services indicate SegWit-capable node.
commandToString :: MessageCommand -> ByteString Source #
Convert a MessageCommand to its string representation.
stringToCommand :: ByteString -> MessageCommand Source #
Read a MessageCommand from its string representation.