haskoin-core-0.4.2: Implementation of the core Bitcoin protocol features.

Safe HaskellNone
LanguageHaskell98

Network.Haskoin.Internals

Contents

Description

This module expose haskoin internals. No guarantee is made on the stability of the interface of these internal modules.

Synopsis

Documentation

hash512 :: ByteString -> Hash512 Source #

Compute SHA-512.

hash256 :: ByteString -> Hash256 Source #

Compute SHA-256.

hash160 :: ByteString -> Hash160 Source #

Compute RIPEMD-160.

sha1 :: ByteString -> Hash160 Source #

Compute SHA1

doubleHash256 :: ByteString -> Hash256 Source #

Compute two rounds of SHA-256.

checkSum32 :: ByteString -> CheckSum32 Source #

Computes a 32 bit checksum.

hmac512 :: ByteString -> ByteString -> Hash512 Source #

Computes HMAC over SHA-512.

hmac256 :: ByteString -> ByteString -> Hash256 Source #

Computes HMAC over SHA-256.

split512 :: Hash512 -> (Hash256, Hash256) Source #

Split a Hash512 into a pair of Hash256.

join512 :: (Hash256, Hash256) -> Hash512 Source #

Join a pair of Hash256 into a Hash512.

hmacDRBGNew :: EntropyInput -> Nonce -> PersString -> WorkingState Source #

hmacDRBGRsd :: WorkingState -> EntropyInput -> AdditionalInput -> WorkingState Source #

addrToBase58 :: Address -> ByteString Source #

Transforms an Address into a base58 encoded String

base58ToAddr :: ByteString -> Maybe Address Source #

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.

encodeBase58 :: ByteString -> ByteString Source #

Encode a ByteString to a base 58 representation.

decodeBase58 :: ByteString -> Maybe ByteString Source #

Decode a base58-encoded ByteString. This can fail if the input ByteString contains invalid base58 characters such as 0, O, l, I.

encodeBase58Check :: ByteString -> ByteString Source #

Computes a checksum for the input ByteString and encodes the input and the checksum to a base58 representation.

decodeBase58Check :: ByteString -> Maybe ByteString Source #

Decode a base58-encoded string that contains a checksum. This function returns Nothing if the input string contains invalid base58 characters or if the checksum fails.

data PubKeyI c Source #

Instances

Read PubKeyU Source # 
Read PubKeyC Source # 
Read PubKey Source # 
Show PubKeyU Source # 
Show PubKeyC Source # 
Show PubKey Source # 
IsString PubKeyU Source # 

Methods

fromString :: String -> PubKeyU #

IsString PubKeyC Source # 

Methods

fromString :: String -> PubKeyC #

IsString PubKey Source # 

Methods

fromString :: String -> PubKey #

ToJSON PubKeyU Source # 
ToJSON PubKeyC Source # 
ToJSON PubKey Source # 
FromJSON PubKeyU Source # 
FromJSON PubKeyC Source # 
FromJSON PubKey Source # 
Serialize PubKeyU Source # 
Serialize PubKeyC Source # 
Serialize PubKey Source # 
Eq (PubKeyI c) Source # 

Methods

(==) :: PubKeyI c -> PubKeyI c -> Bool #

(/=) :: PubKeyI c -> PubKeyI c -> Bool #

NFData (PubKeyI c) Source # 

Methods

rnf :: PubKeyI c -> () #

type PubKey = PubKeyI Generic 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.

type PubKeyC = PubKeyI Compressed Source #

type PubKeyU = PubKeyI Uncompressed Source #

derivePubKey :: PrvKeyI c -> PubKeyI c Source #

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

pubKeyAddr :: Serialize (PubKeyI c) => PubKeyI c -> Address Source #

Computes an Address from a public key

tweakPubKeyC :: PubKeyC -> Hash256 -> Maybe PubKeyC Source #

Tweak a compressed public key

data PrvKeyI c 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.

type PrvKey = PrvKeyI Generic Source #

type PrvKeyC = PrvKeyI Compressed Source #

type PrvKeyU = PrvKeyI Uncompressed Source #

encodePrvKey :: PrvKeyI c -> ByteString Source #

