haskoin-0.1.0: Implementation of the Bitcoin protocol.

Safe HaskellNone

Network.Haskoin.Crypto

Contents

Description

This package provides the elliptic curve cryptography required for creating and validating bitcoin transactions. It also provides SHA-256 and RIPEMD-160 hashing functions; as well as mnemonic keys from BIP-0039.

Synopsis

Elliptic Curve Keys

Public Keys

data PubKey Source

Elliptic curve public key type. Two constructors are provided for creating compressed and uncompressed public keys from a Point. The use of compressed keys is preferred as it produces shorter keys without compromising security. Uncompressed keys are supported for backwards compatibility.

Constructors

PubKey

Compressed public key

Fields

pubKeyPoint :: !Point
 
PubKeyU

Uncompressed public key

Fields

pubKeyPoint :: !Point
 

isValidPubKey :: PubKey -> BoolSource

Returns True if the public key is valid. This will check if the public key point lies on the curve.

isPubKeyU :: PubKey -> BoolSource

Returns True if the public key is uncompressed

derivePubKey :: PrvKey -> PubKeySource

Derives a public key from a private key. This function will preserve information on key compression (PrvKey becomes PubKey and PrvKeyU becomes PubKeyU)

pubKeyAddr :: PubKey -> AddressSource

Computes an Address value from a public key

Private Keys

data PrvKey Source

Elliptic curve private key type. Two constructors are provided for creating compressed or uncompressed private keys. Compression information is stored in private key WIF formats and needs to be preserved to generate the correct addresses from the corresponding public key.

Constructors

PrvKey

Compressed private key

Fields

prvKeyFieldN :: !FieldN
 
PrvKeyU

Uncompressed private key

Fields

prvKeyFieldN :: !FieldN
 

isValidPrvKey :: Integer -> BoolSource

Returns True if the private key is valid. This will check if the integer value representing the private key is greater than 0 and smaller than the curve order N.

makePrvKey :: Integer -> Maybe PrvKeySource

Builds a compressed private key from an Integer value. Returns Nothing if the Integer would not produce a valid private key. For security, the Integer needs to be generated from a random source with sufficient entropy.

makePrvKeyU :: Integer -> Maybe PrvKeySource

Builds an uncompressed private key from an Integer value. Returns Nothing if the Integer would not produce a valid private key. For security, the Integer needs to be generated from a random source with sufficient entropy.

fromPrvKey :: PrvKey -> IntegerSource

Returns the Integer value of a private key

isPrvKeyU :: PrvKey -> BoolSource

Returns True of the private key is uncompressed

putPrvKey :: PrvKey -> PutSource

Serialize a private key into the Data.Binary.Put monad as a 32 byte big endian ByteString. This is useful when a constant length serialization format for private keys is required

getPrvKey :: Get PrvKeySource

Deserializes a compressed private key from the Data.Binary.Get monad as a 32 byte big endian ByteString.

getPrvKeyU :: Get PrvKeySource

Deserializes an uncompressed private key from the Data.Binary.Get monad as a 32 byte big endian ByteString

fromWIF :: String -> Maybe PrvKeySource

Decodes a private key from a WIF encoded String. This function can fail if the input string does not decode correctly as a base 58 string or if the checksum fails. http://en.bitcoin.it/wiki/Wallet_import_format

toWIF :: PrvKey -> StringSource

Encodes a private key into WIF format

ECDSA

SecretT Monad

The SecretT monad is a monadic wrapper around HMAC DRBG (deterministic random byte generator) using SHA-256. The specification is defined in http://csrc.nist.gov/publications/nistpubs/800-90A/SP800-90A.pdf. The SecretT monad is used to generate random private keys and random nonces for ECDSA signatures.

type SecretT m = StateT (SecretState m) mSource

StateT monad stack tracking the internal state of HMAC DRBG pseudo random number generator using SHA-256. The SecretT monad is run with the withSource function by providing it a source of entropy.

