| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Network.Haskoin.Internals
Contents
Description
This module expose haskoin internals. No guarantee is made on the stability of the interface of these internal modules.
- module Network.Haskoin.Util
- module Network.Haskoin.Constants
- data Hash512
- data Hash256
- data Hash160
- data CheckSum32
- bsToHash512 :: ByteString -> Maybe Hash512
- bsToHash256 :: ByteString -> Maybe Hash256
- bsToHash160 :: ByteString -> Maybe Hash160
- hash512 :: ByteString -> Hash512
- hash256 :: ByteString -> Hash256
- hash160 :: ByteString -> Hash160
- sha1 :: ByteString -> Hash160
- doubleHash256 :: ByteString -> Hash256
- bsToCheckSum32 :: ByteString -> Maybe CheckSum32
- checkSum32 :: ByteString -> CheckSum32
- hmac512 :: ByteString -> ByteString -> Hash512
- hmac256 :: ByteString -> ByteString -> Hash256
- split512 :: Hash512 -> (Hash256, Hash256)
- join512 :: (Hash256, Hash256) -> Hash512
- hmacDRBGNew :: EntropyInput -> Nonce -> PersString -> WorkingState
- hmacDRBGUpd :: ProvidedData -> ByteString -> ByteString -> (ByteString, ByteString)
- hmacDRBGRsd :: WorkingState -> EntropyInput -> AdditionalInput -> WorkingState
- hmacDRBGGen :: WorkingState -> Word16 -> AdditionalInput -> (WorkingState, Maybe ByteString)
- type WorkingState = (ByteString, ByteString, Word16)
- data Address- = PubKeyAddress { - getAddrHash :: !Hash160
 
- | ScriptAddress { - getAddrHash :: !Hash160
 
 
- = PubKeyAddress { 
- addrToBase58 :: Address -> ByteString
- base58ToAddr :: ByteString -> Maybe Address
- encodeBase58 :: ByteString -> ByteString
- decodeBase58 :: ByteString -> Maybe ByteString
- encodeBase58Check :: ByteString -> ByteString
- decodeBase58Check :: ByteString -> Maybe ByteString
- data PubKeyI c
- type PubKey = PubKeyI Generic
- type PubKeyC = PubKeyI Compressed
- type PubKeyU = PubKeyI Uncompressed
- makePubKey :: PubKey -> PubKey
- makePubKeyG :: Bool -> PubKey -> PubKey
- makePubKeyC :: PubKey -> PubKeyC
- makePubKeyU :: PubKey -> PubKeyU
- toPubKeyG :: PubKeyI c -> PubKey
- eitherPubKey :: PubKeyI c -> Either PubKeyU PubKeyC
- maybePubKeyC :: PubKeyI c -> Maybe PubKeyC
- maybePubKeyU :: PubKeyI c -> Maybe PubKeyU
- derivePubKey :: PrvKeyI c -> PubKeyI c
- pubKeyAddr :: Binary (PubKeyI c) => PubKeyI c -> Address
- tweakPubKeyC :: PubKeyC -> Hash256 -> Maybe PubKeyC
- data PrvKeyI c
- type PrvKey = PrvKeyI Generic
- type PrvKeyC = PrvKeyI Compressed
- type PrvKeyU = PrvKeyI Uncompressed
- makePrvKey :: SecKey -> PrvKey
- makePrvKeyG :: Bool -> SecKey -> PrvKey
- makePrvKeyC :: SecKey -> PrvKeyC
- makePrvKeyU :: SecKey -> PrvKeyU
- toPrvKeyG :: PrvKeyI c -> PrvKey
- eitherPrvKey :: PrvKeyI c -> Either PrvKeyU PrvKeyC
- maybePrvKeyC :: PrvKeyI c -> Maybe PrvKeyC
- maybePrvKeyU :: PrvKeyI c -> Maybe PrvKeyU
- encodePrvKey :: PrvKeyI c -> ByteString
- decodePrvKey :: (SecKey -> PrvKeyI c) -> ByteString -> Maybe (PrvKeyI c)
- prvKeyPutMonad :: PrvKeyI c -> Put
- prvKeyGetMonad :: (SecKey -> PrvKeyI c) -> Get (PrvKeyI c)
- fromWif :: ByteString -> Maybe PrvKey
- toWif :: PrvKeyI c -> ByteString
- tweakPrvKeyC :: PrvKeyC -> Hash256 -> Maybe PrvKeyC
- data XPubKey = XPubKey {}
- data XPrvKey = XPrvKey {}
- type ChainCode = Hash256
- type KeyIndex = Word32
- data DerivationException = DerivationException String
- makeXPrvKey :: ByteString -> XPrvKey
- deriveXPubKey :: XPrvKey -> XPubKey
- prvSubKey :: XPrvKey -> KeyIndex -> XPrvKey
- pubSubKey :: XPubKey -> KeyIndex -> XPubKey
- hardSubKey :: XPrvKey -> KeyIndex -> XPrvKey
- xPrvIsHard :: XPrvKey -> Bool
- xPubIsHard :: XPubKey -> Bool
- xPrvChild :: XPrvKey -> KeyIndex
- xPubChild :: XPubKey -> KeyIndex
- xPubID :: XPubKey -> Hash160
- xPrvID :: XPrvKey -> Hash160
- xPubFP :: XPubKey -> Word32
- xPrvFP :: XPrvKey -> Word32
- xPubAddr :: XPubKey -> Address
- xPubExport :: XPubKey -> ByteString
- xPrvExport :: XPrvKey -> ByteString
- xPubImport :: ByteString -> Maybe XPubKey
- xPrvImport :: ByteString -> Maybe XPrvKey
- xPrvWif :: XPrvKey -> ByteString
- prvSubKeys :: XPrvKey -> KeyIndex -> [(XPrvKey, KeyIndex)]
- pubSubKeys :: XPubKey -> KeyIndex -> [(XPubKey, KeyIndex)]
- hardSubKeys :: XPrvKey -> KeyIndex -> [(XPrvKey, KeyIndex)]
- deriveAddr :: XPubKey -> KeyIndex -> (Address, PubKeyC)
- deriveAddrs :: XPubKey -> KeyIndex -> [(Address, PubKeyC, KeyIndex)]
- deriveMSAddr :: [XPubKey] -> Int -> KeyIndex -> (Address, RedeemScript)
- deriveMSAddrs :: [XPubKey] -> Int -> KeyIndex -> [(Address, RedeemScript, KeyIndex)]
- cycleIndex :: KeyIndex -> [KeyIndex]
- data DerivPathI t where- (:|) :: HardOrGeneric t => !(DerivPathI t) -> !KeyIndex -> DerivPathI t
- (:/) :: GenericOrSoft t => !(DerivPathI t) -> !KeyIndex -> DerivPathI t
- Deriv :: DerivPathI t
 
- class HardOrGeneric a
- class GenericOrSoft a
- type DerivPath = DerivPathI Generic
- type HardPath = DerivPathI Hard
- type SoftPath = DerivPathI Soft
- data Bip32PathIndex
- derivePath :: DerivPathI t -> XPrvKey -> XPrvKey
- derivePubPath :: SoftPath -> XPubKey -> XPubKey
- toHard :: DerivPathI t -> Maybe HardPath
- toSoft :: DerivPathI t -> Maybe SoftPath
- toGeneric :: DerivPathI t -> DerivPath
- (++/) :: DerivPathI t1 -> DerivPathI t2 -> DerivPath
- pathToStr :: DerivPathI t -> String
- data XKey- = XPrv { - getXPrvKey :: !XPrvKey
 
- | XPub { - getXPubKey :: !XPubKey
 
 
- = XPrv { 
- data ParsedPath- = ParsedPrv { }
- | ParsedPub { }
- | ParsedEmpty { }
 
- parsePath :: String -> Maybe ParsedPath
- parseHard :: String -> Maybe HardPath
- parseSoft :: String -> Maybe SoftPath
- applyPath :: ParsedPath -> XKey -> Either String XKey
- derivePathAddr :: XPubKey -> SoftPath -> KeyIndex -> (Address, PubKeyC)
- derivePathAddrs :: XPubKey -> SoftPath -> KeyIndex -> [(Address, PubKeyC, KeyIndex)]
- derivePathMSAddr :: [XPubKey] -> SoftPath -> Int -> KeyIndex -> (Address, RedeemScript)
- derivePathMSAddrs :: [XPubKey] -> SoftPath -> Int -> KeyIndex -> [(Address, RedeemScript, KeyIndex)]
- concatBip32Segments :: [Bip32PathIndex] -> DerivPath
- type SecretT m = StateT (SecretState m) m
- newtype Signature = Signature {- getSignature :: Sig
 
- withSource :: Monad m => (Int -> m ByteString) -> SecretT m a -> m a
- getEntropy :: Int -> IO ByteString
- signMsg :: Hash256 -> PrvKey -> Signature
- verifySig :: Hash256 -> Signature -> PubKey -> Bool
- genPrvKey :: Monad m => SecretT m PrvKey
- isCanonicalHalfOrder :: Signature -> Bool
- decodeDerSig :: ByteString -> Maybe Signature
- decodeStrictSig :: ByteString -> Maybe Signature
- type Entropy = ByteString
- type Mnemonic = ByteString
- type Passphrase = ByteString
- type Seed = ByteString
- toMnemonic :: Entropy -> Either String Mnemonic
- fromMnemonic :: Mnemonic -> Either String Entropy
- mnemonicToSeed :: Passphrase -> Mnemonic -> Either String Seed
- getBits :: Int -> ByteString -> ByteString
- data Addr = Addr {- addrList :: ![NetworkAddressTime]
 
- type NetworkAddressTime = (Word32, NetworkAddress)
- data Alert = Alert {}
- data GetData = GetData {- getDataList :: ![InvVector]
 
- data Inv = Inv {}
- data InvVector = InvVector {}
- data InvType
- data NetworkAddress = NetworkAddress {- naServices :: !Word64
- naAddress :: !SockAddr
 
- data NotFound = NotFound {- notFoundList :: ![InvVector]
 
- newtype Ping = Ping {}
- newtype Pong = Pong {}
- data Reject = Reject {}
- data RejectCode
- reject :: MessageCommand -> RejectCode -> ByteString -> Reject
- newtype VarInt = VarInt {}
- newtype VarString = VarString {}
- data Version = Version {}
- data 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
 
- data MessageHeader = MessageHeader {- headMagic :: !Word32
- headCmd :: !MessageCommand
- headPayloadSize :: !Word32
- headChecksum :: !CheckSum32
 
- 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
- data ScriptOp- = OP_PUSHDATA !ByteString !PushDataType
- | OP_0
- | OP_1NEGATE
- | OP_RESERVED
- | OP_1
- | OP_2
- | OP_3
- | OP_4
- | OP_5
- | OP_6
- | OP_7
- | OP_8
- | OP_9
- | OP_10
- | OP_11
- | OP_12
- | OP_13
- | OP_14
- | OP_15
- | OP_16
- | OP_NOP
- | OP_VER
- | OP_IF
- | OP_NOTIF
- | OP_VERIF
- | OP_VERNOTIF
- | OP_ELSE
- | OP_ENDIF
- | OP_VERIFY
- | OP_RETURN
- | OP_TOALTSTACK
- | OP_FROMALTSTACK
- | OP_IFDUP
- | OP_DEPTH
- | OP_DROP
- | OP_DUP
- | OP_NIP
- | OP_OVER
- | OP_PICK
- | OP_ROLL
- | OP_ROT
- | OP_SWAP
- | OP_TUCK
- | OP_2DROP
- | OP_2DUP
- | OP_3DUP
- | OP_2OVER
- | OP_2ROT
- | OP_2SWAP
- | OP_CAT
- | OP_SUBSTR
- | OP_LEFT
- | OP_RIGHT
- | OP_SIZE
- | OP_INVERT
- | OP_AND
- | OP_OR
- | OP_XOR
- | OP_EQUAL
- | OP_EQUALVERIFY
- | OP_RESERVED1
- | OP_RESERVED2
- | OP_1ADD
- | OP_1SUB
- | OP_2MUL
- | OP_2DIV
- | OP_NEGATE
- | OP_ABS
- | OP_NOT
- | OP_0NOTEQUAL
- | OP_ADD
- | OP_SUB
- | OP_MUL
- | OP_DIV
- | OP_MOD
- | OP_LSHIFT
- | OP_RSHIFT
- | OP_BOOLAND
- | OP_BOOLOR
- | OP_NUMEQUAL
- | OP_NUMEQUALVERIFY
- | OP_NUMNOTEQUAL
- | OP_LESSTHAN
- | OP_GREATERTHAN
- | OP_LESSTHANOREQUAL
- | OP_GREATERTHANOREQUAL
- | OP_MIN
- | OP_MAX
- | OP_WITHIN
- | OP_RIPEMD160
- | OP_SHA1
- | OP_SHA256
- | OP_HASH160
- | OP_HASH256
- | OP_CODESEPARATOR
- | OP_CHECKSIG
- | OP_CHECKSIGVERIFY
- | OP_CHECKMULTISIG
- | OP_CHECKMULTISIGVERIFY
- | OP_NOP1
- | OP_NOP2
- | OP_NOP3
- | OP_NOP4
- | OP_NOP5
- | OP_NOP6
- | OP_NOP7
- | OP_NOP8
- | OP_NOP9
- | OP_NOP10
- | OP_PUBKEYHASH
- | OP_PUBKEY
- | OP_INVALIDOPCODE !Word8
 
- data Script = Script {}
- data PushDataType
- isPushOp :: ScriptOp -> Bool
- opPushData :: ByteString -> ScriptOp
- data ScriptOutput- = PayPK { }
- | PayPKHash { }
- | PayMulSig { }
- | PayScriptHash { }
 
- data ScriptInput
- data SimpleInput- = SpendPK { }
- | SpendPKHash { - getInputSig :: !TxSignature
- getInputKey :: !PubKey
 
- | SpendMulSig { }
 
- type RedeemScript = ScriptOutput
- scriptAddr :: ScriptOutput -> Address
- scriptRecipient :: Script -> Either String Address
- scriptSender :: Script -> Either String Address
- encodeInput :: ScriptInput -> Script
- encodeInputBS :: ScriptInput -> ByteString
- decodeInput :: Script -> Either String ScriptInput
- decodeInputBS :: ByteString -> Either String ScriptInput
- encodeOutput :: ScriptOutput -> Script
- encodeOutputBS :: ScriptOutput -> ByteString
- decodeOutput :: Script -> Either String ScriptOutput
- decodeOutputBS :: ByteString -> Either String ScriptOutput
- sortMulSig :: ScriptOutput -> ScriptOutput
- intToScriptOp :: Int -> ScriptOp
- scriptOpToInt :: ScriptOp -> Either String Int
- isPayPK :: ScriptOutput -> Bool
- isPayPKHash :: ScriptOutput -> Bool
- isPayMulSig :: ScriptOutput -> Bool
- isPayScriptHash :: ScriptOutput -> Bool
- isSpendPK :: ScriptInput -> Bool
- isSpendPKHash :: ScriptInput -> Bool
- isSpendMulSig :: ScriptInput -> Bool
- isScriptHashInput :: ScriptInput -> Bool
- data SigHash- = SigAll { - anyoneCanPay :: !Bool
 
- | SigNone { - anyoneCanPay :: !Bool
 
- | SigSingle { - anyoneCanPay :: !Bool
 
- | SigUnknown { - anyoneCanPay :: !Bool
- getSigCode :: !Word8
 
 
- = SigAll { 
- encodeSigHash32 :: SigHash -> ByteString
- isSigAll :: SigHash -> Bool
- isSigNone :: SigHash -> Bool
- isSigSingle :: SigHash -> Bool
- isSigUnknown :: SigHash -> Bool
- txSigHash :: Tx -> Script -> Int -> SigHash -> Hash256
- data TxSignature = TxSignature {- txSignature :: !Signature
- sigHashType :: !SigHash
 
- encodeSig :: TxSignature -> ByteString
- decodeSig :: ByteString -> Either String TxSignature
- decodeCanonicalSig :: ByteString -> Either String TxSignature
- verifySpend :: Tx -> Int -> Script -> [Flag] -> Bool
- evalScript :: Script -> Script -> SigCheck -> [Flag] -> Bool
- type SigCheck = [ScriptOp] -> TxSignature -> PubKey -> Bool
- data Flag
- data ProgramData
- type Stack = [StackValue]
- encodeInt :: Int64 -> StackValue
- decodeInt :: StackValue -> Maybe Int64
- encodeBool :: Bool -> StackValue
- decodeBool :: StackValue -> Bool
- runStack :: ProgramData -> Stack
- checkStack :: Stack -> Bool
- dumpScript :: [ScriptOp] -> ByteString
- dumpStack :: Stack -> ByteString
- execScript :: Script -> Script -> SigCheck -> [Flag] -> Either EvalError ProgramData
- data Tx = Tx {}
- data TxIn = TxIn {- prevOutput :: !OutPoint
- scriptInput :: !ByteString
- txInSequence :: !Word32
 
- data TxOut = TxOut {- outValue :: !Word64
- scriptOutput :: !ByteString
 
- data OutPoint = OutPoint {- outPointHash :: !TxHash
- outPointIndex :: !Word32
 
- data CoinbaseTx = CoinbaseTx {- cbVersion :: !Word32
- cbPrevOutput :: !OutPoint
- cbData :: !ByteString
- cbInSequence :: !Word32
- cbOut :: ![TxOut]
- cbLockTime :: !Word32
 
- newtype TxHash = TxHash {}
- txHash :: Tx -> TxHash
- hexToTxHash :: ByteString -> Maybe TxHash
- txHashToHex :: TxHash -> ByteString
- nosigTxHash :: Tx -> TxHash
- cbHash :: CoinbaseTx -> TxHash
- class Coin c where
- buildTx :: [OutPoint] -> [(ScriptOutput, Word64)] -> Either String Tx
- buildAddrTx :: [OutPoint] -> [(ByteString, Word64)] -> Either String Tx
- data SigInput = SigInput {- sigDataOut :: !ScriptOutput
- sigDataOP :: !OutPoint
- sigDataSH :: !SigHash
- sigDataRedeem :: !(Maybe RedeemScript)
 
- signTx :: Tx -> [SigInput] -> [PrvKey] -> Either String Tx
- signInput :: Tx -> Int -> SigInput -> PrvKey -> Either String Tx
- mergeTxs :: [Tx] -> [(ScriptOutput, OutPoint)] -> Either String Tx
- verifyStdTx :: Tx -> [(ScriptOutput, OutPoint)] -> Bool
- verifyStdInput :: Tx -> Int -> ScriptOutput -> Bool
- guessTxSize :: Int -> [(Int, Int)] -> Int -> Int -> Int
- chooseCoins :: Coin c => Word64 -> Word64 -> Bool -> [c] -> Either String ([c], Word64)
- chooseCoinsSink :: (Monad m, Coin c) => Word64 -> Word64 -> Bool -> Sink c m (Either String ([c], Word64))
- chooseMSCoins :: Coin c => Word64 -> Word64 -> (Int, Int) -> Bool -> [c] -> Either String ([c], Word64)
- chooseMSCoinsSink :: (Monad m, Coin c) => Word64 -> Word64 -> (Int, Int) -> Bool -> Sink c m (Either String ([c], Word64))
- getFee :: Word64 -> Int -> Word64
- getMSFee :: Word64 -> (Int, Int) -> Int -> Word64
- data Block = Block {- blockHeader :: !BlockHeader
- blockCoinbaseTx :: !CoinbaseTx
- blockTxns :: ![Tx]
 
- data BlockHeader = BlockHeader {- blockVersion :: !Word32
- prevBlock :: !BlockHash
- merkleRoot :: !Hash256
- blockTimestamp :: !Word32
- blockBits :: !Word32
- bhNonce :: !Word32
 
- type BlockLocator = [BlockHash]
- data GetBlocks = GetBlocks {}
- data GetHeaders = GetHeaders {}
- type BlockHeaderCount = (BlockHeader, VarInt)
- newtype BlockHash = BlockHash {}
- blockHashToHex :: BlockHash -> ByteString
- hexToBlockHash :: ByteString -> Maybe BlockHash
- data Headers = Headers {- headersList :: ![BlockHeaderCount]
 
- headerHash :: BlockHeader -> BlockHash
- decodeCompact :: Word32 -> Integer
- encodeCompact :: Integer -> Word32
- data MerkleBlock = MerkleBlock {- merkleHeader :: !BlockHeader
- merkleTotalTxns :: !Word32
- mHashes :: ![Hash256]
- mFlags :: ![Bool]
 
- type MerkleRoot = Hash256
- type FlagBits = [Bool]
- type PartialMerkleTree = [Hash256]
- calcTreeHeight :: Int -> Int
- calcTreeWidth :: Int -> Int -> Int
- buildMerkleRoot :: [TxHash] -> MerkleRoot
- calcHash :: Int -> Int -> [TxHash] -> Hash256
- buildPartialMerkle :: [(TxHash, Bool)] -> (FlagBits, PartialMerkleTree)
- extractMatches :: FlagBits -> PartialMerkleTree -> Int -> Either String (MerkleRoot, [TxHash])
- data ArbitraryByteString = ArbitraryByteString ByteString
- data ArbitraryNotNullByteString = ArbitraryNotNullByteString ByteString
- newtype ArbitraryUTCTime = ArbitraryUTCTime UTCTime
- newtype ArbitraryHash512 = ArbitraryHash512 Hash512
- newtype ArbitraryHash256 = ArbitraryHash256 Hash256
- newtype ArbitraryHash160 = ArbitraryHash160 Hash160
- newtype ArbitraryCheckSum32 = ArbitraryCheckSum32 CheckSum32
- data ArbitraryByteString = ArbitraryByteString ByteString
- data ArbitraryNotNullByteString = ArbitraryNotNullByteString ByteString
- newtype ArbitraryPrvKey = ArbitraryPrvKey PrvKey
- newtype ArbitraryPrvKeyC = ArbitraryPrvKeyC PrvKeyC
- newtype ArbitraryPrvKeyU = ArbitraryPrvKeyU PrvKeyU
- data ArbitraryPubKey = ArbitraryPubKey PrvKey PubKey
- data ArbitraryPubKeyC = ArbitraryPubKeyC PrvKeyC PubKeyC
- data ArbitraryPubKeyU = ArbitraryPubKeyU PrvKeyU PubKeyU
- newtype ArbitraryAddress = ArbitraryAddress Address
- newtype ArbitraryPubKeyAddress = ArbitraryPubKeyAddress Address
- newtype ArbitraryScriptAddress = ArbitraryScriptAddress Address
- data ArbitrarySignature = ArbitrarySignature Hash256 PrvKey Signature
- data ArbitraryXPrvKey = ArbitraryXPrvKey XPrvKey
- data ArbitraryXPubKey = ArbitraryXPubKey XPrvKey XPubKey
- data ArbitraryHardPath = ArbitraryHardPath HardPath
- data ArbitrarySoftPath = ArbitrarySoftPath SoftPath
- data ArbitraryDerivPath = ArbitraryDerivPath DerivPath
- data ArbitraryParsedPath = ArbitraryParsedPath ParsedPath
- newtype ArbitraryVarInt = ArbitraryVarInt VarInt
- newtype ArbitraryVarString = ArbitraryVarString VarString
- newtype ArbitraryNetworkAddress = ArbitraryNetworkAddress NetworkAddress
- newtype ArbitraryNetworkAddressTime = ArbitraryNetworkAddressTime (Word32, NetworkAddress)
- newtype ArbitraryInvType = ArbitraryInvType InvType
- newtype ArbitraryInvVector = ArbitraryInvVector InvVector
- newtype ArbitraryInv = ArbitraryInv Inv
- newtype ArbitraryVersion = ArbitraryVersion Version
- newtype ArbitraryAddr = ArbitraryAddr Addr
- newtype ArbitraryAlert = ArbitraryAlert Alert
- newtype ArbitraryReject = ArbitraryReject Reject
- newtype ArbitraryRejectCode = ArbitraryRejectCode RejectCode
- newtype ArbitraryGetData = ArbitraryGetData GetData
- newtype ArbitraryNotFound = ArbitraryNotFound NotFound
- newtype ArbitraryPing = ArbitraryPing Ping
- newtype ArbitraryPong = ArbitraryPong Pong
- data ArbitraryBloomFlags = ArbitraryBloomFlags BloomFlags
- data ArbitraryBloomFilter = ArbitraryBloomFilter Int Double BloomFilter
- data ArbitraryFilterLoad = ArbitraryFilterLoad FilterLoad
- data ArbitraryFilterAdd = ArbitraryFilterAdd FilterAdd
- newtype ArbitraryMessageCommand = ArbitraryMessageCommand MessageCommand
- newtype ArbitraryMessageHeader = ArbitraryMessageHeader MessageHeader
- newtype ArbitraryMessage = ArbitraryMessage Message
- newtype ArbitraryScriptOp = ArbitraryScriptOp ScriptOp
- newtype ArbitraryScript = ArbitraryScript Script
- newtype ArbitraryIntScriptOp = ArbitraryIntScriptOp ScriptOp
- newtype ArbitraryPushDataType = ArbitraryPushDataType PushDataType
- data ArbitraryTxSignature = ArbitraryTxSignature TxHash PrvKey TxSignature
- newtype ArbitrarySigHash = ArbitrarySigHash SigHash
- newtype ArbitraryValidSigHash = ArbitraryValidSigHash SigHash
- data ArbitraryMSParam = ArbitraryMSParam Int Int
- newtype ArbitraryScriptOutput = ArbitraryScriptOutput ScriptOutput
- newtype ArbitrarySimpleOutput = ArbitrarySimpleOutput ScriptOutput
- newtype ArbitraryPKOutput = ArbitraryPKOutput ScriptOutput
- newtype ArbitraryPKHashOutput = ArbitraryPKHashOutput ScriptOutput
- newtype ArbitraryMSOutput = ArbitraryMSOutput ScriptOutput
- newtype ArbitraryMSCOutput = ArbitraryMSCOutput ScriptOutput
- newtype ArbitrarySHOutput = ArbitrarySHOutput ScriptOutput
- newtype ArbitraryScriptInput = ArbitraryScriptInput ScriptInput
- newtype ArbitrarySimpleInput = ArbitrarySimpleInput ScriptInput
- newtype ArbitraryPKInput = ArbitraryPKInput ScriptInput
- newtype ArbitraryPKHashInput = ArbitraryPKHashInput ScriptInput
- newtype ArbitraryPKHashCInput = ArbitraryPKHashCInput ScriptInput
- newtype ArbitraryMSInput = ArbitraryMSInput ScriptInput
- newtype ArbitrarySHInput = ArbitrarySHInput ScriptInput
- newtype ArbitraryMulSigSHCInput = ArbitraryMulSigSHCInput ScriptInput
- newtype ArbitrarySatoshi = ArbitrarySatoshi Word64
- newtype ArbitraryTx = ArbitraryTx Tx
- newtype ArbitraryTxHash = ArbitraryTxHash TxHash
- newtype ArbitraryTxIn = ArbitraryTxIn TxIn
- newtype ArbitraryTxOut = ArbitraryTxOut TxOut
- newtype ArbitraryOutPoint = ArbitraryOutPoint OutPoint
- newtype ArbitraryCoinbaseTx = ArbitraryCoinbaseTx CoinbaseTx
- newtype ArbitraryAddrOnlyTx = ArbitraryAddrOnlyTx Tx
- newtype ArbitraryAddrOnlyTxIn = ArbitraryAddrOnlyTxIn TxIn
- newtype ArbitraryAddrOnlyTxOut = ArbitraryAddrOnlyTxOut TxOut
- data ArbitrarySigInput = ArbitrarySigInput SigInput [PrvKey]
- data ArbitraryPKSigInput = ArbitraryPKSigInput SigInput PrvKey
- data ArbitraryPKHashSigInput = ArbitraryPKHashSigInput SigInput PrvKey
- data ArbitraryMSSigInput = ArbitraryMSSigInput SigInput [PrvKey]
- data ArbitrarySHSigInput = ArbitrarySHSigInput SigInput [PrvKey]
- data ArbitrarySigningData = ArbitrarySigningData Tx [SigInput] [PrvKey]
- data ArbitraryPartialTxs = ArbitraryPartialTxs [Tx] [(ScriptOutput, OutPoint, Int, Int)]
- newtype ArbitraryBlock = ArbitraryBlock Block
- newtype ArbitraryBlockHeader = ArbitraryBlockHeader BlockHeader
- newtype ArbitraryBlockHash = ArbitraryBlockHash BlockHash
- newtype ArbitraryGetBlocks = ArbitraryGetBlocks GetBlocks
- newtype ArbitraryGetHeaders = ArbitraryGetHeaders GetHeaders
- newtype ArbitraryHeaders = ArbitraryHeaders Headers
- newtype ArbitraryMerkleBlock = ArbitraryMerkleBlock MerkleBlock
Documentation
module Network.Haskoin.Util
module Network.Haskoin.Constants
data CheckSum32 Source
bsToHash512 :: ByteString -> Maybe Hash512 Source
bsToHash256 :: ByteString -> Maybe Hash256 Source
bsToHash160 :: ByteString -> Maybe Hash160 Source
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.
hmacDRBGNew :: EntropyInput -> Nonce -> PersString -> WorkingState Source
hmacDRBGUpd :: ProvidedData -> ByteString -> ByteString -> (ByteString, ByteString) Source
hmacDRBGRsd :: WorkingState -> EntropyInput -> AdditionalInput -> WorkingState Source
hmacDRBGGen :: WorkingState -> Word16 -> AdditionalInput -> (WorkingState, Maybe ByteString) Source
type WorkingState = (ByteString, ByteString, Word16) Source
Data type representing a Bitcoin address
Constructors
| PubKeyAddress | Public Key Hash Address | 
| Fields 
 | |
| ScriptAddress | Script Hash Address | 
| Fields 
 | |
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.
Instances
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.
makePubKey :: PubKey -> PubKey Source
makePubKeyG :: Bool -> PubKey -> PubKey Source
makePubKeyC :: PubKey -> PubKeyC Source
makePubKeyU :: PubKey -> PubKeyU Source
maybePubKeyC :: PubKeyI c -> Maybe PubKeyC Source
maybePubKeyU :: PubKeyI c -> Maybe PubKeyU Source
derivePubKey :: PrvKeyI c -> PubKeyI c Source
pubKeyAddr :: Binary (PubKeyI c) => PubKeyI c -> Address Source
Computes an Address from a public key
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.
makePrvKey :: SecKey -> PrvKey Source
makePrvKeyG :: Bool -> SecKey -> PrvKey Source
makePrvKeyC :: SecKey -> PrvKeyC Source
makePrvKeyU :: SecKey -> PrvKeyU Source
maybePrvKeyC :: PrvKeyI c -> Maybe PrvKeyC Source
maybePrvKeyU :: PrvKeyI c -> Maybe PrvKeyU 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
prvKeyPutMonad :: PrvKeyI c -> Put Source
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
Data type representing an extended BIP32 public key.
Constructors
| XPubKey | |
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 | |
data DerivationException Source
A derivation exception is thrown in the very unlikely event that a derivation is invalid.
Constructors
| DerivationException String | 
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.
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.
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/.
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.
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.
cycleIndex :: KeyIndex -> [KeyIndex] Source
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
class HardOrGeneric a Source
class GenericOrSoft a Source
type DerivPath = DerivPathI Generic Source
type HardPath = DerivPathI Hard Source
type SoftPath = DerivPathI Soft Source
data Bip32PathIndex Source
Constructors
| Bip32HardIndex KeyIndex | |
| Bip32SoftIndex KeyIndex | 
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
toHard :: DerivPathI t -> Maybe HardPath Source
toSoft :: DerivPathI t -> Maybe SoftPath Source
toGeneric :: DerivPathI t -> DerivPath Source
(++/) :: DerivPathI t1 -> DerivPathI t2 -> DerivPath Source
Append two derivation paths together. The result will be a mixed derivation path.
pathToStr :: DerivPathI t -> String Source
Constructors
| XPrv | |
| Fields 
 | |
| XPub | |
| Fields 
 | |
data ParsedPath Source
Constructors
| ParsedPrv | |
| Fields | |
| ParsedPub | |
| Fields | |
| ParsedEmpty | |
| Fields | |
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.
Data type representing an ECDSA signature.
Constructors
| Signature | |
| Fields 
 | |
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.
Data types
type Entropy = ByteString Source
type Mnemonic = ByteString Source
type Passphrase = ByteString Source
type Seed = ByteString Source
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.
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 | |
| 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 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 
 | |
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 | |
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 
 | |
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 TCP/IP connection is still valid.
Constructors
| Ping | |
A Pong message is sent as a response to a ping message.
Constructors
| Pong | |
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
reject :: MessageCommand -> RejectCode -> ByteString -> Reject Source
Convenience function to build a Reject message
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 variable length strings. Variable length strings are
 serialized as a VarInt followed by a bytestring.
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.
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 
 | |
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 FilterLoad Source
Set a new bloom filter on the peer connection.
Constructors
| FilterLoad | |
| Fields | |
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 | 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.
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)
Data type representing all of the operators allowed inside a Script.
Constructors
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
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 | 
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. | 
| Fields | |
| PayPKHash | Pay to a public key hash. | 
| Fields | |
| PayMulSig | Pay to multiple public keys. | 
| Fields 
 | |
| PayScriptHash | Pay to a script hash. | 
| Fields | |
data ScriptInput Source
Constructors
| RegularInput | |
| Fields | |
| ScriptHashInput | |
| Fields | |
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. | 
| Fields | |
| SpendPKHash | Spend the coins of a PayPKHash output. | 
| Fields 
 | |
| SpendMulSig | Spend the coins of a PayMulSig output. | 
| Fields | |
type RedeemScript = ScriptOutput Source
scriptAddr :: ScriptOutput -> Address Source
Computes a script address from a script output. This address can be used in a pay to script hash output.
scriptRecipient :: Script -> Either String Address Source
Computes the recipient address of a script. This function fails if the script could not be decoded as a pay to public key hash or pay to script hash.
scriptSender :: Script -> Either String Address Source
Computes the sender address of a script. This function fails if the script could not be decoded as a spend public key hash or script hash input.
encodeInput :: ScriptInput -> Script Source
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]
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.
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. | 
| Fields 
 | |
encodeSigHash32 :: SigHash -> ByteString Source
Encodes a SigHash to a 32 bit-long bytestring.
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.
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 | |
| Fields 
 | |
encodeSig :: TxSignature -> ByteString Source
Serialize a TxSignature to a ByteString.
decodeSig :: ByteString -> Either String TxSignature Source
Decode a TxSignature from a ByteString.
Script evaluation
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
Helper functions
encodeInt :: Int64 -> StackValue Source
Encoding function for the stack value format of integers. Most significant bit defines sign.
encodeBool :: Bool -> StackValue Source
decodeBool :: StackValue -> Bool Source
Conversion of StackValue to Bool (true if non-zero).
runStack :: ProgramData -> Stack Source
checkStack :: Stack -> Bool Source
dumpScript :: [ScriptOp] -> ByteString Source
dumpStack :: Stack -> ByteString Source
Data type representing a bitcoin transaction
Constructors
| Tx | |
Data type representing a transaction input.
Constructors
| TxIn | |
| Fields 
 | |
Data type representing a transaction output.
Constructors
| TxOut | |
| Fields 
 | |
The OutPoint is used inside a transaction input to reference the previous transaction output that it is spending.
Constructors
| OutPoint | |
| Fields 
 | |
data CoinbaseTx Source
Data type representing the coinbase transaction of a Block. Coinbase
 transactions are special types of transactions which are created by miners
 when they find a new block. Coinbase transactions have no inputs. They have
 outputs sending the newly generated bitcoins together with all the block's
 fees to a bitcoin address (usually the miners address). Data can be embedded
 in a Coinbase transaction which can be chosen by the miner of a block. This
 data also typically contains some randomness which is used, together with
 the nonce, to find a partial hash collision on the block's hash.
Constructors
| CoinbaseTx | |
| Fields 
 | |
hexToTxHash :: ByteString -> Maybe TxHash Source
txHashToHex :: TxHash -> ByteString Source
nosigTxHash :: Tx -> TxHash Source
cbHash :: CoinbaseTx -> TxHash Source
Computes the hash of a coinbase transaction.
Any type can be used as a Coin if it can provide a value in Satoshi. The value is used in coin selection algorithms.
Instances
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 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 
 | |
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.
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.
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.
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.
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.
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 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 CoinbaseTx of this
 Block. Variations in the CoinbaseTx will result in different merkle
 roots in the BlockHeader.
Constructors
| BlockHeader | |
| Fields 
 | |
type BlockLocator = [BlockHash] 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 
 | |
type BlockHeaderCount = (BlockHeader, VarInt) Source
BlockHeader type with a transaction count as VarInt
Constructors
| BlockHash | |
| Fields | |
The Headers type is used to return a list of block headers in
 response to a GetHeaders message.
Constructors
| Headers | |
| Fields 
 | |
headerHash :: BlockHeader -> BlockHash Source
Compute the hash of a block header
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 
 | |
type MerkleRoot = Hash256 Source
type PartialMerkleTree = [Hash256] Source
Computes the height of a merkle tree.
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.
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.
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.
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.
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.
data ArbitraryByteString Source
Arbitrary strict ByteString
Constructors
| ArbitraryByteString ByteString | 
data ArbitraryNotNullByteString Source
Arbitrary strict ByteString that is not empty
Constructors
| ArbitraryNotNullByteString ByteString | 
newtype ArbitraryUTCTime Source
Arbitrary UTCTime that generates dates after 01 Jan 1970 01:00:00 CET
Constructors
| ArbitraryUTCTime UTCTime | 
newtype ArbitraryHash512 Source
Constructors
| ArbitraryHash512 Hash512 | 
newtype ArbitraryHash256 Source
Constructors
| ArbitraryHash256 Hash256 | 
newtype ArbitraryHash160 Source
Constructors
| ArbitraryHash160 Hash160 | 
newtype ArbitraryCheckSum32 Source
Constructors
| ArbitraryCheckSum32 CheckSum32 | 
data ArbitraryByteString Source
Arbitrary strict ByteString
Constructors
| ArbitraryByteString ByteString | 
data ArbitraryNotNullByteString Source
Arbitrary strict ByteString that is not empty
Constructors
| ArbitraryNotNullByteString ByteString | 
newtype ArbitraryPrvKey Source
Arbitrary private key (can be both compressed or uncompressed)
Constructors
| ArbitraryPrvKey PrvKey | 
newtype ArbitraryPrvKeyU Source
Arbitrary uncompressed private key
Constructors
| ArbitraryPrvKeyU PrvKeyU | 
data ArbitraryPubKey Source
Arbitrary public key (can be both compressed or uncompressed) with its corresponding private key.
Constructors
| ArbitraryPubKey PrvKey PubKey | 
data ArbitraryPubKeyC Source
Arbitrary compressed public key with its corresponding private key.
Constructors
| ArbitraryPubKeyC PrvKeyC PubKeyC | 
data ArbitraryPubKeyU Source
Arbitrary uncompressed public key with its corresponding private key.
Constructors
| ArbitraryPubKeyU PrvKeyU PubKeyU | 
newtype ArbitraryAddress Source
Arbitrary address (can be a pubkey or script hash address)
Constructors
| ArbitraryAddress Address | 
newtype ArbitraryPubKeyAddress Source
Arbitrary public key hash address
Constructors
| ArbitraryPubKeyAddress Address | 
newtype ArbitraryScriptAddress Source
Arbitrary script hash address
Constructors
| ArbitraryScriptAddress Address | 
data ArbitrarySignature 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.
Constructors
| ArbitrarySignature Hash256 PrvKey Signature | 
data ArbitraryXPubKey Source
Arbitrary extended public key with its corresponding private key.
Constructors
| ArbitraryXPubKey XPrvKey XPubKey | 
data ArbitraryHardPath Source
Constructors
| ArbitraryHardPath HardPath | 
data ArbitrarySoftPath Source
Constructors
| ArbitrarySoftPath SoftPath | 
data ArbitraryDerivPath Source
Constructors
| ArbitraryDerivPath DerivPath | 
data ArbitraryParsedPath Source
Constructors
| ArbitraryParsedPath ParsedPath | 
newtype ArbitraryNetworkAddress Source
Arbitrary NetworkAddress
Constructors
| ArbitraryNetworkAddress NetworkAddress | 
newtype ArbitraryNetworkAddressTime Source
Arbitrary NetworkAddressTime
Constructors
| ArbitraryNetworkAddressTime (Word32, NetworkAddress) | 
Instances
newtype ArbitraryAlert Source
Arbitrary alert with random payload and signature. Signature is not valid.
Constructors
| ArbitraryAlert Alert | 
data ArbitraryBloomFlags Source
Arbitrary bloom filter flags
Constructors
| ArbitraryBloomFlags BloomFlags | 
data ArbitraryBloomFilter Source
Arbitrary bloom filter with its corresponding number of elements and false positive rate.
Constructors
| ArbitraryBloomFilter Int Double BloomFilter | 
newtype ArbitraryMessageCommand Source
Arbitrary MessageCommand
Constructors
| ArbitraryMessageCommand MessageCommand | 
newtype ArbitraryMessageHeader Source
Arbitrary MessageHeader
Constructors
| ArbitraryMessageHeader MessageHeader | 
newtype ArbitraryScriptOp Source
Arbitrary ScriptOp (push operations have random data)
Constructors
| ArbitraryScriptOp ScriptOp | 
newtype ArbitraryScript Source
Arbitrary Script with random script ops
Constructors
| ArbitraryScript Script | 
newtype ArbitraryIntScriptOp Source
Arbtirary ScriptOp with a value in [OP_1 .. OP_16]
Constructors
| ArbitraryIntScriptOp ScriptOp | 
newtype ArbitraryPushDataType Source
Arbitrary PushDataType
Constructors
| ArbitraryPushDataType PushDataType | 
data ArbitraryTxSignature Source
Arbitrary message hash, private key and corresponding TxSignature. The signature is generated deterministically using a random message and a random private key.
Constructors
| ArbitraryTxSignature TxHash PrvKey TxSignature | 
newtype ArbitrarySigHash Source
Arbitrary SigHash (including invalid/unknown sighash codes)
Constructors
| ArbitrarySigHash SigHash | 
newtype ArbitraryValidSigHash Source
Arbitrary valid SigHash
Constructors
| ArbitraryValidSigHash SigHash | 
newtype ArbitraryScriptOutput Source
Arbitrary ScriptOutput (Can by any valid type)
Constructors
| ArbitraryScriptOutput ScriptOutput | 
newtype ArbitrarySimpleOutput Source
Arbitrary ScriptOutput of type PayPK, PayPKHash or PayMS (Not PayScriptHash)
Constructors
| ArbitrarySimpleOutput ScriptOutput | 
newtype ArbitraryPKOutput Source
Arbitrary ScriptOutput of type PayPK
Constructors
| ArbitraryPKOutput ScriptOutput | 
newtype ArbitraryPKHashOutput Source
Arbitrary ScriptOutput of type PayPKHash
Constructors
| ArbitraryPKHashOutput ScriptOutput | 
newtype ArbitraryMSOutput Source
Arbitrary ScriptOutput of type PayMS
Constructors
| ArbitraryMSOutput ScriptOutput | 
newtype ArbitraryMSCOutput Source
Arbitrary ScriptOutput of type PayMS containing only compressed keys
Constructors
| ArbitraryMSCOutput ScriptOutput | 
newtype ArbitrarySHOutput Source
Arbitrary ScriptOutput of type PayScriptHash
Constructors
| ArbitrarySHOutput ScriptOutput | 
newtype ArbitraryScriptInput Source
Arbitrary ScriptInput
Constructors
| ArbitraryScriptInput ScriptInput | 
newtype ArbitrarySimpleInput Source
Arbitrary ScriptInput of type SpendPK, SpendPKHash or SpendMulSig (not ScriptHashInput)
Constructors
| ArbitrarySimpleInput ScriptInput | 
newtype ArbitraryPKInput Source
Arbitrary ScriptInput of type SpendPK
Constructors
| ArbitraryPKInput ScriptInput | 
newtype ArbitraryPKHashInput Source
Arbitrary ScriptInput of type SpendPK
Constructors
| ArbitraryPKHashInput ScriptInput | 
newtype ArbitraryPKHashCInput Source
Arbitrary ScriptInput of type SpendPK with a compressed public key
Constructors
| ArbitraryPKHashCInput ScriptInput | 
newtype ArbitraryMSInput Source
Arbitrary ScriptInput of type SpendMulSig
Constructors
| ArbitraryMSInput ScriptInput | 
newtype ArbitrarySHInput Source
Arbitrary ScriptInput of type ScriptHashInput
Constructors
| ArbitrarySHInput ScriptInput | 
newtype ArbitraryMulSigSHCInput Source
Arbitrary ScriptInput of type ScriptHashInput containing a RedeemScript of type PayMulSig and an input of type SpendMulSig. Only compressed keys are used.
Constructors
| ArbitraryMulSigSHCInput ScriptInput | 
newtype ArbitrarySatoshi Source
Arbitrary amount of Satoshi as Word64 (Between 1 and 21e14)
Constructors
| ArbitrarySatoshi Word64 | 
newtype ArbitraryTxHash Source
Constructors
| ArbitraryTxHash TxHash | 
newtype ArbitraryAddrOnlyTx Source
Arbitrary Tx containing only inputs of type SpendPKHash, SpendScriptHash (multisig) and outputs of type PayPKHash and PaySH. Only compressed public keys are used.
Constructors
| ArbitraryAddrOnlyTx Tx | 
newtype ArbitraryAddrOnlyTxIn Source
Arbitrary TxIn that can only be of type SpendPKHash or SpendScriptHash (multisig). Only compressed public keys are used.
Constructors
| ArbitraryAddrOnlyTxIn TxIn | 
newtype ArbitraryAddrOnlyTxOut Source
Arbitrary TxOut that can only be of type PayPKHash or PaySH
Constructors
| ArbitraryAddrOnlyTxOut TxOut | 
data ArbitrarySigInput Source
Arbitrary SigInput with the corresponding private keys used to generate the ScriptOutput or RedeemScript
Constructors
| ArbitrarySigInput SigInput [PrvKey] | 
data ArbitraryPKSigInput Source
Arbitrary SigInput with a ScriptOutput of type PayPK
Constructors
| ArbitraryPKSigInput SigInput PrvKey | 
data ArbitraryPKHashSigInput Source
Arbitrary SigInput with a ScriptOutput of type PayPKHash
Constructors
| ArbitraryPKHashSigInput SigInput PrvKey | 
data ArbitraryMSSigInput Source
Arbitrary SigInput with a ScriptOutput of type PayMulSig
Constructors
| ArbitraryMSSigInput SigInput [PrvKey] | 
data ArbitrarySHSigInput Source
Arbitrary SigInput with ScriptOutput of type PaySH and a RedeemScript
Constructors
| ArbitrarySHSigInput SigInput [PrvKey] | 
data ArbitrarySigningData Source
Arbitrary Tx (empty TxIn), SigInputs and PrvKeys that can be passed to signTx or detSignTx to fully sign the Tx.
Constructors
| ArbitrarySigningData Tx [SigInput] [PrvKey] | 
data ArbitraryPartialTxs Source
Constructors
| ArbitraryPartialTxs [Tx] [(ScriptOutput, OutPoint, Int, Int)] | 
newtype ArbitraryBlockHeader Source
Arbitrary BlockHeader
Constructors
| ArbitraryBlockHeader BlockHeader | 
newtype ArbitraryBlockHash Source
Constructors
| ArbitraryBlockHash BlockHash | 
newtype ArbitraryMerkleBlock Source
Arbitrary MerkleBlock
Constructors
| ArbitraryMerkleBlock MerkleBlock |