Serialize private key as 32-byte big-endian ByteString

decodePrvKey :: (SecKey -> PrvKeyI c) -> ByteString -> Maybe (PrvKeyI c) Source #

Deserialize private key as 32-byte big-endian ByteString

fromWif :: ByteString -> Maybe PrvKey Source #

Decodes a private key from a WIF encoded ByteString. 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 :: PrvKeyI c -> ByteString Source #

Encodes a private key into WIF format

tweakPrvKeyC :: PrvKeyC -> Hash256 -> Maybe PrvKeyC Source #

Tweak a private key

data XPubKey Source #

Data type representing an extended BIP32 public key.

Constructors

XPubKey 

Fields

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

makeXPrvKey :: ByteString -> XPrvKey Source #

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

deriveXPubKey :: XPrvKey -> XPubKey Source #

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.

prvSubKey Source #

Arguments

:: XPrvKey

Extended parent private key

-> KeyIndex

Child derivation index

-> XPrvKey

Extended child private key

Compute a private, soft child key derivation. A private soft 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/.

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

pubSubKey Source #

Arguments

:: XPubKey

Extended Parent public key

-> KeyIndex

Child derivation index

-> XPubKey

Extended child public key

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

hardSubKey Source #

Arguments

:: XPrvKey

Extended Parent private key

-> KeyIndex

Child derivation index

-> XPrvKey

Extended child private key

Compute a hard child key derivation. Hard derivations can only be computed for private keys. Hard 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'/.

xPrvIsHard :: XPrvKey -> Bool Source #

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

xPubIsHard :: XPubKey -> Bool Source #

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

xPrvChild :: XPrvKey -> KeyIndex Source #

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

xPubChild :: XPubKey -> KeyIndex Source #

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

xPubID :: XPubKey -> Hash160 Source #

Computes the key identifier of an extended public key.

xPrvID :: XPrvKey -> Hash160 Source #

Computes the key identifier of an extended private key.

xPubFP :: XPubKey -> Word32 Source #

Computes the key fingerprint of an extended public key.

xPrvFP :: XPrvKey -> Word32 Source #

Computes the key fingerprint of an extended private key.

xPubAddr :: XPubKey -> Address Source #

Computer the Address of an extended public key.

xPubExport :: XPubKey -> ByteString Source #

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

xPrvExport :: XPrvKey -> ByteString Source #

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

xPubImport :: ByteString -> Maybe XPubKey Source #

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

xPrvImport :: ByteString -> Maybe XPrvKey Source #

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

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

prvSubKeys :: XPrvKey -> KeyIndex -> [(XPrvKey, KeyIndex)] Source #

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

pubSubKeys :: XPubKey -> KeyIndex -> [(XPubKey, KeyIndex)] Source #

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

hardSubKeys :: XPrvKey -> KeyIndex -> [(XPrvKey, KeyIndex)] Source #

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

deriveAddr :: XPubKey -> KeyIndex -> (Address, PubKeyC) Source #

Derive an address from a public key and an index. The derivation type is a public, soft derivation.

deriveAddrs :: XPubKey -> KeyIndex -> [(Address, PubKeyC, KeyIndex)] Source #

Cyclic list of all addresses derived from a public key starting from an offset index. The derivation types are public, soft derivations.

deriveMSAddr :: [XPubKey] -> Int -> KeyIndex -> (Address, RedeemScript) Source #

Derive a multisig address from a list of public keys, the number of required signatures (m) and a derivation index. The derivation type is a public, soft derivation.

deriveMSAddrs :: [XPubKey] -> Int -> KeyIndex -> [(Address, RedeemScript, KeyIndex)] Source #

Cyclic list of all multisig addresses derived from a list of public keys, a number of required signatures (m) and starting from an offset index. The derivation type is a public, soft derivation.

data DerivPathI t where Source #

Data type representing a derivation path. Two constructors are provided for specifying soft or hard derivations. The path 01'/2 for example can be expressed as Deriv : 0 :| 1 : 2. The HardOrGeneric and GenericOrSoft type classes are used to constrain the valid values for the phantom type t. If you mix hard (:|) and soft (:/) paths, the only valid type for t is Generic. Otherwise, t can be Hard if you only have hard derivation or Soft if you only have soft derivations.