withSource :: Monad m => (Int -> m ByteString) -> SecretT m a -> m aSource

Run a SecretT monad by providing it a source of entropy. You can use devURandom, devRandom or provide your own entropy source function.

devURandom :: Int -> IO ByteStringSource

/dev/urandom entropy source. This is only available on machines supporting it. This function is meant to be used together with withSource.

devRandom :: Int -> IO ByteStringSource

/dev/random entropy source. This is only available on machines supporting it. This function is meant to be used together with withSource.

genPrvKey :: Monad m => SecretT m PrvKeySource

Produce a new PrvKey randomly from the SecretT monad.

Signatures

Elliptic curve cryptography standards are defined in http://www.secg.org/download/aid-780/sec1-v2.pdf

data Signature Source

Data type representing an ECDSA signature.

signMsg :: Monad m => Word256 -> PrvKey -> SecretT m SignatureSource

Safely sign a message inside the SecretT monad. The SecretT monad will generate a new nonce for each signature.

detSignMsg :: Word256 -> PrvKey -> SignatureSource

Sign a message using ECDSA deterministic signatures as defined by RFC 6979 http://tools.ietf.org/html/rfc6979

verifySig :: Word256 -> Signature -> PubKey -> BoolSource

Verify an ECDSA signature

isCanonicalHalfOrder :: Signature -> BoolSource

Returns True if the S component of a Signature is <= order/2. Signatures need to pass this test to be canonical.

Big words

type Word512 = BigWord Mod512Source

Data type representing a 512 bit unsigned integer. It is implemented as an Integer modulo 2^512.

type Word256 = BigWord Mod256Source

Data type representing a 256 bit unsigned integer. It is implemented as an Integer modulo 2^256.

type Word160 = BigWord Mod160Source

Data type representing a 160 bit unsigned integer. It is implemented as an Integer modulo 2^160.

type Word128 = BigWord Mod128Source

Data type representing a 128 bit unsigned integer. It is implemented as an Integer modulo 2^128.

Hash functions

type TxHash = BigWord Mod256TxSource

Type representing a transaction hash.

type BlockHash = BigWord Mod256BlockSource

Type representing a block hash.

txHash :: Tx -> TxHashSource

Computes the hash of a transaction.

cbHash :: CoinbaseTx -> TxHashSource

Computes the hash of a coinbase transaction.

headerHash :: BlockHeader -> BlockHashSource

Compute the hash of a block header

encodeTxHashLE :: TxHash -> StringSource

Encodes a TxHash as little endian in HEX format. This is mostly used for displaying transaction ids. Internally, these ids are handled as big endian but are transformed to little endian when displaying them.

decodeTxHashLE :: String -> Maybe TxHashSource

Decodes a little endian TxHash in HEX format.

encodeBlockHashLE :: BlockHash -> StringSource

Encodes a BlockHash as little endian in HEX format. This is mostly used for displaying Block hash ids. Internally, these ids are handled as big endian but are transformed to little endian when displaying them.

decodeBlockHashLE :: String -> Maybe BlockHashSource

Decodes a little endian BlockHash in HEX format.

hash512 :: ByteString -> Word512Source

Computes SHA-512.

hash512BS :: ByteString -> ByteStringSource

Computes SHA-512 and returns the result as a bytestring.

hash256 :: ByteString -> Word256Source

Computes SHA-256.

hash256BS :: ByteString -> ByteStringSource

Computes SHA-256 and returns the result as a bytestring.

hashSha1 :: ByteString -> Word160Source

Computes SHA-160.

hashSha1BS :: ByteString -> ByteStringSource

Computes SHA-160 and returns the result as a bytestring.

hash160 :: ByteString -> Word160Source

Computes RIPEMD-160.

hash160BS :: ByteString -> ByteStringSource

Computes RIPEMD-160 and returns the result as a bytestring.

doubleHash256 :: ByteString -> Word256Source

