| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Network.Haskoin.Test
Description
This package provides test types for Network.Haskoin
Synopsis
- arbitraryBS :: Gen ByteString
- arbitraryBS1 :: Gen ByteString
- arbitraryBSn :: Int -> Gen ByteString
- arbitraryUTCTime :: Gen UTCTime
- arbitraryMaybe :: Gen a -> Gen (Maybe a)
- newtype TestCoin = TestCoin {}
- arbitraryTxHash :: Gen TxHash
- arbitrarySatoshi :: Network -> Gen TestCoin
- arbitraryOutPoint :: Gen OutPoint
- arbitraryTxOut :: Network -> Gen TxOut
- arbitraryTxIn :: Network -> Gen TxIn
- arbitraryTx :: Network -> Gen Tx
- arbitraryLegacyTx :: Network -> Gen Tx
- arbitraryWitnessTx :: Network -> Gen Tx
- arbitraryWLTx :: Network -> Bool -> Gen Tx
- arbitraryAddrOnlyTx :: Network -> Gen Tx
- arbitraryAddrOnlyTxFull :: Network -> Gen Tx
- arbitraryAddrOnlyTxIn :: Network -> Gen TxIn
- arbitraryAddrOnlyTxInFull :: Network -> Gen TxIn
- arbitraryAddrOnlyTxOut :: Network -> Gen TxOut
- arbitrarySigInput :: Network -> Gen (SigInput, [SecKeyI])
- arbitraryPKSigInput :: Network -> Gen (SigInput, SecKeyI)
- arbitraryPKHashSigInput :: Network -> Gen (SigInput, SecKeyI)
- arbitraryAnyInput :: Network -> Bool -> Gen (SigInput, SecKeyI)
- arbitraryInputStuff :: Network -> Gen (Word64, OutPoint, SigHash)
- arbitraryMSSigInput :: Network -> Gen (SigInput, [SecKeyI])
- arbitrarySHSigInput :: Network -> Gen (SigInput, [SecKeyI])
- arbitrarySigningData :: Network -> Gen (Tx, [SigInput], [SecKeyI])
- arbitraryEmptyTx :: Network -> Gen Tx
- arbitraryPartialTxs :: Network -> Gen ([Tx], [(ScriptOutput, Word64, OutPoint, Int, Int)])
- arbitraryScript :: Gen Script
- arbitraryScriptOp :: Gen ScriptOp
- arbitraryIntScriptOp :: Gen ScriptOp
- arbitraryPushDataType :: Gen PushDataType
- arbitrarySigHash :: Gen SigHash
- arbitraryValidSigHash :: Network -> Gen SigHash
- arbitraryTxSignature :: Network -> Gen (TxHash, SecKey, TxSignature)
- arbitraryTxSignatureEmpty :: Network -> Gen TxSignature
- arbitraryMSParam :: Gen (Int, Int)
- arbitraryScriptOutput :: Network -> Gen ScriptOutput
- arbitrarySimpleOutput :: Gen ScriptOutput
- arbitraryPKOutput :: Gen ScriptOutput
- arbitraryPKHashOutput :: Gen ScriptOutput
- arbitraryWPKHashOutput :: Gen ScriptOutput
- arbitraryWSHOutput :: Gen ScriptOutput
- arbitraryMSOutput :: Gen ScriptOutput
- arbitraryMSOutputC :: Gen ScriptOutput
- arbitrarySHOutput :: Network -> Gen ScriptOutput
- arbitraryDCOutput :: Gen ScriptOutput
- arbitraryScriptInput :: Network -> Gen ScriptInput
- arbitrarySimpleInput :: Network -> Gen ScriptInput
- arbitraryPKInput :: Network -> Gen ScriptInput
- arbitraryPKHashInput :: Network -> Gen ScriptInput
- arbitraryPKHashInputFull :: Network -> Gen ScriptInput
- arbitraryPKHashInputFullC :: Network -> Gen ScriptInput
- arbitraryMSInput :: Network -> Gen ScriptInput
- arbitrarySHInput :: Network -> Gen ScriptInput
- arbitraryMulSigSHInput :: Network -> Gen ScriptInput
- arbitraryMulSigSHInputC :: Network -> Gen ScriptInput
- arbitraryMulSigSHInputFull :: Network -> Gen ScriptInput
- arbitraryMulSigSHInputFullC :: Network -> Gen ScriptInput
- arbitraryVarInt :: Gen VarInt
- arbitraryVarString :: Gen VarString
- arbitraryNetworkAddress :: Gen NetworkAddress
- arbitraryNetworkAddressTime :: Gen (Word32, NetworkAddress)
- arbitraryInvType :: Gen InvType
- arbitraryInvVector :: Gen InvVector
- arbitraryInv1 :: Gen Inv
- arbitraryVersion :: Gen Version
- arbitraryAddr1 :: Gen Addr
- arbitraryAlert :: Gen Alert
- arbitraryReject :: Gen Reject
- arbitraryRejectCode :: Gen RejectCode
- arbitraryGetData :: Gen GetData
- arbitraryNotFound :: Gen NotFound
- arbitraryPing :: Gen Ping
- arbitraryPong :: Gen Pong
- arbitraryBloomFlags :: Gen BloomFlags
- arbitraryBloomFilter :: Gen (Int, Double, BloomFilter)
- arbitraryFilterLoad :: Gen FilterLoad
- arbitraryFilterAdd :: Gen FilterAdd
- arbitraryMessageCommand :: Gen MessageCommand
- arbitraryMessageHeader :: Gen MessageHeader
- arbitraryMessage :: Network -> Gen Message
- arbitrarySecKeyI :: Gen SecKeyI
- arbitraryKeyPair :: Gen (SecKeyI, PubKeyI)
- arbitraryXPrvKey :: Network -> Gen XPrvKey
- arbitraryXPubKey :: Network -> Gen (XPrvKey, XPubKey)
- genIndex :: Gen Word32
- arbitraryBip32PathIndex :: Gen Bip32PathIndex
- arbitraryHardPath :: Gen HardPath
- arbitrarySoftPath :: Gen SoftPath
- arbitraryDerivPath :: Gen DerivPath
- arbitraryParsedPath :: Gen ParsedPath
- arbitrarySignature :: Gen (Hash256, SecKey, Sig)
- arbitraryHash160 :: Gen Hash160
- arbitraryHash256 :: Gen Hash256
- arbitraryHash512 :: Gen Hash512
- arbitraryCheckSum32 :: Gen CheckSum32
- arbitraryBlock :: Network -> Gen Block
- arbitraryBlockHeader :: Gen BlockHeader
- arbitraryBlockHash :: Gen BlockHash
- arbitraryGetBlocks :: Gen GetBlocks
- arbitraryGetHeaders :: Gen GetHeaders
- arbitraryHeaders :: Gen Headers
- arbitraryMerkleBlock :: Gen MerkleBlock
- arbitraryAddress :: Network -> Gen Address
- arbitraryPubKeyAddress :: Network -> Gen Address
- arbitraryScriptAddress :: Network -> Gen Address
Documentation
arbitraryBS :: Gen ByteString Source #
Arbitrary strict ByteString.
arbitraryBS1 :: Gen ByteString Source #
Arbitrary non-empty strict ByteString
arbitraryBSn :: Int -> Gen ByteString Source #
Arbitrary strict ByteString of a given length
arbitraryUTCTime :: Gen UTCTime Source #
Arbitrary UTCTime that generates dates after 01 Jan 1970 01:00:00 CET
Constructors
| TestCoin | |
| Fields | |
arbitraryTxHash :: Gen TxHash Source #
Arbitrary transaction hash (for non-existent transaction).
arbitrarySatoshi :: Network -> Gen TestCoin Source #
Arbitrary amount of Satoshi as Word64 (Between 1 and 21e14)
arbitraryWitnessTx :: Network -> Gen Tx Source #
Arbitrary witness transaction (witness data is fake).
arbitraryAddrOnlyTx :: Network -> Gen Tx Source #
Arbitrary transaction containing only inputs of type SpendPKHash,
 SpendScriptHash (multisig) and outputs of type PayPKHash and PaySH.
 Only compressed public keys are used.