Using this type is as easy as writing the required derivation like in these example: Deriv : 0 : 1 :/ 2 :: SoftPath Deriv :| 0 :| 1 :| 2 :: HardPath Deriv :| 0 : 1 : 2 :: DerivPath

Constructors

(:|) :: HardOrGeneric t => !(DerivPathI t) -> !KeyIndex -> DerivPathI t 
(:/) :: GenericOrSoft t => !(DerivPathI t) -> !KeyIndex -> DerivPathI t 
Deriv :: DerivPathI t 

Instances

Read SoftPath Source # 
Read DerivPath Source # 
Read HardPath Source # 
Show SoftPath Source # 
Show DerivPath Source # 
Show HardPath Source # 
IsString SoftPath Source # 
IsString DerivPath Source # 
IsString HardPath Source # 
FromJSON SoftPath Source # 
FromJSON DerivPath Source # 
FromJSON HardPath Source # 
Eq (DerivPathI t) Source # 

Methods

(==) :: DerivPathI t -> DerivPathI t -> Bool #

(/=) :: DerivPathI t -> DerivPathI t -> Bool #

ToJSON (DerivPathI t) Source # 
NFData (DerivPathI t) Source # 

Methods

rnf :: DerivPathI t -> () #

type DerivPath = DerivPathI Generic Source #

derivePath :: DerivPathI t -> XPrvKey -> XPrvKey Source #

Derive a private key from a derivation path

derivePubPath :: SoftPath -> XPubKey -> XPubKey Source #

Derive a public key from a soft derivation path

(++/) :: DerivPathI t1 -> DerivPathI t2 -> DerivPath Source #

Append two derivation paths together. The result will be a mixed derivation path.

data XKey Source #

Constructors

XPrv 

Fields

XPub 

Fields

Instances

Eq XKey Source # 

Methods

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

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

Show XKey Source # 

Methods

showsPrec :: Int -> XKey -> ShowS #

show :: XKey -> String #

showList :: [XKey] -> ShowS #

parsePath :: String -> Maybe ParsedPath Source #

Parse derivation path string for extended key. Forms: “m0'2”, “M23/4”.

applyPath :: ParsedPath -> XKey -> Either String XKey Source #

Apply a parsed path to an extended key to derive the new key defined in the path. If the path starts with m/, a private key will be returned and if the path starts with M/, a public key will be returned. Private derivations on a public key, and public derivations with a hard segment, return an error value.

derivePathAddr :: XPubKey -> SoftPath -> KeyIndex -> (Address, PubKeyC) Source #

Derive an address from a given parent path.

derivePathAddrs :: XPubKey -> SoftPath -> KeyIndex -> [(Address, PubKeyC, KeyIndex)] Source #

Cyclic list of all addresses derived from a given parent path and starting from the given offset index.

derivePathMSAddr :: [XPubKey] -> SoftPath -> Int -> KeyIndex -> (Address, RedeemScript) Source #

Derive a multisig address from a given parent path. The number of required signatures (m in m of n) is also needed.

derivePathMSAddrs :: [XPubKey] -> SoftPath -> Int -> KeyIndex -> [(Address, RedeemScript, KeyIndex)] Source #

Cyclic list of all multisig addresses derived from a given parent path and starting from the given offset index. The number of required signatures (m in m of n) is also needed.

type SecretT m = StateT (SecretState m) m Source #

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

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

getEntropy :: Int -> IO ByteString #

Get a specific number of bytes of cryptographically secure random data using the system-specific facilities.

Use RDRAND if available and XOR with '/dev/urandom' on *nix and CryptAPI when on Windows. In short, this entropy is considered cryptographically secure but not true entropy.

signMsg :: Hash256 -> PrvKeyI c -> Signature Source #

Sign a message

verifySig :: Hash256 -> Signature -> PubKeyI c -> Bool Source #

Verify an ECDSA signature

genPrvKey :: Monad m => SecretT m PrvKey Source #

Produce a new PrvKey randomly from the SecretT monad.

