{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NamedFieldPuns             #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE ScopedTypeVariables        #-}
{-|
Module      : Haskoin.Transaction.Partial
Copyright   : No rights reserved
License     : MIT
Maintainer  : matt@bitnomial.com
Stability   : experimental
Portability : POSIX

Code related to PSBT parsing and serialization.
-}
module Haskoin.Transaction.Partial
    ( -- * Partially-Signed Transactions
      PartiallySignedTransaction (..)
    , Input (..)
    , Output (..)
    , UnknownMap (..)
    , Key (..)
    , merge
    , mergeInput
    , mergeOutput
    , complete
    , finalTransaction
    , emptyPSBT
    , emptyInput
    , emptyOutput
    ) where

import           Control.Applicative        ((<|>))
import           Control.DeepSeq
import           Control.Monad              (guard, replicateM, void)
import           Data.ByteString            (ByteString)
import qualified Data.ByteString            as B
import           Data.Bytes.Get             (runGetS)
import           Data.Bytes.Put             (runPutS)
import           Data.Bytes.Serial          (Serial (..))
import           Data.HashMap.Strict        (HashMap)
import qualified Data.HashMap.Strict        as HashMap
import           Data.Hashable              (Hashable)
import           Data.List                  (foldl')
import           Data.Maybe                 (fromMaybe, isJust)
import           Data.Serialize             (Get, Put, Serialize)
import qualified Data.Serialize             as S
import           GHC.Generics               (Generic)
import           GHC.Word                   (Word32, Word8)
import           Haskoin.Address            (Address (..), pubKeyAddr)
import           Haskoin.Keys               (Fingerprint, KeyIndex, PubKeyI)
import           Haskoin.Network            (VarInt (..), VarString (..),
                                             putVarInt)
import           Haskoin.Script             (Script (..), ScriptOp (..),
                                             ScriptOutput (..), SigHash,
                                             decodeOutput, decodeOutputBS,
                                             encodeOutputBS, isPayScriptHash,
                                             opPushData, toP2SH, toP2WSH)
import           Haskoin.Transaction.Common (Tx (..), TxOut, WitnessStack,
                                             outPointIndex, prevOutput,
                                             scriptInput, scriptOutput)
import           Haskoin.Util               (eitherToMaybe)

-- | PSBT data type as specified in
-- [BIP-174](https://github.com/bitcoin/bips/blob/master/bip-0174.mediawiki).
-- 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.
data PartiallySignedTransaction =
    PartiallySignedTransaction
    { PartiallySignedTransaction -> Tx
unsignedTransaction :: Tx
    , PartiallySignedTransaction -> UnknownMap
globalUnknown       :: UnknownMap
    , PartiallySignedTransaction -> [Input]
inputs              :: [Input]
    , PartiallySignedTransaction -> [Output]
outputs             :: [Output]
    } deriving (Int -> PartiallySignedTransaction -> ShowS
[PartiallySignedTransaction] -> ShowS
PartiallySignedTransaction -> String
(Int -> PartiallySignedTransaction -> ShowS)
-> (PartiallySignedTransaction -> String)
-> ([PartiallySignedTransaction] -> ShowS)
-> Show PartiallySignedTransaction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PartiallySignedTransaction] -> ShowS
$cshowList :: [PartiallySignedTransaction] -> ShowS
show :: PartiallySignedTransaction -> String
$cshow :: PartiallySignedTransaction -> String
showsPrec :: Int -> PartiallySignedTransaction -> ShowS
$cshowsPrec :: Int -> PartiallySignedTransaction -> ShowS
Show, PartiallySignedTransaction -> PartiallySignedTransaction -> Bool
(PartiallySignedTransaction -> PartiallySignedTransaction -> Bool)
-> (PartiallySignedTransaction
    -> PartiallySignedTransaction -> Bool)
-> Eq PartiallySignedTransaction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PartiallySignedTransaction -> PartiallySignedTransaction -> Bool
$c/= :: PartiallySignedTransaction -> PartiallySignedTransaction -> Bool
== :: PartiallySignedTransaction -> PartiallySignedTransaction -> Bool
$c== :: PartiallySignedTransaction -> PartiallySignedTransaction -> Bool
Eq, (forall x.
 PartiallySignedTransaction -> Rep PartiallySignedTransaction x)
-> (forall x.
    Rep PartiallySignedTransaction x -> PartiallySignedTransaction)
-> Generic PartiallySignedTransaction
forall x.
Rep PartiallySignedTransaction x -> PartiallySignedTransaction
forall x.
PartiallySignedTransaction -> Rep PartiallySignedTransaction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PartiallySignedTransaction x -> PartiallySignedTransaction
$cfrom :: forall x.
PartiallySignedTransaction -> Rep PartiallySignedTransaction x
Generic)

instance NFData PartiallySignedTransaction

-- | Inputs contain all of the data needed to sign a transaction and all of the
-- resulting signature data after signing.
data Input = Input
    { Input -> Maybe Tx
nonWitnessUtxo     :: Maybe Tx
    , Input -> Maybe TxOut
witnessUtxo        :: Maybe TxOut
    , Input -> HashMap PubKeyI ByteString
partialSigs        :: HashMap PubKeyI ByteString
    , Input -> Maybe SigHash
sigHashType        :: Maybe SigHash
    , Input -> Maybe Script
inputRedeemScript  :: Maybe Script
    , Input -> Maybe Script
inputWitnessScript :: Maybe Script
    , Input -> HashMap PubKeyI (Fingerprint, [Fingerprint])
inputHDKeypaths    :: HashMap PubKeyI (Fingerprint, [KeyIndex])
    , Input -> Maybe Script
finalScriptSig     :: Maybe Script
    , Input -> Maybe WitnessStack
finalScriptWitness :: Maybe WitnessStack
    , Input -> UnknownMap
inputUnknown       :: UnknownMap
    } deriving (Int -> Input -> ShowS
[Input] -> ShowS
Input -> String
(Int -> Input -> ShowS)
-> (Input -> String) -> ([Input] -> ShowS) -> Show Input
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Input] -> ShowS
$cshowList :: [Input] -> ShowS
show :: Input -> String
$cshow :: Input -> String
showsPrec :: Int -> Input -> ShowS
$cshowsPrec :: Int -> Input -> ShowS
Show, Input -> Input -> Bool
(Input -> Input -> Bool) -> (Input -> Input -> Bool) -> Eq Input
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Input -> Input -> Bool
$c/= :: Input -> Input -> Bool
== :: Input -> Input -> Bool
$c== :: Input -> Input -> Bool
Eq, (forall x. Input -> Rep Input x)
-> (forall x. Rep Input x -> Input) -> Generic Input
forall x. Rep Input x -> Input
forall x. Input -> Rep Input x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Input x -> Input
$cfrom :: forall x. Input -> Rep Input x
Generic)

instance NFData Input

-- | Outputs can contain information needed to spend the output at a later date.
data Output = Output
    { Output -> Maybe Script
outputRedeemScript  :: Maybe Script
    , Output -> Maybe Script
outputWitnessScript :: Maybe Script
    , Output -> HashMap PubKeyI (Fingerprint, [Fingerprint])
outputHDKeypaths    :: HashMap PubKeyI (Fingerprint, [KeyIndex])
    , Output -> UnknownMap
outputUnknown       :: UnknownMap
    } deriving (Int -> Output -> ShowS
[Output] -> ShowS
Output -> String
(Int -> Output -> ShowS)
-> (Output -> String) -> ([Output] -> ShowS) -> Show Output
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Output] -> ShowS
$cshowList :: [Output] -> ShowS
show :: Output -> String
$cshow :: Output -> String
showsPrec :: Int -> Output -> ShowS
$cshowsPrec :: Int -> Output -> ShowS
Show, Output -> Output -> Bool
(Output -> Output -> Bool)
-> (Output -> Output -> Bool) -> Eq Output
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Output -> Output -> Bool
$c/= :: Output -> Output -> Bool
== :: Output -> Output -> Bool
$c== :: Output -> Output -> Bool
Eq, (forall x. Output -> Rep Output x)
-> (forall x. Rep Output x -> Output) -> Generic Output
forall x. Rep Output x -> Output
forall x. Output -> Rep Output x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Output x -> Output
$cfrom :: forall x. Output -> Rep Output x
Generic)

instance NFData Output

-- | 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.
newtype UnknownMap = UnknownMap { UnknownMap -> HashMap Key ByteString
unknownMap :: HashMap Key ByteString }
    deriving (Int -> UnknownMap -> ShowS
[UnknownMap] -> ShowS
UnknownMap -> String
(Int -> UnknownMap -> ShowS)
-> (UnknownMap -> String)
-> ([UnknownMap] -> ShowS)
-> Show UnknownMap
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnknownMap] -> ShowS
$cshowList :: [UnknownMap] -> ShowS
show :: UnknownMap -> String
$cshow :: UnknownMap -> String
showsPrec :: Int -> UnknownMap -> ShowS
$cshowsPrec :: Int -> UnknownMap -> ShowS
Show, UnknownMap -> UnknownMap -> Bool
(UnknownMap -> UnknownMap -> Bool)
-> (UnknownMap -> UnknownMap -> Bool) -> Eq UnknownMap
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnknownMap -> UnknownMap -> Bool
$c/= :: UnknownMap -> UnknownMap -> Bool
== :: UnknownMap -> UnknownMap -> Bool
$c== :: UnknownMap -> UnknownMap -> Bool
Eq, b -> UnknownMap -> UnknownMap
NonEmpty UnknownMap -> UnknownMap
UnknownMap -> UnknownMap -> UnknownMap
(UnknownMap -> UnknownMap -> UnknownMap)
-> (NonEmpty UnknownMap -> UnknownMap)
-> (forall b. Integral b => b -> UnknownMap -> UnknownMap)
-> Semigroup UnknownMap
forall b. Integral b => b -> UnknownMap -> UnknownMap
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> UnknownMap -> UnknownMap
$cstimes :: forall b. Integral b => b -> UnknownMap -> UnknownMap
sconcat :: NonEmpty UnknownMap -> UnknownMap
$csconcat :: NonEmpty UnknownMap -> UnknownMap
<> :: UnknownMap -> UnknownMap -> UnknownMap
$c<> :: UnknownMap -> UnknownMap -> UnknownMap
Semigroup, Semigroup UnknownMap
UnknownMap
Semigroup UnknownMap =>
UnknownMap
-> (UnknownMap -> UnknownMap -> UnknownMap)
-> ([UnknownMap] -> UnknownMap)
-> Monoid UnknownMap
[UnknownMap] -> UnknownMap
UnknownMap -> UnknownMap -> UnknownMap
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [UnknownMap] -> UnknownMap
$cmconcat :: [UnknownMap] -> UnknownMap
mappend :: UnknownMap -> UnknownMap -> UnknownMap
$cmappend :: UnknownMap -> UnknownMap -> UnknownMap
mempty :: UnknownMap
$cmempty :: UnknownMap
$cp1Monoid :: Semigroup UnknownMap
Monoid, (forall x. UnknownMap -> Rep UnknownMap x)
-> (forall x. Rep UnknownMap x -> UnknownMap) -> Generic UnknownMap
forall x. Rep UnknownMap x -> UnknownMap
forall x. UnknownMap -> Rep UnknownMap x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UnknownMap x -> UnknownMap
$cfrom :: forall x. UnknownMap -> Rep UnknownMap x
Generic)

