haskoin-core-1.1.0: Bitcoin & Bitcoin Cash library for Haskell
CopyrightNo rights reserved
LicenseMIT
Maintainermatt@bitnomial.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe-Inferred
LanguageHaskell2010

Haskoin.Transaction.Partial

Description

Code related to PSBT parsing and serialization.

Synopsis

Partially-Signed Transactions

data PSBT 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 PSBT line up by index with the inputs and outputs in the unsigned transaction.

Constructors

PSBT 

Instances

Instances details
Generic PSBT Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Associated Types

type Rep PSBT :: Type -> Type #

Methods

from :: PSBT -> Rep PSBT x #

to :: Rep PSBT x -> PSBT #

Read PSBT Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Show PSBT Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

showsPrec :: Int -> PSBT -> ShowS #

show :: PSBT -> String #

showList :: [PSBT] -> ShowS #

NFData PSBT Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

rnf :: PSBT -> () #

Eq PSBT Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

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

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

type Rep PSBT Source # 
Instance details

Defined in Haskoin.Transaction.Partial

type Rep PSBT = D1 ('MetaData "PSBT" "Haskoin.Transaction.Partial" "haskoin-core-1.1.0-EPeWWz60EKPlWai44F9WC" 'False) (C1 ('MetaCons "PSBT" 'PrefixI 'True) ((S1 ('MetaSel ('Just "unsignedTransaction") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Tx) :*: S1 ('MetaSel ('Just "globalUnknown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnknownMap)) :*: (S1 ('MetaSel ('Just "inputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Input]) :*: S1 ('MetaSel ('Just "outputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Output]))))

putPSBT :: MonadPut m => Ctx -> PSBT -> m () Source #

data Input Source #

Inputs contain all of the data needed to sign a transaction and all of the resulting signature data after signing.

Instances

Instances details
Generic Input Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Associated Types

type Rep Input :: Type -> Type #

Methods

from :: Input -> Rep Input x #

to :: Rep Input x -> Input #

Read Input Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Show Input Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

showsPrec :: Int -> Input -> ShowS #

show :: Input -> String #

showList :: [Input] -> ShowS #

NFData Input Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

rnf :: Input -> () #

Eq Input Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

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

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

type Rep Input Source # 
Instance details

Defined in Haskoin.Transaction.Partial

putInput :: MonadPut m => Ctx -> Input -> m () Source #

data Output Source #

Outputs can contain information needed to spend the output at a later date.

Instances

Instances details
Generic Output Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Associated Types

type Rep Output :: Type -> Type #

Methods

from :: Output -> Rep Output x #

to :: Rep Output x -> Output #

Read Output Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Show Output Source # 
Instance details

Defined in Haskoin.Transaction.Partial

NFData Output Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

rnf :: Output -> () #

Eq Output Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

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

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

type Rep Output Source # 
Instance details

Defined in Haskoin.Transaction.Partial

type Rep Output = D1 ('MetaData "Output" "Haskoin.Transaction.Partial" "haskoin-core-1.1.0-EPeWWz60EKPlWai44F9WC" 'False) (C1 ('MetaCons "Output" 'PrefixI 'True) ((S1 ('MetaSel ('Just "outputRedeemScript") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Script)) :*: S1 ('MetaSel ('Just "outputWitnessScript") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Script))) :*: (S1 ('MetaSel ('Just "outputHDKeypaths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap PublicKey (Fingerprint, [KeyIndex]))) :*: S1 ('MetaSel ('Just "outputUnknown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnknownMap))))

putOutput :: MonadPut m => Ctx -> Output -> m () Source #

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 

Instances

Instances details
Monoid UnknownMap Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Semigroup UnknownMap Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Generic UnknownMap Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Associated Types

type Rep UnknownMap :: Type -> Type #

Read UnknownMap Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Show UnknownMap Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Serial UnknownMap Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

serialize :: MonadPut m => UnknownMap -> m () #

deserialize :: MonadGet m => m UnknownMap #

NFData UnknownMap Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

rnf :: UnknownMap -> () #

Eq UnknownMap Source # 
Instance details

Defined in Haskoin.Transaction.Partial

type Rep UnknownMap Source # 
Instance details

Defined in Haskoin.Transaction.Partial

type Rep UnknownMap = D1 ('MetaData "UnknownMap" "Haskoin.Transaction.Partial" "haskoin-core-1.1.0-EPeWWz60EKPlWai44F9WC" 'True) (C1 ('MetaCons "UnknownMap" 'PrefixI 'True) (S1 ('MetaSel ('Just "unknownMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap Key ByteString))))

data Key Source #

Raw keys for the map type used in PSBTs.

Constructors

Key 

Fields

Instances

Instances details
Generic Key Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Associated Types

type Rep Key :: Type -> Type #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

Read Key Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Show Key Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Binary Key Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

put :: Key -> Put #

get :: Get Key #

putList :: [Key] -> Put #

Serial Key Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

serialize :: MonadPut m => Key -> m () #

deserialize :: MonadGet m => m Key #

Serialize Key Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

put :: Putter Key #

get :: Get Key #

NFData Key Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

rnf :: Key -> () #

Eq Key Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

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

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

Hashable Key Source # 
Instance details

Defined in Haskoin.Transaction.Partial

Methods

hashWithSalt :: Int -> Key -> Int #

hash :: Key -> Int #

type Rep Key Source # 
Instance details

Defined in Haskoin.Transaction.Partial

type Rep Key = D1 ('MetaData "Key" "Haskoin.Transaction.Partial" "haskoin-core-1.1.0-EPeWWz60EKPlWai44F9WC" '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 :: PSBT -> PSBT -> Maybe PSBT Source #

Take two PSBTs and merge them. The unsignedTransaction field in both must be the same.

mergeMany :: [PSBT] -> Maybe PSBT Source #

A version of merge for a collection of PSBTs.

Since: 0.21.0

complete :: Ctx -> PSBT -> PSBT Source #

Take partial signatures from all of the Inputs and finalize the signature.

finalTransaction :: PSBT -> Tx Source #

Take a finalized PSBT and produce the signed final transaction. You may need to call complete on the PSBT before producing the final transaction.

emptyPSBT :: Tx -> PSBT Source #

Take an unsigned transaction and produce an empty PSBT

Signing

data PSBTSigner Source #

A abstraction which covers varying key configurations. Use the Semigroup instance to create signers for sets of keys: `signerA <> signerB` can sign anything for which signerA or signerB could sign.

since 0.21

getSignerKey :: PSBTSigner -> PublicKey -> Maybe (Fingerprint, DerivPath) -> Maybe SecKey Source #

Fetch the secret key for the given PublicKey if possible.

since 0.21

secKeySigner :: Ctx -> SecKey -> PSBTSigner Source #

This signer can sign for one key.

since 0.21

xPrvSigner Source #

Arguments

:: Ctx 
-> XPrvKey 
-> Maybe (Fingerprint, DerivPath)

Origin data, if the input key is explicitly a child key

-> PSBTSigner 

This signer can sign with any child key, provided that derivation information is present.

since 0.21

signPSBT :: Network -> Ctx -> PSBTSigner -> PSBT -> PSBT Source #

Update a PSBT with signatures when possible. This function uses inputHDKeypaths in order to calculate secret keys.

since 0.21