Data types

Entropy encoding and decoding

toMnemonic :: Entropy -> Either String Mnemonic Source #

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

fromMnemonic :: Mnemonic -> Either String Entropy Source #

Revert toMnemonic. Do not use this to generate seeds. Instead use mnemonicToSeed. This outputs the original entropy used to generate a mnemonic.

Generating 512-bit seeds

mnemonicToSeed :: Passphrase -> Mnemonic -> Either String Seed Source #

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.

Helper functions

getBits :: Int -> ByteString -> ByteString Source #

Obtain Int bits from beginning of ByteString. Resulting ByteString will be smallest required to hold that many bits, padded with zeroes to the right.

data Addr Source #

Provides information on known nodes in the bitcoin network. An Addr type is sent inside a Message as a response to a GetAddr message.

Constructors

Addr 

Instances

Eq Addr Source # 

Methods

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

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

Show Addr Source # 

Methods

showsPrec :: Int -> Addr -> ShowS #

show :: Addr -> String #

showList :: [Addr] -> ShowS #

Serialize Addr Source # 

Methods

put :: Putter Addr #

get :: Get Addr #

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

data 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 for which a node wants to request information. The response to a GetBlock message wille 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 to obtain information on unknown object hashes.

Constructors

GetData 

Fields

data Inv Source #

Inv messages are used by nodes to advertise their knowledge of new objects by publishing a list of hashes. Inv messages can be sent unsolicited or in response to a GetBlocks message.

Constructors

Inv 

Fields

Instances

data InvVector Source #

Invectory vectors represent hashes identifying objects such as a Block or a Tx. They are sent inside messages to notify other peers about new data or data they have requested.

Constructors

InvVector 

Fields

  • invType :: !InvType

    Type of the object referenced by this inventory vector

  • invHash :: !Hash256

    Hash of the object referenced by this inventory vector

data InvType Source #

Data type identifying the type of an inventory vector.

Constructors

InvError

Error. Data containing this type can be ignored.

InvTx

InvVector hash is related to a transaction

InvBlock

InvVector hash is related to a block

InvMerkleBlock

InvVector has is related to a merkle block

data NetworkAddress Source #

Data type describing a bitcoin network address. Addresses are stored in IPv6. IPv4 addresses are mapped to IPv6 using IPv4 mapped IPv6 addresses: http://en.wikipedia.org/wiki/IPv6#IPv4-mapped_IPv6_addresses. Sometimes, timestamps are sent together with the NetworkAddress such as in the Addr data type.

Constructors

NetworkAddress 

Fields

data 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

newtype Ping Source #

A Ping message is sent to bitcoin peers to check if a TCP/IP connection is still valid.

Constructors

Ping 

Fields

  • pingNonce :: Word64

    A random nonce used to identify the recipient of the ping request once a Pong response is received.

newtype Pong Source #

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

Constructors

Pong 

Fields

  • pongNonce :: Word64

    When responding to a Ping request, the nonce from the Ping is copied in the Pong response.

data Reject Source #

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

Constructors

Reject 

Fields

reject :: MessageCommand -> RejectCode -> ByteString -> Reject Source #

Convenience function to build a Reject message

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

newtype VarString Source #

Data type for variable length strings. Variable length strings are serialized as a VarInt followed by a bytestring.

Constructors

VarString 

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

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.

data Message Source #

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.

data MessageHeader Source #

Data type representing the header of a Message. All messages sent between nodes contain a message header.

Constructors

MessageHeader 

Fields

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.

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.

Constructors

BloomFilter 

Fields

newtype FilterAdd Source #

Add the given data element to the connections current filter without requiring a completely new one to be set.

Constructors

FilterAdd 

bloomCreate Source #

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.

bloomInsert Source #

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.

bloomContains Source #

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.

isBloomValid Source #

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)

data ScriptOp Source #

Data type representing all of the operators allowed inside a Script.

data Script Source #

Data type representing a transaction script. Scripts are defined as lists of script operators ScriptOp. Scripts are used to:

  • Define the spending conditions in the output of a transaction
  • Provide the spending signatures in the input of a transaction