instance NFData UnknownMap

-- | Raw keys for the map type used in PSBTs.
data Key = Key
    { Key -> Word8
keyType :: Word8
    , Key -> ByteString
key     :: ByteString
    } deriving (Int -> Key -> ShowS
[Key] -> ShowS
Key -> String
(Int -> Key -> ShowS)
-> (Key -> String) -> ([Key] -> ShowS) -> Show Key
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Key] -> ShowS
$cshowList :: [Key] -> ShowS
show :: Key -> String
$cshow :: Key -> String
showsPrec :: Int -> Key -> ShowS
$cshowsPrec :: Int -> Key -> ShowS
Show, Key -> Key -> Bool
(Key -> Key -> Bool) -> (Key -> Key -> Bool) -> Eq Key
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Key -> Key -> Bool
$c/= :: Key -> Key -> Bool
== :: Key -> Key -> Bool
$c== :: Key -> Key -> Bool
Eq, (forall x. Key -> Rep Key x)
-> (forall x. Rep Key x -> Key) -> Generic Key
forall x. Rep Key x -> Key
forall x. Key -> Rep Key x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Key x -> Key
$cfrom :: forall x. Key -> Rep Key x
Generic)

instance NFData Key

instance Hashable Key

-- | Take two 'PartiallySignedTransaction's and merge them. The
-- 'unsignedTransaction' field in both must be the same.
merge :: PartiallySignedTransaction
      -> PartiallySignedTransaction
      -> Maybe PartiallySignedTransaction
merge :: PartiallySignedTransaction
-> PartiallySignedTransaction -> Maybe PartiallySignedTransaction
merge psbt1 :: PartiallySignedTransaction
psbt1 psbt2 :: PartiallySignedTransaction
psbt2
    | PartiallySignedTransaction -> Tx
unsignedTransaction PartiallySignedTransaction
psbt1 Tx -> Tx -> Bool
forall a. Eq a => a -> a -> Bool
== PartiallySignedTransaction -> Tx
unsignedTransaction PartiallySignedTransaction
psbt2
    = PartiallySignedTransaction -> Maybe PartiallySignedTransaction
forall a. a -> Maybe a
Just (PartiallySignedTransaction -> Maybe PartiallySignedTransaction)
-> PartiallySignedTransaction -> Maybe PartiallySignedTransaction
forall a b. (a -> b) -> a -> b
$ PartiallySignedTransaction
psbt1
        { globalUnknown :: UnknownMap
globalUnknown = PartiallySignedTransaction -> UnknownMap
globalUnknown PartiallySignedTransaction
psbt1 UnknownMap -> UnknownMap -> UnknownMap
forall a. Semigroup a => a -> a -> a
<> PartiallySignedTransaction -> UnknownMap
globalUnknown PartiallySignedTransaction
psbt2
        , inputs :: [Input]
inputs = (Input -> Input -> Input) -> [Input] -> [Input] -> [Input]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Input -> Input -> Input
mergeInput (PartiallySignedTransaction -> [Input]
inputs PartiallySignedTransaction
psbt1) (PartiallySignedTransaction -> [Input]
inputs PartiallySignedTransaction
psbt2)
        , outputs :: [Output]
outputs = (Output -> Output -> Output) -> [Output] -> [Output] -> [Output]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Output -> Output -> Output
mergeOutput (PartiallySignedTransaction -> [Output]
outputs PartiallySignedTransaction
psbt1) (PartiallySignedTransaction -> [Output]
outputs PartiallySignedTransaction
psbt2)
        }
merge _ _ = Maybe PartiallySignedTransaction
forall a. Maybe a
Nothing

mergeInput :: Input -> Input -> Input
mergeInput :: Input -> Input -> Input
mergeInput a :: Input
a b :: Input
b = Input :: Maybe Tx
-> Maybe TxOut
-> HashMap PubKeyI ByteString
-> Maybe SigHash
-> Maybe Script
-> Maybe Script
-> HashMap PubKeyI (Fingerprint, [Fingerprint])
-> Maybe Script
-> Maybe WitnessStack
-> UnknownMap
-> Input
Input
    { nonWitnessUtxo :: Maybe Tx
nonWitnessUtxo =
            if Maybe TxOut -> Bool
forall a. Maybe a -> Bool
isJust Maybe TxOut
witUtx
            then Maybe Tx
forall a. Maybe a
Nothing
            else Input -> Maybe Tx
nonWitnessUtxo Input
a Maybe Tx -> Maybe Tx -> Maybe Tx
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Input -> Maybe Tx
nonWitnessUtxo Input
b
    , witnessUtxo :: Maybe TxOut
witnessUtxo =
            Maybe TxOut
witUtx
    , sigHashType :: Maybe SigHash
sigHashType =
            Input -> Maybe SigHash
sigHashType Input
a Maybe SigHash -> Maybe SigHash -> Maybe SigHash
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Input -> Maybe SigHash
sigHashType Input
b
    , partialSigs :: HashMap PubKeyI ByteString
partialSigs =
            Input -> HashMap PubKeyI ByteString
partialSigs Input
a HashMap PubKeyI ByteString
-> HashMap PubKeyI ByteString -> HashMap PubKeyI ByteString
forall a. Semigroup a => a -> a -> a
<> Input -> HashMap PubKeyI ByteString
partialSigs Input
b
    , inputHDKeypaths :: HashMap PubKeyI (Fingerprint, [Fingerprint])
inputHDKeypaths =
            Input -> HashMap PubKeyI (Fingerprint, [Fingerprint])
inputHDKeypaths Input
a HashMap PubKeyI (Fingerprint, [Fingerprint])
-> HashMap PubKeyI (Fingerprint, [Fingerprint])
-> HashMap PubKeyI (Fingerprint, [Fingerprint])
forall a. Semigroup a => a -> a -> a
<> Input -> HashMap PubKeyI (Fingerprint, [Fingerprint])
inputHDKeypaths Input
b
    , inputUnknown :: UnknownMap
inputUnknown =
            Input -> UnknownMap
inputUnknown Input
a UnknownMap -> UnknownMap -> UnknownMap
forall a. Semigroup a => a -> a -> a
<> Input -> UnknownMap
inputUnknown Input
b
    , inputRedeemScript :: Maybe Script
inputRedeemScript =
            Input -> Maybe Script
inputRedeemScript Input
a Maybe Script -> Maybe Script -> Maybe Script
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Input -> Maybe Script
inputRedeemScript Input
b
    , inputWitnessScript :: Maybe Script
inputWitnessScript =
            Input -> Maybe Script
inputWitnessScript Input
a Maybe Script -> Maybe Script -> Maybe Script
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Input -> Maybe Script
inputWitnessScript Input
b
    , finalScriptSig :: Maybe Script
finalScriptSig =
            Input -> Maybe Script
finalScriptSig Input
a Maybe Script -> Maybe Script -> Maybe Script
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Input -> Maybe Script
finalScriptSig Input
b
    , finalScriptWitness :: Maybe WitnessStack
finalScriptWitness =
            Input -> Maybe WitnessStack
finalScriptWitness Input
a Maybe WitnessStack -> Maybe WitnessStack -> Maybe WitnessStack
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Input -> Maybe WitnessStack
finalScriptWitness Input
b
    }
  where
    witUtx :: Maybe TxOut
witUtx = Input -> Maybe TxOut
witnessUtxo Input
a Maybe TxOut -> Maybe TxOut -> Maybe TxOut
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Input -> Maybe TxOut
witnessUtxo Input
b

mergeOutput :: Output -> Output -> Output
mergeOutput :: Output -> Output -> Output
mergeOutput a :: Output
a b :: Output
b = Output :: Maybe Script
-> Maybe Script
-> HashMap PubKeyI (Fingerprint, [Fingerprint])
-> UnknownMap
-> Output
Output
    { outputRedeemScript :: Maybe Script
outputRedeemScript =
            Output -> Maybe Script
outputRedeemScript Output
a Maybe Script -> Maybe Script -> Maybe Script
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Output -> Maybe Script
outputRedeemScript Output
b
    , outputWitnessScript :: Maybe Script
outputWitnessScript =
            Output -> Maybe Script
outputWitnessScript Output
a Maybe Script -> Maybe Script -> Maybe Script
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Output -> Maybe Script
outputWitnessScript Output
b
    , outputHDKeypaths :: HashMap PubKeyI (Fingerprint, [Fingerprint])
outputHDKeypaths =
            Output -> HashMap PubKeyI (Fingerprint, [Fingerprint])
outputHDKeypaths Output
a HashMap PubKeyI (Fingerprint, [Fingerprint])
-> HashMap PubKeyI (Fingerprint, [Fingerprint])
-> HashMap PubKeyI (Fingerprint, [Fingerprint])
forall a. Semigroup a => a -> a -> a
<> Output -> HashMap PubKeyI (Fingerprint, [Fingerprint])
outputHDKeypaths Output
b
    , outputUnknown :: UnknownMap
outputUnknown =
            Output -> UnknownMap
outputUnknown Output
a UnknownMap -> UnknownMap -> UnknownMap
forall a. Semigroup a => a -> a -> a
<> Output -> UnknownMap
outputUnknown Output
b
    }

-- | Take partial signatures from all of the 'Input's and finalize the signature.
complete :: PartiallySignedTransaction
         -> PartiallySignedTransaction
complete :: PartiallySignedTransaction -> PartiallySignedTransaction
complete psbt :: PartiallySignedTransaction
psbt =
    PartiallySignedTransaction
psbt
    {
        inputs :: [Input]
inputs = ((Fingerprint, Input) -> Input)
-> [(Fingerprint, Input)] -> [Input]
forall a b. (a -> b) -> [a] -> [b]
map
                 ((Maybe ScriptOutput, Input) -> Input
completeInput ((Maybe ScriptOutput, Input) -> Input)
-> ((Fingerprint, Input) -> (Maybe ScriptOutput, Input))
-> (Fingerprint, Input)
-> Input
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Fingerprint, Input) -> (Maybe ScriptOutput, Input)
analyzeInputs)
                 ([Input] -> [(Fingerprint, Input)]
forall a. [a] -> [(Fingerprint, a)]
indexed ([Input] -> [(Fingerprint, Input)])
-> [Input] -> [(Fingerprint, Input)]
forall a b. (a -> b) -> a -> b
$ PartiallySignedTransaction -> [Input]
inputs PartiallySignedTransaction
psbt)
    }
  where
    analyzeInputs :: (Fingerprint, Input) -> (Maybe ScriptOutput, Input)
analyzeInputs (i :: Fingerprint
i, input :: Input
input) =
        (,)
        (TxOut -> Maybe ScriptOutput
outputScript (TxOut -> Maybe ScriptOutput) -> Maybe TxOut -> Maybe ScriptOutput
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Input -> Maybe TxOut
witnessUtxo Input
input Maybe TxOut -> Maybe TxOut -> Maybe TxOut
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe TxOut
nonWitScript)
        Input
input
      where
        nonWitScript :: Maybe TxOut
nonWitScript = Fingerprint -> Tx -> Maybe TxOut
getPrevOut Fingerprint
i (Tx -> Maybe TxOut) -> Maybe Tx -> Maybe TxOut
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Input -> Maybe Tx
nonWitnessUtxo Input
input

    getPrevOut :: Fingerprint -> Tx -> Maybe TxOut