arbitraryAddrOnlyTxFull :: Network -> Gen Tx Source #
Like arbitraryAddrOnlyTx without empty signatures in the inputs.
arbitraryAddrOnlyTxIn :: Network -> Gen TxIn Source #
Arbitrary TxIn that can only be of type SpendPKHash or SpendScriptHash
 (multisig). Only compressed public keys are used.
arbitraryAddrOnlyTxInFull :: Network -> Gen TxIn Source #
like arbitraryAddrOnlyTxIn with no empty signatures.
arbitrarySigInput :: Network -> Gen (SigInput, [SecKeyI]) Source #
Arbitrary SigInput with the corresponding private keys used
 to generate the ScriptOutput or RedeemScript.
arbitraryPKSigInput :: Network -> Gen (SigInput, SecKeyI) Source #
Arbitrary SigInput with a ScriptOutput of type PayPK.
arbitraryPKHashSigInput :: Network -> Gen (SigInput, SecKeyI) Source #
Arbitrary SigInput with a ScriptOutput of type PayPKHash.
arbitraryMSSigInput :: Network -> Gen (SigInput, [SecKeyI]) Source #
Arbitrary SigInput with a ScriptOutput of type PayMulSig.
arbitrarySHSigInput :: Network -> Gen (SigInput, [SecKeyI]) Source #
Arbitrary SigInput with ScriptOutput of type PaySH and a
 RedeemScript.