Computes two rounds of SHA-256.

doubleHash256BS :: ByteString -> ByteStringSource

Computes two rounds of SHA-256 and returns the result as a bytestring.

chksum32 :: ByteString -> CheckSum32Source

Computes a 32 bit checksum.

hmac512 :: ByteString -> ByteString -> Word512Source

Computes HMAC over SHA-512.

hmac512BS :: ByteString -> ByteString -> ByteStringSource

Computes HMAC over SHA-512 and return the result as a bytestring.

hmac256 :: ByteString -> ByteString -> Word256Source

Computes HMAC over SHA-256.

hmac256BS :: ByteString -> ByteString -> ByteStringSource

Computes HMAC over SHA-256 and return the result as a bytestring.

split512 :: Word512 -> (Word256, Word256)Source

Split a Word512 into a pair of Word256.

join512 :: (Word256, Word256) -> Word512Source

Join a pair of Word256 into a Word512.

murmurHash3 :: Word32 -> ByteString -> Word32Source

MurmurHash3 (x86_32). For more details, see http://code.google.com/p/smhasher/source/browse/trunk/MurmurHash3.cpp This code is used in the bloom filters of SPV nodes.

Number representations

decodeCompact :: Word32 -> IntegerSource

Decode the compact number used in the difficulty target of a block into an Integer.

As described in the Satoshi reference implementation srcbignum.h:

The compact format is a representation of a whole number N using an unsigned 32bit number similar to a floating point format. The most significant 8 bits are the unsigned exponent of base 256. This exponent can be thought of as number of bytes of N. The lower 23 bits are the mantissa. Bit number 24 (0x800000) represents the sign of N.

    N = (-1^sign) * mantissa * 256^(exponent-3)

encodeCompact :: Integer -> Word32Source

Encode an Integer to the compact number format used in the difficulty target of a block.

Base58 and Addresses

data Address Source

Data type representing a Bitcoin address

Constructors

PubKeyAddress

Public Key Hash Address

Fields

getAddrHash :: Word160
 
ScriptAddress

Script Hash Address

Fields

getAddrHash :: Word160
 

base58ToAddr :: String -> Maybe AddressSource

Decodes an Address from a base58 encoded String. This function can fail if the String is not properly encoded as base58 or the checksum fails.

addrToBase58 :: Address -> StringSource

Transforms an Address into a base58 encoded String

encodeBase58 :: ByteString -> ByteStringSource

Encode a bytestring to a base 58 representation.

decodeBase58 :: ByteString -> Maybe ByteStringSource

Decode a base 58 encoded bytestring. This can fail if the input bytestring contains invalid base 58 characters such as 0,O,l,I

encodeBase58Check :: ByteString -> ByteStringSource

Computes a checksum for the input bytestring and encodes the input and the checksum to a base 58 representation.

decodeBase58Check :: ByteString -> Maybe ByteStringSource

Decode a base 58 encoded bytestring that contains a checksum. This function returns Nothing if the input bytestring contains invalid base 58 characters or if the checksum fails.

Mnemonic keys (BIP-0039)

toMnemonic :: Entropy -> Either String MnemonicSource

Provide intial entropy as a ByteString of length multiple of 4 bytes. Output a mnemonic sentence.

mnemonicToSeed :: Passphrase -> Mnemonic -> Either String SeedSource

Get a 512-bit seed from a mnemonic sentence. Will calculate checksum. Passphrase can be used to protect the mnemonic. Use an empty string as passphrase if none is required.

Extended Keys

Extended Private Keys

data XPrvKey Source

Data type representing an extended BIP32 private key. An extended key is a node in a tree of key derivations. It has a depth in the tree, a parent node and an index to differentiate it from other siblings.

Constructors

XPrvKey 

Fields

xPrvDepth :: !Word8

Depth in the tree of key derivations.

xPrvParent :: !Word32

Fingerprint of the parent key.