getPrevOut i :: Fingerprint
i tx :: Tx
tx =
       (Tx -> [TxOut]
txOut Tx
tx [TxOut] -> Fingerprint -> Maybe TxOut
forall b. [b] -> Fingerprint -> Maybe b
!!?) (Fingerprint -> Maybe TxOut)
-> (TxIn -> Fingerprint) -> TxIn -> Maybe TxOut
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       Fingerprint -> Fingerprint
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Fingerprint -> Fingerprint)
-> (TxIn -> Fingerprint) -> TxIn -> Fingerprint
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       OutPoint -> Fingerprint
outPointIndex (OutPoint -> Fingerprint)
-> (TxIn -> OutPoint) -> TxIn -> Fingerprint
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       TxIn -> OutPoint
prevOutput (TxIn -> Maybe TxOut) -> Maybe TxIn -> Maybe TxOut
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<
       Tx -> [TxIn]
txIn (PartiallySignedTransaction -> Tx
unsignedTransaction PartiallySignedTransaction
psbt) [TxIn] -> Fingerprint -> Maybe TxIn
forall b. [b] -> Fingerprint -> Maybe b
!!? Fingerprint
i
    xs :: [b]
xs !!? :: [b] -> Fingerprint -> Maybe b
!!? i :: Fingerprint
i = Fingerprint -> [(Fingerprint, b)] -> Maybe b
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Fingerprint
i ([(Fingerprint, b)] -> Maybe b) -> [(Fingerprint, b)] -> Maybe b
forall a b. (a -> b) -> a -> b
$ [b] -> [(Fingerprint, b)]
forall a. [a] -> [(Fingerprint, a)]
indexed [b]
xs

    outputScript :: TxOut -> Maybe ScriptOutput
outputScript = Either String ScriptOutput -> Maybe ScriptOutput
forall a b. Either a b -> Maybe b
eitherToMaybe (Either String ScriptOutput -> Maybe ScriptOutput)
-> (TxOut -> Either String ScriptOutput)
-> TxOut
-> Maybe ScriptOutput
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either String ScriptOutput
decodeOutputBS (ByteString -> Either String ScriptOutput)
-> (TxOut -> ByteString) -> TxOut -> Either String ScriptOutput
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOut -> ByteString
scriptOutput

    completeInput :: (Maybe ScriptOutput, Input) -> Input
completeInput (Nothing, input :: Input
input)     = Input
input
    completeInput (Just script :: ScriptOutput
script, input :: Input
input) = Input -> ScriptOutput -> Input
completeSig Input
input ScriptOutput
script

    indexed :: [a] -> [(Word32, a)]
    indexed :: [a] -> [(Fingerprint, a)]
indexed = [Fingerprint] -> [a] -> [(Fingerprint, a)]
forall a b. [a] -> [b] -> [(a, b)]
zip [0..]

completeSig :: Input -> ScriptOutput -> Input

completeSig :: Input -> ScriptOutput -> Input
completeSig input :: Input
input (PayPK k :: PubKeyI
k) =
    Input
input
    { finalScriptSig :: Maybe Script
finalScriptSig =
            Either String Script -> Maybe Script
forall a b. Either a b -> Maybe b
eitherToMaybe (Either String Script -> Maybe Script)
-> (ByteString -> Either String Script)
-> ByteString
-> Maybe Script
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Get Script -> ByteString -> Either String Script
forall a. Get a -> ByteString -> Either String a
runGetS Get Script
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize (ByteString -> Maybe Script) -> Maybe ByteString -> Maybe Script
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<
            PubKeyI -> HashMap PubKeyI ByteString -> Maybe ByteString
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup PubKeyI
k (Input -> HashMap PubKeyI ByteString
partialSigs Input
input)
    }

completeSig input :: Input
input (PayPKHash h :: Hash160
h)
    | [(k :: PubKeyI
k, sig :: ByteString
sig)] <- HashMap PubKeyI ByteString -> [(PubKeyI, ByteString)]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList (Input -> HashMap PubKeyI ByteString
partialSigs Input
input)
    , Hash160 -> Address
PubKeyAddress Hash160
h Address -> Address -> Bool
forall a. Eq a => a -> a -> Bool
== PubKeyI -> Address
pubKeyAddr PubKeyI
k =
            Input
input
            {
                finalScriptSig :: Maybe Script
finalScriptSig =
                    Script -> Maybe Script
forall a. a -> Maybe a
Just (Script -> Maybe Script) -> Script -> Maybe Script
forall a b. (a -> b) -> a -> b
$
                    [ScriptOp] -> Script
Script
                    [
                        ByteString -> ScriptOp
opPushData ByteString
sig,
                        ByteString -> ScriptOp
opPushData (Put -> ByteString
runPutS (PubKeyI -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize PubKeyI
k))
                    ]
            }

completeSig input :: Input
input (PayMulSig pubKeys :: [PubKeyI]
pubKeys m :: Int
m)
    | WitnessStack -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length WitnessStack
sigs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
m =
          Input
input { finalScriptSig :: Maybe Script
finalScriptSig = Maybe Script
finalSig }
  where
    sigs :: WitnessStack
sigs = Int -> [PubKeyI] -> Input -> WitnessStack
collectSigs Int
m [PubKeyI]
pubKeys Input
input
    finalSig :: Maybe Script
finalSig =
        [ScriptOp] -> Script
Script ([ScriptOp] -> Script)
-> (Script -> [ScriptOp]) -> Script -> Script
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
        (ScriptOp
OP_0 ScriptOp -> [ScriptOp] -> [ScriptOp]
forall a. a -> [a] -> [a]
:) ([ScriptOp] -> [ScriptOp])
-> (Script -> [ScriptOp]) -> Script -> [ScriptOp]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
        ((ByteString -> ScriptOp) -> WitnessStack -> [ScriptOp]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ScriptOp
opPushData WitnessStack
sigs [ScriptOp] -> [ScriptOp] -> [ScriptOp]
forall a. Semigroup a => a -> a -> a
<>) ([ScriptOp] -> [ScriptOp])
-> (Script -> [ScriptOp]) -> Script -> [ScriptOp]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
        ScriptOp -> [ScriptOp]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ScriptOp -> [ScriptOp])
-> (Script -> ScriptOp) -> Script -> [ScriptOp]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ScriptOp
opPushData (ByteString -> ScriptOp)
-> (Script -> ByteString) -> Script -> ScriptOp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Put -> ByteString
runPutS (Put -> ByteString) -> (Script -> Put) -> Script -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Script -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize (Script -> Script) -> Maybe Script -> Maybe Script
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
        Input -> Maybe Script
inputRedeemScript Input
input

completeSig input :: Input
input (PayScriptHash h :: Hash160
h)
    | Just rdmScript :: Script
rdmScript <- Input -> Maybe Script
inputRedeemScript Input
input
    , Hash160 -> ScriptOutput
PayScriptHash Hash160
h ScriptOutput -> ScriptOutput -> Bool
forall a. Eq a => a -> a -> Bool
== Script -> ScriptOutput
toP2SH Script
rdmScript
    , Right decodedScript :: ScriptOutput
decodedScript <- Script -> Either String ScriptOutput
decodeOutput Script
rdmScript
    , Bool -> Bool
not (ScriptOutput -> Bool
isPayScriptHash ScriptOutput
decodedScript) =
            Input -> ScriptOutput -> Input
completeSig Input
input ScriptOutput
decodedScript

completeSig input :: Input
input (PayWitnessPKHash h :: Hash160
h)
    | [(k :: PubKeyI
k, sig :: ByteString
sig)] <- HashMap PubKeyI ByteString -> [(PubKeyI, ByteString)]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList (Input -> HashMap PubKeyI ByteString
partialSigs Input
input)
    , Hash160 -> Address
PubKeyAddress Hash160
h Address -> Address -> Bool
forall a. Eq a => a -> a -> Bool
== PubKeyI -> Address
pubKeyAddr PubKeyI
k =
            Input
input
            {
                finalScriptWitness :: Maybe WitnessStack
finalScriptWitness =
                    WitnessStack -> Maybe WitnessStack
forall a. a -> Maybe a
Just [ByteString
sig, Put -> ByteString
runPutS (Put -> ByteString) -> Put -> ByteString
forall a b. (a -> b) -> a -> b
$ PubKeyI -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize PubKeyI
k],
                finalScriptSig :: Maybe Script
finalScriptSig =
                    [ScriptOp] -> Script
Script ([ScriptOp] -> Script)
-> (Script -> [ScriptOp]) -> Script -> Script
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScriptOp -> [ScriptOp]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ScriptOp -> [ScriptOp])
-> (Script -> ScriptOp) -> Script -> [ScriptOp]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ScriptOp
opPushData (ByteString -> ScriptOp)
-> (Script -> ByteString) -> Script -> ScriptOp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Put -> ByteString
runPutS (Put -> ByteString) -> (Script -> Put) -> Script -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Script -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize (Script -> Script) -> Maybe Script -> Maybe Script
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                    Input -> Maybe Script
inputRedeemScript Input
input
            }
completeSig input :: Input
input (PayWitnessScriptHash h :: Hash256
h)
    | Just witScript :: Script
witScript <- Input -> Maybe Script
inputWitnessScript Input
input
    , Hash256 -> ScriptOutput
PayWitnessScriptHash Hash256
h ScriptOutput -> ScriptOutput -> Bool
forall a. Eq a => a -> a -> Bool
== Script -> ScriptOutput
toP2WSH Script
witScript
    , Right decodedScript :: ScriptOutput
decodedScript <- Script -> Either String ScriptOutput
decodeOutput Script
witScript =
            Input -> ScriptOutput -> Input
completeWitnessSig Input
input ScriptOutput
decodedScript

completeSig input :: Input
input _ = Input
input

completeWitnessSig :: Input -> ScriptOutput -> Input
completeWitnessSig :: Input -> ScriptOutput -> Input
completeWitnessSig input :: Input
input script :: ScriptOutput
script@(PayMulSig pubKeys :: [PubKeyI]
pubKeys m :: Int
m)
    | WitnessStack -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length WitnessStack
sigs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
m =
          Input
input
          {
              finalScriptWitness :: Maybe WitnessStack
finalScriptWitness = WitnessStack -> Maybe WitnessStack
forall a. a -> Maybe a
Just WitnessStack
finalWit,
              finalScriptSig :: Maybe Script
finalScriptSig = Maybe Script
finalSig
          }
  where
    sigs :: WitnessStack
sigs = Int -> [PubKeyI] -> Input -> WitnessStack
collectSigs Int
m [PubKeyI]
pubKeys Input
input
    finalSig :: Maybe Script
finalSig = [ScriptOp] -> Script
Script ([ScriptOp] -> Script)
-> (Script -> [ScriptOp]) -> Script -> Script
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScriptOp -> [ScriptOp]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ScriptOp -> [ScriptOp])
-> (Script -> ScriptOp) -> Script -> [ScriptOp]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ScriptOp
opPushData (ByteString -> ScriptOp)
-> (Script -> ByteString) -> Script -> ScriptOp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Put -> ByteString
runPutS (Put -> ByteString) -> (Script -> Put) -> Script -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Script -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize (Script -> Script) -> Maybe Script -> Maybe Script
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
               Input -> Maybe Script
inputRedeemScript Input
input
    finalWit :: WitnessStack