Constructors

Script 

Fields

data PushDataType Source #

Data type representing the type of an OP_PUSHDATA opcode.

Constructors

OPCODE

The next opcode bytes is data to be pushed onto the stack

OPDATA1

The next byte contains the number of bytes to be pushed onto the stack

OPDATA2

The next two bytes contains the number of bytes to be pushed onto the stack

OPDATA4

The next four bytes contains the number of bytes to be pushed onto the stack

isPushOp :: ScriptOp -> Bool Source #

Check whether opcode is only data.

opPushData :: ByteString -> ScriptOp Source #

Optimally encode data using one of the 4 types of data pushing opcodes

data ScriptOutput Source #

Data type describing standard transaction output scripts. Output scripts provide the conditions that must be fulfilled for someone to spend the output coins.

Constructors

PayPK

Pay to a public key.

PayPKHash

Pay to a public key hash.

PayMulSig

Pay to multiple public keys.

PayScriptHash

Pay to a script hash.

DataCarrier

Provably unspendable data carrier.

data SimpleInput Source #

Data type describing standard transaction input scripts. Input scripts provide the signing data required to unlock the coins of the output they are trying to spend.

Constructors

SpendPK

Spend the coins of a PayPK output.

SpendPKHash

Spend the coins of a PayPKHash output.

SpendMulSig

Spend the coins of a PayMulSig output.

scriptAddr :: ScriptOutput -> Address Source #

Computes a script address from a script output. This address can be used in a pay to script hash output.

encodeInputBS :: ScriptInput -> ByteString Source #

Similar to encodeInput but encodes to a ByteString

decodeInput :: Script -> Either String ScriptInput Source #

Decodes a ScriptInput from a Script. This function fails if the script can not be parsed as a standard script input.

decodeInputBS :: ByteString -> Either String ScriptInput Source #

Similar to decodeInput but decodes from a ByteString

encodeOutput :: ScriptOutput -> Script Source #

Computes a Script from a ScriptOutput. The Script is a list of ScriptOp can can be used to build a Tx.

encodeOutputBS :: ScriptOutput -> ByteString Source #

Similar to encodeOutput but encodes to a ByteString

decodeOutput :: Script -> Either String ScriptOutput Source #

Tries to decode a ScriptOutput from a Script. This can fail if the script is not recognized as any of the standard output types.

decodeOutputBS :: ByteString -> Either String ScriptOutput Source #

Similar to decodeOutput but decodes from a ByteString

sortMulSig :: ScriptOutput -> ScriptOutput Source #

Sorts the public keys of a multisignature output in ascending order by comparing their serialized representations. This feature allows for easier multisignature account management as participants in a multisignature wallet will blindly agree on an ordering of the public keys without having to communicate.

intToScriptOp :: Int -> ScriptOp Source #

Transforms integers [1 .. 16] to ScriptOp [OP_1 .. OP_16]

scriptOpToInt :: ScriptOp -> Either String Int Source #

Decode ScriptOp [OP_1 .. OP_16] to integers [1 .. 16]. This functions fails for other values of ScriptOp

isPayPK :: ScriptOutput -> Bool Source #

Returns True if the script is a pay to public key output.

isPayPKHash :: ScriptOutput -> Bool Source #

Returns True if the script is a pay to public key hash output.

isPayMulSig :: ScriptOutput -> Bool Source #

Returns True if the script is a pay to multiple public keys output.

isPayScriptHash :: ScriptOutput -> Bool Source #

Returns true if the script is a pay to script hash output.

isSpendPK :: ScriptInput -> Bool Source #

Returns True if the input script is spending a public key.

isSpendPKHash :: ScriptInput -> Bool Source #

Returns True if the input script is spending a public key hash.

isSpendMulSig :: ScriptInput -> Bool Source #

Returns True if the input script is spending a multisignature output.

isDataCarrier :: ScriptOutput -> Bool Source #

Returns True if the script is an OP_RETURN "datacarrier" output

data SigHash Source #