arbitraryPartialTxs :: Network -> Gen ([Tx], [(ScriptOutput, Word64, OutPoint, Int, Int)]) Source #
Arbitrary partially-signed transactions.
arbitraryPushDataType :: Gen PushDataType Source #
Arbitrary PushDataType.
arbitrarySigHash :: Gen SigHash Source #
Arbitrary SigHash (including invalid/unknown sighash codes).
arbitraryTxSignature :: Network -> Gen (TxHash, SecKey, TxSignature) Source #
Arbitrary message hash, private key and corresponding TxSignature. The
 signature is generated deterministically using a random message and a random
 private key.
arbitraryTxSignatureEmpty :: Network -> Gen TxSignature Source #
Arbitrary transaction signature that could also be empty.
arbitraryScriptOutput :: Network -> Gen ScriptOutput Source #
Arbitrary ScriptOutput (Can by any valid type).
arbitrarySimpleOutput :: Gen ScriptOutput Source #
Arbitrary ScriptOutput of type PayPK, PayPKHash or PayMS
 (Not PayScriptHash, DataCarrier, or SegWit)
arbitraryPKOutput :: Gen ScriptOutput Source #
Arbitrary ScriptOutput of type PayPK
arbitraryPKHashOutput :: Gen ScriptOutput Source #
Arbitrary ScriptOutput of type PayPKHash
arbitraryWPKHashOutput :: Gen ScriptOutput Source #
Arbitrary PayWitnessPKHash output.
arbitraryWSHOutput :: Gen ScriptOutput Source #
Arbitrary PayWitnessScriptHash output.
arbitraryMSOutput :: Gen ScriptOutput Source #
Arbitrary ScriptOutput of type PayMS.
arbitraryMSOutputC :: Gen ScriptOutput Source #
Arbitrary ScriptOutput of type PayMS, only using compressed keys.
arbitrarySHOutput :: Network -> Gen ScriptOutput Source #
Arbitrary ScriptOutput of type PayScriptHash.
arbitraryDCOutput :: Gen ScriptOutput Source #
Arbitrary ScriptOutput of type DataCarrier.
arbitraryScriptInput :: Network -> Gen ScriptInput Source #
Arbitrary ScriptInput.
arbitrarySimpleInput :: Network -> Gen ScriptInput Source #
Arbitrary ScriptInput of type SpendPK, SpendPKHash or SpendMulSig
 (not ScriptHashInput)
arbitraryPKInput :: Network -> Gen ScriptInput Source #
Arbitrary ScriptInput of type SpendPK.
arbitraryPKHashInput :: Network -> Gen ScriptInput Source #
Arbitrary ScriptInput of type SpendPK.
arbitraryPKHashInputFull :: Network -> Gen ScriptInput Source #
Like arbitraryPKHashInput without empty signatures.
arbitraryPKHashInputFullC :: Network -> Gen ScriptInput Source #
Like above but only compressed.
arbitraryMSInput :: Network -> Gen ScriptInput Source #
Arbitrary ScriptInput of type SpendMulSig.
arbitrarySHInput :: Network -> Gen ScriptInput Source #
Arbitrary ScriptInput of type ScriptHashInput.
arbitraryMulSigSHInput :: Network -> Gen ScriptInput Source #
Arbitrary ScriptInput of type ScriptHashInput containing a
 RedeemScript of type PayMulSig and an input of type SpendMulSig.