finalWit = ByteString
forall a. Monoid a => a
mempty ByteString -> WitnessStack -> WitnessStack
forall a. a -> [a] -> [a]
: WitnessStack
sigs WitnessStack -> WitnessStack -> WitnessStack
forall a. Semigroup a => a -> a -> a
<> [ScriptOutput -> ByteString
encodeOutputBS ScriptOutput
script]

completeWitnessSig input :: Input
input _ = Input
input

collectSigs :: Int -> [PubKeyI] -> Input -> [ByteString]
collectSigs :: Int -> [PubKeyI] -> Input -> WitnessStack
collectSigs m :: Int
m pubKeys :: [PubKeyI]
pubKeys input :: Input
input =
    Int -> WitnessStack -> WitnessStack
forall a. Int -> [a] -> [a]
take Int
m (WitnessStack -> WitnessStack)
-> (WitnessStack -> WitnessStack) -> WitnessStack -> WitnessStack
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WitnessStack -> WitnessStack
forall a. [a] -> [a]
reverse (WitnessStack -> WitnessStack) -> WitnessStack -> WitnessStack
forall a b. (a -> b) -> a -> b
$ (WitnessStack -> PubKeyI -> WitnessStack)
-> WitnessStack -> [PubKeyI] -> WitnessStack
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' WitnessStack -> PubKeyI -> WitnessStack
lookupKey [] [PubKeyI]
pubKeys
  where
    lookupKey :: WitnessStack -> PubKeyI -> WitnessStack
lookupKey sigs :: WitnessStack
sigs key :: PubKeyI
key =
        WitnessStack
-> (ByteString -> WitnessStack) -> Maybe ByteString -> WitnessStack
forall b a. b -> (a -> b) -> Maybe a -> b
maybe WitnessStack
sigs (ByteString -> WitnessStack -> WitnessStack
forall a. a -> [a] -> [a]
: WitnessStack
sigs) (Maybe ByteString -> WitnessStack)
-> Maybe ByteString -> WitnessStack
forall a b. (a -> b) -> a -> b
$
        PubKeyI -> HashMap PubKeyI ByteString -> Maybe ByteString
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup PubKeyI
key (Input -> HashMap PubKeyI ByteString
partialSigs Input
input)

-- | Take a finalized 'PartiallySignedTransaction' and produce the signed final
-- transaction. You may need to call 'complete' on the
-- 'PartiallySignedTransaction' before producing the final transaction.
finalTransaction :: PartiallySignedTransaction -> Tx
finalTransaction :: PartiallySignedTransaction -> Tx
finalTransaction psbt :: PartiallySignedTransaction
psbt =
    ([TxIn], [WitnessStack]) -> Tx
setInputs (([TxIn], [WitnessStack]) -> Tx)
-> ([(TxIn, Input)] -> ([TxIn], [WitnessStack]))
-> [(TxIn, Input)]
-> Tx
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    (([TxIn], [WitnessStack])
 -> (TxIn, Input) -> ([TxIn], [WitnessStack]))
-> ([TxIn], [WitnessStack])
-> [(TxIn, Input)]
-> ([TxIn], [WitnessStack])
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ([TxIn], [WitnessStack])
-> (TxIn, Input) -> ([TxIn], [WitnessStack])
finalizeInput ([], []) ([(TxIn, Input)] -> Tx) -> [(TxIn, Input)] -> Tx
forall a b. (a -> b) -> a -> b
$
    [TxIn] -> [Input] -> [(TxIn, Input)]
forall a b. [a] -> [b] -> [(a, b)]
zip (Tx -> [TxIn]
txIn Tx
tx) (PartiallySignedTransaction -> [Input]
inputs PartiallySignedTransaction
psbt)
  where
    tx :: Tx
tx = PartiallySignedTransaction -> Tx
unsignedTransaction PartiallySignedTransaction
psbt
    hasWitness :: Bool
hasWitness =
        (Input -> Bool) -> [Input] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any
        (Maybe WitnessStack -> Bool
forall a. Maybe a -> Bool
isJust (Maybe WitnessStack -> Bool)
-> (Input -> Maybe WitnessStack) -> Input -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Input -> Maybe WitnessStack
finalScriptWitness)
        (PartiallySignedTransaction -> [Input]
inputs PartiallySignedTransaction
psbt)
    setInputs :: ([TxIn], [WitnessStack]) -> Tx
setInputs (ins :: [TxIn]
ins, witData :: [WitnessStack]
witData) =
        Tx
tx
        {
            txIn :: [TxIn]
txIn = [TxIn] -> [TxIn]
forall a. [a] -> [a]
reverse [TxIn]
ins,
            txWitness :: [WitnessStack]
txWitness = if Bool
hasWitness then [WitnessStack] -> [WitnessStack]
forall a. [a] -> [a]
reverse [WitnessStack]
witData else []
        }
    finalizeInput :: ([TxIn], [WitnessStack])
-> (TxIn, Input) -> ([TxIn], [WitnessStack])
finalizeInput (ins :: [TxIn]
ins, witData :: [WitnessStack]
witData) (txInput :: TxIn
txInput, psbtInput :: Input
psbtInput) =
        ([TxIn], [WitnessStack])
-> (Script -> ([TxIn], [WitnessStack]))
-> Maybe Script
-> ([TxIn], [WitnessStack])
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([TxIn], [WitnessStack])
finalWitness Script -> ([TxIn], [WitnessStack])
forall a. Serial a => a -> ([TxIn], [WitnessStack])
finalScript (Maybe Script -> ([TxIn], [WitnessStack]))
-> Maybe Script -> ([TxIn], [WitnessStack])
forall a b. (a -> b) -> a -> b
$
        Input -> Maybe Script
finalScriptSig Input
psbtInput
      where
        finalScript :: a -> ([TxIn], [WitnessStack])
finalScript script :: a
script =
            (
                TxIn
txInput { scriptInput :: ByteString
scriptInput = Put -> ByteString
runPutS (Put -> ByteString) -> Put -> ByteString
forall a b. (a -> b) -> a -> b
$ a -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize a
script } TxIn -> [TxIn] -> [TxIn]
forall a. a -> [a] -> [a]
: [TxIn]
ins,
                [] WitnessStack -> [WitnessStack] -> [WitnessStack]
forall a. a -> [a] -> [a]
: [WitnessStack]
witData
            )
        finalWitness :: ([TxIn], [WitnessStack])
finalWitness =
            (
                [TxIn]
ins,
                WitnessStack -> Maybe WitnessStack -> WitnessStack
forall a. a -> Maybe a -> a
fromMaybe [] (Input -> Maybe WitnessStack
finalScriptWitness Input
psbtInput) WitnessStack -> [WitnessStack] -> [WitnessStack]
forall a. a -> [a] -> [a]
: [WitnessStack]
witData
            )

-- | Take an unsigned transaction and produce an empty
-- 'PartiallySignedTransaction'
emptyPSBT :: Tx -> PartiallySignedTransaction
emptyPSBT :: Tx -> PartiallySignedTransaction
emptyPSBT tx :: Tx
tx = PartiallySignedTransaction :: Tx
-> UnknownMap -> [Input] -> [Output] -> PartiallySignedTransaction
PartiallySignedTransaction
    { unsignedTransaction :: Tx
unsignedTransaction = Tx
tx
    , globalUnknown :: UnknownMap
globalUnknown = UnknownMap
forall a. Monoid a => a
mempty
    , inputs :: [Input]
inputs = Int -> Input -> [Input]
forall a. Int -> a -> [a]
replicate ([TxIn] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Tx -> [TxIn]
txIn Tx
tx)) Input
emptyInput
    , outputs :: [Output]
outputs = Int -> Output -> [Output]
forall a. Int -> a -> [a]
replicate ([TxOut] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Tx -> [TxOut]
txOut Tx
tx)) Output
emptyOutput
    }

emptyInput :: Input
emptyInput :: Input
emptyInput = Maybe Tx
-> Maybe TxOut
-> HashMap PubKeyI ByteString
-> Maybe SigHash
-> Maybe Script
-> Maybe Script
-> HashMap PubKeyI (Fingerprint, [Fingerprint])
-> Maybe Script
-> Maybe WitnessStack
-> UnknownMap
-> Input
Input
    Maybe Tx
forall a. Maybe a
Nothing Maybe TxOut
forall a. Maybe a
Nothing HashMap PubKeyI ByteString
forall k v. HashMap k v
HashMap.empty Maybe SigHash
forall a. Maybe a
Nothing
    Maybe Script
forall a. Maybe a
Nothing Maybe Script
forall a. Maybe a
Nothing HashMap PubKeyI (Fingerprint, [Fingerprint])
forall k v. HashMap k v
HashMap.empty
    Maybe Script
forall a. Maybe a
Nothing Maybe WitnessStack
forall a. Maybe a
Nothing (HashMap Key ByteString -> UnknownMap
UnknownMap HashMap Key ByteString
forall k v. HashMap k v
HashMap.empty)

emptyOutput :: Output
emptyOutput :: Output
emptyOutput = Maybe Script
-> Maybe Script
-> HashMap PubKeyI (Fingerprint, [Fingerprint])
-> UnknownMap
-> Output
Output Maybe Script
forall a. Maybe a
Nothing Maybe Script
forall a. Maybe a
Nothing HashMap PubKeyI (Fingerprint, [Fingerprint])
forall k v. HashMap k v
HashMap.empty (HashMap Key ByteString -> UnknownMap
UnknownMap HashMap Key ByteString
forall k v. HashMap k v
HashMap.empty)

instance Serialize PartiallySignedTransaction where
    get :: Get PartiallySignedTransaction
get = do
        ByteString
magic <- Int -> Get ByteString
S.getBytes 4
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> Bool -> Get ()
forall a b. (a -> b) -> a -> b
$ ByteString
magic ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== "psbt"
        Word8
headerSep <- Get Word8
S.getWord8
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> Bool -> Get ()
forall a b. (a -> b) -> a -> b
$ Word8
headerSep Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0xff

        Word8
keySize <- Get Word8
S.getWord8
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> Bool -> Get ()
forall a b. (a -> b) -> a -> b
$ Word8
keySize Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 1
        Word8
globalUnsignedTxType <- Get Word8
S.getWord8
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> Bool -> Get ()
forall a b. (a -> b) -> a -> b
$ Word8
globalUnsignedTxType Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0x00
        Tx
unsignedTransaction <- Get Tx -> Get Tx
forall a. Get a -> Get a
getSizedBytes Get Tx
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> Bool -> Get ()
forall a b. (a -> b) -> a -> b
$ (TxIn -> Bool) -> [TxIn] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (ByteString -> Bool
B.null (ByteString -> Bool) -> (TxIn -> ByteString) -> TxIn -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxIn -> ByteString
scriptInput) (Tx -> [TxIn]
txIn Tx
unsignedTransaction)
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> Bool -> Get ()
forall a b. (a -> b) -> a -> b
$ [WitnessStack] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Tx -> [WitnessStack]
txWitness Tx
unsignedTransaction)

        UnknownMap
globalUnknown <- Get UnknownMap
forall t. Serialize t => Get t
S.get
        Word8
globalEnd <- Get Word8
S.getWord8
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> Bool -> Get ()
forall a b. (a -> b) -> a -> b
$ Word8
globalEnd Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0x00

        [Input]
inputs <-
            Int -> Get Input -> Get [Input]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM
            ([TxIn] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Tx -> [TxIn]
txIn Tx
unsignedTransaction))
            Get Input