Data type representing the different ways a transaction can be signed. When producing a signature, a hash of the transaction is used as the message to be signed. The SigHash parameter controls which parts of the transaction are used or ignored to produce the transaction hash. The idea is that if some part of a transaction is not used to produce the transaction hash, then you can change that part of the transaction after producing a signature without invalidating that signature.

If the anyoneCanPay flag is True, then only the current input is signed. Otherwise, all of the inputs of a transaction are signed. The default value for anyoneCanPay is False.

Constructors

SigAll

Sign all of the outputs of a transaction (This is the default value). Changing any of the outputs of the transaction will invalidate the signature.

Fields

SigNone

Sign none of the outputs of a transaction. This allows anyone to change any of the outputs of the transaction.

Fields

SigSingle

Sign only the output corresponding the the current transaction input. You care about your own output in the transaction but you don't care about any of the other outputs.

Fields

SigUnknown

Unrecognized sighash types will decode to SigUnknown.

encodeSigHash32 :: SigHash -> ByteString Source #

Encodes a SigHash to a 32 bit-long bytestring.

isSigAll :: SigHash -> Bool Source #

Returns True if the SigHash has the value SigAll.

isSigNone :: SigHash -> Bool Source #

Returns True if the SigHash has the value SigNone.

isSigSingle :: SigHash -> Bool Source #

Returns True if the SigHash has the value SigSingle.

isSigUnknown :: SigHash -> Bool Source #

Returns True if the SigHash has the value SigUnknown.

txSigHash Source #

Arguments

:: Tx

Transaction to sign.

-> Script

Output script that is being spent.

-> Int

Index of the input that is being signed.

-> SigHash

What parts of the transaction should be signed.

-> Hash256

Result hash to be signed.

Computes the hash that will be used for signing a transaction.

data TxSignature Source #

Data type representing a Signature together with a SigHash. The SigHash is serialized as one byte at the end of a regular ECDSA Signature. All signatures in transaction inputs are of type TxSignature.

Constructors

TxSignature 

encodeSig :: TxSignature -> ByteString Source #

Serialize a TxSignature to a ByteString.

decodeSig :: ByteString -> Either String TxSignature Source #

Decode a TxSignature from a ByteString.

Script evaluation

verifySpend Source #

Arguments

:: Tx

The spending transaction

-> Int

The input index

-> Script

The output script we are spending

-> [Flag]

Evaluation flags

-> Bool 

Uses evalScript to check that the input script of a spending transaction satisfies the output script.

type SigCheck = [ScriptOp] -> TxSignature -> PubKey -> Bool Source #

Defines the type of function required by script evaluating functions to check transaction signatures.

Evaluation data types

data ProgramData Source #

Data type of the evaluation state.

type Stack = [StackValue] Source #

Helper functions

encodeInt :: Int64 -> StackValue Source #

Encoding function for the stack value format of integers. Most significant bit defines sign. Note that this function will encode any Int64 into a StackValue, thus producing stack-encoded integers which are not valid numeric opcodes, as they exceed 4 bytes in length.

decodeInt :: StackValue -> Maybe Int64 Source #

Used for decoding numeric opcodes. Will not return an integer that takes up more than 4 bytes on the stack (the size limit for numeric opcodes). The naming is kept for backwards compatibility.

decodeFullInt :: StackValue -> Maybe Int64 Source #

Decode an Int64 from the stack value integer format. Inverse of encodeInt. Note that only integers decoded by decodeInt are valid numeric opcodes (numeric opcodes can only be up to 4 bytes in size). However, in the case of eg. CHECKLOCKTIMEVERIFY, we need to be able to encode and decode stack integers up to (maxBound :: Word32), which are 5 bytes.

cltvEncodeInt :: Word32 -> StackValue Source #

Helper function for encoding the argument to OP_CHECKLOCKTIMEVERIFY

cltvDecodeInt :: StackValue -> Maybe Word32 Source #

Decode the integer argument to OP_CHECKLOCKTIMEVERIFY (CLTV) from a stack value. The full uint32 range is needed in order to represent timestamps for use with CLTV. Reference: https://github.com/bitcoin/bips/blob/master/bip-0065.mediawiki#Detailed_Specification

encodeBool :: Bool -> StackValue Source #

decodeBool :: StackValue -> Bool Source #