xPrvIndex :: !Word32

Key derivation index.

xPrvChain :: !ChainCode

Chain code.

xPrvKey :: !PrvKey

The private key of this extended key node.

makeXPrvKey :: ByteString -> Maybe XPrvKeySource

Build a BIP32 compatible extended private key from a bytestring. This will produce a root node (depth=0 and parent=0).

xPrvIsPrime :: XPrvKey -> BoolSource

Returns True if the extended private key was derived through a prime derivation.

xPrvChild :: XPrvKey -> Word32Source

Returns the derivation index of this extended private key without the prime bit set.

xPrvID :: XPrvKey -> Word160Source

Computes the key identifier of an extended private key.

xPrvFP :: XPrvKey -> Word32Source

Computes the key fingerprint of an extended private key.

xPrvExport :: XPrvKey -> StringSource

Exports an extended private key to the BIP32 key export format (base 58).

xPrvImport :: String -> Maybe XPrvKeySource

Decodes a BIP32 encoded extended private key. This function will fail if invalid base 58 characters are detected or if the checksum fails.

xPrvWIF :: XPrvKey -> StringSource

Export an extended private key to WIF (Wallet Import Format).

Extended Public Keys

data XPubKey Source

Data type representing an extended BIP32 public key.

Constructors

XPubKey 

Fields

xPubDepth :: !Word8

Depth in the tree of key derivations.

xPubParent :: !Word32

Fingerprint of the parent key.

xPubIndex :: !Word32

Key derivation index.

xPubChain :: !ChainCode

Chain code.

xPubKey :: !PubKey

The public key of this extended key node.

deriveXPubKey :: XPrvKey -> XPubKeySource

Derive an extended public key from an extended private key. This function will preserve the depth, parent, index and chaincode fields of the extended private keys.

xPubIsPrime :: XPubKey -> BoolSource

Returns True if the extended public key was derived through a prime derivation.

xPubChild :: XPubKey -> Word32Source

Returns the derivation index of this extended public key without the prime bit set.

xPubID :: XPubKey -> Word160Source

Computes the key identifier of an extended public key.

xPubFP :: XPubKey -> Word32Source

Computes the key fingerprint of an extended public key.

xPubAddr :: XPubKey -> AddressSource

Computer the Address of an extended public key.

xPubExport :: XPubKey -> StringSource

Exports an extended public key to the BIP32 key export format (base 58).

xPubImport :: String -> Maybe XPubKeySource

Decodes a BIP32 encoded extended public key. This function will fail if invalid base 58 characters are detected or if the checksum fails.

Child key derivations

prvSubKeySource

Arguments

:: XPrvKey

Extended parent private key

-> Word32

Child derivation index

-> Maybe XPrvKey

Extended child private key

Compute a private, non-prime child key derivation. A private non-prime derivation will allow the equivalent extended public key to derive the public key for this child. Given a parent key m and a derivation index i, this function will compute m/i/.

Non-prime derivations allow for more flexibility such as read-only wallets. However, care must be taken not the leak both the parent extended public key and one of the extended child private keys as this would compromise the extended parent private key.

pubSubKeySource

Arguments

:: XPubKey

Extended Parent public key

-> Word32

Child derivation index

-> Maybe XPubKey

Extended child public key

Compute a public, non-prime child key derivation. Given a parent key M and a derivation index i, this function will compute M/i/.

primeSubKeySource

Arguments

:: XPrvKey

Extended Parent private key

-> Word32

Child derivation index

-> Maybe XPrvKey

Extended child private key

Compute a prime child key derivation. Prime derivations can only be computed for private keys. Prime derivations do not allow the parent public key to derive the child public keys. However, they are safer as a breach of the parent public key and child private keys does not lead to a breach of the parent private key. Given a parent key m and a derivation index i, this function will compute m/i'/.

prvSubKeys :: XPrvKey -> Word32 -> [(XPrvKey, Word32)]Source