forall t. Serialize t => Get t
S.get
        [Output]
outputs <-
            Int -> Get Output -> Get [Output]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM
            ([TxOut] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Tx -> [TxOut]
txOut Tx
unsignedTransaction))
            Get Output
forall t. Serialize t => Get t
S.get

        PartiallySignedTransaction -> Get PartiallySignedTransaction
forall (m :: * -> *) a. Monad m => a -> m a
return
            PartiallySignedTransaction :: Tx
-> UnknownMap -> [Input] -> [Output] -> PartiallySignedTransaction
PartiallySignedTransaction
            {
                Tx
unsignedTransaction :: Tx
unsignedTransaction :: Tx
unsignedTransaction,
                UnknownMap
globalUnknown :: UnknownMap
globalUnknown :: UnknownMap
globalUnknown,
                [Input]
inputs :: [Input]
inputs :: [Input]
inputs,
                [Output]
outputs :: [Output]
outputs :: [Output]
outputs
            }

    put :: Putter PartiallySignedTransaction
put PartiallySignedTransaction
        {
            Tx
unsignedTransaction :: Tx
unsignedTransaction :: PartiallySignedTransaction -> Tx
unsignedTransaction,
            UnknownMap
globalUnknown :: UnknownMap
globalUnknown :: PartiallySignedTransaction -> UnknownMap
globalUnknown,
            [Input]
inputs :: [Input]
inputs :: PartiallySignedTransaction -> [Input]
inputs,
            [Output]
outputs :: [Output]
outputs :: PartiallySignedTransaction -> [Output]
outputs
        } = do
        Putter ByteString
S.putByteString "psbt"
        Putter Word8
S.putWord8 0xff -- Header separator

        Putter Word8
S.putWord8 0x01 -- Key size
        Putter Word8
S.putWord8 0x00 -- Unsigned Transaction type
        Put -> Put
putSizedBytes (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ Tx -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize Tx
unsignedTransaction
        Putter UnknownMap
forall t. Serialize t => Putter t
S.put UnknownMap
globalUnknown
        Putter Word8
S.putWord8 0x00 -- Global end

        (Input -> Put) -> [Input] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Input -> Put
forall t. Serialize t => Putter t
S.put [Input]
inputs
        (Output -> Put) -> [Output] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Output -> Put
forall t. Serialize t => Putter t
S.put [Output]
outputs

instance Serialize Key where
    get :: Get Key
get = do
        VarInt keySize :: Word64
keySize <- Get VarInt
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> Bool -> Get ()
forall a b. (a -> b) -> a -> b
$ Word64
keySize Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
> 0
        Word8
t <- Get Word8
S.getWord8
        ByteString
k <- Int -> Get ByteString
S.getBytes (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
keySize Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1)
        Key -> Get Key
forall (m :: * -> *) a. Monad m => a -> m a
return (Word8 -> ByteString -> Key
Key Word8
t ByteString
k)

    put :: Putter Key
put (Key t :: Word8
t k :: ByteString
k) = do
        Int -> Put
forall (m :: * -> *) a. (MonadPut m, Integral a) => a -> m ()
putVarInt (Int -> Put) -> Int -> Put
forall a b. (a -> b) -> a -> b
$ 1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ByteString -> Int
B.length ByteString
k
        Putter Word8
S.putWord8 Word8
t
        Putter ByteString
S.putByteString ByteString
k

instance Serialize UnknownMap where
    get :: Get UnknownMap
get = HashMap Key ByteString -> Get UnknownMap
go HashMap Key ByteString
forall k v. HashMap k v
HashMap.empty
      where
        getItem :: HashMap Key ByteString -> Get UnknownMap
getItem m :: HashMap Key ByteString
m = do
            Key
k <- Get Key
forall t. Serialize t => Get t
S.get
            VarString v :: ByteString
v <- Get VarString
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
            HashMap Key ByteString -> Get UnknownMap
go (HashMap Key ByteString -> Get UnknownMap)
-> HashMap Key ByteString -> Get UnknownMap
forall a b. (a -> b) -> a -> b
$ Key
-> ByteString -> HashMap Key ByteString -> HashMap Key ByteString
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HashMap.insert Key
k ByteString
v HashMap Key ByteString
m
        go :: HashMap Key ByteString -> Get UnknownMap
go m :: HashMap Key ByteString
m = do
            Word8
isEnd <- Get Word8 -> Get Word8
forall a. Get a -> Get a
S.lookAhead Get Word8
S.getWord8
            if Word8
isEnd Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 0x00
                then UnknownMap -> Get UnknownMap
forall (m :: * -> *) a. Monad m => a -> m a
return (HashMap Key ByteString -> UnknownMap
UnknownMap HashMap Key ByteString
m)
                else HashMap Key ByteString -> Get UnknownMap
getItem HashMap Key ByteString
m

    put :: Putter UnknownMap
put (UnknownMap m :: HashMap Key ByteString
m) =
        PutM (HashMap Key ()) -> Put
forall (f :: * -> *) a. Functor f => f a -> f ()
void (PutM (HashMap Key ()) -> Put) -> PutM (HashMap Key ()) -> Put
forall a b. (a -> b) -> a -> b
$
        (Key -> Putter ByteString)
-> HashMap Key ByteString -> PutM (HashMap Key ())
forall (f :: * -> *) k v1 v2.
Applicative f =>
(k -> v1 -> f v2) -> HashMap k v1 -> f (HashMap k v2)
HashMap.traverseWithKey
        (\k :: Key
k v :: ByteString
v -> Putter Key
forall t. Serialize t => Putter t
S.put Key
k Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> VarString -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize (ByteString -> VarString
VarString ByteString
v))
        HashMap Key ByteString
m

instance Serialize Input where
    get :: Get Input
get =
        (Int -> Input -> InputType -> Get Input)
-> ((HashMap Key ByteString -> HashMap Key ByteString)
    -> Input -> Input)
-> Input
-> Get Input
forall t a.
(Bounded t, Enum t) =>
(Int -> a -> t -> Get a)
-> ((HashMap Key ByteString -> HashMap Key ByteString) -> a -> a)
-> a
-> Get a
getMap Int -> Input -> InputType -> Get Input
getInputItem (HashMap Key ByteString -> HashMap Key ByteString)
-> Input -> Input
setInputUnknown Input
emptyInput
      where
        setInputUnknown :: (HashMap Key ByteString -> HashMap Key ByteString)
-> Input -> Input
setInputUnknown f :: HashMap Key ByteString -> HashMap Key ByteString
f input :: Input
input =
            Input
input
            {
                inputUnknown :: UnknownMap
inputUnknown =
                    HashMap Key ByteString -> UnknownMap
UnknownMap (HashMap Key ByteString -> HashMap Key ByteString
f (UnknownMap -> HashMap Key ByteString
unknownMap (Input -> UnknownMap
inputUnknown Input
input)))
            }

    put :: Input -> Put
put Input
        {
            Maybe Tx
nonWitnessUtxo :: Maybe Tx
nonWitnessUtxo :: Input -> Maybe Tx
nonWitnessUtxo,
            Maybe TxOut
witnessUtxo :: Maybe TxOut
witnessUtxo :: Input -> Maybe TxOut
witnessUtxo,
            HashMap PubKeyI ByteString
partialSigs :: HashMap PubKeyI ByteString
partialSigs :: Input -> HashMap PubKeyI ByteString
partialSigs,
            Maybe SigHash
sigHashType :: Maybe SigHash
sigHashType :: Input -> Maybe SigHash
sigHashType,
            Maybe Script
inputRedeemScript :: Maybe Script
inputRedeemScript :: Input -> Maybe Script
inputRedeemScript,
            Maybe Script
inputWitnessScript :: Maybe Script
inputWitnessScript :: Input -> Maybe Script
inputWitnessScript,
            HashMap PubKeyI (Fingerprint, [Fingerprint])
inputHDKeypaths :: HashMap PubKeyI (Fingerprint, [Fingerprint])
inputHDKeypaths :: Input -> HashMap PubKeyI (Fingerprint, [Fingerprint])
inputHDKeypaths,
            Maybe Script
finalScriptSig :: Maybe Script
finalScriptSig :: Input -> Maybe Script
finalScriptSig,
            Maybe WitnessStack
finalScriptWitness :: Maybe WitnessStack
finalScriptWitness :: Input -> Maybe WitnessStack
finalScriptWitness,
            UnknownMap
inputUnknown :: UnknownMap
inputUnknown :: Input -> UnknownMap
inputUnknown
        } = do
        (Tx -> Put) -> Maybe Tx -> Put
forall (m :: * -> *) a. Monad m => (a -> m ()) -> Maybe a -> m ()
whenJust (InputType -> Put -> Put
forall t. Enum t => t -> Put -> Put
putKeyValue InputType
InNonWitnessUtxo (Put -> Put) -> (Tx -> Put) -> Tx -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tx -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize)
            Maybe Tx
nonWitnessUtxo
        (TxOut -> Put) -> Maybe TxOut -> Put
forall (m :: * -> *) a. Monad m => (a -> m ()) -> Maybe a -> m ()
whenJust (InputType -> Put -> Put
forall t. Enum t => t -> Put -> Put
putKeyValue InputType
InWitnessUtxo (Put -> Put) -> (TxOut -> Put) -> TxOut -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOut -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize)
            Maybe TxOut
witnessUtxo
        HashMap PubKeyI ByteString -> Put
putPartialSig HashMap PubKeyI ByteString
partialSigs
        (SigHash -> Put) -> Maybe SigHash -> Put
forall (m :: * -> *) a. Monad m => (a -> m ()) -> Maybe a -> m ()
whenJust SigHash -> Put
forall a. Integral a => a -> Put
putSigHash
            Maybe SigHash
sigHashType
        (Script -> Put) -> Maybe Script -> Put
forall (m :: * -> *) a. Monad m => (a -> m ()) -> Maybe a -> m ()
whenJust (InputType -> Put -> Put
forall t. Enum t => t -> Put -> Put
putKeyValue InputType
InRedeemScript (Put -> Put) -> (Script -> Put) -> Script -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Script -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize)
            Maybe Script
inputRedeemScript
        (Script -> Put) -> Maybe Script -> Put
forall (m :: * -> *) a. Monad m => (a -> m ()) -> Maybe a -> m ()
whenJust (InputType -> Put -> Put
forall t. Enum t => t -> Put -> Put
putKeyValue InputType
InWitnessScript (Put -> Put) -> (Script -> Put) -> Script -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Script -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize)
            Maybe Script
inputWitnessScript
        InputType -> HashMap PubKeyI (Fingerprint, [Fingerprint]) -> Put
forall t.
Enum t =>
t -> HashMap PubKeyI (Fingerprint, [Fingerprint]) -> Put
putHDPath InputType
InBIP32Derivation HashMap PubKeyI (Fingerprint, [Fingerprint])
inputHDKeypaths
        (Script -> Put) -> Maybe Script -> Put
forall (m :: * -> *) a. Monad m => (a -> m ()) -> Maybe a -> m ()
whenJust (InputType -> Put -> Put
forall t. Enum t => t -> Put -> Put
putKeyValue InputType
InFinalScriptSig (Put -> Put) -> (Script -> Put) -> Script -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Script -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize)
            Maybe Script
finalScriptSig
        (WitnessStack -> Put) -> Maybe WitnessStack -> Put
forall (m :: * -> *) a. Monad m => (a -> m ()) -> Maybe a -> m ()
whenJust (InputType -> Put -> Put
forall t. Enum t => t -> Put -> Put
putKeyValue InputType
InFinalScriptWitness (Put -> Put) -> (WitnessStack -> Put) -> WitnessStack -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WitnessStack -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize)
            Maybe WitnessStack
finalScriptWitness
        Putter UnknownMap
forall t. Serialize t => Putter t
S.put UnknownMap
inputUnknown
        Putter Word8
S.putWord8 0x00
      where
        putPartialSig :: HashMap PubKeyI ByteString -> Put
putPartialSig =
            (VarString -> Put) -> InputType -> HashMap PubKeyI VarString -> Put
forall t a. Enum t => (a -> Put) -> t -> HashMap PubKeyI a -> Put
putPubKeyMap VarString -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize InputType
InPartialSig (HashMap PubKeyI VarString -> Put)
-> (HashMap PubKeyI ByteString -> HashMap PubKeyI VarString)
-> HashMap PubKeyI ByteString
-> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> VarString)
-> HashMap PubKeyI ByteString -> HashMap PubKeyI VarString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> VarString
VarString
        putSigHash :: a -> Put