Conversion of StackValue to Bool (true if non-zero).

execScript Source #

Arguments

:: Script

scriptSig ( redeemScript )

-> Script

scriptPubKey

-> SigCheck

signature verification Function

-> [Flag]

Evaluation flags

-> Either EvalError ProgramData 

data Tx Source #

Data type representing a bitcoin transaction

Instances

createTx :: Word32 -> [TxIn] -> [TxOut] -> Word32 -> Tx Source #

txIn :: Tx -> [TxIn] Source #

data TxIn Source #

Data type representing a transaction input.

Constructors

TxIn 

Fields

  • prevOutput :: !OutPoint

    Reference the previous transaction output (hash + position)

  • scriptInput :: !ByteString

    Script providing the requirements of the previous transaction output to spend those coins.

  • txInSequence :: !Word32

    Transaction version as defined by the sender of the transaction. The intended use is for replacing transactions with new information before the transaction is included in a block.

data TxOut Source #

Data type representing a transaction output.

Constructors

TxOut 

Fields

data OutPoint Source #

The OutPoint is used inside a transaction input to reference the previous transaction output that it is spending.

Constructors

OutPoint 

Fields

class Coin c where Source #

Any type can be used as a Coin if it can provide a value in Satoshi. The value is used in coin selection algorithms.

Minimal complete definition

coinValue

Methods

coinValue :: c -> Word64 Source #

buildTx :: [OutPoint] -> [(ScriptOutput, Word64)] -> Either String Tx Source #

Build a transaction by providing a list of outpoints as inputs and a list of ScriptOutput and amounts as outputs.

buildAddrTx :: [OutPoint] -> [(ByteString, Word64)] -> Either String Tx Source #

Build a transaction by providing a list of outpoints as inputs and a list of recipients addresses and amounts as outputs.

data SigInput Source #

Data type used to specify the signing parameters of a transaction input. To sign an input, the previous output script, outpoint and sighash are required. When signing a pay to script hash output, an additional redeem script is required.

Constructors

SigInput 

Fields

signTx Source #

Arguments

:: Tx

Transaction to sign

-> [SigInput]

SigInput signing parameters

-> [PrvKey]

List of private keys to use for signing

-> Either String Tx

Signed transaction

Sign a transaction by providing the SigInput signing paramters and a list of private keys. The signature is computed deterministically as defined in RFC-6979.

signInput :: Tx -> Int -> SigInput -> PrvKey -> Either String Tx Source #

Sign a single input in a transaction deterministically (RFC-6979).

verifyStdTx :: Tx -> [(ScriptOutput, OutPoint)] -> Bool Source #

Verify if a transaction is valid and all of its inputs are standard.

verifyStdInput :: Tx -> Int -> ScriptOutput -> Bool Source #

Verify if a transaction input is valid and standard.

guessTxSize Source #

Arguments

:: Int

Number of regular transaction inputs.

-> [(Int, Int)]

For every multisig input in the transaction, provide the multisig parameters m of n (m,n) for that input.

-> Int

Number of pay to public key hash outputs.

-> Int

Number of pay to script hash outputs.

-> Int

Upper bound on the transaction size.

Computes an upper bound on the size of a transaction based on some known properties of the transaction.

chooseCoins Source #

Arguments

:: Coin c 
=> Word64

Target price to pay.

-> Word64

Fee price per 1000 bytes.

-> Bool

Try to find better solution when one is found

-> [c]

List of ordered coins to choose from.

-> Either String ([c], Word64)

Coin selection result and change amount.

Coin selection algorithm for normal (non-multisig) transactions. This function returns the selected coins together with the amount of change to send back to yourself, taking the fee into account.

chooseCoinsSink Source #

Arguments

:: (Monad m, Coin c) 
=> Word64

Target price to pay.

-> Word64

Fee price per 1000 bytes.

-> Bool

Try to find better solution when one is found

-> Sink c m (Either String ([c], Word64))

Coin selection result and change amount.

Coin selection algorithm for normal (non-multisig) transactions. This function returns the selected coins together with the amount of change to send back to yourself, taking the fee into account. This version uses a Sink if you need conduit-based coin selection.