arbitraryMulSigSHInputC :: Network -> Gen ScriptInput Source #
Arbitrary ScriptInput of type ScriptHashInput containing a
 RedeemScript of type PayMulSig and an input of type SpendMulSig.
arbitraryMulSigSHInputFull :: Network -> Gen ScriptInput Source #
Like arbitraryMulSigSHCInput with no empty signatures.
arbitraryMulSigSHInputFullC :: Network -> Gen ScriptInput Source #
Like arbitraryMulSigSHCInput with no empty signatures.
arbitraryNetworkAddress :: Gen NetworkAddress Source #
Arbitrary NetworkAddress.
arbitraryNetworkAddressTime :: Gen (Word32, NetworkAddress) Source #
Arbitrary NetworkAddressTime.
arbitraryAlert :: Gen Alert Source #
Arbitrary Alert with random payload and signature. Signature is not
 valid.
arbitraryRejectCode :: Gen RejectCode Source #
Arbitrary RejectCode.
arbitraryBloomFlags :: Gen BloomFlags Source #
Arbitrary bloom filter flags.
arbitraryBloomFilter :: Gen (Int, Double, BloomFilter) Source #
Arbitrary bloom filter with its corresponding number of elements and false positive rate.
arbitraryFilterLoad :: Gen FilterLoad Source #
Arbitrary FilterLoad.
arbitraryMessageCommand :: Gen MessageCommand Source #
Arbitrary MessageCommand.
arbitraryMessageHeader :: Gen MessageHeader Source #
Arbitrary MessageHeader.
arbitrarySecKeyI :: Gen SecKeyI Source #
Arbitrary private key with arbitrary compressed flag.
arbitraryKeyPair :: Gen (SecKeyI, PubKeyI) Source #
Arbitrary keypair, both either compressed or not.
arbitraryXPubKey :: Network -> Gen (XPrvKey, XPubKey) Source #
Arbitrary extended public key with its corresponding private key.
arbitraryBip32PathIndex :: Gen Bip32PathIndex Source #
Arbitrary BIP-32 path index. Can be hardened or not.
arbitraryHardPath :: Gen HardPath Source #
Arbitrary BIP-32 derivation path composed of only hardened derivations.
arbitrarySoftPath :: Gen SoftPath Source #
Arbitrary BIP-32 derivation path composed of only non-hardened derivations.
arbitraryDerivPath :: Gen DerivPath Source #
Arbitrary derivation path composed of hardened and non-hardened derivations.
arbitraryParsedPath :: Gen ParsedPath Source #
Arbitrary parsed derivation path. Can contain ParsedPrv, ParsedPub or
 ParsedEmpty elements.
arbitrarySignature :: Gen (Hash256, SecKey, Sig) Source #
Arbitrary message hash, private key, nonce and corresponding signature. The signature is generated with a random message, random private key and a random nonce.
arbitraryHash160 :: Gen Hash160 Source #
Arbitrary 160-bit hash.
arbitraryHash256 :: Gen Hash256 Source #
Arbitrary 256-bit hash.
arbitraryHash512 :: Gen Hash512 Source #
Arbitrary 512-bit hash.
arbitraryCheckSum32 :: Gen CheckSum32 Source #
Arbitrary 32-bit checksum.
arbitraryBlockHeader :: Gen BlockHeader Source #
Block header with random hash.
arbitraryBlockHash :: Gen BlockHash Source #
Arbitrary block hash.
arbitraryGetBlocks :: Gen GetBlocks Source #
Arbitrary GetBlocks object with at least one block hash.
arbitraryGetHeaders :: Gen GetHeaders Source #
Arbitrary GetHeaders object with at least one block header.
arbitraryMerkleBlock :: Gen MerkleBlock Source #
Arbitrary MerkleBlock with at least one hash.