putSigHash sigHash :: a
sigHash = do
            InputType -> Put
forall t. Enum t => t -> Put
putKey InputType
InSigHashType
            Putter Word8
S.putWord8 0x04
            Putter Fingerprint
S.putWord32le (a -> Fingerprint
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
sigHash)

instance Serialize Output where
    get :: Get Output
get = (Int -> Output -> OutputType -> Get Output)
-> ((HashMap Key ByteString -> HashMap Key ByteString)
    -> Output -> Output)
-> Output
-> Get Output
forall t a.
(Bounded t, Enum t) =>
(Int -> a -> t -> Get a)
-> ((HashMap Key ByteString -> HashMap Key ByteString) -> a -> a)
-> a
-> Get a
getMap Int -> Output -> OutputType -> Get Output
getOutputItem (HashMap Key ByteString -> HashMap Key ByteString)
-> Output -> Output
setOutputUnknown Output
emptyOutput
      where
        setOutputUnknown :: (HashMap Key ByteString -> HashMap Key ByteString)
-> Output -> Output
setOutputUnknown f :: HashMap Key ByteString -> HashMap Key ByteString
f output :: Output
output =
            Output
output
            {
                outputUnknown :: UnknownMap
outputUnknown =
                    HashMap Key ByteString -> UnknownMap
UnknownMap (HashMap Key ByteString -> HashMap Key ByteString
f (UnknownMap -> HashMap Key ByteString
unknownMap (Output -> UnknownMap
outputUnknown Output
output)))
            }

    put :: Output -> Put
put Output
        {
            Maybe Script
outputRedeemScript :: Maybe Script
outputRedeemScript :: Output -> Maybe Script
outputRedeemScript,
            Maybe Script
outputWitnessScript :: Maybe Script
outputWitnessScript :: Output -> Maybe Script
outputWitnessScript,
            HashMap PubKeyI (Fingerprint, [Fingerprint])
outputHDKeypaths :: HashMap PubKeyI (Fingerprint, [Fingerprint])
outputHDKeypaths :: Output -> HashMap PubKeyI (Fingerprint, [Fingerprint])
outputHDKeypaths,
            UnknownMap
outputUnknown :: UnknownMap
outputUnknown :: Output -> UnknownMap
outputUnknown
        } = do
        (Script -> Put) -> Maybe Script -> Put
forall (m :: * -> *) a. Monad m => (a -> m ()) -> Maybe a -> m ()
whenJust (OutputType -> Put -> Put
forall t. Enum t => t -> Put -> Put
putKeyValue OutputType
OutRedeemScript (Put -> Put) -> (Script -> Put) -> Script -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Script -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize)
            Maybe Script
outputRedeemScript
        (Script -> Put) -> Maybe Script -> Put
forall (m :: * -> *) a. Monad m => (a -> m ()) -> Maybe a -> m ()
whenJust (OutputType -> Put -> Put
forall t. Enum t => t -> Put -> Put
putKeyValue OutputType
OutWitnessScript (Put -> Put) -> (Script -> Put) -> Script -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Script -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize)
            Maybe Script
outputWitnessScript
        OutputType -> HashMap PubKeyI (Fingerprint, [Fingerprint]) -> Put
forall t.
Enum t =>
t -> HashMap PubKeyI (Fingerprint, [Fingerprint]) -> Put
putHDPath OutputType
OutBIP32Derivation
            HashMap PubKeyI (Fingerprint, [Fingerprint])
outputHDKeypaths
        Putter UnknownMap
forall t. Serialize t => Putter t
S.put UnknownMap
outputUnknown
        Putter Word8
S.putWord8 0x00

putSizedBytes :: Put -> Put
putSizedBytes :: Put -> Put
putSizedBytes f :: Put
f = do
    Int -> Put
forall (m :: * -> *) a. (MonadPut m, Integral a) => a -> m ()
putVarInt (ByteString -> Int
B.length ByteString
bs)
    Putter ByteString
S.putByteString ByteString
bs
  where
    bs :: ByteString
bs = Put -> ByteString
S.runPut Put
f

getSizedBytes :: Get a -> Get a
getSizedBytes :: Get a -> Get a
getSizedBytes f :: Get a
f =
    Get Int -> Get a -> Get a
forall a. Get Int -> Get a -> Get a
S.getNested
    (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int) -> (VarInt -> Word64) -> VarInt -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VarInt -> Word64
getVarInt (VarInt -> Int) -> Get VarInt -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get VarInt
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize)
    Get a
f

putKeyValue :: Enum t => t -> Put -> Put
putKeyValue :: t -> Put -> Put
putKeyValue t :: t
t v :: Put
v = do
    t -> Put
forall t. Enum t => t -> Put
putKey t
t
    Put -> Put
putSizedBytes Put
v

putKey :: Enum t => t -> Put
putKey :: t -> Put
putKey t :: t
t = do
    Putter Word8
forall (m :: * -> *) a. (MonadPut m, Integral a) => a -> m ()
putVarInt (1 :: Word8)
    Putter Word8
S.putWord8 (t -> Word8
forall a. Enum a => a -> Word8
enumWord8 t
t)

getMap :: (Bounded t, Enum t)
       => (Int -> a -> t -> Get a)
       -> ((HashMap Key ByteString -> HashMap Key ByteString) -> a -> a)
       -> a -> Get a
getMap :: (Int -> a -> t -> Get a)
-> ((HashMap Key ByteString -> HashMap Key ByteString) -> a -> a)
-> a
-> Get a
getMap getMapItem :: Int -> a -> t -> Get a
getMapItem setUnknown :: (HashMap Key ByteString -> HashMap Key ByteString) -> a -> a
setUnknown = a -> Get a
go
  where
    getItem :: Word64 -> a -> Either Word8 t -> Get a
getItem keySize :: Word64
keySize m :: a
m (Right t :: t
t) =
        Int -> a -> t -> Get a
getMapItem (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
keySize Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1) a
m t
t Get a -> (a -> Get a) -> Get a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> Get a
go
    getItem keySize :: Word64
keySize m :: a
m (Left t :: Word8
t)  = do
        ByteString
k <- Int -> Get ByteString
S.getBytes (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
keySize Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1)
        VarString v :: ByteString
v <- Get VarString
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
        a -> Get a
go (a -> Get a) -> a -> Get a
forall a b. (a -> b) -> a -> b
$ (HashMap Key ByteString -> HashMap Key ByteString) -> a -> a
setUnknown (Key
-> ByteString -> HashMap Key ByteString -> HashMap Key ByteString
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HashMap.insert (Word8 -> ByteString -> Key
Key Word8
t ByteString
k) ByteString
v) a
m
    go :: a -> Get a
go m :: a
m = do
        Word64
keySize <- VarInt -> Word64
getVarInt (VarInt -> Word64) -> Get VarInt -> Get Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get VarInt
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
        if Word64
keySize Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
== 0
            then a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return a
m
            else Word64 -> a -> Either Word8 t -> Get a
getItem Word64
keySize a
m (Either Word8 t -> Get a) -> Get (Either Word8 t) -> Get a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (Word8 -> Either Word8 t
forall a. (Bounded a, Enum a) => Word8 -> Either Word8 a
word8Enum (Word8 -> Either Word8 t) -> Get Word8 -> Get (Either Word8 t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
S.getWord8)

data InputType
    = InNonWitnessUtxo
    | InWitnessUtxo
    | InPartialSig
    | InSigHashType
    | InRedeemScript
    | InWitnessScript
    | InBIP32Derivation
    | InFinalScriptSig
    | InFinalScriptWitness
    deriving (Int -> InputType -> ShowS
[InputType] -> ShowS
InputType -> String
(Int -> InputType -> ShowS)
-> (InputType -> String)
-> ([InputType] -> ShowS)
-> Show InputType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputType] -> ShowS
$cshowList :: [InputType] -> ShowS
show :: InputType -> String
$cshow :: InputType -> String
showsPrec :: Int -> InputType -> ShowS
$cshowsPrec :: Int -> InputType -> ShowS
Show, InputType -> InputType -> Bool
(InputType -> InputType -> Bool)
-> (InputType -> InputType -> Bool) -> Eq InputType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputType -> InputType -> Bool
$c/= :: InputType -> InputType -> Bool
== :: InputType -> InputType -> Bool
$c== :: InputType -> InputType -> Bool
Eq, Int -> InputType
InputType -> Int
InputType -> [InputType]
InputType -> InputType
InputType -> InputType -> [InputType]
InputType -> InputType -> InputType -> [InputType]
(InputType -> InputType)
-> (InputType -> InputType)
-> (Int -> InputType)
-> (InputType -> Int)
-> (InputType -> [InputType])
-> (InputType -> InputType -> [InputType])
-> (InputType -> InputType -> [InputType])
-> (InputType -> InputType -> InputType -> [InputType])
-> Enum InputType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: InputType -> InputType -> InputType -> [InputType]
$cenumFromThenTo :: InputType -> InputType -> InputType -> [InputType]
enumFromTo :: InputType -> InputType -> [InputType]
$cenumFromTo :: InputType -> InputType -> [InputType]
enumFromThen :: InputType -> InputType -> [InputType]
$cenumFromThen :: InputType -> InputType -> [InputType]
enumFrom :: InputType -> [InputType]
$cenumFrom :: InputType -> [InputType]
fromEnum :: InputType -> Int
$cfromEnum :: InputType -> Int
toEnum :: Int -> InputType
$ctoEnum :: Int -> InputType
pred :: InputType -> InputType
$cpred :: InputType -> InputType
succ :: InputType -> InputType
$csucc :: InputType -> InputType
Enum, InputType
InputType -> InputType -> Bounded InputType
forall a. a -> a -> Bounded a
maxBound :: InputType
$cmaxBound :: InputType
minBound :: InputType
$cminBound :: InputType
Bounded, (forall x. InputType -> Rep InputType x)
-> (forall x. Rep InputType x -> InputType) -> Generic InputType
forall x. Rep InputType x -> InputType
forall x. InputType -> Rep InputType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InputType x -> InputType
$cfrom :: forall x. InputType -> Rep InputType x
Generic)

instance NFData InputType