Cyclic list of all private non-prime child key derivations of a parent key starting from an offset index.

pubSubKeys :: XPubKey -> Word32 -> [(XPubKey, Word32)]Source

Cyclic list of all public non-prime child key derivations of a parent key starting from an offset index.

primeSubKeys :: XPrvKey -> Word32 -> [(XPrvKey, Word32)]Source

Cyclic list of all prime child key derivations of a parent key starting from an offset index.

Multisig derivations

mulSigSubKeySource

Arguments

:: [XPubKey]

List of extended parent public keys

-> Word32

Child key derivation index

-> Maybe [XPubKey]

List of extended child public keys

Compute a public, non-prime subkey derivation for all of the parent public keys in the input. This function will succeed only if the child key derivations for all the parent keys are valid.

This function is intended to be used in the context of multisignature accounts. Parties exchanging their master public keys to create a multisignature account can then individually generate all the receiving multisignature addresses without further communication.

mulSigSubKeys :: [XPubKey] -> Word32 -> [([XPubKey], Word32)]Source

Cyclic list of all public, non-prime multisig key derivations of a list of parent keys starting from an offset index.

Derivation tree interoperability

To improve BIP32 wallet interoperability, a standard derivation tree is used. All accounts are generated through prime derivations from the master key. This ensures that the master key is not compromised if an account is compromised. Every account will generate receiving addresses from the non-prime subtree index 0 and internal change addresses from the non-prime subtree index 1. MasterKey, AccountKey and AddressKey types are defined to conform to the wallet interoperability format.

Master keys

newtype MasterKey Source

Data type representing an extended private key at the root of the derivation tree. Master keys have depth 0 and no parents. They are represented as m/ in BIP32 notation.

Constructors

MasterKey 

Fields

masterKey :: XPrvKey
 

loadMasterKey :: XPrvKey -> Maybe MasterKeySource

Load a MasterKey from an XPrvKey. This function will fail if the extended private key does not have the properties of a MasterKey.

Account keys

newtype AccPrvKey Source

Data type representing a private account key. Account keys are generated from a MasterKey through prime derivation. This guarantees that the MasterKey will not be compromised if the account key is compromised. AccPrvKey is represented as m/i'/ in BIP32 notation.

Constructors

AccPrvKey 

newtype AccPubKey Source

Data type representing a public account key. It is computed through derivation from an AccPrvKey. It can not be derived from the MasterKey directly (property of prime derivation). It is represented as M/i'/ in BIP32 notation. AccPubKey is used for generating receiving payment addresses without the knowledge of the AccPrvKey.

Constructors

AccPubKey 

loadPrvAcc :: XPrvKey -> Maybe AccPrvKeySource

Load a private account key from an XPrvKey. This function will fail if the extended private key does not have the properties of a AccPrvKey.

loadPubAcc :: XPubKey -> Maybe AccPubKeySource

Load a public account key from an XPubKey. This function will fail if the extended public key does not have the properties of a AccPubKey.

accPrvKey :: MasterKey -> KeyIndex -> Maybe AccPrvKeySource

Computes an AccPrvKey from a MasterKey and a derivation index.

accPubKey :: MasterKey -> KeyIndex -> Maybe AccPubKeySource

Computes an AccPubKey from a MasterKey and a derivation index.

accPrvKeys :: MasterKey -> KeyIndex -> [(AccPrvKey, KeyIndex)]Source

Cyclic list of all valid AccPrvKey derived from a MasterKey and starting from an offset index.

accPubKeys :: MasterKey -> KeyIndex -> [(AccPubKey, KeyIndex)]Source

Cyclic list of all valid AccPubKey derived from a MasterKey and starting from an offset index.

Address keys

newtype AddrPrvKey Source