chooseMSCoins Source #

Arguments

:: Coin c 
=> Word64

Target price to pay.

-> Word64

Fee price per 1000 bytes.

-> (Int, Int)

Multisig parameters m of n (m,n).

-> Bool

Try to find better solution when one is found

-> [c] 
-> Either String ([c], Word64)

Coin selection result and change amount.

Coin selection algorithm for multisignature transactions. This function returns the selected coins together with the amount of change to send back to yourself, taking the fee into account. This function assumes all the coins are script hash outputs that send funds to a multisignature address.

chooseMSCoinsSink Source #

Arguments

:: (Monad m, Coin c) 
=> Word64

Target price to pay.

-> Word64

Fee price per 1000 bytes.

-> (Int, Int)

Multisig parameters m of n (m,n).

-> Bool

Try to find better solution when one is found

-> Sink c m (Either String ([c], Word64))

Coin selection result and change amount.

Coin selection algorithm for multisignature transactions. This function returns the selected coins together with the amount of change to send back to yourself, taking the fee into account. This function assumes all the coins are script hash outputs that send funds to a multisignature address. This version uses a Sink if you need conduit-based coin selection.

data Block Source #

Data type describing a block in the bitcoin protocol. Blocks are sent in response to GetData messages that are requesting information from a block hash.

Constructors

Block 

Fields

data BlockHeader Source #

Data type recording information on a Block. The hash of a block is defined as the hash of this data structure. The block mining process involves finding a partial hash collision by varying the nonce in the BlockHeader and/or additional randomness in the coinbase tx of this Block. Variations in the coinbase tx will result in different merkle roots in the BlockHeader.

data GetBlocks Source #

Data type representing a GetBlocks message request. It is used in the bitcoin protocol to retrieve blocks from a peer by providing it a BlockLocator object. The BlockLocator is a sparse list of block hashes from the caller node with the purpose of informing the receiving node about the state of the caller's blockchain. The receiver node will detect a wrong branch in the caller's main chain and send the caller appropriate Blocks. The response to a GetBlocks message is an Inv message containing the list of block hashes pertaining to the request.

Constructors

GetBlocks 

Fields

data GetHeaders Source #

Similar to the GetBlocks message type but for retrieving block headers only. The response to a GetHeaders request is a Headers message containing a list of block headers pertaining to the request. A maximum of 2000 block headers can be returned. GetHeaders is used by thin (SPV) clients to exclude block contents when synchronizing the blockchain.

Constructors

GetHeaders 

Fields

  • getHeadersVersion :: !Word32

    The protocol version

  • getHeadersBL :: !BlockLocator

    Block locator object. It is a list of block hashes from the most recent block back to the Genesis block. The list is dense at first and sparse towards the end.

  • getHeadersHashStop :: !BlockHash

    Hash of the last desired block header. When set to zero, the maximum number of block headers is returned (2000)

type BlockHeaderCount = (BlockHeader, VarInt) Source #

BlockHeader type with a transaction count as VarInt

data Headers Source #

The Headers type is used to return a list of block headers in response to a GetHeaders message.

Constructors

Headers 

Fields

decodeCompact :: Word32 -> Integer Source #

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

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

data MerkleBlock Source #

Constructors

MerkleBlock 

Fields

  • merkleHeader :: !BlockHeader

    Header information for this merkle block.

  • merkleTotalTxns :: !Word32

    Number of transactions in the block (including unmatched transactions).

  • mHashes :: ![Hash256]

    Hashes in depth-first order. They are used to rebuild a partial merkle tree.

  • mFlags :: ![Bool]

    Flag bits, packed per 8 in a byte. Least significant bit first. Flag bits are used to rebuild a partial merkle tree.

calcTreeHeight Source #

Arguments

:: Int

Number of transactions (leaf nodes).

-> Int

Height of the merkle tree.

Computes the height of a merkle tree.

calcTreeWidth Source #

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.

buildMerkleRoot Source #

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.

calcHash Source #

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

-> Hash256

Hash of the node at the specified position.

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

buildPartialMerkle Source #

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.

extractMatches Source #

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.