data OutputType
    = OutRedeemScript
    | OutWitnessScript
    | OutBIP32Derivation
    deriving (Int -> OutputType -> ShowS
[OutputType] -> ShowS
OutputType -> String
(Int -> OutputType -> ShowS)
-> (OutputType -> String)
-> ([OutputType] -> ShowS)
-> Show OutputType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OutputType] -> ShowS
$cshowList :: [OutputType] -> ShowS
show :: OutputType -> String
$cshow :: OutputType -> String
showsPrec :: Int -> OutputType -> ShowS
$cshowsPrec :: Int -> OutputType -> ShowS
Show, OutputType -> OutputType -> Bool
(OutputType -> OutputType -> Bool)
-> (OutputType -> OutputType -> Bool) -> Eq OutputType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutputType -> OutputType -> Bool
$c/= :: OutputType -> OutputType -> Bool
== :: OutputType -> OutputType -> Bool
$c== :: OutputType -> OutputType -> Bool
Eq, Int -> OutputType
OutputType -> Int
OutputType -> [OutputType]
OutputType -> OutputType
OutputType -> OutputType -> [OutputType]
OutputType -> OutputType -> OutputType -> [OutputType]
(OutputType -> OutputType)
-> (OutputType -> OutputType)
-> (Int -> OutputType)
-> (OutputType -> Int)
-> (OutputType -> [OutputType])
-> (OutputType -> OutputType -> [OutputType])
-> (OutputType -> OutputType -> [OutputType])
-> (OutputType -> OutputType -> OutputType -> [OutputType])
-> Enum OutputType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: OutputType -> OutputType -> OutputType -> [OutputType]
$cenumFromThenTo :: OutputType -> OutputType -> OutputType -> [OutputType]
enumFromTo :: OutputType -> OutputType -> [OutputType]
$cenumFromTo :: OutputType -> OutputType -> [OutputType]
enumFromThen :: OutputType -> OutputType -> [OutputType]
$cenumFromThen :: OutputType -> OutputType -> [OutputType]
enumFrom :: OutputType -> [OutputType]
$cenumFrom :: OutputType -> [OutputType]
fromEnum :: OutputType -> Int
$cfromEnum :: OutputType -> Int
toEnum :: Int -> OutputType
$ctoEnum :: Int -> OutputType
pred :: OutputType -> OutputType
$cpred :: OutputType -> OutputType
succ :: OutputType -> OutputType
$csucc :: OutputType -> OutputType
Enum, OutputType
OutputType -> OutputType -> Bounded OutputType
forall a. a -> a -> Bounded a
maxBound :: OutputType
$cmaxBound :: OutputType
minBound :: OutputType
$cminBound :: OutputType
Bounded, (forall x. OutputType -> Rep OutputType x)
-> (forall x. Rep OutputType x -> OutputType) -> Generic OutputType
forall x. Rep OutputType x -> OutputType
forall x. OutputType -> Rep OutputType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OutputType x -> OutputType
$cfrom :: forall x. OutputType -> Rep OutputType x
Generic)

instance NFData OutputType

getInputItem :: Int -> Input -> InputType -> Get Input

getInputItem :: Int -> Input -> InputType -> Get Input
getInputItem 0 input :: Input
input@Input{nonWitnessUtxo :: Input -> Maybe Tx
nonWitnessUtxo = Maybe Tx
Nothing} InNonWitnessUtxo = do
    Tx
utxo <- Get Tx -> Get Tx
forall a. Get a -> Get a
getSizedBytes Get Tx
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
    Input -> Get Input
forall (m :: * -> *) a. Monad m => a -> m a
return Input
input { nonWitnessUtxo :: Maybe Tx
nonWitnessUtxo = Tx -> Maybe Tx
forall a. a -> Maybe a
Just Tx
utxo }

getInputItem 0 input :: Input
input@Input{witnessUtxo :: Input -> Maybe TxOut
witnessUtxo = Maybe TxOut
Nothing} InWitnessUtxo = do
    TxOut
utxo <- Get TxOut -> Get TxOut
forall a. Get a -> Get a
getSizedBytes Get TxOut
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
    Input -> Get Input
forall (m :: * -> *) a. Monad m => a -> m a
return Input
input { witnessUtxo :: Maybe TxOut
witnessUtxo = TxOut -> Maybe TxOut
forall a. a -> Maybe a
Just TxOut
utxo }

getInputItem keySize :: Int
keySize input :: Input
input InPartialSig = do
    (k :: PubKeyI
k, v :: ByteString
v) <- Get (PubKeyI, ByteString)
getPartialSig
    Input -> Get Input
forall (m :: * -> *) a. Monad m => a -> m a
return
        Input
input
        {
            partialSigs :: HashMap PubKeyI ByteString
partialSigs = PubKeyI
-> ByteString
-> HashMap PubKeyI ByteString
-> HashMap PubKeyI ByteString
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HashMap.insert PubKeyI
k ByteString
v (Input -> HashMap PubKeyI ByteString
partialSigs Input
input)
        }
  where
    getPartialSig :: Get (PubKeyI, ByteString)
getPartialSig =
        (,)
        (PubKeyI -> ByteString -> (PubKeyI, ByteString))
-> Get PubKeyI -> Get (ByteString -> (PubKeyI, ByteString))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get PubKeyI -> Get PubKeyI
forall a. Int -> Get a -> Get a
S.isolate Int
keySize Get PubKeyI
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
        Get (ByteString -> (PubKeyI, ByteString))
-> Get ByteString -> Get (PubKeyI, ByteString)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (VarString -> ByteString
getVarString (VarString -> ByteString) -> Get VarString -> Get ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get VarString
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize)

getInputItem 0 input :: Input
input@Input{sigHashType :: Input -> Maybe SigHash
sigHashType = Maybe SigHash
Nothing} InSigHashType = do
    VarInt size :: Word64
size <- Get VarInt
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
    Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> Bool -> Get ()
forall a b. (a -> b) -> a -> b
$ Word64
size Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
== 0x04
    SigHash
sigHash <- Fingerprint -> SigHash
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Fingerprint -> SigHash) -> Get Fingerprint -> Get SigHash
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Fingerprint
S.getWord32le
    Input -> Get Input
forall (m :: * -> *) a. Monad m => a -> m a
return (Input -> Get Input) -> Input -> Get Input
forall a b. (a -> b) -> a -> b
$ Input
input { sigHashType :: Maybe SigHash
sigHashType = SigHash -> Maybe SigHash
forall a. a -> Maybe a
Just SigHash
sigHash }

getInputItem 0 input :: Input
input@Input{inputRedeemScript :: Input -> Maybe Script
inputRedeemScript = Maybe Script
Nothing} InRedeemScript = do
    Script
script <- Get Script -> Get Script
forall a. Get a -> Get a
getSizedBytes Get Script
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
    Input -> Get Input
forall (m :: * -> *) a. Monad m => a -> m a
return (Input -> Get Input) -> Input -> Get Input
forall a b. (a -> b) -> a -> b
$ Input
input { inputRedeemScript :: Maybe Script
inputRedeemScript = Script -> Maybe Script
forall a. a -> Maybe a
Just Script
script }

getInputItem 0 input :: Input
input@Input{inputWitnessScript :: Input -> Maybe Script
inputWitnessScript = Maybe Script
Nothing} InWitnessScript = do
    Script
script <- Get Script -> Get Script
forall a. Get a -> Get a
getSizedBytes Get Script
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
    Input -> Get Input
forall (m :: * -> *) a. Monad m => a -> m a
return (Input -> Get Input) -> Input -> Get Input
forall a b. (a -> b) -> a -> b
$ Input
input { inputWitnessScript :: Maybe Script
inputWitnessScript = Script -> Maybe Script
forall a. a -> Maybe a
Just Script
script }

getInputItem keySize :: Int
keySize input :: Input
input InBIP32Derivation = do
    (k :: PubKeyI
k, v :: (Fingerprint, [Fingerprint])
v) <- Int -> Get (PubKeyI, (Fingerprint, [Fingerprint]))
getHDPath Int
keySize
    Input -> Get Input
forall (m :: * -> *) a. Monad m => a -> m a
return
        Input
input
        {
            inputHDKeypaths :: HashMap PubKeyI (Fingerprint, [Fingerprint])
inputHDKeypaths = PubKeyI
-> (Fingerprint, [Fingerprint])
-> HashMap PubKeyI (Fingerprint, [Fingerprint])
-> HashMap PubKeyI (Fingerprint, [Fingerprint])
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HashMap.insert PubKeyI
k (Fingerprint, [Fingerprint])
v (Input -> HashMap PubKeyI (Fingerprint, [Fingerprint])
inputHDKeypaths Input
input)
        }

getInputItem 0 input :: Input
input@Input{finalScriptSig :: Input -> Maybe Script
finalScriptSig = Maybe Script
Nothing} InFinalScriptSig = do
    Script
script <- Get Script -> Get Script
forall a. Get a -> Get a
getSizedBytes Get Script
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
    Input -> Get Input
forall (m :: * -> *) a. Monad m => a -> m a
return (Input -> Get Input) -> Input -> Get Input
forall a b. (a -> b) -> a -> b
$ Input
input { finalScriptSig :: Maybe Script
finalScriptSig = Script -> Maybe Script
forall a. a -> Maybe a
Just Script
script }

getInputItem 0 input :: Input
input@Input{finalScriptWitness :: Input -> Maybe WitnessStack
finalScriptWitness = Maybe WitnessStack
Nothing} InFinalScriptWitness = do
    WitnessStack
scripts <- (VarString -> ByteString) -> [VarString] -> WitnessStack
forall a b. (a -> b) -> [a] -> [b]
map VarString -> ByteString
getVarString ([VarString] -> WitnessStack)
-> Get [VarString] -> Get WitnessStack
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get [VarString]
getVarIntList
    Input -> Get Input
forall (m :: * -> *) a. Monad m => a -> m a
return (Input -> Get Input) -> Input -> Get Input
forall a b. (a -> b) -> a -> b
$ Input
input { finalScriptWitness :: Maybe WitnessStack
finalScriptWitness = WitnessStack -> Maybe WitnessStack
forall a. a -> Maybe a
Just WitnessStack
scripts }
  where
    getVarIntList :: Get [VarString]
getVarIntList = do
        VarInt n :: Word64
n <- Get VarInt
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
        Int -> Get VarString -> Get [VarString]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
n) Get VarString
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize

getInputItem keySize :: Int
keySize input :: Input
input inputType :: InputType
inputType = String -> Get Input
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get Input) -> String -> Get Input
forall a b. (a -> b) -> a -> b
$
    "Incorrect key size for input item or item already existed: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<>
    (Int, Input, InputType) -> String
forall a. Show a => a -> String
show (Int
keySize, Input
input, InputType
inputType)

getOutputItem :: Int -> Output -> OutputType -> Get Output

getOutputItem :: Int -> Output -> OutputType -> Get Output
getOutputItem 0 output :: Output
output@Output{outputRedeemScript :: Output -> Maybe Script
outputRedeemScript = Maybe Script
Nothing} OutRedeemScript = do
    Script
script <- Get Script -> Get Script
forall a. Get a -> Get a
getSizedBytes Get Script
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
    Output -> Get Output
forall (m :: * -> *) a. Monad m => a -> m a
return (Output -> Get Output) -> Output -> Get Output
forall a b. (a -> b) -> a -> b
$ Output
output { outputRedeemScript :: Maybe Script
outputRedeemScript = Script -> Maybe Script
forall a. a -> Maybe a
Just Script
script }