Data type representing a private address key. Private address keys are generated through a non-prime derivation from an AccPrvKey. Non-prime derivation is used so that the public account key can generate the receiving payment addresses without knowledge of the private account key. AccPrvKey is represented as m/i'/0/j/ in BIP32 notation if it is a regular receiving address. Internal (change) addresses are represented as m/i'/1/j/. Non-prime subtree 0 is used for regular receiving addresses and non-prime subtree 1 for internal (change) addresses.

Constructors

AddrPrvKey 

newtype AddrPubKey Source

Data type representing a public address key. They are generated through non-prime derivation from an AccPubKey. This is a useful feature for read-only wallets. They are represented as M/i'/0/j in BIP32 notation for regular receiving addresses and by M/i'/1/j for internal (change) addresses.

Constructors

AddrPubKey 

addr :: AddrPubKey -> AddressSource

Computes an Address from an AddrPubKey.

extPrvKey :: AccPrvKey -> KeyIndex -> Maybe AddrPrvKeySource

Computes an external AddrPrvKey from an AccPrvKey and a derivation index.

extPubKey :: AccPubKey -> KeyIndex -> Maybe AddrPubKeySource

Computes an external AddrPubKey from an AccPubKey and a derivation index.

intPrvKey :: AccPrvKey -> KeyIndex -> Maybe AddrPrvKeySource

Computes an internal AddrPrvKey from an AccPrvKey and a derivation index.

intPubKey :: AccPubKey -> KeyIndex -> Maybe AddrPubKeySource

Computes an internal AddrPubKey from an AccPubKey and a derivation index.

extPrvKeys :: AccPrvKey -> KeyIndex -> [(AddrPrvKey, KeyIndex)]Source

Cyclic list of all valid external AddrPrvKey derived from a AccPrvKey and starting from an offset index.

extPubKeys :: AccPubKey -> KeyIndex -> [(AddrPubKey, KeyIndex)]Source

Cyclic list of all valid external AddrPubKey derived from a AccPubKey and starting from an offset index.

intPrvKeys :: AccPrvKey -> KeyIndex -> [(AddrPrvKey, KeyIndex)]Source

Cyclic list of all internal AddrPrvKey derived from a AccPrvKey and starting from an offset index.

intPubKeys :: AccPubKey -> KeyIndex -> [(AddrPubKey, KeyIndex)]Source

Cyclic list of all internal AddrPubKey derived from a AccPubKey and starting from an offset index.

extAddr :: AccPubKey -> KeyIndex -> Maybe AddressSource

Computes an external address from an AccPubKey and a derivation index.

intAddr :: AccPubKey -> KeyIndex -> Maybe AddressSource

Computes an internal addres from an AccPubKey and a derivation index.

extAddrs :: AccPubKey -> KeyIndex -> [(Address, KeyIndex)]Source

Cyclic list of all external addresses derived from a AccPubKey and starting from an offset index.

intAddrs :: AccPubKey -> KeyIndex -> [(Address, KeyIndex)]Source

Cyclic list of all internal addresses derived from a AccPubKey and starting from an offset index.

extAddrs' :: AccPubKey -> KeyIndex -> [(Address, KeyIndex)]Source

Same as extAddrs with the list reversed.

intAddrs' :: AccPubKey -> KeyIndex -> [(Address, KeyIndex)]Source

Same as intAddrs with the list reversed.

Multisig address keys

extMulSigKey :: AccPubKey -> [XPubKey] -> KeyIndex -> Maybe [AddrPubKey]Source

Computes a list of external AddrPubKey from an AccPubKey, a list of thirdparty multisig keys and a derivation index. This is useful for computing the public keys associated with a derivation index for multisig accounts.

intMulSigKey :: AccPubKey -> [XPubKey] -> KeyIndex -> Maybe [AddrPubKey]Source

Computes a list of internal AddrPubKey from an AccPubKey, a list of thirdparty multisig keys and a derivation index. This is useful for computing the public keys associated with a derivation index for multisig accounts.

