| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Network.Haskoin.Network
Description
This package provides basic types used for the Bitcoin networking protocol together with Data.Serialize instances for efficiently serializing and de-serializing them. More information on the bitcoin protocol is available here: http://en.bitcoin.it/wiki/Protocol_specification
Synopsis
- newtype Addr = Addr {}
- type NetworkAddressTime = (Word32, NetworkAddress)
- data Alert = Alert {}
- newtype GetData = GetData {- getDataList :: [InvVector]
 
- newtype Inv = Inv {}
- data InvVector = InvVector {}
- data InvType
- data NetworkAddress = NetworkAddress {- naServices :: !Word64
- naAddress :: !SockAddr
 
- newtype NotFound = NotFound {- notFoundList :: [InvVector]
 
- newtype Ping = Ping {}
- newtype Pong = Pong {}
- data Reject = Reject {}
- data RejectCode
- newtype VarInt = VarInt {}
- newtype VarString = VarString {}
- 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 -> Maybe MessageCommand
- data Message- = MVersion !Version
- | MVerAck
- | MAddr !Addr
- | MInv !Inv
- | MGetData !GetData
- | MNotFound !NotFound
- | MGetBlocks !GetBlocks
- | MGetHeaders !GetHeaders
- | MTx !Tx
- | MBlock !Block
- | MMerkleBlock !MerkleBlock
- | MHeaders !Headers
- | MGetAddr
- | MFilterLoad !FilterLoad
- | MFilterAdd !FilterAdd
- | MFilterClear
- | MPing !Ping
- | MPong !Pong
- | MAlert !Alert
- | MMempool
- | MReject !Reject
- | MSendHeaders
 
- data MessageHeader = MessageHeader {- headMagic :: !Word32
- headCmd :: !MessageCommand
- headPayloadSize :: !Word32
- headChecksum :: !CheckSum32
 
- msgType :: Message -> MessageCommand
- putMessage :: Network -> Putter Message
- getMessage :: Network -> Get Message
- data BloomFlags
- data BloomFilter = BloomFilter {- bloomData :: !(Seq Word8)
- bloomHashFuncs :: !Word32
- bloomTweak :: !Word32
- bloomFlags :: !BloomFlags
 
- newtype FilterLoad = FilterLoad {}
- newtype FilterAdd = FilterAdd {}
- bloomCreate :: Int -> Double -> Word32 -> BloomFlags -> BloomFilter
- bloomInsert :: BloomFilter -> ByteString -> BloomFilter
- bloomContains :: BloomFilter -> ByteString -> Bool
- isBloomValid :: BloomFilter -> Bool
- isBloomEmpty :: BloomFilter -> Bool
- isBloomFull :: BloomFilter -> Bool
- acceptsFilters :: Word64 -> Bool
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 | |
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 | |
| Fields 
 | |
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 
 | |
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 | |
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 
 | |
Instances
| Eq NetworkAddress Source # | |
| Defined in Network.Haskoin.Network.Common Methods (==) :: NetworkAddress -> NetworkAddress -> Bool # (/=) :: NetworkAddress -> NetworkAddress -> Bool # | |
| Show NetworkAddress Source # | |
| Defined in Network.Haskoin.Network.Common Methods showsPrec :: Int -> NetworkAddress -> ShowS # show :: NetworkAddress -> String # showList :: [NetworkAddress] -> ShowS # | |
| Serialize NetworkAddress Source # | |
| Defined in Network.Haskoin.Network.Common | |
| NFData NetworkAddress Source # | |
| Defined in Network.Haskoin.Network.Common Methods rnf :: NetworkAddress -> () # | |
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 
 | |
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 
 | |
data RejectCode Source #
Constructors
| RejectMalformed | |
| RejectInvalid | |
| RejectObsolete | |
| RejectDuplicate | |
| RejectNonStandard | |
| RejectDust | |
| RejectInsufficientFee | |
| RejectCheckpoint | 
Instances
| Eq RejectCode Source # | |
| Defined in Network.Haskoin.Network.Common | |
| Read RejectCode Source # | |
| Defined in Network.Haskoin.Network.Common Methods readsPrec :: Int -> ReadS RejectCode # readList :: ReadS [RejectCode] # readPrec :: ReadPrec RejectCode # readListPrec :: ReadPrec [RejectCode] # | |
| Show RejectCode Source # | |
| Defined in Network.Haskoin.Network.Common Methods showsPrec :: Int -> RejectCode -> ShowS # show :: RejectCode -> String # showList :: [RejectCode] -> ShowS # | |
| Serialize RejectCode Source # | |
| Defined in Network.Haskoin.Network.Common | |
Data type representing a variable-length integer. The VarInt type
 usually precedes an array or a string that can vary in length.
Data type for serialization of variable-length strings.
Constructors
| VarString | |
| Fields | |
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 
 | |
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
| Eq MessageCommand Source # | |
| Defined in Network.Haskoin.Network.Common Methods (==) :: MessageCommand -> MessageCommand -> Bool # (/=) :: MessageCommand -> MessageCommand -> Bool # | |
| Read MessageCommand Source # | |
| Defined in Network.Haskoin.Network.Common Methods readsPrec :: Int -> ReadS MessageCommand # readList :: ReadS [MessageCommand] # | |
| Show MessageCommand Source # | |
| Defined in Network.Haskoin.Network.Common Methods showsPrec :: Int -> MessageCommand -> ShowS # show :: MessageCommand -> String # showList :: [MessageCommand] -> ShowS # | |
| IsString MessageCommand Source # | |
| Defined in Network.Haskoin.Network.Common Methods fromString :: String -> MessageCommand # | |
| Serialize MessageCommand Source # | |
| Defined in Network.Haskoin.Network.Common | |
| NFData MessageCommand Source # | |
| Defined in Network.Haskoin.Network.Common Methods rnf :: MessageCommand -> () # | |
Useful Functions
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 -> Maybe MessageCommand Source #
Read a MessageCommand from its string representation.
Network Message
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.
Constructors
data MessageHeader Source #
Data type representing the header of a Message. All messages sent between
 nodes contain a message header.
Constructors
| MessageHeader | |
| Fields 
 | |
Instances
| Eq MessageHeader Source # | |
| Defined in Network.Haskoin.Network.Message Methods (==) :: MessageHeader -> MessageHeader -> Bool # (/=) :: MessageHeader -> MessageHeader -> Bool # | |
| Show MessageHeader Source # | |
| Defined in Network.Haskoin.Network.Message Methods showsPrec :: Int -> MessageHeader -> ShowS # show :: MessageHeader -> String # showList :: [MessageHeader] -> ShowS # | |
| Serialize MessageHeader Source # | |
| Defined in Network.Haskoin.Network.Message | |
| NFData MessageHeader Source # | |
| Defined in Network.Haskoin.Network.Message Methods rnf :: MessageHeader -> () # | |
msgType :: Message -> MessageCommand Source #
Get MessageCommand assocated with a message.
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) | 
Instances
| Eq BloomFlags Source # | |
| Defined in Network.Haskoin.Network.Bloom | |
| Read BloomFlags Source # | |
| Defined in Network.Haskoin.Network.Bloom Methods readsPrec :: Int -> ReadS BloomFlags # readList :: ReadS [BloomFlags] # readPrec :: ReadPrec BloomFlags # readListPrec :: ReadPrec [BloomFlags] # | |
| Show BloomFlags Source # | |
| Defined in Network.Haskoin.Network.Bloom Methods showsPrec :: Int -> BloomFlags -> ShowS # show :: BloomFlags -> String # showList :: [BloomFlags] -> ShowS # | |
| Serialize BloomFlags Source # | |
| Defined in Network.Haskoin.Network.Bloom | |
| NFData BloomFlags Source # | |
| Defined in Network.Haskoin.Network.Bloom Methods rnf :: BloomFlags -> () # | |
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 
 | |
Instances
| Eq BloomFilter Source # | |
| Defined in Network.Haskoin.Network.Bloom | |
| Read BloomFilter Source # | |
| Defined in Network.Haskoin.Network.Bloom Methods readsPrec :: Int -> ReadS BloomFilter # readList :: ReadS [BloomFilter] # readPrec :: ReadPrec BloomFilter # readListPrec :: ReadPrec [BloomFilter] # | |
| Show BloomFilter Source # | |
| Defined in Network.Haskoin.Network.Bloom Methods showsPrec :: Int -> BloomFilter -> ShowS # show :: BloomFilter -> String # showList :: [BloomFilter] -> ShowS # | |
| Serialize BloomFilter Source # | |
| Defined in Network.Haskoin.Network.Bloom | |
| NFData BloomFilter Source # | |
| Defined in Network.Haskoin.Network.Bloom Methods rnf :: BloomFilter -> () # | |
newtype FilterLoad Source #
Set a new bloom filter on the peer connection.
Constructors
| FilterLoad | |
| Fields | |
Instances
| Eq FilterLoad Source # | |
| Defined in Network.Haskoin.Network.Bloom | |
| Read FilterLoad Source # | |
| Defined in Network.Haskoin.Network.Bloom Methods readsPrec :: Int -> ReadS FilterLoad # readList :: ReadS [FilterLoad] # readPrec :: ReadPrec FilterLoad # readListPrec :: ReadPrec [FilterLoad] # | |
| Show FilterLoad Source # | |
| Defined in Network.Haskoin.Network.Bloom Methods showsPrec :: Int -> FilterLoad -> ShowS # show :: FilterLoad -> String # showList :: [FilterLoad] -> ShowS # | |
| Serialize FilterLoad Source # | |
| Defined in Network.Haskoin.Network.Bloom | |
| NFData FilterLoad Source # | |
| Defined in Network.Haskoin.Network.Bloom Methods rnf :: FilterLoad -> () # | |
Add the given data element to the connections current filter without requiring a completely new one to be set.
Constructors
| FilterAdd | |
| Fields | |
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.
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.
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.
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?