getOutputItem 0 output :: Output
output@Output{outputWitnessScript :: Output -> Maybe Script
outputWitnessScript = Maybe Script
Nothing} OutWitnessScript = do
    Script
script <- Get Script -> Get Script
forall a. Get a -> Get a
getSizedBytes Get Script
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
    Output -> Get Output
forall (m :: * -> *) a. Monad m => a -> m a
return (Output -> Get Output) -> Output -> Get Output
forall a b. (a -> b) -> a -> b
$ Output
output { outputWitnessScript :: Maybe Script
outputWitnessScript = Script -> Maybe Script
forall a. a -> Maybe a
Just Script
script }

getOutputItem keySize :: Int
keySize output :: Output
output OutBIP32Derivation = do
    (k :: PubKeyI
k, v :: (Fingerprint, [Fingerprint])
v) <- Int -> Get (PubKeyI, (Fingerprint, [Fingerprint]))
getHDPath Int
keySize
    Output -> Get Output
forall (m :: * -> *) a. Monad m => a -> m a
return (Output -> Get Output) -> Output -> Get Output
forall a b. (a -> b) -> a -> b
$ Output
output { outputHDKeypaths :: HashMap PubKeyI (Fingerprint, [Fingerprint])
outputHDKeypaths = PubKeyI
-> (Fingerprint, [Fingerprint])
-> HashMap PubKeyI (Fingerprint, [Fingerprint])
-> HashMap PubKeyI (Fingerprint, [Fingerprint])
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HashMap.insert PubKeyI
k (Fingerprint, [Fingerprint])
v (Output -> HashMap PubKeyI (Fingerprint, [Fingerprint])
outputHDKeypaths Output
output) }

getOutputItem keySize :: Int
keySize output :: Output
output outputType :: OutputType
outputType = String -> Get Output
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get Output) -> String -> Get Output
forall a b. (a -> b) -> a -> b
$
    "Incorrect key size for output item or item already existed: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<>
    (Int, Output, OutputType) -> String
forall a. Show a => a -> String
show (Int
keySize, Output
output, OutputType
outputType)

getHDPath :: Int -> Get (PubKeyI, (Fingerprint, [KeyIndex]))
getHDPath :: Int -> Get (PubKeyI, (Fingerprint, [Fingerprint]))
getHDPath keySize :: Int
keySize =
    (,)
    (PubKeyI
 -> (Fingerprint, [Fingerprint])
 -> (PubKeyI, (Fingerprint, [Fingerprint])))
-> Get PubKeyI
-> Get
     ((Fingerprint, [Fingerprint])
      -> (PubKeyI, (Fingerprint, [Fingerprint])))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get PubKeyI -> Get PubKeyI
forall a. Int -> Get a -> Get a
S.isolate Int
keySize Get PubKeyI
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
    Get
  ((Fingerprint, [Fingerprint])
   -> (PubKeyI, (Fingerprint, [Fingerprint])))
-> Get (Fingerprint, [Fingerprint])
-> Get (PubKeyI, (Fingerprint, [Fingerprint]))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (PSBTHDPath -> (Fingerprint, [Fingerprint])
unPSBTHDPath (PSBTHDPath -> (Fingerprint, [Fingerprint]))
-> Get PSBTHDPath -> Get (Fingerprint, [Fingerprint])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get PSBTHDPath
forall t. Serialize t => Get t
S.get)

putHDPath :: Enum t => t -> HashMap PubKeyI (Fingerprint, [KeyIndex]) -> Put
putHDPath :: t -> HashMap PubKeyI (Fingerprint, [Fingerprint]) -> Put
putHDPath t :: t
t = (PSBTHDPath -> Put) -> t -> HashMap PubKeyI PSBTHDPath -> Put
forall t a. Enum t => (a -> Put) -> t -> HashMap PubKeyI a -> Put
putPubKeyMap PSBTHDPath -> Put
forall t. Serialize t => Putter t
S.put t
t (HashMap PubKeyI PSBTHDPath -> Put)
-> (HashMap PubKeyI (Fingerprint, [Fingerprint])
    -> HashMap PubKeyI PSBTHDPath)
-> HashMap PubKeyI (Fingerprint, [Fingerprint])
-> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Fingerprint, [Fingerprint]) -> PSBTHDPath)
-> HashMap PubKeyI (Fingerprint, [Fingerprint])
-> HashMap PubKeyI PSBTHDPath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Fingerprint, [Fingerprint]) -> PSBTHDPath
PSBTHDPath

newtype PSBTHDPath =
    PSBTHDPath { PSBTHDPath -> (Fingerprint, [Fingerprint])
unPSBTHDPath :: (Fingerprint, [KeyIndex]) }
    deriving (Int -> PSBTHDPath -> ShowS
[PSBTHDPath] -> ShowS
PSBTHDPath -> String
(Int -> PSBTHDPath -> ShowS)
-> (PSBTHDPath -> String)
-> ([PSBTHDPath] -> ShowS)
-> Show PSBTHDPath
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PSBTHDPath] -> ShowS
$cshowList :: [PSBTHDPath] -> ShowS
show :: PSBTHDPath -> String
$cshow :: PSBTHDPath -> String
showsPrec :: Int -> PSBTHDPath -> ShowS
$cshowsPrec :: Int -> PSBTHDPath -> ShowS
Show, PSBTHDPath -> PSBTHDPath -> Bool
(PSBTHDPath -> PSBTHDPath -> Bool)
-> (PSBTHDPath -> PSBTHDPath -> Bool) -> Eq PSBTHDPath
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PSBTHDPath -> PSBTHDPath -> Bool
$c/= :: PSBTHDPath -> PSBTHDPath -> Bool
== :: PSBTHDPath -> PSBTHDPath -> Bool
$c== :: PSBTHDPath -> PSBTHDPath -> Bool
Eq, (forall x. PSBTHDPath -> Rep PSBTHDPath x)
-> (forall x. Rep PSBTHDPath x -> PSBTHDPath) -> Generic PSBTHDPath
forall x. Rep PSBTHDPath x -> PSBTHDPath
forall x. PSBTHDPath -> Rep PSBTHDPath x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PSBTHDPath x -> PSBTHDPath
$cfrom :: forall x. PSBTHDPath -> Rep PSBTHDPath x
Generic)

instance NFData PSBTHDPath

instance Serialize PSBTHDPath where
    get :: Get PSBTHDPath
get = do
        VarInt valueSize :: Word64
valueSize <- Get VarInt
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
        Bool -> Get ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Get ()) -> Bool -> Get ()
forall a b. (a -> b) -> a -> b
$ Word64
valueSize Word64 -> Word64 -> Word64
forall a. Integral a => a -> a -> a
`mod` 4 Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
== 0
        let numIndices :: Int
numIndices = (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
valueSize Int -> Int -> Int
forall a. Num a => a -> a -> a
- 4) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` 4
        (Fingerprint, [Fingerprint]) -> PSBTHDPath
PSBTHDPath ((Fingerprint, [Fingerprint]) -> PSBTHDPath)
-> Get (Fingerprint, [Fingerprint]) -> Get PSBTHDPath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
            Int
-> Get (Fingerprint, [Fingerprint])
-> Get (Fingerprint, [Fingerprint])
forall a. Int -> Get a -> Get a
S.isolate
                (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
valueSize)
                ((,) (Fingerprint -> [Fingerprint] -> (Fingerprint, [Fingerprint]))
-> Get Fingerprint
-> Get ([Fingerprint] -> (Fingerprint, [Fingerprint]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Fingerprint
S.getWord32le Get ([Fingerprint] -> (Fingerprint, [Fingerprint]))
-> Get [Fingerprint] -> Get (Fingerprint, [Fingerprint])
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get [Fingerprint]
getKeyIndexList Int
numIndices)
      where
        getKeyIndexList :: Int -> Get [Fingerprint]
getKeyIndexList n :: Int
n = Int -> Get Fingerprint -> Get [Fingerprint]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n Get Fingerprint
S.getWord32le

    put :: PSBTHDPath -> Put
put (PSBTHDPath (fp :: Fingerprint
fp, kis :: [Fingerprint]
kis)) = do
        Int -> Put
forall (m :: * -> *) a. (MonadPut m, Integral a) => a -> m ()
putVarInt (ByteString -> Int
B.length ByteString
bs)
        Putter ByteString
S.putByteString ByteString
bs
      where
        bs :: ByteString
bs = Put -> ByteString
S.runPut (Put -> ByteString) -> Put -> ByteString
forall a b. (a -> b) -> a -> b
$ Putter Fingerprint
S.putWord32le Fingerprint
fp Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Putter Fingerprint -> [Fingerprint] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Putter Fingerprint
S.putWord32le [Fingerprint]
kis

putPubKeyMap :: Enum t => (a -> Put) -> t -> HashMap PubKeyI a -> Put
putPubKeyMap :: (a -> Put) -> t -> HashMap PubKeyI a -> Put
putPubKeyMap f :: a -> Put
f t :: t
t =
    PutM (HashMap PubKeyI ()) -> Put
forall (f :: * -> *) a. Functor f => f a -> f ()
void (PutM (HashMap PubKeyI ()) -> Put)
-> (HashMap PubKeyI a -> PutM (HashMap PubKeyI ()))
-> HashMap PubKeyI a
-> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PubKeyI -> a -> Put)
-> HashMap PubKeyI a -> PutM (HashMap PubKeyI ())
forall (f :: * -> *) k v1 v2.
Applicative f =>
(k -> v1 -> f v2) -> HashMap k v1 -> f (HashMap k v2)
HashMap.traverseWithKey PubKeyI -> a -> Put
forall a. Serial a => a -> a -> Put
putItem
  where
    putItem :: a -> a -> Put
putItem k :: a
k v :: a
v = do
        Putter Key
forall t. Serialize t => Putter t
S.put Putter Key -> Putter Key
forall a b. (a -> b) -> a -> b
$ Word8 -> ByteString -> Key
Key (t -> Word8
forall a. Enum a => a -> Word8
enumWord8 t
t) (Put -> ByteString
runPutS (a -> Put
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize a
k))
        a -> Put
f a
v

enumWord8 :: Enum a => a -> Word8
enumWord8 :: a -> Word8
enumWord8 = Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word8) -> (a -> Int) -> a -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Int
forall a. Enum a => a -> Int
fromEnum

word8Enum :: forall a. (Bounded a, Enum a) => Word8 -> Either Word8 a
word8Enum :: Word8 -> Either Word8 a
word8Enum n :: Word8
n | Word8
n Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= a -> Word8
forall a. Enum a => a -> Word8
enumWord8 (a
forall a. Bounded a => a
maxBound :: a) = a -> Either Word8 a
forall a b. b -> Either a b
Right (a -> Either Word8 a) -> (Int -> a) -> Int -> Either Word8 a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a
forall a. Enum a => Int -> a
toEnum (Int -> Either Word8 a) -> Int -> Either Word8 a
forall a b. (a -> b) -> a -> b
$ Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
n
word8Enum n :: Word8
n = Word8 -> Either Word8 a
forall a b. a -> Either a b
Left Word8
n

whenJust :: Monad m => (a -> m ()) -> Maybe a -> m ()
whenJust :: (a -> m ()) -> Maybe a -> m ()
whenJust = m () -> (a -> m ()) -> Maybe a -> m ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())