extMulSigKeys :: AccPubKey -> [XPubKey] -> KeyIndex -> [([AddrPubKey], KeyIndex)]Source

Cyclic list of all external multisignature AddrPubKey derivations starting from an offset index.

intMulSigKeys :: AccPubKey -> [XPubKey] -> KeyIndex -> [([AddrPubKey], KeyIndex)]Source

Cyclic list of all internal multisignature AddrPubKey derivations starting from an offset index.

extMulSigAddr :: AccPubKey -> [XPubKey] -> Int -> KeyIndex -> Maybe AddressSource

Computes an external multisig address from an AccPubKey, a list of thirdparty multisig keys and a derivation index.

intMulSigAddr :: AccPubKey -> [XPubKey] -> Int -> KeyIndex -> Maybe AddressSource

Computes an internal multisig address from an AccPubKey, a list of thirdparty multisig keys and a derivation index.

extMulSigAddrs :: AccPubKey -> [XPubKey] -> Int -> KeyIndex -> [(Address, KeyIndex)]Source

Cyclic list of all external multisig addresses derived from an AccPubKey and a list of thirdparty multisig keys. The list starts at an offset index.

intMulSigAddrs :: AccPubKey -> [XPubKey] -> Int -> KeyIndex -> [(Address, KeyIndex)]Source

Cyclic list of all internal multisig addresses derived from an AccPubKey and a list of thirdparty multisig keys. The list starts at an offset index.

Bloom filters

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 are probabilistic and have a false positive rate. 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.

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

Only auto-update on outputs that are pay-to-pubkey or pay-to-multisig. This is the default setting.

bloomCreateSource

Arguments

:: Int

Number of elements

-> Double

False positive rate

-> Word32

A random nonce (tweak) for the hash function. It should be a random number but the secureness of the random value is not of geat consequence.

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

bloomInsertSource

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.

bloomContainsSource

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.

isBloomValidSource

Arguments

:: BloomFilter

Bloom filter to test

-> Bool

True if the given filter is valid

Tests if a given bloom filter is valid.

isBloomEmpty :: BloomFilter -> BoolSource

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

isBloomFull :: BloomFilter -> BoolSource

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

Partial merkle trees

calcTreeHeightSource

Arguments

:: Int

Number of transactions (leaf nodes).

-> Int

Height of the merkle tree.

Computes the height of a merkle tree.

calcTreeWidthSource

Arguments

:: Int

Number of transactions (leaf nodes).

-> Int

Height at which we want to compute the width.

-> Int

Width of the merkle tree.

Computes the width of a merkle tree at a specific height. The transactions are at height 0.

buildMerkleRootSource

Arguments

:: [TxHash]

List of transaction hashes (leaf nodes).

-> MerkleRoot

Root of the merkle tree.

Computes the root of a merkle tree from a list of leaf node hashes.

calcHashSource

Arguments

:: Int

Height of the node in the merkle tree.

-> Int

Position of the node (0 for the leftmost node).

-> [TxHash]

Transaction hashes of the merkle tree (leaf nodes).

-> Word256

Hash of the node at the specified position.

Computes the hash of a specific node in a merkle tree.

buildPartialMerkleSource

Arguments

:: [(TxHash, Bool)]

List of transactions hashes forming the leaves of the merkle tree and a bool indicating if that transaction should be included in the partial merkle tree.

-> (FlagBits, PartialMerkleTree)

Flag bits (used to parse the partial merkle tree) and the partial merkle tree.

Build a partial merkle tree.

extractMatchesSource

Arguments

:: FlagBits

Flag bits (produced by buildPartialMerkle).

-> PartialMerkleTree

Partial merkle tree.

-> Int

Number of transaction at height 0 (leaf nodes).

-> Either String (MerkleRoot, [TxHash])

Merkle root and the list of matching transaction hashes.

Extracts the matching hashes from a partial merkle tree. This will return the list of transaction hashes that have been included (set to True) in a call to buildPartialMerkle.