Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Language.Bitcoin.Script.Descriptors
Description
A library for working with bitcoin script descriptors. Documentation taken from https://github.com/bitcoin/bitcoin/blob/master/doc/descriptors.md.
Synopsis
- data OutputDescriptor
- outputDescriptorAtIndex :: KeyIndex -> OutputDescriptor -> OutputDescriptor
- data ScriptDescriptor
- scriptDescriptorAtIndex :: KeyIndex -> ScriptDescriptor -> ScriptDescriptor
- data KeyDescriptor = KeyDescriptor {}
- data Origin = Origin {
- fingerprint :: Fingerprint
- derivation :: DerivPath
- data Key
- = Pubkey PubKeyI
- | SecretKey SecKeyI
- | XPub XPubKey DerivPath KeyCollection
- data KeyCollection
- isDefinite :: KeyDescriptor -> Bool
- keyAtIndex :: Word32 -> Key -> Key
- keyDescriptorAtIndex :: KeyIndex -> KeyDescriptor -> KeyDescriptor
- keyDescPubKey :: KeyDescriptor -> Maybe PubKeyI
- pubKey :: PubKeyI -> KeyDescriptor
- secKey :: SecKeyI -> KeyDescriptor
- keyBytes :: KeyDescriptor -> Maybe ByteString
- outputDescriptorPubKeys :: OutputDescriptor -> [PubKeyI]
- scriptDescriptorPubKeys :: ScriptDescriptor -> [PubKeyI]
- descriptorToText :: Network -> OutputDescriptor -> Text
- descriptorToTextWithChecksum :: Network -> OutputDescriptor -> Text
- keyDescriptorToText :: Network -> KeyDescriptor -> Text
- data ChecksumDescriptor = ChecksumDescriptor {}
- data ChecksumStatus
- parseDescriptor :: Network -> Text -> Either String ChecksumDescriptor
- outputDescriptorParser :: Network -> Parser ChecksumDescriptor
- parseKeyDescriptor :: Network -> Text -> Either String KeyDescriptor
- keyDescriptorParser :: Network -> Parser KeyDescriptor
- descriptorAddresses :: OutputDescriptor -> [Address]
- compile :: ScriptDescriptor -> Maybe Script
- data TransactionScripts = TransactionScripts {
- txScriptPubKey :: Script
- txRedeemScript :: Maybe Script
- txWitnessScript :: Maybe Script
- outputDescriptorScripts :: OutputDescriptor -> Maybe TransactionScripts
- toPsbtInput :: Tx -> Int -> OutputDescriptor -> Either PsbtInputError Input
- data PsbtInputError
- descriptorChecksum :: Text -> Maybe Text
- validDescriptorChecksum :: Text -> Text -> Bool
Descriptors
data OutputDescriptor Source #
High level description for a bitcoin output
Constructors
ScriptPubKey ScriptDescriptor | The output is secured by the given script. |
P2SH ScriptDescriptor | P2SH embed the argument. |
P2WPKH KeyDescriptor | P2WPKH output for the given compressed pubkey. |
P2WSH ScriptDescriptor | P2WSH embed the argument. |
WrappedWPkh KeyDescriptor | P2SH-P2WPKH the given compressed pubkey. |
WrappedWSh ScriptDescriptor | P2SH-P2WSH the given script |
Combo KeyDescriptor | An alias for the collection of pk(KEY) and pkh(KEY). If the key is compressed, it also includes wpkh(KEY) and sh(wpkh(KEY)). |
Addr Address | The script which ADDR expands to. |
Instances
Show OutputDescriptor Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Syntax Methods showsPrec :: Int -> OutputDescriptor -> ShowS # show :: OutputDescriptor -> String # showList :: [OutputDescriptor] -> ShowS # | |
Eq OutputDescriptor Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Syntax Methods (==) :: OutputDescriptor -> OutputDescriptor -> Bool # (/=) :: OutputDescriptor -> OutputDescriptor -> Bool # |
outputDescriptorAtIndex :: KeyIndex -> OutputDescriptor -> OutputDescriptor Source #
Specialize key families occurring in the descriptor to the given index
Since: 0.2.1
data ScriptDescriptor Source #
High level description of a bitcoin script
Constructors
Pk KeyDescriptor | Require a signature for this key |
Pkh KeyDescriptor | Require a key matching this hash and a signature for that key |
Multi Int [KeyDescriptor] | k-of-n multisig script. |
SortedMulti Int [KeyDescriptor] | k-of-n multisig script with keys sorted lexicographically in the resulting script. |
Raw ByteString | the script whose hex encoding is HEX. |
Instances
Show ScriptDescriptor Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Syntax Methods showsPrec :: Int -> ScriptDescriptor -> ShowS # show :: ScriptDescriptor -> String # showList :: [ScriptDescriptor] -> ShowS # | |
Eq ScriptDescriptor Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Syntax Methods (==) :: ScriptDescriptor -> ScriptDescriptor -> Bool # (/=) :: ScriptDescriptor -> ScriptDescriptor -> Bool # |
scriptDescriptorAtIndex :: KeyIndex -> ScriptDescriptor -> ScriptDescriptor Source #
Specialize key families occurring in the descriptor to the given index
Since: 0.2.1
Keys
data KeyDescriptor Source #
Instances
Show KeyDescriptor Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Syntax Methods showsPrec :: Int -> KeyDescriptor -> ShowS # show :: KeyDescriptor -> String # showList :: [KeyDescriptor] -> ShowS # | |
Eq KeyDescriptor Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Syntax Methods (==) :: KeyDescriptor -> KeyDescriptor -> Bool # (/=) :: KeyDescriptor -> KeyDescriptor -> Bool # |
Constructors
Origin | |
Fields
|
Constructors
Pubkey PubKeyI | DER-hex encoded secp256k1 public key |
SecretKey SecKeyI | (de)serialized as WIF |
XPub XPubKey DerivPath KeyCollection |
Instances
data KeyCollection Source #
Represent whether the key corresponds to a collection (and how) or a single key.
Instances
Show KeyCollection Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Syntax Methods showsPrec :: Int -> KeyCollection -> ShowS # show :: KeyCollection -> String # showList :: [KeyCollection] -> ShowS # | |
Eq KeyCollection Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Syntax Methods (==) :: KeyCollection -> KeyCollection -> Bool # (/=) :: KeyCollection -> KeyCollection -> Bool # | |
Ord KeyCollection Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Syntax Methods compare :: KeyCollection -> KeyCollection -> Ordering # (<) :: KeyCollection -> KeyCollection -> Bool # (<=) :: KeyCollection -> KeyCollection -> Bool # (>) :: KeyCollection -> KeyCollection -> Bool # (>=) :: KeyCollection -> KeyCollection -> Bool # max :: KeyCollection -> KeyCollection -> KeyCollection # min :: KeyCollection -> KeyCollection -> KeyCollection # |
isDefinite :: KeyDescriptor -> Bool Source #
Test whether the key descriptor corresponds to a single key
keyAtIndex :: Word32 -> Key -> Key Source #
For key families, get the key at the given index. Otherwise, return the input key.
Since: 0.2.1
keyDescriptorAtIndex :: KeyIndex -> KeyDescriptor -> KeyDescriptor Source #
Specialize key families occurring in the descriptor to the given index
Since: 0.2.1
keyDescPubKey :: KeyDescriptor -> Maybe PubKeyI Source #
Produce a pubkey if possible
pubKey :: PubKeyI -> KeyDescriptor Source #
Simple explicit public key with no origin information
secKey :: SecKeyI -> KeyDescriptor Source #
Simple explicit secret key with no origin information
keyBytes :: KeyDescriptor -> Maybe ByteString Source #
Produce a key literal if possible
outputDescriptorPubKeys :: OutputDescriptor -> [PubKeyI] Source #
Extract pubkeys from an OutputDescriptor
where possible
scriptDescriptorPubKeys :: ScriptDescriptor -> [PubKeyI] Source #
Extract pubkeys from a ScriptDescriptor
where possible
Text representation
descriptorToText :: Network -> OutputDescriptor -> Text Source #
descriptorToTextWithChecksum :: Network -> OutputDescriptor -> Text Source #
keyDescriptorToText :: Network -> KeyDescriptor -> Text Source #
Parsing
data ChecksumDescriptor Source #
An OutputDescriptor
with checksum details
Constructors
ChecksumDescriptor | |
Fields
|
Instances
Show ChecksumDescriptor Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Parser Methods showsPrec :: Int -> ChecksumDescriptor -> ShowS # show :: ChecksumDescriptor -> String # showList :: [ChecksumDescriptor] -> ShowS # | |
Eq ChecksumDescriptor Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Parser Methods (==) :: ChecksumDescriptor -> ChecksumDescriptor -> Bool # (/=) :: ChecksumDescriptor -> ChecksumDescriptor -> Bool # |
data ChecksumStatus Source #
The status of an output descriptor's checksum
Constructors
Valid | Checksum provided is valid |
Invalid | Checksum provided is invalid |
Fields
| |
Absent | Checksum is not provided |
Instances
Show ChecksumStatus Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Parser Methods showsPrec :: Int -> ChecksumStatus -> ShowS # show :: ChecksumStatus -> String # showList :: [ChecksumStatus] -> ShowS # | |
Eq ChecksumStatus Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Parser Methods (==) :: ChecksumStatus -> ChecksumStatus -> Bool # (/=) :: ChecksumStatus -> ChecksumStatus -> Bool # |
parseDescriptor :: Network -> Text -> Either String ChecksumDescriptor Source #
outputDescriptorParser :: Network -> Parser ChecksumDescriptor Source #
parseKeyDescriptor :: Network -> Text -> Either String KeyDescriptor Source #
keyDescriptorParser :: Network -> Parser KeyDescriptor Source #
Conversions
descriptorAddresses :: OutputDescriptor -> [Address] Source #
Get the set of addresses associated with an output descriptor. The list will be empty if:
- any keys are indefinite
- the output is p2pk
- the output has a non-standard script
The list can contain more than one address in the case of the "combo" construct.
compile :: ScriptDescriptor -> Maybe Script Source #
Produce the script described by the descriptor. Fails when any keys in the descriptor are indeterminate.
data TransactionScripts Source #
Constructors
TransactionScripts | |
Fields
|
Instances
Show TransactionScripts Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Utils Methods showsPrec :: Int -> TransactionScripts -> ShowS # show :: TransactionScripts -> String # showList :: [TransactionScripts] -> ShowS # | |
Eq TransactionScripts Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Utils Methods (==) :: TransactionScripts -> TransactionScripts -> Bool # (/=) :: TransactionScripts -> TransactionScripts -> Bool # |
PSBT
Arguments
:: Tx | Transaction being spent |
-> Int | Output being spent |
-> OutputDescriptor | Descriptor for output being spent |
-> Either PsbtInputError Input |
data PsbtInputError Source #
Constructors
OutputIndexOOB Tx Int | |
CompileError ScriptDescriptor | |
KeyNotAvailable KeyDescriptor | |
InvalidOutput OutputDescriptor |
Instances
Exception PsbtInputError Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Utils Methods toException :: PsbtInputError -> SomeException # | |
Show PsbtInputError Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Utils Methods showsPrec :: Int -> PsbtInputError -> ShowS # show :: PsbtInputError -> String # showList :: [PsbtInputError] -> ShowS # | |
Eq PsbtInputError Source # | |
Defined in Language.Bitcoin.Script.Descriptors.Utils Methods (==) :: PsbtInputError -> PsbtInputError -> Bool # (/=) :: PsbtInputError -> PsbtInputError -> Bool # |