Copyright | No rights reserved |
---|---|
License | UNLICENSE |
Maintainer | matt@bitnomial.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Network.Haskoin.Transaction.Partial
Description
Code related to PSBT parsing and serialization.
Synopsis
- data PartiallySignedTransaction = PartiallySignedTransaction {
- unsignedTransaction :: Tx
- globalUnknown :: UnknownMap
- inputs :: [Input]
- outputs :: [Output]
- data Input = Input {
- nonWitnessUtxo :: Maybe Tx
- witnessUtxo :: Maybe TxOut
- partialSigs :: HashMap PubKeyI ByteString
- sigHashType :: Maybe SigHash
- inputRedeemScript :: Maybe Script
- inputWitnessScript :: Maybe Script
- inputHDKeypaths :: HashMap PubKeyI (Fingerprint, [KeyIndex])
- finalScriptSig :: Maybe Script
- finalScriptWitness :: Maybe WitnessStack
- inputUnknown :: UnknownMap
- data Output = Output {}
- newtype UnknownMap = UnknownMap {}
- data Key = Key {
- keyType :: Word8
- key :: ByteString
- merge :: PartiallySignedTransaction -> PartiallySignedTransaction -> Maybe PartiallySignedTransaction
- mergeInput :: Input -> Input -> Input
- mergeOutput :: Output -> Output -> Output
- complete :: PartiallySignedTransaction -> PartiallySignedTransaction
- finalTransaction :: PartiallySignedTransaction -> Tx
- emptyPSBT :: Tx -> PartiallySignedTransaction
- emptyInput :: Input
- emptyOutput :: Output
Documentation
data PartiallySignedTransaction Source #
PSBT data type as specified in BIP-174. This
contains an unsigned transaction, inputs and outputs, and unspecified extra data. There is one input per input in the
unsigned transaction, and one output per output in the unsigned transaction. The inputs and outputs in the
PartiallySignedTransaction
line up by index with the inputs and outputs in the unsigned transaction.
Constructors
PartiallySignedTransaction | |
Fields
|
Instances
Eq PartiallySignedTransaction Source # | |
Defined in Network.Haskoin.Transaction.Partial Methods (==) :: PartiallySignedTransaction -> PartiallySignedTransaction -> Bool # (/=) :: PartiallySignedTransaction -> PartiallySignedTransaction -> Bool # | |
Show PartiallySignedTransaction Source # | |
Defined in Network.Haskoin.Transaction.Partial Methods showsPrec :: Int -> PartiallySignedTransaction -> ShowS # show :: PartiallySignedTransaction -> String # showList :: [PartiallySignedTransaction] -> ShowS # | |
Serialize PartiallySignedTransaction Source # | |
Defined in Network.Haskoin.Transaction.Partial |
Inputs contain all of the data needed to sign a transaction and all of the resulting signature data after signing.
Constructors
Input | |
Fields
|
Outputs can contain information needed to spend the output at a later date.
Constructors
Output | |
Fields |
newtype UnknownMap Source #
A map of raw PSBT keys to byte strings for extra data. The keyType
field cannot overlap with any of the reserved
keyType
fields specified in the PSBT specification.
Constructors
UnknownMap | |
Fields |
Instances
Eq UnknownMap Source # | |
Defined in Network.Haskoin.Transaction.Partial | |
Show UnknownMap Source # | |
Defined in Network.Haskoin.Transaction.Partial Methods showsPrec :: Int -> UnknownMap -> ShowS # show :: UnknownMap -> String # showList :: [UnknownMap] -> ShowS # | |
Semigroup UnknownMap Source # | |
Defined in Network.Haskoin.Transaction.Partial Methods (<>) :: UnknownMap -> UnknownMap -> UnknownMap # sconcat :: NonEmpty UnknownMap -> UnknownMap # stimes :: Integral b => b -> UnknownMap -> UnknownMap # | |
Monoid UnknownMap Source # | |
Defined in Network.Haskoin.Transaction.Partial Methods mempty :: UnknownMap # mappend :: UnknownMap -> UnknownMap -> UnknownMap # mconcat :: [UnknownMap] -> UnknownMap # | |
Serialize UnknownMap Source # | |
Defined in Network.Haskoin.Transaction.Partial |
Raw keys for the map type used in PSBTs.
Constructors
Key | |
Fields
|
Instances
Eq Key Source # | |
Show Key Source # | |
Generic Key Source # | |
Hashable Key Source # | |
Defined in Network.Haskoin.Transaction.Partial | |
Serialize Key Source # | |
type Rep Key Source # | |
Defined in Network.Haskoin.Transaction.Partial type Rep Key = D1 (MetaData "Key" "Network.Haskoin.Transaction.Partial" "haskoin-core-0.9.0-9luCRjUjDcyCwjYBmjo0zV" False) (C1 (MetaCons "Key" PrefixI True) (S1 (MetaSel (Just "keyType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word8) :*: S1 (MetaSel (Just "key") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) |
merge :: PartiallySignedTransaction -> PartiallySignedTransaction -> Maybe PartiallySignedTransaction Source #
Take two PartiallySignedTransaction
s and merge them. The unsignedTransaction
field in both must be the same.
complete :: PartiallySignedTransaction -> PartiallySignedTransaction Source #
Take partial signatures from all of the Input
s and finalize the signature.
finalTransaction :: PartiallySignedTransaction -> Tx Source #
Take a finalized PartiallySignedTransaction
and produce the signed final transaction. You may need to call
complete
on the PartiallySignedTransaction
before producing the final transaction.
emptyPSBT :: Tx -> PartiallySignedTransaction Source #
Take an unsigned transaction and produce an empty PartiallySignedTransaction
emptyInput :: Input Source #
emptyOutput :: Output Source #