{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
module Ledger.Tx
( module Export
, DecoratedTxOut(..)
, toTxOut
, toTxInfoTxOut
, decoratedTxOutPubKeyHash
, decoratedTxOutAddress
, decoratedTxOutDatum
, decoratedTxOutValue
, decoratedTxOutPubKeyDatum
, decoratedTxOutScriptDatum
, decoratedTxOutStakingCredential
, decoratedTxOutReferenceScript
, decoratedTxOutValidatorHash
, decoratedTxOutValidator
, _PublicKeyDecoratedTxOut
, _ScriptDecoratedTxOut
, _decoratedTxOutAddress
, mkDecoratedTxOut
, mkPubkeyDecoratedTxOut
, mkScriptDecoratedTxOut
, DatumFromQuery(..)
, datumInDatumFromQuery
, CardanoTx(..)
, cardanoApiTx
, emulatorTx
, onCardanoTx
, cardanoTxMap
, getCardanoTxId
, getCardanoTxInputs
, getCardanoTxCollateralInputs
, getCardanoTxOutRefs
, getCardanoTxOutputs
, getCardanoTxRedeemers
, getCardanoTxSpentOutputs
, getCardanoTxProducedOutputs
, getCardanoTxReturnCollateral
, getCardanoTxProducedReturnCollateral
, getCardanoTxTotalCollateral
, getCardanoTxFee
, getCardanoTxMint
, getCardanoTxValidityRange
, getCardanoTxData
, SomeCardanoApiTx(.., CardanoApiEmulatorEraTx)
, ToCardanoError(..)
, addSignature
, addSignature'
, addCardanoTxSignature
, pubKeyTxOut
, updateUtxo
, updateUtxoCollateral
, txOutRefs
, unspentOutputsTx
, getTxBodyContentInputs
, getTxBodyContentCollateralInputs
, getTxBodyContentReturnCollateral
, getTxBodyContentMint
, txBodyContentIns
, txBodyContentCollateralIns
, txBodyContentOuts
, txId
) where
import Cardano.Api qualified as C
import Cardano.Api.Shelley qualified as C.Api
import Cardano.Crypto.Hash (SHA256, digest)
import Cardano.Crypto.Wallet qualified as Crypto
import Cardano.Ledger.Alonzo.Tx (ValidatedTx (..))
import Cardano.Ledger.Alonzo.TxWitness (txwitsVKey)
import Codec.CBOR.Write qualified as Write
import Codec.Serialise (Serialise (encode))
import Control.DeepSeq (NFData)
import Control.Lens (At (at), Getter, Lens', Traversal', lens, makeLenses, makePrisms, to, views, (&), (?~), (^.), (^?))
import Data.Aeson (FromJSON, ToJSON)
import Data.Data (Proxy (Proxy))
import Data.Map (Map)
import Data.Map qualified as Map
import Data.Maybe (isJust)
import Data.OpenApi qualified as OpenApi
import Data.Set (Set)
import Data.Set qualified as Set
import Data.Tuple (swap)
import GHC.Generics (Generic)
import Ledger.Address (Address, CardanoAddress, PaymentPubKey, cardanoAddressCredential, cardanoStakingCredential,
pubKeyAddress)
import Ledger.Crypto (Passphrase, signTx, signTx', toPublicKey)
import Ledger.Orphans ()
import Ledger.Slot (SlotRange)
import Ledger.Tx.CardanoAPI (SomeCardanoApiTx (SomeTx), ToCardanoError (..))
import Ledger.Tx.CardanoAPI qualified as CardanoAPI
import Plutus.Script.Utils.Scripts (scriptHash)
import Plutus.V1.Ledger.Api qualified as V1
import Plutus.V1.Ledger.Tx qualified as V1.Tx hiding (TxIn (..), TxInType (..))
import Plutus.V2.Ledger.Api qualified as V2
import Plutus.V2.Ledger.Tx qualified as V2.Tx hiding (TxIn (..), TxInType (..))
import Prettyprinter (Pretty (pretty), braces, colon, hang, nest, viaShow, vsep, (<+>))
import Ledger.Tx.Internal as Export
import Plutus.V1.Ledger.Tx as Export hiding (TxIn (..), TxInType (..), TxOut (..), inRef, inScripts, inType, outAddress,
outValue, pubKeyTxIn, pubKeyTxIns, scriptTxIn, scriptTxIns, txOutPubKey)
data DatumFromQuery
= DatumUnknown
| DatumInline V2.Datum
| DatumInBody V2.Datum
deriving (Int -> DatumFromQuery -> ShowS
[DatumFromQuery] -> ShowS
DatumFromQuery -> String
(Int -> DatumFromQuery -> ShowS)
-> (DatumFromQuery -> String)
-> ([DatumFromQuery] -> ShowS)
-> Show DatumFromQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DatumFromQuery] -> ShowS
$cshowList :: [DatumFromQuery] -> ShowS
show :: DatumFromQuery -> String
$cshow :: DatumFromQuery -> String
showsPrec :: Int -> DatumFromQuery -> ShowS
$cshowsPrec :: Int -> DatumFromQuery -> ShowS
Show, DatumFromQuery -> DatumFromQuery -> Bool
(DatumFromQuery -> DatumFromQuery -> Bool)
-> (DatumFromQuery -> DatumFromQuery -> Bool) -> Eq DatumFromQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DatumFromQuery -> DatumFromQuery -> Bool
$c/= :: DatumFromQuery -> DatumFromQuery -> Bool
== :: DatumFromQuery -> DatumFromQuery -> Bool
$c== :: DatumFromQuery -> DatumFromQuery -> Bool
Eq, [DatumFromQuery] -> Encoding
DatumFromQuery -> Encoding
(DatumFromQuery -> Encoding)
-> (forall s. Decoder s DatumFromQuery)
-> ([DatumFromQuery] -> Encoding)
-> (forall s. Decoder s [DatumFromQuery])
-> Serialise DatumFromQuery
forall s. Decoder s [DatumFromQuery]
forall s. Decoder s DatumFromQuery
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
decodeList :: Decoder s [DatumFromQuery]
$cdecodeList :: forall s. Decoder s [DatumFromQuery]
encodeList :: [DatumFromQuery] -> Encoding
$cencodeList :: [DatumFromQuery] -> Encoding
decode :: Decoder s DatumFromQuery
$cdecode :: forall s. Decoder s DatumFromQuery
encode :: DatumFromQuery -> Encoding
$cencode :: DatumFromQuery -> Encoding
Serialise, (forall x. DatumFromQuery -> Rep DatumFromQuery x)
-> (forall x. Rep DatumFromQuery x -> DatumFromQuery)
-> Generic DatumFromQuery
forall x. Rep DatumFromQuery x -> DatumFromQuery
forall x. DatumFromQuery -> Rep DatumFromQuery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DatumFromQuery x -> DatumFromQuery
$cfrom :: forall x. DatumFromQuery -> Rep DatumFromQuery x
Generic, [DatumFromQuery] -> Encoding
[DatumFromQuery] -> Value
DatumFromQuery -> Encoding
DatumFromQuery -> Value
(DatumFromQuery -> Value)
-> (DatumFromQuery -> Encoding)
-> ([DatumFromQuery] -> Value)
-> ([DatumFromQuery] -> Encoding)
-> ToJSON DatumFromQuery
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DatumFromQuery] -> Encoding
$ctoEncodingList :: [DatumFromQuery] -> Encoding
toJSONList :: [DatumFromQuery] -> Value
$ctoJSONList :: [DatumFromQuery] -> Value
toEncoding :: DatumFromQuery -> Encoding
$ctoEncoding :: DatumFromQuery -> Encoding
toJSON :: DatumFromQuery -> Value
$ctoJSON :: DatumFromQuery -> Value
ToJSON, Value -> Parser [DatumFromQuery]
Value -> Parser DatumFromQuery
(Value -> Parser DatumFromQuery)
-> (Value -> Parser [DatumFromQuery]) -> FromJSON DatumFromQuery
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DatumFromQuery]
$cparseJSONList :: Value -> Parser [DatumFromQuery]
parseJSON :: Value -> Parser DatumFromQuery
$cparseJSON :: Value -> Parser DatumFromQuery
FromJSON, DatumFromQuery -> ()
(DatumFromQuery -> ()) -> NFData DatumFromQuery
forall a. (a -> ()) -> NFData a
rnf :: DatumFromQuery -> ()
$crnf :: DatumFromQuery -> ()
NFData, Typeable DatumFromQuery
Typeable DatumFromQuery
-> (Proxy DatumFromQuery
-> Declare (Definitions Schema) NamedSchema)
-> ToSchema DatumFromQuery
Proxy DatumFromQuery -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a
-> (Proxy a -> Declare (Definitions Schema) NamedSchema)
-> ToSchema a
declareNamedSchema :: Proxy DatumFromQuery -> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy DatumFromQuery -> Declare (Definitions Schema) NamedSchema
$cp1ToSchema :: Typeable DatumFromQuery
OpenApi.ToSchema)
makePrisms ''DatumFromQuery
datumInDatumFromQuery :: Traversal' DatumFromQuery V2.Datum
datumInDatumFromQuery :: (Datum -> f Datum) -> DatumFromQuery -> f DatumFromQuery
datumInDatumFromQuery Datum -> f Datum
_ DatumFromQuery
DatumUnknown = DatumFromQuery -> f DatumFromQuery
forall (f :: * -> *) a. Applicative f => a -> f a
pure DatumFromQuery
DatumUnknown
datumInDatumFromQuery Datum -> f Datum
f (DatumInline Datum
d) = Datum -> DatumFromQuery
DatumInline (Datum -> DatumFromQuery) -> f Datum -> f DatumFromQuery
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Datum -> f Datum
f Datum
d
datumInDatumFromQuery Datum -> f Datum
f (DatumInBody Datum
d) = Datum -> DatumFromQuery
DatumInBody (Datum -> DatumFromQuery) -> f Datum -> f DatumFromQuery
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Datum -> f Datum
f Datum
d
data DecoratedTxOut =
PublicKeyDecoratedTxOut {
DecoratedTxOut -> PubKeyHash
_decoratedTxOutPubKeyHash :: V1.PubKeyHash,
DecoratedTxOut -> Maybe StakingCredential
_decoratedTxOutStakingCredential :: Maybe V1.StakingCredential,
DecoratedTxOut -> Value
_decoratedTxOutValue :: V2.Value,
DecoratedTxOut -> Maybe (DatumHash, DatumFromQuery)
_decoratedTxOutPubKeyDatum :: Maybe (V2.DatumHash, DatumFromQuery),
DecoratedTxOut -> Maybe (Versioned Script)
_decoratedTxOutReferenceScript :: Maybe (Versioned V1.Script)
}
| ScriptDecoratedTxOut {
DecoratedTxOut -> ValidatorHash
_decoratedTxOutValidatorHash :: V1.ValidatorHash,
_decoratedTxOutStakingCredential :: Maybe V1.StakingCredential,
_decoratedTxOutValue :: V2.Value,
DecoratedTxOut -> (DatumHash, DatumFromQuery)
_decoratedTxOutScriptDatum :: (V2.DatumHash, DatumFromQuery),
_decoratedTxOutReferenceScript :: Maybe (Versioned V1.Script),
DecoratedTxOut -> Maybe (Versioned Validator)
_decoratedTxOutValidator :: Maybe (Versioned V1.Validator)
}
deriving (Int -> DecoratedTxOut -> ShowS
[DecoratedTxOut] -> ShowS
DecoratedTxOut -> String
(Int -> DecoratedTxOut -> ShowS)
-> (DecoratedTxOut -> String)
-> ([DecoratedTxOut] -> ShowS)
-> Show DecoratedTxOut
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecoratedTxOut] -> ShowS
$cshowList :: [DecoratedTxOut] -> ShowS
show :: DecoratedTxOut -> String
$cshow :: DecoratedTxOut -> String
showsPrec :: Int -> DecoratedTxOut -> ShowS
$cshowsPrec :: Int -> DecoratedTxOut -> ShowS
Show, DecoratedTxOut -> DecoratedTxOut -> Bool
(DecoratedTxOut -> DecoratedTxOut -> Bool)
-> (DecoratedTxOut -> DecoratedTxOut -> Bool) -> Eq DecoratedTxOut
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecoratedTxOut -> DecoratedTxOut -> Bool
$c/= :: DecoratedTxOut -> DecoratedTxOut -> Bool
== :: DecoratedTxOut -> DecoratedTxOut -> Bool
$c== :: DecoratedTxOut -> DecoratedTxOut -> Bool
Eq, [DecoratedTxOut] -> Encoding
DecoratedTxOut -> Encoding
(DecoratedTxOut -> Encoding)
-> (forall s. Decoder s DecoratedTxOut)
-> ([DecoratedTxOut] -> Encoding)
-> (forall s. Decoder s [DecoratedTxOut])
-> Serialise DecoratedTxOut
forall s. Decoder s [DecoratedTxOut]
forall s. Decoder s DecoratedTxOut
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
decodeList :: Decoder s [DecoratedTxOut]
$cdecodeList :: forall s. Decoder s [DecoratedTxOut]
encodeList :: [DecoratedTxOut] -> Encoding
$cencodeList :: [DecoratedTxOut] -> Encoding
decode :: Decoder s DecoratedTxOut
$cdecode :: forall s. Decoder s DecoratedTxOut
encode :: DecoratedTxOut -> Encoding
$cencode :: DecoratedTxOut -> Encoding
Serialise, (forall x. DecoratedTxOut -> Rep DecoratedTxOut x)
-> (forall x. Rep DecoratedTxOut x -> DecoratedTxOut)
-> Generic DecoratedTxOut
forall x. Rep DecoratedTxOut x -> DecoratedTxOut
forall x. DecoratedTxOut -> Rep DecoratedTxOut x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DecoratedTxOut x -> DecoratedTxOut
$cfrom :: forall x. DecoratedTxOut -> Rep DecoratedTxOut x
Generic, [DecoratedTxOut] -> Encoding
[DecoratedTxOut] -> Value
DecoratedTxOut -> Encoding
DecoratedTxOut -> Value
(DecoratedTxOut -> Value)
-> (DecoratedTxOut -> Encoding)
-> ([DecoratedTxOut] -> Value)
-> ([DecoratedTxOut] -> Encoding)
-> ToJSON DecoratedTxOut
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DecoratedTxOut] -> Encoding
$ctoEncodingList :: [DecoratedTxOut] -> Encoding
toJSONList :: [DecoratedTxOut] -> Value
$ctoJSONList :: [DecoratedTxOut] -> Value
toEncoding :: DecoratedTxOut -> Encoding
$ctoEncoding :: DecoratedTxOut -> Encoding
toJSON :: DecoratedTxOut -> Value
$ctoJSON :: DecoratedTxOut -> Value
ToJSON, Value -> Parser [DecoratedTxOut]
Value -> Parser DecoratedTxOut
(Value -> Parser DecoratedTxOut)
-> (Value -> Parser [DecoratedTxOut]) -> FromJSON DecoratedTxOut
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DecoratedTxOut]
$cparseJSONList :: Value -> Parser [DecoratedTxOut]
parseJSON :: Value -> Parser DecoratedTxOut
$cparseJSON :: Value -> Parser DecoratedTxOut
FromJSON, DecoratedTxOut -> ()
(DecoratedTxOut -> ()) -> NFData DecoratedTxOut
forall a. (a -> ()) -> NFData a
rnf :: DecoratedTxOut -> ()
$crnf :: DecoratedTxOut -> ()
NFData, Typeable DecoratedTxOut
Typeable DecoratedTxOut
-> (Proxy DecoratedTxOut
-> Declare (Definitions Schema) NamedSchema)
-> ToSchema DecoratedTxOut
Proxy DecoratedTxOut -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a
-> (Proxy a -> Declare (Definitions Schema) NamedSchema)
-> ToSchema a
declareNamedSchema :: Proxy DecoratedTxOut -> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy DecoratedTxOut -> Declare (Definitions Schema) NamedSchema
$cp1ToSchema :: Typeable DecoratedTxOut
OpenApi.ToSchema)
makeLenses ''DecoratedTxOut
makePrisms ''DecoratedTxOut
mkDecoratedTxOut
:: CardanoAddress -> V2.Value -> (V2.DatumHash, DatumFromQuery) -> Maybe (Versioned V1.Script)
-> DecoratedTxOut
mkDecoratedTxOut :: CardanoAddress
-> Value
-> (DatumHash, DatumFromQuery)
-> Maybe (Versioned Script)
-> DecoratedTxOut
mkDecoratedTxOut CardanoAddress
a Value
v (DatumHash, DatumFromQuery)
dat Maybe (Versioned Script)
rs = let
sc :: Maybe StakingCredential
sc = CardanoAddress -> Maybe StakingCredential
forall era. AddressInEra era -> Maybe StakingCredential
cardanoStakingCredential CardanoAddress
a
in case CardanoAddress -> Credential
forall era. AddressInEra era -> Credential
cardanoAddressCredential CardanoAddress
a of
(V2.PubKeyCredential PubKeyHash
c) -> PubKeyHash
-> Maybe StakingCredential
-> Value
-> Maybe (DatumHash, DatumFromQuery)
-> Maybe (Versioned Script)
-> DecoratedTxOut
PublicKeyDecoratedTxOut PubKeyHash
c Maybe StakingCredential
sc Value
v ((DatumHash, DatumFromQuery) -> Maybe (DatumHash, DatumFromQuery)
forall a. a -> Maybe a
Just (DatumHash, DatumFromQuery)
dat) Maybe (Versioned Script)
rs
(V2.ScriptCredential ValidatorHash
c) -> ValidatorHash
-> Maybe StakingCredential
-> Value
-> (DatumHash, DatumFromQuery)
-> Maybe (Versioned Script)
-> Maybe (Versioned Validator)
-> DecoratedTxOut
ScriptDecoratedTxOut ValidatorHash
c Maybe StakingCredential
sc Value
v (DatumHash, DatumFromQuery)
dat Maybe (Versioned Script)
rs Maybe (Versioned Validator)
forall a. Maybe a
Nothing
mkPubkeyDecoratedTxOut
:: CardanoAddress -> V2.Value -> Maybe (V2.DatumHash, DatumFromQuery) -> Maybe (Versioned V1.Script)
-> Maybe DecoratedTxOut
mkPubkeyDecoratedTxOut :: CardanoAddress
-> Value
-> Maybe (DatumHash, DatumFromQuery)
-> Maybe (Versioned Script)
-> Maybe DecoratedTxOut
mkPubkeyDecoratedTxOut CardanoAddress
a Value
v Maybe (DatumHash, DatumFromQuery)
dat Maybe (Versioned Script)
rs = let
sc :: Maybe StakingCredential
sc = CardanoAddress -> Maybe StakingCredential
forall era. AddressInEra era -> Maybe StakingCredential
cardanoStakingCredential CardanoAddress
a
in case CardanoAddress -> Credential
forall era. AddressInEra era -> Credential
cardanoAddressCredential CardanoAddress
a of
(V2.PubKeyCredential PubKeyHash
c) -> DecoratedTxOut -> Maybe DecoratedTxOut
forall a. a -> Maybe a
Just (DecoratedTxOut -> Maybe DecoratedTxOut)
-> DecoratedTxOut -> Maybe DecoratedTxOut
forall a b. (a -> b) -> a -> b
$ PubKeyHash
-> Maybe StakingCredential
-> Value
-> Maybe (DatumHash, DatumFromQuery)
-> Maybe (Versioned Script)
-> DecoratedTxOut
PublicKeyDecoratedTxOut PubKeyHash
c Maybe StakingCredential
sc Value
v Maybe (DatumHash, DatumFromQuery)
dat Maybe (Versioned Script)
rs
Credential
_ -> Maybe DecoratedTxOut
forall a. Maybe a
Nothing
mkScriptDecoratedTxOut
:: CardanoAddress
-> V2.Value
-> (V2.DatumHash, DatumFromQuery)
-> Maybe (Versioned V1.Script)
-> Maybe (Versioned V1.Validator)
-> Maybe DecoratedTxOut
mkScriptDecoratedTxOut :: CardanoAddress
-> Value
-> (DatumHash, DatumFromQuery)
-> Maybe (Versioned Script)
-> Maybe (Versioned Validator)
-> Maybe DecoratedTxOut
mkScriptDecoratedTxOut CardanoAddress
a Value
v (DatumHash, DatumFromQuery)
dat Maybe (Versioned Script)
rs Maybe (Versioned Validator)
val = let
sc :: Maybe StakingCredential
sc = CardanoAddress -> Maybe StakingCredential
forall era. AddressInEra era -> Maybe StakingCredential
cardanoStakingCredential CardanoAddress
a
in case CardanoAddress -> Credential
forall era. AddressInEra era -> Credential
cardanoAddressCredential CardanoAddress
a of
(V2.ScriptCredential ValidatorHash
c) -> DecoratedTxOut -> Maybe DecoratedTxOut
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DecoratedTxOut -> Maybe DecoratedTxOut)
-> DecoratedTxOut -> Maybe DecoratedTxOut
forall a b. (a -> b) -> a -> b
$ ValidatorHash
-> Maybe StakingCredential
-> Value
-> (DatumHash, DatumFromQuery)
-> Maybe (Versioned Script)
-> Maybe (Versioned Validator)
-> DecoratedTxOut
ScriptDecoratedTxOut ValidatorHash
c Maybe StakingCredential
sc Value
v (DatumHash, DatumFromQuery)
dat Maybe (Versioned Script)
rs Maybe (Versioned Validator)
val
Credential
_ -> Maybe DecoratedTxOut
forall a. Maybe a
Nothing
_decoratedTxOutAddress :: DecoratedTxOut -> Address
_decoratedTxOutAddress :: DecoratedTxOut -> Address
_decoratedTxOutAddress PublicKeyDecoratedTxOut{PubKeyHash
_decoratedTxOutPubKeyHash :: PubKeyHash
_decoratedTxOutPubKeyHash :: DecoratedTxOut -> PubKeyHash
_decoratedTxOutPubKeyHash, Maybe StakingCredential
_decoratedTxOutStakingCredential :: Maybe StakingCredential
_decoratedTxOutStakingCredential :: DecoratedTxOut -> Maybe StakingCredential
_decoratedTxOutStakingCredential} =
Credential -> Maybe StakingCredential -> Address
V1.Address (PubKeyHash -> Credential
V1.PubKeyCredential PubKeyHash
_decoratedTxOutPubKeyHash) Maybe StakingCredential
_decoratedTxOutStakingCredential
_decoratedTxOutAddress ScriptDecoratedTxOut{ValidatorHash
_decoratedTxOutValidatorHash :: ValidatorHash
_decoratedTxOutValidatorHash :: DecoratedTxOut -> ValidatorHash
_decoratedTxOutValidatorHash, Maybe StakingCredential
_decoratedTxOutStakingCredential :: Maybe StakingCredential
_decoratedTxOutStakingCredential :: DecoratedTxOut -> Maybe StakingCredential
_decoratedTxOutStakingCredential} =
Credential -> Maybe StakingCredential -> Address
V1.Address (ValidatorHash -> Credential
V1.ScriptCredential ValidatorHash
_decoratedTxOutValidatorHash) Maybe StakingCredential
_decoratedTxOutStakingCredential
decoratedTxOutAddress :: Getter DecoratedTxOut Address
decoratedTxOutAddress :: (Address -> f Address) -> DecoratedTxOut -> f DecoratedTxOut
decoratedTxOutAddress = (DecoratedTxOut -> Address)
-> (Address -> f Address) -> DecoratedTxOut -> f DecoratedTxOut
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to DecoratedTxOut -> Address
_decoratedTxOutAddress
decoratedTxOutDatum :: Traversal' DecoratedTxOut (V2.DatumHash, DatumFromQuery)
decoratedTxOutDatum :: ((DatumHash, DatumFromQuery) -> f (DatumHash, DatumFromQuery))
-> DecoratedTxOut -> f DecoratedTxOut
decoratedTxOutDatum (DatumHash, DatumFromQuery) -> f (DatumHash, DatumFromQuery)
f p :: DecoratedTxOut
p@(PublicKeyDecoratedTxOut PubKeyHash
pkh Maybe StakingCredential
sc Value
v Maybe (DatumHash, DatumFromQuery)
dat Maybe (Versioned Script)
rs) =
f DecoratedTxOut
-> ((DatumHash, DatumFromQuery) -> f DecoratedTxOut)
-> Maybe (DatumHash, DatumFromQuery)
-> f DecoratedTxOut
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (DecoratedTxOut -> f DecoratedTxOut
forall (f :: * -> *) a. Applicative f => a -> f a
pure DecoratedTxOut
p) (((DatumHash, DatumFromQuery) -> DecoratedTxOut)
-> f (DatumHash, DatumFromQuery) -> f DecoratedTxOut
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ (DatumHash, DatumFromQuery)
dat' -> PubKeyHash
-> Maybe StakingCredential
-> Value
-> Maybe (DatumHash, DatumFromQuery)
-> Maybe (Versioned Script)
-> DecoratedTxOut
PublicKeyDecoratedTxOut PubKeyHash
pkh Maybe StakingCredential
sc Value
v ((DatumHash, DatumFromQuery) -> Maybe (DatumHash, DatumFromQuery)
forall a. a -> Maybe a
Just (DatumHash, DatumFromQuery)
dat') Maybe (Versioned Script)
rs) (f (DatumHash, DatumFromQuery) -> f DecoratedTxOut)
-> ((DatumHash, DatumFromQuery) -> f (DatumHash, DatumFromQuery))
-> (DatumHash, DatumFromQuery)
-> f DecoratedTxOut
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DatumHash, DatumFromQuery) -> f (DatumHash, DatumFromQuery)
f) Maybe (DatumHash, DatumFromQuery)
dat
decoratedTxOutDatum (DatumHash, DatumFromQuery) -> f (DatumHash, DatumFromQuery)
f (ScriptDecoratedTxOut ValidatorHash
vh Maybe StakingCredential
sc Value
v (DatumHash, DatumFromQuery)
dat Maybe (Versioned Script)
rs Maybe (Versioned Validator)
val) =
(\(DatumHash, DatumFromQuery)
dat' -> ValidatorHash
-> Maybe StakingCredential
-> Value
-> (DatumHash, DatumFromQuery)
-> Maybe (Versioned Script)
-> Maybe (Versioned Validator)
-> DecoratedTxOut
ScriptDecoratedTxOut ValidatorHash
vh Maybe StakingCredential
sc Value
v (DatumHash, DatumFromQuery)
dat' Maybe (Versioned Script)
rs Maybe (Versioned Validator)
val) ((DatumHash, DatumFromQuery) -> DecoratedTxOut)
-> f (DatumHash, DatumFromQuery) -> f DecoratedTxOut
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (DatumHash, DatumFromQuery) -> f (DatumHash, DatumFromQuery)
f (DatumHash, DatumFromQuery)
dat
toTxOut :: C.NetworkId -> DecoratedTxOut -> Either ToCardanoError TxOut
toTxOut :: NetworkId -> DecoratedTxOut -> Either ToCardanoError TxOut
toTxOut NetworkId
networkId DecoratedTxOut
p =
TxOut CtxTx BabbageEra -> TxOut
TxOut (TxOut CtxTx BabbageEra -> TxOut)
-> Either ToCardanoError (TxOut CtxTx BabbageEra)
-> Either ToCardanoError TxOut
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CardanoAddress
-> TxOutValue BabbageEra
-> TxOutDatum CtxTx BabbageEra
-> ReferenceScript BabbageEra
-> TxOut CtxTx BabbageEra
forall ctx era.
AddressInEra era
-> TxOutValue era
-> TxOutDatum ctx era
-> ReferenceScript era
-> TxOut ctx era
C.TxOut
(CardanoAddress
-> TxOutValue BabbageEra
-> TxOutDatum CtxTx BabbageEra
-> ReferenceScript BabbageEra
-> TxOut CtxTx BabbageEra)
-> Either ToCardanoError CardanoAddress
-> Either
ToCardanoError
(TxOutValue BabbageEra
-> TxOutDatum CtxTx BabbageEra
-> ReferenceScript BabbageEra
-> TxOut CtxTx BabbageEra)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NetworkId -> Address -> Either ToCardanoError CardanoAddress
CardanoAPI.toCardanoAddressInEra NetworkId
networkId (DecoratedTxOut
p DecoratedTxOut -> Getting Address DecoratedTxOut Address -> Address
forall s a. s -> Getting a s a -> a
^. Getting Address DecoratedTxOut Address
Getter DecoratedTxOut Address
decoratedTxOutAddress)
Either
ToCardanoError
(TxOutValue BabbageEra
-> TxOutDatum CtxTx BabbageEra
-> ReferenceScript BabbageEra
-> TxOut CtxTx BabbageEra)
-> Either ToCardanoError (TxOutValue BabbageEra)
-> Either
ToCardanoError
(TxOutDatum CtxTx BabbageEra
-> ReferenceScript BabbageEra -> TxOut CtxTx BabbageEra)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Value -> Either ToCardanoError (TxOutValue BabbageEra)
CardanoAPI.toCardanoTxOutValue (DecoratedTxOut
p DecoratedTxOut -> Getting Value DecoratedTxOut Value -> Value
forall s a. s -> Getting a s a -> a
^. Getting Value DecoratedTxOut Value
Lens' DecoratedTxOut Value
decoratedTxOutValue)
Either
ToCardanoError
(TxOutDatum CtxTx BabbageEra
-> ReferenceScript BabbageEra -> TxOut CtxTx BabbageEra)
-> Either ToCardanoError (TxOutDatum CtxTx BabbageEra)
-> Either
ToCardanoError
(ReferenceScript BabbageEra -> TxOut CtxTx BabbageEra)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Maybe (DatumHash, DatumFromQuery)
-> Either ToCardanoError (TxOutDatum CtxTx BabbageEra)
toTxOutDatum (Maybe (DatumHash, DatumFromQuery)
-> Either ToCardanoError (TxOutDatum CtxTx BabbageEra))
-> Maybe (DatumHash, DatumFromQuery)
-> Either ToCardanoError (TxOutDatum CtxTx BabbageEra)
forall a b. (a -> b) -> a -> b
$ DecoratedTxOut
p DecoratedTxOut
-> Getting
(First (DatumHash, DatumFromQuery))
DecoratedTxOut
(DatumHash, DatumFromQuery)
-> Maybe (DatumHash, DatumFromQuery)
forall s a. s -> Getting (First a) s a -> Maybe a
^? Getting
(First (DatumHash, DatumFromQuery))
DecoratedTxOut
(DatumHash, DatumFromQuery)
Traversal' DecoratedTxOut (DatumHash, DatumFromQuery)
decoratedTxOutDatum)
Either
ToCardanoError
(ReferenceScript BabbageEra -> TxOut CtxTx BabbageEra)
-> Either ToCardanoError (ReferenceScript BabbageEra)
-> Either ToCardanoError (TxOut CtxTx BabbageEra)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe (Versioned Script)
-> Either ToCardanoError (ReferenceScript BabbageEra)
CardanoAPI.toCardanoReferenceScript (DecoratedTxOut
p DecoratedTxOut
-> Getting
(Maybe (Versioned Script))
DecoratedTxOut
(Maybe (Versioned Script))
-> Maybe (Versioned Script)
forall s a. s -> Getting a s a -> a
^. Getting
(Maybe (Versioned Script))
DecoratedTxOut
(Maybe (Versioned Script))
Lens' DecoratedTxOut (Maybe (Versioned Script))
decoratedTxOutReferenceScript))
toTxOutDatum :: Maybe (V2.DatumHash, DatumFromQuery) -> Either ToCardanoError (C.TxOutDatum C.CtxTx C.BabbageEra)
toTxOutDatum :: Maybe (DatumHash, DatumFromQuery)
-> Either ToCardanoError (TxOutDatum CtxTx BabbageEra)
toTxOutDatum = OutputDatum -> Either ToCardanoError (TxOutDatum CtxTx BabbageEra)
CardanoAPI.toCardanoTxOutDatum (OutputDatum
-> Either ToCardanoError (TxOutDatum CtxTx BabbageEra))
-> (Maybe (DatumHash, DatumFromQuery) -> OutputDatum)
-> Maybe (DatumHash, DatumFromQuery)
-> Either ToCardanoError (TxOutDatum CtxTx BabbageEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (DatumHash, DatumFromQuery) -> OutputDatum
toPlutusOutputDatum
toTxInfoTxOut :: DecoratedTxOut -> V2.Tx.TxOut
toTxInfoTxOut :: DecoratedTxOut -> TxOut
toTxInfoTxOut DecoratedTxOut
p =
Address -> Value -> OutputDatum -> Maybe ScriptHash -> TxOut
V2.Tx.TxOut (DecoratedTxOut
p DecoratedTxOut -> Getting Address DecoratedTxOut Address -> Address
forall s a. s -> Getting a s a -> a
^. Getting Address DecoratedTxOut Address
Getter DecoratedTxOut Address
decoratedTxOutAddress) (DecoratedTxOut
p DecoratedTxOut -> Getting Value DecoratedTxOut Value -> Value
forall s a. s -> Getting a s a -> a
^. Getting Value DecoratedTxOut Value
Lens' DecoratedTxOut Value
decoratedTxOutValue)
(Maybe (DatumHash, DatumFromQuery) -> OutputDatum
toPlutusOutputDatum (Maybe (DatumHash, DatumFromQuery) -> OutputDatum)
-> Maybe (DatumHash, DatumFromQuery) -> OutputDatum
forall a b. (a -> b) -> a -> b
$ DecoratedTxOut
p DecoratedTxOut
-> Getting
(First (DatumHash, DatumFromQuery))
DecoratedTxOut
(DatumHash, DatumFromQuery)
-> Maybe (DatumHash, DatumFromQuery)
forall s a. s -> Getting (First a) s a -> Maybe a
^? Getting
(First (DatumHash, DatumFromQuery))
DecoratedTxOut
(DatumHash, DatumFromQuery)
Traversal' DecoratedTxOut (DatumHash, DatumFromQuery)
decoratedTxOutDatum)
(LensLike'
(Const (Maybe ScriptHash))
DecoratedTxOut
(Maybe (Versioned Script))
-> (Maybe (Versioned Script) -> Maybe ScriptHash)
-> DecoratedTxOut
-> Maybe ScriptHash
forall s (m :: * -> *) r a.
MonadReader s m =>
LensLike' (Const r) s a -> (a -> r) -> m r
views LensLike'
(Const (Maybe ScriptHash))
DecoratedTxOut
(Maybe (Versioned Script))
Lens' DecoratedTxOut (Maybe (Versioned Script))
decoratedTxOutReferenceScript ((Versioned Script -> ScriptHash)
-> Maybe (Versioned Script) -> Maybe ScriptHash
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Versioned Script -> ScriptHash
scriptHash) DecoratedTxOut
p)
toPlutusOutputDatum :: Maybe (V2.DatumHash, DatumFromQuery) -> V2.Tx.OutputDatum
toPlutusOutputDatum :: Maybe (DatumHash, DatumFromQuery) -> OutputDatum
toPlutusOutputDatum Maybe (DatumHash, DatumFromQuery)
Nothing = OutputDatum
V2.Tx.NoOutputDatum
toPlutusOutputDatum (Just (DatumHash
_, DatumInline Datum
d)) = Datum -> OutputDatum
V2.Tx.OutputDatum Datum
d
toPlutusOutputDatum (Just (DatumHash
dh, DatumFromQuery
_)) = DatumHash -> OutputDatum
V2.Tx.OutputDatumHash DatumHash
dh
instance Pretty DecoratedTxOut where
pretty :: DecoratedTxOut -> Doc ann
pretty DecoratedTxOut
p =
Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [ Doc ann
"-" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Value -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (DecoratedTxOut
p DecoratedTxOut -> Getting Value DecoratedTxOut Value -> Value
forall s a. s -> Getting a s a -> a
^. Getting Value DecoratedTxOut Value
Lens' DecoratedTxOut Value
decoratedTxOutValue) Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
"addressed to"
, Address -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (DecoratedTxOut
p DecoratedTxOut -> Getting Address DecoratedTxOut Address -> Address
forall s a. s -> Getting a s a -> a
^. Getting Address DecoratedTxOut Address
Getter DecoratedTxOut Address
decoratedTxOutAddress)]
data CardanoTx
= EmulatorTx { CardanoTx -> Tx
_emulatorTx :: Tx }
| CardanoApiTx { CardanoTx -> SomeCardanoApiTx
_cardanoApiTx :: SomeCardanoApiTx }
deriving (CardanoTx -> CardanoTx -> Bool
(CardanoTx -> CardanoTx -> Bool)
-> (CardanoTx -> CardanoTx -> Bool) -> Eq CardanoTx
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CardanoTx -> CardanoTx -> Bool
$c/= :: CardanoTx -> CardanoTx -> Bool
== :: CardanoTx -> CardanoTx -> Bool
$c== :: CardanoTx -> CardanoTx -> Bool
Eq, Int -> CardanoTx -> ShowS
[CardanoTx] -> ShowS
CardanoTx -> String
(Int -> CardanoTx -> ShowS)
-> (CardanoTx -> String)
-> ([CardanoTx] -> ShowS)
-> Show CardanoTx
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CardanoTx] -> ShowS
$cshowList :: [CardanoTx] -> ShowS
show :: CardanoTx -> String
$cshow :: CardanoTx -> String
showsPrec :: Int -> CardanoTx -> ShowS
$cshowsPrec :: Int -> CardanoTx -> ShowS
Show, (forall x. CardanoTx -> Rep CardanoTx x)
-> (forall x. Rep CardanoTx x -> CardanoTx) -> Generic CardanoTx
forall x. Rep CardanoTx x -> CardanoTx
forall x. CardanoTx -> Rep CardanoTx x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CardanoTx x -> CardanoTx
$cfrom :: forall x. CardanoTx -> Rep CardanoTx x
Generic)
deriving anyclass (Value -> Parser [CardanoTx]
Value -> Parser CardanoTx
(Value -> Parser CardanoTx)
-> (Value -> Parser [CardanoTx]) -> FromJSON CardanoTx
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CardanoTx]
$cparseJSONList :: Value -> Parser [CardanoTx]
parseJSON :: Value -> Parser CardanoTx
$cparseJSON :: Value -> Parser CardanoTx
FromJSON, [CardanoTx] -> Encoding
[CardanoTx] -> Value
CardanoTx -> Encoding
CardanoTx -> Value
(CardanoTx -> Value)
-> (CardanoTx -> Encoding)
-> ([CardanoTx] -> Value)
-> ([CardanoTx] -> Encoding)
-> ToJSON CardanoTx
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CardanoTx] -> Encoding
$ctoEncodingList :: [CardanoTx] -> Encoding
toJSONList :: [CardanoTx] -> Value
$ctoJSONList :: [CardanoTx] -> Value
toEncoding :: CardanoTx -> Encoding
$ctoEncoding :: CardanoTx -> Encoding
toJSON :: CardanoTx -> Value
$ctoJSON :: CardanoTx -> Value
ToJSON, Typeable CardanoTx
Typeable CardanoTx
-> (Proxy CardanoTx -> Declare (Definitions Schema) NamedSchema)
-> ToSchema CardanoTx
Proxy CardanoTx -> Declare (Definitions Schema) NamedSchema
forall a.
Typeable a
-> (Proxy a -> Declare (Definitions Schema) NamedSchema)
-> ToSchema a
declareNamedSchema :: Proxy CardanoTx -> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy CardanoTx -> Declare (Definitions Schema) NamedSchema
$cp1ToSchema :: Typeable CardanoTx
OpenApi.ToSchema, [CardanoTx] -> Encoding
CardanoTx -> Encoding
(CardanoTx -> Encoding)
-> (forall s. Decoder s CardanoTx)
-> ([CardanoTx] -> Encoding)
-> (forall s. Decoder s [CardanoTx])
-> Serialise CardanoTx
forall s. Decoder s [CardanoTx]
forall s. Decoder s CardanoTx
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
decodeList :: Decoder s [CardanoTx]
$cdecodeList :: forall s. Decoder s [CardanoTx]
encodeList :: [CardanoTx] -> Encoding
$cencodeList :: [CardanoTx] -> Encoding
decode :: Decoder s CardanoTx
$cdecode :: forall s. Decoder s CardanoTx
encode :: CardanoTx -> Encoding
$cencode :: CardanoTx -> Encoding
Serialise)
makeLenses ''CardanoTx
getEmulatorEraTx :: SomeCardanoApiTx -> C.Tx C.BabbageEra
getEmulatorEraTx :: SomeCardanoApiTx -> Tx BabbageEra
getEmulatorEraTx (SomeTx Tx era
tx EraInMode era CardanoMode
C.BabbageEraInCardanoMode) = Tx era
Tx BabbageEra
tx
getEmulatorEraTx SomeCardanoApiTx
_ = String -> Tx BabbageEra
forall a. HasCallStack => String -> a
error String
"getEmulatorEraTx: Expected a Babbage tx"
pattern CardanoApiEmulatorEraTx :: C.Tx C.BabbageEra -> SomeCardanoApiTx
pattern $bCardanoApiEmulatorEraTx :: Tx BabbageEra -> SomeCardanoApiTx
$mCardanoApiEmulatorEraTx :: forall r.
SomeCardanoApiTx -> (Tx BabbageEra -> r) -> (Void# -> r) -> r
CardanoApiEmulatorEraTx tx <- (getEmulatorEraTx -> tx) where
CardanoApiEmulatorEraTx Tx BabbageEra
tx = Tx BabbageEra
-> EraInMode BabbageEra CardanoMode -> SomeCardanoApiTx
forall era.
IsCardanoEra era =>
Tx era -> EraInMode era CardanoMode -> SomeCardanoApiTx
SomeTx Tx BabbageEra
tx EraInMode BabbageEra CardanoMode
C.BabbageEraInCardanoMode
{-# COMPLETE CardanoApiEmulatorEraTx #-}
instance Pretty CardanoTx where
pretty :: CardanoTx -> Doc ann
pretty CardanoTx
tx =
let lines' :: [Doc ann]
lines' =
[ Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"inputs:" Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: (TxIn -> Doc ann) -> [TxIn] -> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TxIn -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (CardanoTx -> [TxIn]
getCardanoTxInputs CardanoTx
tx)))
, Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"reference inputs:" Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: (TxIn -> Doc ann) -> [TxIn] -> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TxIn -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (CardanoTx -> [TxIn]
getCardanoTxReferenceInputs CardanoTx
tx)))
, Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"collateral inputs:" Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: (TxIn -> Doc ann) -> [TxIn] -> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TxIn -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (CardanoTx -> [TxIn]
getCardanoTxCollateralInputs CardanoTx
tx)))
, Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"outputs:" Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: (TxOut -> Doc ann) -> [TxOut] -> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TxOut -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (CardanoTx -> [TxOut]
getCardanoTxOutputs CardanoTx
tx)))
]
[Doc ann] -> [Doc ann] -> [Doc ann]
forall a. Semigroup a => a -> a -> a
<> [Doc ann] -> (TxOut -> [Doc ann]) -> Maybe TxOut -> [Doc ann]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\TxOut
out -> [Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"return collateral:", TxOut -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxOut
out])]) (CardanoTx -> Maybe TxOut
getCardanoTxReturnCollateral CardanoTx
tx)
[Doc ann] -> [Doc ann] -> [Doc ann]
forall a. Semigroup a => a -> a -> a
<> [Doc ann] -> (Value -> [Doc ann]) -> Maybe Value -> [Doc ann]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Value
val -> [Doc ann
"total collateral:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Value -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Value
val]) (CardanoTx -> Maybe Value
getCardanoTxTotalCollateral CardanoTx
tx)
[Doc ann] -> [Doc ann] -> [Doc ann]
forall a. [a] -> [a] -> [a]
++ [ Doc ann
"mint:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Value -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (CardanoTx -> Value
getCardanoTxMint CardanoTx
tx)
, Doc ann
"fee:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Value -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (CardanoTx -> Value
getCardanoTxFee CardanoTx
tx)
] [Doc ann] -> [Doc ann] -> [Doc ann]
forall a. [a] -> [a] -> [a]
++ (Tx -> [Doc ann])
-> (SomeCardanoApiTx -> [Doc ann]) -> CardanoTx -> [Doc ann]
forall r. (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
onCardanoTx (\Tx
tx' ->
[ Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"mps:"Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: ((MintingPolicyHash, (Redeemer, Maybe (Versioned TxOutRef)))
-> Doc ann)
-> [(MintingPolicyHash, (Redeemer, Maybe (Versioned TxOutRef)))]
-> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (MintingPolicyHash, (Redeemer, Maybe (Versioned TxOutRef)))
-> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Map MintingPolicyHash (Redeemer, Maybe (Versioned TxOutRef))
-> [(MintingPolicyHash, (Redeemer, Maybe (Versioned TxOutRef)))]
forall k a. Map k a -> [(k, a)]
Map.toList (Tx -> Map MintingPolicyHash (Redeemer, Maybe (Versioned TxOutRef))
txMintingWitnesses Tx
tx'))))
, Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"signatures:"Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: ((PubKey, Signature) -> Doc ann)
-> [(PubKey, Signature)] -> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (PubKey -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (PubKey -> Doc ann)
-> ((PubKey, Signature) -> PubKey)
-> (PubKey, Signature)
-> Doc ann
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PubKey, Signature) -> PubKey
forall a b. (a, b) -> a
fst) (Map PubKey Signature -> [(PubKey, Signature)]
forall k a. Map k a -> [(k, a)]
Map.toList (Tx -> Map PubKey Signature
txSignatures Tx
tx'))))
]) ([Doc ann] -> SomeCardanoApiTx -> [Doc ann]
forall a b. a -> b -> a
const []) CardanoTx
tx [Doc ann] -> [Doc ann] -> [Doc ann]
forall a. [a] -> [a] -> [a]
++
[ Doc ann
"validity range:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> SlotRange -> Doc ann
forall a ann. Show a => a -> Doc ann
viaShow (CardanoTx -> SlotRange
getCardanoTxValidityRange CardanoTx
tx)
, Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"data:"Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: ((DatumHash, Datum) -> Doc ann)
-> [(DatumHash, Datum)] -> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (DatumHash, Datum) -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Map DatumHash Datum -> [(DatumHash, Datum)]
forall k a. Map k a -> [(k, a)]
Map.toList (CardanoTx -> Map DatumHash Datum
getCardanoTxData CardanoTx
tx))))
, Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"redeemers:"Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: (Redeemer -> Doc ann) -> [Redeemer] -> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Redeemer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Map ScriptPurpose Redeemer -> [Redeemer]
forall k a. Map k a -> [a]
Map.elems (Map ScriptPurpose Redeemer -> [Redeemer])
-> Map ScriptPurpose Redeemer -> [Redeemer]
forall a b. (a -> b) -> a -> b
$ CardanoTx -> Map ScriptPurpose Redeemer
getCardanoTxRedeemers CardanoTx
tx)))
]
in Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
nest Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"Tx" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> TxId -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (CardanoTx -> TxId
getCardanoTxId CardanoTx
tx) Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> Doc ann
forall ann. Doc ann
colon, Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
braces ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann]
lines')]
instance Pretty SomeCardanoApiTx where
pretty :: SomeCardanoApiTx -> Doc ann
pretty = CardanoTx -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (CardanoTx -> Doc ann)
-> (SomeCardanoApiTx -> CardanoTx) -> SomeCardanoApiTx -> Doc ann
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeCardanoApiTx -> CardanoTx
CardanoApiTx
instance Pretty CardanoAPI.CardanoBuildTx where
pretty :: CardanoBuildTx -> Doc ann
pretty CardanoBuildTx
txBodyContent = case [KeyWitness BabbageEra] -> TxBody BabbageEra -> Tx BabbageEra
forall era. [KeyWitness era] -> TxBody era -> Tx era
C.makeSignedTransaction [] (TxBody BabbageEra -> Tx BabbageEra)
-> Either ToCardanoError (TxBody BabbageEra)
-> Either ToCardanoError (Tx BabbageEra)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (PParams (BabbageEra StandardCrypto))
-> Map RdmrPtr ExUnits
-> CardanoBuildTx
-> Either ToCardanoError (TxBody BabbageEra)
CardanoAPI.makeTransactionBody Maybe (PParams (BabbageEra StandardCrypto))
forall a. Maybe a
Nothing Map RdmrPtr ExUnits
forall a. Monoid a => a
mempty CardanoBuildTx
txBodyContent of
Right Tx BabbageEra
tx -> SomeCardanoApiTx -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (SomeCardanoApiTx -> Doc ann) -> SomeCardanoApiTx -> Doc ann
forall a b. (a -> b) -> a -> b
$ Tx BabbageEra -> SomeCardanoApiTx
CardanoApiEmulatorEraTx Tx BabbageEra
tx
Either ToCardanoError (Tx BabbageEra)
_ -> CardanoBuildTx -> Doc ann
forall a ann. Show a => a -> Doc ann
viaShow CardanoBuildTx
txBodyContent
getTxBodyContent :: SomeCardanoApiTx -> C.TxBodyContent C.ViewTx C.BabbageEra
getTxBodyContent :: SomeCardanoApiTx -> TxBodyContent ViewTx BabbageEra
getTxBodyContent (CardanoApiEmulatorEraTx (C.Tx (C.TxBody TxBodyContent ViewTx BabbageEra
bodyContent) [KeyWitness BabbageEra]
_)) = TxBodyContent ViewTx BabbageEra
bodyContent
onCardanoTx :: (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
onCardanoTx :: (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
onCardanoTx Tx -> r
l SomeCardanoApiTx -> r
_ (EmulatorTx Tx
tx) = Tx -> r
l Tx
tx
onCardanoTx Tx -> r
_ SomeCardanoApiTx -> r
r (CardanoApiTx SomeCardanoApiTx
ctx) = SomeCardanoApiTx -> r
r SomeCardanoApiTx
ctx
cardanoTxMap :: (Tx -> Tx) -> (SomeCardanoApiTx -> SomeCardanoApiTx) -> CardanoTx -> CardanoTx
cardanoTxMap :: (Tx -> Tx)
-> (SomeCardanoApiTx -> SomeCardanoApiTx) -> CardanoTx -> CardanoTx
cardanoTxMap Tx -> Tx
l SomeCardanoApiTx -> SomeCardanoApiTx
_ (EmulatorTx Tx
tx) = Tx -> CardanoTx
EmulatorTx (Tx -> Tx
l Tx
tx)
cardanoTxMap Tx -> Tx
_ SomeCardanoApiTx -> SomeCardanoApiTx
r (CardanoApiTx SomeCardanoApiTx
ctx) = SomeCardanoApiTx -> CardanoTx
CardanoApiTx (SomeCardanoApiTx -> SomeCardanoApiTx
r SomeCardanoApiTx
ctx)
getCardanoTxId :: CardanoTx -> V1.Tx.TxId
getCardanoTxId :: CardanoTx -> TxId
getCardanoTxId = (Tx -> TxId) -> (SomeCardanoApiTx -> TxId) -> CardanoTx -> TxId
forall r. (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
onCardanoTx Tx -> TxId
txId SomeCardanoApiTx -> TxId
getCardanoApiTxId
getCardanoApiTxId :: SomeCardanoApiTx -> V1.Tx.TxId
getCardanoApiTxId :: SomeCardanoApiTx -> TxId
getCardanoApiTxId (SomeTx (C.Tx TxBody era
body [KeyWitness era]
_) EraInMode era CardanoMode
_) = TxId -> TxId
CardanoAPI.fromCardanoTxId (TxId -> TxId) -> TxId -> TxId
forall a b. (a -> b) -> a -> b
$ TxBody era -> TxId
forall era. TxBody era -> TxId
C.getTxId TxBody era
body
getCardanoTxInputs :: CardanoTx -> [TxIn]
getCardanoTxInputs :: CardanoTx -> [TxIn]
getCardanoTxInputs = (Tx -> [TxIn])
-> (SomeCardanoApiTx -> [TxIn]) -> CardanoTx -> [TxIn]
forall r. (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
onCardanoTx
(\Tx
tx -> (TxInput -> TxIn) -> [TxInput] -> [TxIn]
forall a b. (a -> b) -> [a] -> [b]
map (Tx -> TxInput -> TxIn
fillTxInputWitnesses Tx
tx) ([TxInput] -> [TxIn]) -> [TxInput] -> [TxIn]
forall a b. (a -> b) -> a -> b
$ Tx -> [TxInput]
txInputs Tx
tx)
(TxBodyContent ViewTx BabbageEra -> [TxIn]
forall ctx era. TxBodyContent ctx era -> [TxIn]
getTxBodyContentInputs (TxBodyContent ViewTx BabbageEra -> [TxIn])
-> (SomeCardanoApiTx -> TxBodyContent ViewTx BabbageEra)
-> SomeCardanoApiTx
-> [TxIn]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeCardanoApiTx -> TxBodyContent ViewTx BabbageEra
getTxBodyContent)
getTxBodyContentInputs :: C.TxBodyContent ctx era -> [TxIn]
getTxBodyContentInputs :: TxBodyContent ctx era -> [TxIn]
getTxBodyContentInputs C.TxBodyContent {TxIns ctx era
[TxOut CtxTx era]
(TxValidityLowerBound era, TxValidityUpperBound era)
TxScriptValidity era
BuildTxWith ctx (Maybe ProtocolParameters)
TxInsCollateral era
TxInsReference ctx era
TxReturnCollateral CtxTx era
TxTotalCollateral era
TxFee era
TxMetadataInEra era
TxAuxScripts era
TxExtraKeyWitnesses era
TxWithdrawals ctx era
TxCertificates ctx era
TxUpdateProposal era
TxMintValue ctx era
txIns :: forall build era. TxBodyContent build era -> TxIns build era
txInsCollateral :: forall build era. TxBodyContent build era -> TxInsCollateral era
txInsReference :: forall build era.
TxBodyContent build era -> TxInsReference build era
txOuts :: forall build era. TxBodyContent build era -> [TxOut CtxTx era]
txTotalCollateral :: forall build era. TxBodyContent build era -> TxTotalCollateral era
txReturnCollateral :: forall build era.
TxBodyContent build era -> TxReturnCollateral CtxTx era
txFee :: forall build era. TxBodyContent build era -> TxFee era
txValidityRange :: forall build era.
TxBodyContent build era
-> (TxValidityLowerBound era, TxValidityUpperBound era)
txMetadata :: forall build era. TxBodyContent build era -> TxMetadataInEra era
txAuxScripts :: forall build era. TxBodyContent build era -> TxAuxScripts era
txExtraKeyWits :: forall build era.
TxBodyContent build era -> TxExtraKeyWitnesses era
txProtocolParams :: forall build era.
TxBodyContent build era
-> BuildTxWith build (Maybe ProtocolParameters)
txWithdrawals :: forall build era.
TxBodyContent build era -> TxWithdrawals build era
txCertificates :: forall build era.
TxBodyContent build era -> TxCertificates build era
txUpdateProposal :: forall build era. TxBodyContent build era -> TxUpdateProposal era
txMintValue :: forall build era. TxBodyContent build era -> TxMintValue build era
txScriptValidity :: forall build era. TxBodyContent build era -> TxScriptValidity era
txScriptValidity :: TxScriptValidity era
txMintValue :: TxMintValue ctx era
txUpdateProposal :: TxUpdateProposal era
txCertificates :: TxCertificates ctx era
txWithdrawals :: TxWithdrawals ctx era
txProtocolParams :: BuildTxWith ctx (Maybe ProtocolParameters)
txExtraKeyWits :: TxExtraKeyWitnesses era
txAuxScripts :: TxAuxScripts era
txMetadata :: TxMetadataInEra era
txValidityRange :: (TxValidityLowerBound era, TxValidityUpperBound era)
txFee :: TxFee era
txReturnCollateral :: TxReturnCollateral CtxTx era
txTotalCollateral :: TxTotalCollateral era
txOuts :: [TxOut CtxTx era]
txInsReference :: TxInsReference ctx era
txInsCollateral :: TxInsCollateral era
txIns :: TxIns ctx era
..} =
((TxIn, BuildTxWith ctx (Witness WitCtxTxIn era)) -> TxIn)
-> TxIns ctx era -> [TxIn]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((TxOutRef -> Maybe TxInType -> TxIn
`TxIn` Maybe TxInType
forall a. Maybe a
Nothing) (TxOutRef -> TxIn)
-> ((TxIn, BuildTxWith ctx (Witness WitCtxTxIn era)) -> TxOutRef)
-> (TxIn, BuildTxWith ctx (Witness WitCtxTxIn era))
-> TxIn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxIn -> TxOutRef
CardanoAPI.fromCardanoTxIn (TxIn -> TxOutRef)
-> ((TxIn, BuildTxWith ctx (Witness WitCtxTxIn era)) -> TxIn)
-> (TxIn, BuildTxWith ctx (Witness WitCtxTxIn era))
-> TxOutRef
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TxIn, BuildTxWith ctx (Witness WitCtxTxIn era)) -> TxIn
forall a b. (a, b) -> a
fst) TxIns ctx era
txIns
getCardanoTxCollateralInputs :: CardanoTx -> [TxIn]
getCardanoTxCollateralInputs :: CardanoTx -> [TxIn]
getCardanoTxCollateralInputs = (Tx -> [TxIn])
-> (SomeCardanoApiTx -> [TxIn]) -> CardanoTx -> [TxIn]
forall r. (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
onCardanoTx
(\Tx
tx -> (TxInput -> TxIn) -> [TxInput] -> [TxIn]
forall a b. (a -> b) -> [a] -> [b]
map (Tx -> TxInput -> TxIn
fillTxInputWitnesses Tx
tx) ([TxInput] -> [TxIn]) -> [TxInput] -> [TxIn]
forall a b. (a -> b) -> a -> b
$ Tx -> [TxInput]
txCollateralInputs Tx
tx)
(TxBodyContent ViewTx BabbageEra -> [TxIn]
forall ctx era. TxBodyContent ctx era -> [TxIn]
getTxBodyContentCollateralInputs (TxBodyContent ViewTx BabbageEra -> [TxIn])
-> (SomeCardanoApiTx -> TxBodyContent ViewTx BabbageEra)
-> SomeCardanoApiTx
-> [TxIn]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeCardanoApiTx -> TxBodyContent ViewTx BabbageEra
getTxBodyContent)
getTxBodyContentCollateralInputs :: C.TxBodyContent ctx era -> [TxIn]
getTxBodyContentCollateralInputs :: TxBodyContent ctx era -> [TxIn]
getTxBodyContentCollateralInputs C.TxBodyContent {TxIns ctx era
[TxOut CtxTx era]
(TxValidityLowerBound era, TxValidityUpperBound era)
TxScriptValidity era
BuildTxWith ctx (Maybe ProtocolParameters)
TxInsCollateral era
TxInsReference ctx era
TxReturnCollateral CtxTx era
TxTotalCollateral era
TxFee era
TxMetadataInEra era
TxAuxScripts era
TxExtraKeyWitnesses era
TxWithdrawals ctx era
TxCertificates ctx era
TxUpdateProposal era
TxMintValue ctx era
txScriptValidity :: TxScriptValidity era
txMintValue :: TxMintValue ctx era
txUpdateProposal :: TxUpdateProposal era
txCertificates :: TxCertificates ctx era
txWithdrawals :: TxWithdrawals ctx era
txProtocolParams :: BuildTxWith ctx (Maybe ProtocolParameters)
txExtraKeyWits :: TxExtraKeyWitnesses era
txAuxScripts :: TxAuxScripts era
txMetadata :: TxMetadataInEra era
txValidityRange :: (TxValidityLowerBound era, TxValidityUpperBound era)
txFee :: TxFee era
txReturnCollateral :: TxReturnCollateral CtxTx era
txTotalCollateral :: TxTotalCollateral era
txOuts :: [TxOut CtxTx era]
txInsReference :: TxInsReference ctx era
txInsCollateral :: TxInsCollateral era
txIns :: TxIns ctx era
txIns :: forall build era. TxBodyContent build era -> TxIns build era
txInsCollateral :: forall build era. TxBodyContent build era -> TxInsCollateral era
txInsReference :: forall build era.
TxBodyContent build era -> TxInsReference build era
txOuts :: forall build era. TxBodyContent build era -> [TxOut CtxTx era]
txTotalCollateral :: forall build era. TxBodyContent build era -> TxTotalCollateral era
txReturnCollateral :: forall build era.
TxBodyContent build era -> TxReturnCollateral CtxTx era
txFee :: forall build era. TxBodyContent build era -> TxFee era
txValidityRange :: forall build era.
TxBodyContent build era
-> (TxValidityLowerBound era, TxValidityUpperBound era)
txMetadata :: forall build era. TxBodyContent build era -> TxMetadataInEra era
txAuxScripts :: forall build era. TxBodyContent build era -> TxAuxScripts era
txExtraKeyWits :: forall build era.
TxBodyContent build era -> TxExtraKeyWitnesses era
txProtocolParams :: forall build era.
TxBodyContent build era
-> BuildTxWith build (Maybe ProtocolParameters)
txWithdrawals :: forall build era.
TxBodyContent build era -> TxWithdrawals build era
txCertificates :: forall build era.
TxBodyContent build era -> TxCertificates build era
txUpdateProposal :: forall build era. TxBodyContent build era -> TxUpdateProposal era
txMintValue :: forall build era. TxBodyContent build era -> TxMintValue build era
txScriptValidity :: forall build era. TxBodyContent build era -> TxScriptValidity era
..} = TxInsCollateral era -> [TxIn]
forall era. TxInsCollateral era -> [TxIn]
CardanoAPI.fromCardanoTxInsCollateral TxInsCollateral era
txInsCollateral
getCardanoTxReferenceInputs :: CardanoTx -> [TxIn]
getCardanoTxReferenceInputs :: CardanoTx -> [TxIn]
getCardanoTxReferenceInputs = (Tx -> [TxIn])
-> (SomeCardanoApiTx -> [TxIn]) -> CardanoTx -> [TxIn]
forall r. (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
onCardanoTx
(\Tx
tx -> (TxInput -> TxIn) -> [TxInput] -> [TxIn]
forall a b. (a -> b) -> [a] -> [b]
map (Tx -> TxInput -> TxIn
fillTxInputWitnesses Tx
tx) ([TxInput] -> [TxIn]) -> [TxInput] -> [TxIn]
forall a b. (a -> b) -> a -> b
$ Tx -> [TxInput]
txReferenceInputs Tx
tx)
(\(SomeTx (C.Tx (C.TxBody C.TxBodyContent {TxIns ViewTx era
[TxOut CtxTx era]
(TxValidityLowerBound era, TxValidityUpperBound era)
TxScriptValidity era
BuildTxWith ViewTx (Maybe ProtocolParameters)
TxInsCollateral era
TxInsReference ViewTx era
TxReturnCollateral CtxTx era
TxTotalCollateral era
TxFee era
TxMetadataInEra era
TxAuxScripts era
TxExtraKeyWitnesses era
TxWithdrawals ViewTx era
TxCertificates ViewTx era
TxUpdateProposal era
TxMintValue ViewTx era
txScriptValidity :: TxScriptValidity era
txMintValue :: TxMintValue ViewTx era
txUpdateProposal :: TxUpdateProposal era
txCertificates :: TxCertificates ViewTx era
txWithdrawals :: TxWithdrawals ViewTx era
txProtocolParams :: BuildTxWith ViewTx (Maybe ProtocolParameters)
txExtraKeyWits :: TxExtraKeyWitnesses era
txAuxScripts :: TxAuxScripts era
txMetadata :: TxMetadataInEra era
txValidityRange :: (TxValidityLowerBound era, TxValidityUpperBound era)
txFee :: TxFee era
txReturnCollateral :: TxReturnCollateral CtxTx era
txTotalCollateral :: TxTotalCollateral era
txOuts :: [TxOut CtxTx era]
txInsReference :: TxInsReference ViewTx era
txInsCollateral :: TxInsCollateral era
txIns :: TxIns ViewTx era
txIns :: forall build era. TxBodyContent build era -> TxIns build era
txInsCollateral :: forall build era. TxBodyContent build era -> TxInsCollateral era
txInsReference :: forall build era.
TxBodyContent build era -> TxInsReference build era
txOuts :: forall build era. TxBodyContent build era -> [TxOut CtxTx era]
txTotalCollateral :: forall build era. TxBodyContent build era -> TxTotalCollateral era
txReturnCollateral :: forall build era.
TxBodyContent build era -> TxReturnCollateral CtxTx era
txFee :: forall build era. TxBodyContent build era -> TxFee era
txValidityRange :: forall build era.
TxBodyContent build era
-> (TxValidityLowerBound era, TxValidityUpperBound era)
txMetadata :: forall build era. TxBodyContent build era -> TxMetadataInEra era
txAuxScripts :: forall build era. TxBodyContent build era -> TxAuxScripts era
txExtraKeyWits :: forall build era.
TxBodyContent build era -> TxExtraKeyWitnesses era
txProtocolParams :: forall build era.
TxBodyContent build era
-> BuildTxWith build (Maybe ProtocolParameters)
txWithdrawals :: forall build era.
TxBodyContent build era -> TxWithdrawals build era
txCertificates :: forall build era.
TxBodyContent build era -> TxCertificates build era
txUpdateProposal :: forall build era. TxBodyContent build era -> TxUpdateProposal era
txMintValue :: forall build era. TxBodyContent build era -> TxMintValue build era
txScriptValidity :: forall build era. TxBodyContent build era -> TxScriptValidity era
..}) [KeyWitness era]
_) EraInMode era CardanoMode
_) ->
TxInsReference ViewTx era -> [TxIn]
forall build era. TxInsReference build era -> [TxIn]
txInsReferenceToPlutusTxIns TxInsReference ViewTx era
txInsReference)
where
txInsReferenceToPlutusTxIns :: TxInsReference build era -> [TxIn]
txInsReferenceToPlutusTxIns TxInsReference build era
C.TxInsReferenceNone = []
txInsReferenceToPlutusTxIns (C.TxInsReference ReferenceTxInsScriptsInlineDatumsSupportedInEra era
_ [TxIn]
txIns) =
(TxIn -> TxIn) -> [TxIn] -> [TxIn]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((TxOutRef -> Maybe TxInType -> TxIn
`TxIn` Maybe TxInType
forall a. Maybe a
Nothing) (TxOutRef -> TxIn) -> (TxIn -> TxOutRef) -> TxIn -> TxIn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxIn -> TxOutRef
CardanoAPI.fromCardanoTxIn) [TxIn]
txIns
getCardanoTxOutRefs :: CardanoTx -> [(TxOut, V1.Tx.TxOutRef)]
getCardanoTxOutRefs :: CardanoTx -> [(TxOut, TxOutRef)]
getCardanoTxOutRefs = (Tx -> [(TxOut, TxOutRef)])
-> (SomeCardanoApiTx -> [(TxOut, TxOutRef)])
-> CardanoTx
-> [(TxOut, TxOutRef)]
forall r. (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
onCardanoTx Tx -> [(TxOut, TxOutRef)]
txOutRefs SomeCardanoApiTx -> [(TxOut, TxOutRef)]
cardanoApiTxOutRefs
where
cardanoApiTxOutRefs :: SomeCardanoApiTx -> [(TxOut, V1.Tx.TxOutRef)]
cardanoApiTxOutRefs :: SomeCardanoApiTx -> [(TxOut, TxOutRef)]
cardanoApiTxOutRefs (CardanoApiEmulatorEraTx (C.Tx txBody :: TxBody BabbageEra
txBody@(C.TxBody C.TxBodyContent{TxIns ViewTx BabbageEra
[TxOut CtxTx BabbageEra]
(TxValidityLowerBound BabbageEra, TxValidityUpperBound BabbageEra)
TxScriptValidity BabbageEra
BuildTxWith ViewTx (Maybe ProtocolParameters)
TxInsCollateral BabbageEra
TxInsReference ViewTx BabbageEra
TxReturnCollateral CtxTx BabbageEra
TxTotalCollateral BabbageEra
TxFee BabbageEra
TxMetadataInEra BabbageEra
TxAuxScripts BabbageEra
TxExtraKeyWitnesses BabbageEra
TxWithdrawals ViewTx BabbageEra
TxCertificates ViewTx BabbageEra
TxUpdateProposal BabbageEra
TxMintValue ViewTx BabbageEra
txScriptValidity :: TxScriptValidity BabbageEra
txMintValue :: TxMintValue ViewTx BabbageEra
txUpdateProposal :: TxUpdateProposal BabbageEra
txCertificates :: TxCertificates ViewTx BabbageEra
txWithdrawals :: TxWithdrawals ViewTx BabbageEra
txProtocolParams :: BuildTxWith ViewTx (Maybe ProtocolParameters)
txExtraKeyWits :: TxExtraKeyWitnesses BabbageEra
txAuxScripts :: TxAuxScripts BabbageEra
txMetadata :: TxMetadataInEra BabbageEra
txValidityRange :: (TxValidityLowerBound BabbageEra, TxValidityUpperBound BabbageEra)
txFee :: TxFee BabbageEra
txReturnCollateral :: TxReturnCollateral CtxTx BabbageEra
txTotalCollateral :: TxTotalCollateral BabbageEra
txOuts :: [TxOut CtxTx BabbageEra]
txInsReference :: TxInsReference ViewTx BabbageEra
txInsCollateral :: TxInsCollateral BabbageEra
txIns :: TxIns ViewTx BabbageEra
txIns :: forall build era. TxBodyContent build era -> TxIns build era
txInsCollateral :: forall build era. TxBodyContent build era -> TxInsCollateral era
txInsReference :: forall build era.
TxBodyContent build era -> TxInsReference build era
txOuts :: forall build era. TxBodyContent build era -> [TxOut CtxTx era]
txTotalCollateral :: forall build era. TxBodyContent build era -> TxTotalCollateral era
txReturnCollateral :: forall build era.
TxBodyContent build era -> TxReturnCollateral CtxTx era
txFee :: forall build era. TxBodyContent build era -> TxFee era
txValidityRange :: forall build era.
TxBodyContent build era
-> (TxValidityLowerBound era, TxValidityUpperBound era)
txMetadata :: forall build era. TxBodyContent build era -> TxMetadataInEra era
txAuxScripts :: forall build era. TxBodyContent build era -> TxAuxScripts era
txExtraKeyWits :: forall build era.
TxBodyContent build era -> TxExtraKeyWitnesses era
txProtocolParams :: forall build era.
TxBodyContent build era
-> BuildTxWith build (Maybe ProtocolParameters)
txWithdrawals :: forall build era.
TxBodyContent build era -> TxWithdrawals build era
txCertificates :: forall build era.
TxBodyContent build era -> TxCertificates build era
txUpdateProposal :: forall build era. TxBodyContent build era -> TxUpdateProposal era
txMintValue :: forall build era. TxBodyContent build era -> TxMintValue build era
txScriptValidity :: forall build era. TxBodyContent build era -> TxScriptValidity era
..}) [KeyWitness BabbageEra]
_)) =
(Integer, TxOut) -> (TxOut, TxOutRef)
mkOut ((Integer, TxOut) -> (TxOut, TxOutRef))
-> [(Integer, TxOut)] -> [(TxOut, TxOutRef)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Integer] -> [TxOut] -> [(Integer, TxOut)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Integer
0..] ((TxOut CtxTx BabbageEra -> TxOut)
-> [TxOut CtxTx BabbageEra] -> [TxOut]
forall a b. (a -> b) -> [a] -> [b]
map TxOut CtxTx BabbageEra -> TxOut
TxOut [TxOut CtxTx BabbageEra]
txOuts)
where
mkOut :: (Integer, TxOut) -> (TxOut, TxOutRef)
mkOut (Integer
i, TxOut
o) = (TxOut
o, TxId -> Integer -> TxOutRef
V1.TxOutRef (TxId -> TxId
CardanoAPI.fromCardanoTxId (TxId -> TxId) -> TxId -> TxId
forall a b. (a -> b) -> a -> b
$ TxBody BabbageEra -> TxId
forall era. TxBody era -> TxId
C.getTxId TxBody BabbageEra
txBody) Integer
i)
getCardanoTxOutputs :: CardanoTx -> [TxOut]
getCardanoTxOutputs :: CardanoTx -> [TxOut]
getCardanoTxOutputs = ((TxOut, TxOutRef) -> TxOut) -> [(TxOut, TxOutRef)] -> [TxOut]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (TxOut, TxOutRef) -> TxOut
forall a b. (a, b) -> a
fst ([(TxOut, TxOutRef)] -> [TxOut])
-> (CardanoTx -> [(TxOut, TxOutRef)]) -> CardanoTx -> [TxOut]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CardanoTx -> [(TxOut, TxOutRef)]
getCardanoTxOutRefs
getCardanoTxProducedOutputs :: CardanoTx -> Map V1.Tx.TxOutRef TxOut
getCardanoTxProducedOutputs :: CardanoTx -> Map TxOutRef TxOut
getCardanoTxProducedOutputs = [(TxOutRef, TxOut)] -> Map TxOutRef TxOut
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(TxOutRef, TxOut)] -> Map TxOutRef TxOut)
-> (CardanoTx -> [(TxOutRef, TxOut)])
-> CardanoTx
-> Map TxOutRef TxOut
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((TxOut, TxOutRef) -> (TxOutRef, TxOut))
-> [(TxOut, TxOutRef)] -> [(TxOutRef, TxOut)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (TxOut, TxOutRef) -> (TxOutRef, TxOut)
forall a b. (a, b) -> (b, a)
swap ([(TxOut, TxOutRef)] -> [(TxOutRef, TxOut)])
-> (CardanoTx -> [(TxOut, TxOutRef)])
-> CardanoTx
-> [(TxOutRef, TxOut)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CardanoTx -> [(TxOut, TxOutRef)]
getCardanoTxOutRefs
getCardanoTxSpentOutputs :: CardanoTx -> Set V1.Tx.TxOutRef
getCardanoTxSpentOutputs :: CardanoTx -> Set TxOutRef
getCardanoTxSpentOutputs = [TxOutRef] -> Set TxOutRef
forall a. Ord a => [a] -> Set a
Set.fromList ([TxOutRef] -> Set TxOutRef)
-> (CardanoTx -> [TxOutRef]) -> CardanoTx -> Set TxOutRef
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TxIn -> TxOutRef) -> [TxIn] -> [TxOutRef]
forall a b. (a -> b) -> [a] -> [b]
map TxIn -> TxOutRef
txInRef ([TxIn] -> [TxOutRef])
-> (CardanoTx -> [TxIn]) -> CardanoTx -> [TxOutRef]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CardanoTx -> [TxIn]
getCardanoTxInputs
getCardanoTxReturnCollateral :: CardanoTx -> Maybe TxOut
getCardanoTxReturnCollateral :: CardanoTx -> Maybe TxOut
getCardanoTxReturnCollateral = (Tx -> Maybe TxOut)
-> (SomeCardanoApiTx -> Maybe TxOut) -> CardanoTx -> Maybe TxOut
forall r. (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
onCardanoTx Tx -> Maybe TxOut
txReturnCollateral (TxBodyContent ViewTx BabbageEra -> Maybe TxOut
forall ctx. TxBodyContent ctx BabbageEra -> Maybe TxOut
getTxBodyContentReturnCollateral (TxBodyContent ViewTx BabbageEra -> Maybe TxOut)
-> (SomeCardanoApiTx -> TxBodyContent ViewTx BabbageEra)
-> SomeCardanoApiTx
-> Maybe TxOut
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeCardanoApiTx -> TxBodyContent ViewTx BabbageEra
getTxBodyContent)
getTxBodyContentReturnCollateral :: C.TxBodyContent ctx C.Api.BabbageEra -> Maybe TxOut
getTxBodyContentReturnCollateral :: TxBodyContent ctx BabbageEra -> Maybe TxOut
getTxBodyContentReturnCollateral C.TxBodyContent {TxIns ctx BabbageEra
[TxOut CtxTx BabbageEra]
(TxValidityLowerBound BabbageEra, TxValidityUpperBound BabbageEra)
TxScriptValidity BabbageEra
BuildTxWith ctx (Maybe ProtocolParameters)
TxInsCollateral BabbageEra
TxInsReference ctx BabbageEra
TxReturnCollateral CtxTx BabbageEra
TxTotalCollateral BabbageEra
TxFee BabbageEra
TxMetadataInEra BabbageEra
TxAuxScripts BabbageEra
TxExtraKeyWitnesses BabbageEra
TxWithdrawals ctx BabbageEra
TxCertificates ctx BabbageEra
TxUpdateProposal BabbageEra
TxMintValue ctx BabbageEra
txScriptValidity :: TxScriptValidity BabbageEra
txMintValue :: TxMintValue ctx BabbageEra
txUpdateProposal :: TxUpdateProposal BabbageEra
txCertificates :: TxCertificates ctx BabbageEra
txWithdrawals :: TxWithdrawals ctx BabbageEra
txProtocolParams :: BuildTxWith ctx (Maybe ProtocolParameters)
txExtraKeyWits :: TxExtraKeyWitnesses BabbageEra
txAuxScripts :: TxAuxScripts BabbageEra
txMetadata :: TxMetadataInEra BabbageEra
txValidityRange :: (TxValidityLowerBound BabbageEra, TxValidityUpperBound BabbageEra)
txFee :: TxFee BabbageEra
txReturnCollateral :: TxReturnCollateral CtxTx BabbageEra
txTotalCollateral :: TxTotalCollateral BabbageEra
txOuts :: [TxOut CtxTx BabbageEra]
txInsReference :: TxInsReference ctx BabbageEra
txInsCollateral :: TxInsCollateral BabbageEra
txIns :: TxIns ctx BabbageEra
txIns :: forall build era. TxBodyContent build era -> TxIns build era
txInsCollateral :: forall build era. TxBodyContent build era -> TxInsCollateral era
txInsReference :: forall build era.
TxBodyContent build era -> TxInsReference build era
txOuts :: forall build era. TxBodyContent build era -> [TxOut CtxTx era]
txTotalCollateral :: forall build era. TxBodyContent build era -> TxTotalCollateral era
txReturnCollateral :: forall build era.
TxBodyContent build era -> TxReturnCollateral CtxTx era
txFee :: forall build era. TxBodyContent build era -> TxFee era
txValidityRange :: forall build era.
TxBodyContent build era
-> (TxValidityLowerBound era, TxValidityUpperBound era)
txMetadata :: forall build era. TxBodyContent build era -> TxMetadataInEra era
txAuxScripts :: forall build era. TxBodyContent build era -> TxAuxScripts era
txExtraKeyWits :: forall build era.
TxBodyContent build era -> TxExtraKeyWitnesses era
txProtocolParams :: forall build era.
TxBodyContent build era
-> BuildTxWith build (Maybe ProtocolParameters)
txWithdrawals :: forall build era.
TxBodyContent build era -> TxWithdrawals build era
txCertificates :: forall build era.
TxBodyContent build era -> TxCertificates build era
txUpdateProposal :: forall build era. TxBodyContent build era -> TxUpdateProposal era
txMintValue :: forall build era. TxBodyContent build era -> TxMintValue build era
txScriptValidity :: forall build era. TxBodyContent build era -> TxScriptValidity era
..} =
case TxReturnCollateral CtxTx BabbageEra
txReturnCollateral of
TxReturnCollateral CtxTx BabbageEra
C.TxReturnCollateralNone -> Maybe TxOut
forall a. Maybe a
Nothing
C.TxReturnCollateral TxTotalAndReturnCollateralSupportedInEra BabbageEra
_ TxOut CtxTx BabbageEra
txOut -> TxOut -> Maybe TxOut
forall a. a -> Maybe a
Just (TxOut -> Maybe TxOut) -> TxOut -> Maybe TxOut
forall a b. (a -> b) -> a -> b
$ TxOut CtxTx BabbageEra -> TxOut
TxOut TxOut CtxTx BabbageEra
txOut
getCardanoTxProducedReturnCollateral :: CardanoTx -> Map V1.Tx.TxOutRef TxOut
getCardanoTxProducedReturnCollateral :: CardanoTx -> Map TxOutRef TxOut
getCardanoTxProducedReturnCollateral CardanoTx
tx = Map TxOutRef TxOut
-> (TxOut -> Map TxOutRef TxOut)
-> Maybe TxOut
-> Map TxOutRef TxOut
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Map TxOutRef TxOut
forall k a. Map k a
Map.empty (TxOutRef -> TxOut -> Map TxOutRef TxOut
forall k a. k -> a -> Map k a
Map.singleton (TxId -> Integer -> TxOutRef
V1.TxOutRef (CardanoTx -> TxId
getCardanoTxId CardanoTx
tx) Integer
0)) (Maybe TxOut -> Map TxOutRef TxOut)
-> Maybe TxOut -> Map TxOutRef TxOut
forall a b. (a -> b) -> a -> b
$
CardanoTx -> Maybe TxOut
getCardanoTxReturnCollateral CardanoTx
tx
getCardanoTxTotalCollateral :: CardanoTx -> Maybe V1.Value
getCardanoTxTotalCollateral :: CardanoTx -> Maybe Value
getCardanoTxTotalCollateral = (Tx -> Maybe Value)
-> (SomeCardanoApiTx -> Maybe Value) -> CardanoTx -> Maybe Value
forall r. (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
onCardanoTx Tx -> Maybe Value
txTotalCollateral
(\(CardanoApiEmulatorEraTx (C.Tx (C.TxBody C.TxBodyContent {TxIns ViewTx BabbageEra
[TxOut CtxTx BabbageEra]
(TxValidityLowerBound BabbageEra, TxValidityUpperBound BabbageEra)
TxScriptValidity BabbageEra
BuildTxWith ViewTx (Maybe ProtocolParameters)
TxInsCollateral BabbageEra
TxInsReference ViewTx BabbageEra
TxReturnCollateral CtxTx BabbageEra
TxTotalCollateral BabbageEra
TxFee BabbageEra
TxMetadataInEra BabbageEra
TxAuxScripts BabbageEra
TxExtraKeyWitnesses BabbageEra
TxWithdrawals ViewTx BabbageEra
TxCertificates ViewTx BabbageEra
TxUpdateProposal BabbageEra
TxMintValue ViewTx BabbageEra
txScriptValidity :: TxScriptValidity BabbageEra
txMintValue :: TxMintValue ViewTx BabbageEra
txUpdateProposal :: TxUpdateProposal BabbageEra
txCertificates :: TxCertificates ViewTx BabbageEra
txWithdrawals :: TxWithdrawals ViewTx BabbageEra
txProtocolParams :: BuildTxWith ViewTx (Maybe ProtocolParameters)
txExtraKeyWits :: TxExtraKeyWitnesses BabbageEra
txAuxScripts :: TxAuxScripts BabbageEra
txMetadata :: TxMetadataInEra BabbageEra
txValidityRange :: (TxValidityLowerBound BabbageEra, TxValidityUpperBound BabbageEra)
txFee :: TxFee BabbageEra
txReturnCollateral :: TxReturnCollateral CtxTx BabbageEra
txTotalCollateral :: TxTotalCollateral BabbageEra
txOuts :: [TxOut CtxTx BabbageEra]
txInsReference :: TxInsReference ViewTx BabbageEra
txInsCollateral :: TxInsCollateral BabbageEra
txIns :: TxIns ViewTx BabbageEra
txIns :: forall build era. TxBodyContent build era -> TxIns build era
txInsCollateral :: forall build era. TxBodyContent build era -> TxInsCollateral era
txInsReference :: forall build era.
TxBodyContent build era -> TxInsReference build era
txOuts :: forall build era. TxBodyContent build era -> [TxOut CtxTx era]
txTotalCollateral :: forall build era. TxBodyContent build era -> TxTotalCollateral era
txReturnCollateral :: forall build era.
TxBodyContent build era -> TxReturnCollateral CtxTx era
txFee :: forall build era. TxBodyContent build era -> TxFee era
txValidityRange :: forall build era.
TxBodyContent build era
-> (TxValidityLowerBound era, TxValidityUpperBound era)
txMetadata :: forall build era. TxBodyContent build era -> TxMetadataInEra era
txAuxScripts :: forall build era. TxBodyContent build era -> TxAuxScripts era
txExtraKeyWits :: forall build era.
TxBodyContent build era -> TxExtraKeyWitnesses era
txProtocolParams :: forall build era.
TxBodyContent build era
-> BuildTxWith build (Maybe ProtocolParameters)
txWithdrawals :: forall build era.
TxBodyContent build era -> TxWithdrawals build era
txCertificates :: forall build era.
TxBodyContent build era -> TxCertificates build era
txUpdateProposal :: forall build era. TxBodyContent build era -> TxUpdateProposal era
txMintValue :: forall build era. TxBodyContent build era -> TxMintValue build era
txScriptValidity :: forall build era. TxBodyContent build era -> TxScriptValidity era
..}) [KeyWitness BabbageEra]
_)) -> TxTotalCollateral BabbageEra -> Maybe Value
CardanoAPI.fromCardanoTotalCollateral TxTotalCollateral BabbageEra
txTotalCollateral)
getCardanoTxFee :: CardanoTx -> V1.Value
getCardanoTxFee :: CardanoTx -> Value
getCardanoTxFee = (Tx -> Value) -> (SomeCardanoApiTx -> Value) -> CardanoTx -> Value
forall r. (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
onCardanoTx Tx -> Value
txFee (\(SomeTx (C.Tx (C.TxBody C.TxBodyContent {TxIns ViewTx era
[TxOut CtxTx era]
(TxValidityLowerBound era, TxValidityUpperBound era)
TxScriptValidity era
BuildTxWith ViewTx (Maybe ProtocolParameters)
TxInsCollateral era
TxInsReference ViewTx era
TxReturnCollateral CtxTx era
TxTotalCollateral era
TxFee era
TxMetadataInEra era
TxAuxScripts era
TxExtraKeyWitnesses era
TxWithdrawals ViewTx era
TxCertificates ViewTx era
TxUpdateProposal era
TxMintValue ViewTx era
txScriptValidity :: TxScriptValidity era
txMintValue :: TxMintValue ViewTx era
txUpdateProposal :: TxUpdateProposal era
txCertificates :: TxCertificates ViewTx era
txWithdrawals :: TxWithdrawals ViewTx era
txProtocolParams :: BuildTxWith ViewTx (Maybe ProtocolParameters)
txExtraKeyWits :: TxExtraKeyWitnesses era
txAuxScripts :: TxAuxScripts era
txMetadata :: TxMetadataInEra era
txValidityRange :: (TxValidityLowerBound era, TxValidityUpperBound era)
txFee :: TxFee era
txReturnCollateral :: TxReturnCollateral CtxTx era
txTotalCollateral :: TxTotalCollateral era
txOuts :: [TxOut CtxTx era]
txInsReference :: TxInsReference ViewTx era
txInsCollateral :: TxInsCollateral era
txIns :: TxIns ViewTx era
txIns :: forall build era. TxBodyContent build era -> TxIns build era
txInsCollateral :: forall build era. TxBodyContent build era -> TxInsCollateral era
txInsReference :: forall build era.
TxBodyContent build era -> TxInsReference build era
txOuts :: forall build era. TxBodyContent build era -> [TxOut CtxTx era]
txTotalCollateral :: forall build era. TxBodyContent build era -> TxTotalCollateral era
txReturnCollateral :: forall build era.
TxBodyContent build era -> TxReturnCollateral CtxTx era
txFee :: forall build era. TxBodyContent build era -> TxFee era
txValidityRange :: forall build era.
TxBodyContent build era
-> (TxValidityLowerBound era, TxValidityUpperBound era)
txMetadata :: forall build era. TxBodyContent build era -> TxMetadataInEra era
txAuxScripts :: forall build era. TxBodyContent build era -> TxAuxScripts era
txExtraKeyWits :: forall build era.
TxBodyContent build era -> TxExtraKeyWitnesses era
txProtocolParams :: forall build era.
TxBodyContent build era
-> BuildTxWith build (Maybe ProtocolParameters)
txWithdrawals :: forall build era.
TxBodyContent build era -> TxWithdrawals build era
txCertificates :: forall build era.
TxBodyContent build era -> TxCertificates build era
txUpdateProposal :: forall build era. TxBodyContent build era -> TxUpdateProposal era
txMintValue :: forall build era. TxBodyContent build era -> TxMintValue build era
txScriptValidity :: forall build era. TxBodyContent build era -> TxScriptValidity era
..}) [KeyWitness era]
_) EraInMode era CardanoMode
_) -> TxFee era -> Value
forall era. TxFee era -> Value
CardanoAPI.fromCardanoFee TxFee era
txFee)
getCardanoTxMint :: CardanoTx -> V1.Value
getCardanoTxMint :: CardanoTx -> Value
getCardanoTxMint = (Tx -> Value) -> (SomeCardanoApiTx -> Value) -> CardanoTx -> Value
forall r. (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
onCardanoTx Tx -> Value
txMint (TxBodyContent ViewTx BabbageEra -> Value
forall ctx era. TxBodyContent ctx era -> Value
getTxBodyContentMint (TxBodyContent ViewTx BabbageEra -> Value)
-> (SomeCardanoApiTx -> TxBodyContent ViewTx BabbageEra)
-> SomeCardanoApiTx
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeCardanoApiTx -> TxBodyContent ViewTx BabbageEra
getTxBodyContent)
getTxBodyContentMint :: C.TxBodyContent ctx era -> V1.Value
getTxBodyContentMint :: TxBodyContent ctx era -> Value
getTxBodyContentMint C.TxBodyContent {TxIns ctx era
[TxOut CtxTx era]
(TxValidityLowerBound era, TxValidityUpperBound era)
TxScriptValidity era
BuildTxWith ctx (Maybe ProtocolParameters)
TxInsCollateral era
TxInsReference ctx era
TxReturnCollateral CtxTx era
TxTotalCollateral era
TxFee era
TxMetadataInEra era
TxAuxScripts era
TxExtraKeyWitnesses era
TxWithdrawals ctx era
TxCertificates ctx era
TxUpdateProposal era
TxMintValue ctx era
txScriptValidity :: TxScriptValidity era
txMintValue :: TxMintValue ctx era
txUpdateProposal :: TxUpdateProposal era
txCertificates :: TxCertificates ctx era
txWithdrawals :: TxWithdrawals ctx era
txProtocolParams :: BuildTxWith ctx (Maybe ProtocolParameters)
txExtraKeyWits :: TxExtraKeyWitnesses era
txAuxScripts :: TxAuxScripts era
txMetadata :: TxMetadataInEra era
txValidityRange :: (TxValidityLowerBound era, TxValidityUpperBound era)
txFee :: TxFee era
txReturnCollateral :: TxReturnCollateral CtxTx era
txTotalCollateral :: TxTotalCollateral era
txOuts :: [TxOut CtxTx era]
txInsReference :: TxInsReference ctx era
txInsCollateral :: TxInsCollateral era
txIns :: TxIns ctx era
txIns :: forall build era. TxBodyContent build era -> TxIns build era
txInsCollateral :: forall build era. TxBodyContent build era -> TxInsCollateral era
txInsReference :: forall build era.
TxBodyContent build era -> TxInsReference build era
txOuts :: forall build era. TxBodyContent build era -> [TxOut CtxTx era]
txTotalCollateral :: forall build era. TxBodyContent build era -> TxTotalCollateral era
txReturnCollateral :: forall build era.
TxBodyContent build era -> TxReturnCollateral CtxTx era
txFee :: forall build era. TxBodyContent build era -> TxFee era
txValidityRange :: forall build era.
TxBodyContent build era
-> (TxValidityLowerBound era, TxValidityUpperBound era)
txMetadata :: forall build era. TxBodyContent build era -> TxMetadataInEra era
txAuxScripts :: forall build era. TxBodyContent build era -> TxAuxScripts era
txExtraKeyWits :: forall build era.
TxBodyContent build era -> TxExtraKeyWitnesses era
txProtocolParams :: forall build era.
TxBodyContent build era
-> BuildTxWith build (Maybe ProtocolParameters)
txWithdrawals :: forall build era.
TxBodyContent build era -> TxWithdrawals build era
txCertificates :: forall build era.
TxBodyContent build era -> TxCertificates build era
txUpdateProposal :: forall build era. TxBodyContent build era -> TxUpdateProposal era
txMintValue :: forall build era. TxBodyContent build era -> TxMintValue build era
txScriptValidity :: forall build era. TxBodyContent build era -> TxScriptValidity era
..} = TxMintValue ctx era -> Value
forall build era. TxMintValue build era -> Value
CardanoAPI.fromCardanoMintValue TxMintValue ctx era
txMintValue
getCardanoTxValidityRange :: CardanoTx -> SlotRange
getCardanoTxValidityRange :: CardanoTx -> SlotRange
getCardanoTxValidityRange = (Tx -> SlotRange)
-> (SomeCardanoApiTx -> SlotRange) -> CardanoTx -> SlotRange
forall r. (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
onCardanoTx Tx -> SlotRange
txValidRange
(\(SomeTx (C.Tx (C.TxBody C.TxBodyContent {TxIns ViewTx era
[TxOut CtxTx era]
(TxValidityLowerBound era, TxValidityUpperBound era)
TxScriptValidity era
BuildTxWith ViewTx (Maybe ProtocolParameters)
TxInsCollateral era
TxInsReference ViewTx era
TxReturnCollateral CtxTx era
TxTotalCollateral era
TxFee era
TxMetadataInEra era
TxAuxScripts era
TxExtraKeyWitnesses era
TxWithdrawals ViewTx era
TxCertificates ViewTx era
TxUpdateProposal era
TxMintValue ViewTx era
txScriptValidity :: TxScriptValidity era
txMintValue :: TxMintValue ViewTx era
txUpdateProposal :: TxUpdateProposal era
txCertificates :: TxCertificates ViewTx era
txWithdrawals :: TxWithdrawals ViewTx era
txProtocolParams :: BuildTxWith ViewTx (Maybe ProtocolParameters)
txExtraKeyWits :: TxExtraKeyWitnesses era
txAuxScripts :: TxAuxScripts era
txMetadata :: TxMetadataInEra era
txValidityRange :: (TxValidityLowerBound era, TxValidityUpperBound era)
txFee :: TxFee era
txReturnCollateral :: TxReturnCollateral CtxTx era
txTotalCollateral :: TxTotalCollateral era
txOuts :: [TxOut CtxTx era]
txInsReference :: TxInsReference ViewTx era
txInsCollateral :: TxInsCollateral era
txIns :: TxIns ViewTx era
txIns :: forall build era. TxBodyContent build era -> TxIns build era
txInsCollateral :: forall build era. TxBodyContent build era -> TxInsCollateral era
txInsReference :: forall build era.
TxBodyContent build era -> TxInsReference build era
txOuts :: forall build era. TxBodyContent build era -> [TxOut CtxTx era]
txTotalCollateral :: forall build era. TxBodyContent build era -> TxTotalCollateral era
txReturnCollateral :: forall build era.
TxBodyContent build era -> TxReturnCollateral CtxTx era
txFee :: forall build era. TxBodyContent build era -> TxFee era
txValidityRange :: forall build era.
TxBodyContent build era
-> (TxValidityLowerBound era, TxValidityUpperBound era)
txMetadata :: forall build era. TxBodyContent build era -> TxMetadataInEra era
txAuxScripts :: forall build era. TxBodyContent build era -> TxAuxScripts era
txExtraKeyWits :: forall build era.
TxBodyContent build era -> TxExtraKeyWitnesses era
txProtocolParams :: forall build era.
TxBodyContent build era
-> BuildTxWith build (Maybe ProtocolParameters)
txWithdrawals :: forall build era.
TxBodyContent build era -> TxWithdrawals build era
txCertificates :: forall build era.
TxBodyContent build era -> TxCertificates build era
txUpdateProposal :: forall build era. TxBodyContent build era -> TxUpdateProposal era
txMintValue :: forall build era. TxBodyContent build era -> TxMintValue build era
txScriptValidity :: forall build era. TxBodyContent build era -> TxScriptValidity era
..}) [KeyWitness era]
_) EraInMode era CardanoMode
_) -> (TxValidityLowerBound era, TxValidityUpperBound era) -> SlotRange
forall era.
(TxValidityLowerBound era, TxValidityUpperBound era) -> SlotRange
CardanoAPI.fromCardanoValidityRange (TxValidityLowerBound era, TxValidityUpperBound era)
txValidityRange)
getCardanoTxData :: CardanoTx -> Map V1.DatumHash V1.Datum
getCardanoTxData :: CardanoTx -> Map DatumHash Datum
getCardanoTxData = (Tx -> Map DatumHash Datum)
-> (SomeCardanoApiTx -> Map DatumHash Datum)
-> CardanoTx
-> Map DatumHash Datum
forall r. (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
onCardanoTx Tx -> Map DatumHash Datum
txData
(\(SomeTx (C.Tx TxBody era
txBody [KeyWitness era]
_) EraInMode era CardanoMode
_) -> (Map DatumHash Datum, Redeemers) -> Map DatumHash Datum
forall a b. (a, b) -> a
fst ((Map DatumHash Datum, Redeemers) -> Map DatumHash Datum)
-> (Map DatumHash Datum, Redeemers) -> Map DatumHash Datum
forall a b. (a -> b) -> a -> b
$ TxBody era -> (Map DatumHash Datum, Redeemers)
forall era. TxBody era -> (Map DatumHash Datum, Redeemers)
CardanoAPI.scriptDataFromCardanoTxBody TxBody era
txBody)
txBodyContentIns :: Lens' (C.TxBodyContent C.BuildTx C.BabbageEra) [(C.TxIn, C.BuildTxWith C.BuildTx (C.Witness C.WitCtxTxIn C.BabbageEra))]
txBodyContentIns :: ([(TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn BabbageEra))]
-> f [(TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn BabbageEra))])
-> TxBodyContent BuildTx BabbageEra
-> f (TxBodyContent BuildTx BabbageEra)
txBodyContentIns = (TxBodyContent BuildTx BabbageEra
-> [(TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn BabbageEra))])
-> (TxBodyContent BuildTx BabbageEra
-> [(TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn BabbageEra))]
-> TxBodyContent BuildTx BabbageEra)
-> Lens
(TxBodyContent BuildTx BabbageEra)
(TxBodyContent BuildTx BabbageEra)
[(TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn BabbageEra))]
[(TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn BabbageEra))]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens TxBodyContent BuildTx BabbageEra
-> [(TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn BabbageEra))]
forall build era. TxBodyContent build era -> TxIns build era
C.txIns (\TxBodyContent BuildTx BabbageEra
bodyContent [(TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn BabbageEra))]
ins -> TxBodyContent BuildTx BabbageEra
bodyContent { txIns :: [(TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn BabbageEra))]
C.txIns = [(TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn BabbageEra))]
ins })
txBodyContentCollateralIns :: Lens' (C.TxBodyContent C.BuildTx C.BabbageEra) [C.TxIn]
txBodyContentCollateralIns :: ([TxIn] -> f [TxIn])
-> TxBodyContent BuildTx BabbageEra
-> f (TxBodyContent BuildTx BabbageEra)
txBodyContentCollateralIns = (TxBodyContent BuildTx BabbageEra -> [TxIn])
-> (TxBodyContent BuildTx BabbageEra
-> [TxIn] -> TxBodyContent BuildTx BabbageEra)
-> Lens
(TxBodyContent BuildTx BabbageEra)
(TxBodyContent BuildTx BabbageEra)
[TxIn]
[TxIn]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
(\TxBodyContent BuildTx BabbageEra
bodyContent -> case TxBodyContent BuildTx BabbageEra -> TxInsCollateral BabbageEra
forall build era. TxBodyContent build era -> TxInsCollateral era
C.txInsCollateral TxBodyContent BuildTx BabbageEra
bodyContent of TxInsCollateral BabbageEra
C.TxInsCollateralNone -> []; C.TxInsCollateral CollateralSupportedInEra BabbageEra
_ [TxIn]
txIns -> [TxIn]
txIns)
(\TxBodyContent BuildTx BabbageEra
bodyContent [TxIn]
ins -> TxBodyContent BuildTx BabbageEra
bodyContent { txInsCollateral :: TxInsCollateral BabbageEra
C.txInsCollateral = case [TxIn]
ins of [] -> TxInsCollateral BabbageEra
forall era. TxInsCollateral era
C.TxInsCollateralNone; [TxIn]
_ -> CollateralSupportedInEra BabbageEra
-> [TxIn] -> TxInsCollateral BabbageEra
forall era.
CollateralSupportedInEra era -> [TxIn] -> TxInsCollateral era
C.TxInsCollateral CollateralSupportedInEra BabbageEra
C.CollateralInBabbageEra [TxIn]
ins })
txBodyContentOuts :: Lens' (C.TxBodyContent ctx C.BabbageEra) [TxOut]
txBodyContentOuts :: ([TxOut] -> f [TxOut])
-> TxBodyContent ctx BabbageEra -> f (TxBodyContent ctx BabbageEra)
txBodyContentOuts = (TxBodyContent ctx BabbageEra -> [TxOut])
-> (TxBodyContent ctx BabbageEra
-> [TxOut] -> TxBodyContent ctx BabbageEra)
-> Lens
(TxBodyContent ctx BabbageEra)
(TxBodyContent ctx BabbageEra)
[TxOut]
[TxOut]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ((TxOut CtxTx BabbageEra -> TxOut)
-> [TxOut CtxTx BabbageEra] -> [TxOut]
forall a b. (a -> b) -> [a] -> [b]
map TxOut CtxTx BabbageEra -> TxOut
TxOut ([TxOut CtxTx BabbageEra] -> [TxOut])
-> (TxBodyContent ctx BabbageEra -> [TxOut CtxTx BabbageEra])
-> TxBodyContent ctx BabbageEra
-> [TxOut]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxBodyContent ctx BabbageEra -> [TxOut CtxTx BabbageEra]
forall build era. TxBodyContent build era -> [TxOut CtxTx era]
C.txOuts) (\TxBodyContent ctx BabbageEra
bodyContent [TxOut]
outs -> TxBodyContent ctx BabbageEra
bodyContent { txOuts :: [TxOut CtxTx BabbageEra]
C.txOuts = (TxOut -> TxOut CtxTx BabbageEra)
-> [TxOut] -> [TxOut CtxTx BabbageEra]
forall a b. (a -> b) -> [a] -> [b]
map TxOut -> TxOut CtxTx BabbageEra
getTxOut [TxOut]
outs })
getCardanoTxRedeemers :: CardanoTx -> Map V1.ScriptPurpose V1.Redeemer
getCardanoTxRedeemers :: CardanoTx -> Map ScriptPurpose Redeemer
getCardanoTxRedeemers = (Tx -> Map ScriptPurpose Redeemer)
-> (SomeCardanoApiTx -> Map ScriptPurpose Redeemer)
-> CardanoTx
-> Map ScriptPurpose Redeemer
forall r. (Tx -> r) -> (SomeCardanoApiTx -> r) -> CardanoTx -> r
onCardanoTx Tx -> Map ScriptPurpose Redeemer
txRedeemers (Map ScriptPurpose Redeemer
-> SomeCardanoApiTx -> Map ScriptPurpose Redeemer
forall a b. a -> b -> a
const Map ScriptPurpose Redeemer
forall k a. Map k a
Map.empty)
instance Pretty Tx where
pretty :: Tx -> Doc ann
pretty tx :: Tx
tx@(Tx [TxInput]
_txInputs [TxInput]
_txReferenceInputs [TxInput]
_txCollateralInputs [TxOut]
_txOutputs
Maybe TxOut
_txReturnCollateral Maybe Value
_txTotalCollateral Value
_txMint Value
_txFee
SlotRange
_txValidRange Map MintingPolicyHash (Redeemer, Maybe (Versioned TxOutRef))
_txMintingScripts [Withdrawal]
_txWithdrawals [Certificate]
_txCertificates
Map PubKey Signature
_txSignatures ScriptsMap
_txScripts Map DatumHash Datum
_txData Maybe BuiltinByteString
_txMetadata) =
let showNonEmpty :: Bool -> a -> [a]
showNonEmpty Bool
empty a
x = [a
x | Bool -> Bool
not Bool
empty]
lines' :: [Doc ann]
lines' =
[ Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"inputs:" Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: (TxInput -> Doc ann) -> [TxInput] -> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TxInput -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty [TxInput]
_txInputs))
, Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"reference inputs:" Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: (TxInput -> Doc ann) -> [TxInput] -> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TxInput -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty [TxInput]
_txReferenceInputs))
, Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"collateral inputs:" Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: (TxInput -> Doc ann) -> [TxInput] -> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TxInput -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty [TxInput]
_txCollateralInputs))
, Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"outputs:" Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: (TxOut -> Doc ann) -> [TxOut] -> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TxOut -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty [TxOut]
_txOutputs))
]
[Doc ann] -> [Doc ann] -> [Doc ann]
forall a. Semigroup a => a -> a -> a
<> [Doc ann] -> (TxOut -> [Doc ann]) -> Maybe TxOut -> [Doc ann]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\TxOut
out -> [Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"return collateral:", TxOut -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxOut
out])]) Maybe TxOut
_txReturnCollateral
[Doc ann] -> [Doc ann] -> [Doc ann]
forall a. Semigroup a => a -> a -> a
<> [Doc ann] -> (Value -> [Doc ann]) -> Maybe Value -> [Doc ann]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\Value
val -> [Doc ann
"total collateral:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Value -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Value
val]) Maybe Value
_txTotalCollateral
[Doc ann] -> [Doc ann] -> [Doc ann]
forall a. Semigroup a => a -> a -> a
<> [ Doc ann
"mint:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Value -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Value
_txMint
, Doc ann
"fee:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Value -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Value
_txFee
, Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"mps:"Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: ((MintingPolicyHash, (Redeemer, Maybe (Versioned TxOutRef)))
-> Doc ann)
-> [(MintingPolicyHash, (Redeemer, Maybe (Versioned TxOutRef)))]
-> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (MintingPolicyHash, (Redeemer, Maybe (Versioned TxOutRef)))
-> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Map MintingPolicyHash (Redeemer, Maybe (Versioned TxOutRef))
-> [(MintingPolicyHash, (Redeemer, Maybe (Versioned TxOutRef)))]
forall k a. Map k a -> [(k, a)]
Map.assocs Map MintingPolicyHash (Redeemer, Maybe (Versioned TxOutRef))
_txMintingScripts)))
, Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"signatures:"Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: ((PubKey, Signature) -> Doc ann)
-> [(PubKey, Signature)] -> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (PubKey -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (PubKey -> Doc ann)
-> ((PubKey, Signature) -> PubKey)
-> (PubKey, Signature)
-> Doc ann
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PubKey, Signature) -> PubKey
forall a b. (a, b) -> a
fst) (Map PubKey Signature -> [(PubKey, Signature)]
forall k a. Map k a -> [(k, a)]
Map.toList Map PubKey Signature
_txSignatures)))
, Doc ann
"validity range:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> SlotRange -> Doc ann
forall a ann. Show a => a -> Doc ann
viaShow SlotRange
_txValidRange
]
[Doc ann] -> [Doc ann] -> [Doc ann]
forall a. Semigroup a => a -> a -> a
<> (Bool -> Doc ann -> [Doc ann]
forall a. Bool -> a -> [a]
showNonEmpty (Map DatumHash Datum -> Bool
forall k a. Map k a -> Bool
Map.null Map DatumHash Datum
_txData) (Doc ann -> [Doc ann]) -> Doc ann -> [Doc ann]
forall a b. (a -> b) -> a -> b
$ Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"data:"Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: ((DatumHash, Datum) -> Doc ann)
-> [(DatumHash, Datum)] -> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (DatumHash, Datum) -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (Map DatumHash Datum -> [(DatumHash, Datum)]
forall k a. Map k a -> [(k, a)]
Map.toList Map DatumHash Datum
_txData))))
[Doc ann] -> [Doc ann] -> [Doc ann]
forall a. Semigroup a => a -> a -> a
<> (Bool -> Doc ann -> [Doc ann]
forall a. Bool -> a -> [a]
showNonEmpty (ScriptsMap -> Bool
forall k a. Map k a -> Bool
Map.null ScriptsMap
_txScripts) (Doc ann -> [Doc ann]) -> Doc ann -> [Doc ann]
forall a b. (a -> b) -> a -> b
$ Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"attached scripts:"Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: ((ScriptHash, Language) -> Doc ann)
-> [(ScriptHash, Language)] -> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ScriptHash, Language) -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ((Versioned Script -> Language)
-> (ScriptHash, Versioned Script) -> (ScriptHash, Language)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Versioned Script -> Language
forall script. Versioned script -> Language
version ((ScriptHash, Versioned Script) -> (ScriptHash, Language))
-> [(ScriptHash, Versioned Script)] -> [(ScriptHash, Language)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ScriptsMap -> [(ScriptHash, Versioned Script)]
forall k a. Map k a -> [(k, a)]
Map.toList ScriptsMap
_txScripts))))
[Doc ann] -> [Doc ann] -> [Doc ann]
forall a. Semigroup a => a -> a -> a
<> (Bool -> Doc ann -> [Doc ann]
forall a. Bool -> a -> [a]
showNonEmpty ([Withdrawal] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Withdrawal]
_txWithdrawals) (Doc ann -> [Doc ann]) -> Doc ann -> [Doc ann]
forall a b. (a -> b) -> a -> b
$ Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"withdrawals:"Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: (Withdrawal -> Doc ann) -> [Withdrawal] -> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Withdrawal -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty [Withdrawal]
_txWithdrawals)))
[Doc ann] -> [Doc ann] -> [Doc ann]
forall a. Semigroup a => a -> a -> a
<> (Bool -> Doc ann -> [Doc ann]
forall a. Bool -> a -> [a]
showNonEmpty ([Certificate] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Certificate]
_txCertificates) (Doc ann -> [Doc ann]) -> Doc ann -> [Doc ann]
forall a b. (a -> b) -> a -> b
$ Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep (Doc ann
"certificates:"Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
: (Certificate -> Doc ann) -> [Certificate] -> [Doc ann]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Certificate -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty [Certificate]
_txCertificates)))
[Doc ann] -> [Doc ann] -> [Doc ann]
forall a. Semigroup a => a -> a -> a
<> ([Doc ann
"metadata: present" | Maybe BuiltinByteString -> Bool
forall a. Maybe a -> Bool
isJust Maybe BuiltinByteString
_txMetadata])
txid :: TxId
txid = Tx -> TxId
txId Tx
tx
in Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
nest Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"Tx" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> TxId -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxId
txid Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> Doc ann
forall ann. Doc ann
colon, Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
braces ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann]
lines')]
txId :: Tx -> V1.Tx.TxId
txId :: Tx -> TxId
txId Tx
tx = BuiltinByteString -> TxId
TxId (BuiltinByteString -> TxId) -> BuiltinByteString -> TxId
forall a b. (a -> b) -> a -> b
$ ByteString -> BuiltinByteString
forall a arep. ToBuiltin a arep => a -> arep
V1.toBuiltin
(ByteString -> BuiltinByteString)
-> ByteString -> BuiltinByteString
forall a b. (a -> b) -> a -> b
$ Proxy SHA256 -> ByteString -> ByteString
forall h (proxy :: * -> *).
HashAlgorithm h =>
proxy h -> ByteString -> ByteString
digest (Proxy SHA256
forall k (t :: k). Proxy t
Proxy @SHA256)
(ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Proxy SHA256 -> ByteString -> ByteString
forall h (proxy :: * -> *).
HashAlgorithm h =>
proxy h -> ByteString -> ByteString
digest (Proxy SHA256
forall k (t :: k). Proxy t
Proxy @SHA256)
(Encoding -> ByteString
Write.toStrictByteString (Encoding -> ByteString) -> Encoding -> ByteString
forall a b. (a -> b) -> a -> b
$ TxStripped -> Encoding
forall a. Serialise a => a -> Encoding
encode (TxStripped -> Encoding) -> TxStripped -> Encoding
forall a b. (a -> b) -> a -> b
$ Tx -> TxStripped
strip Tx
tx)
updateUtxo :: CardanoTx -> Map V1.Tx.TxOutRef TxOut -> Map V1.Tx.TxOutRef TxOut
updateUtxo :: CardanoTx -> Map TxOutRef TxOut -> Map TxOutRef TxOut
updateUtxo CardanoTx
tx Map TxOutRef TxOut
unspent = (Map TxOutRef TxOut
unspent Map TxOutRef TxOut -> Set TxOutRef -> Map TxOutRef TxOut
forall k a. Ord k => Map k a -> Set k -> Map k a
`Map.withoutKeys` CardanoTx -> Set TxOutRef
getCardanoTxSpentOutputs CardanoTx
tx) Map TxOutRef TxOut -> Map TxOutRef TxOut -> Map TxOutRef TxOut
forall k a. Ord k => Map k a -> Map k a -> Map k a
`Map.union` CardanoTx -> Map TxOutRef TxOut
getCardanoTxProducedOutputs CardanoTx
tx
updateUtxoCollateral :: CardanoTx -> Map V1.Tx.TxOutRef TxOut -> Map V1.Tx.TxOutRef TxOut
updateUtxoCollateral :: CardanoTx -> Map TxOutRef TxOut -> Map TxOutRef TxOut
updateUtxoCollateral CardanoTx
tx Map TxOutRef TxOut
unspent =
(Map TxOutRef TxOut
unspent Map TxOutRef TxOut -> Set TxOutRef -> Map TxOutRef TxOut
forall k a. Ord k => Map k a -> Set k -> Map k a
`Map.withoutKeys` ([TxOutRef] -> Set TxOutRef
forall a. Ord a => [a] -> Set a
Set.fromList ([TxOutRef] -> Set TxOutRef)
-> ([TxIn] -> [TxOutRef]) -> [TxIn] -> Set TxOutRef
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TxIn -> TxOutRef) -> [TxIn] -> [TxOutRef]
forall a b. (a -> b) -> [a] -> [b]
map TxIn -> TxOutRef
txInRef ([TxIn] -> Set TxOutRef) -> [TxIn] -> Set TxOutRef
forall a b. (a -> b) -> a -> b
$ CardanoTx -> [TxIn]
getCardanoTxCollateralInputs CardanoTx
tx))
Map TxOutRef TxOut -> Map TxOutRef TxOut -> Map TxOutRef TxOut
forall k a. Ord k => Map k a -> Map k a -> Map k a
`Map.union` CardanoTx -> Map TxOutRef TxOut
getCardanoTxProducedReturnCollateral CardanoTx
tx
txOutRefs :: Tx -> [(TxOut, V1.Tx.TxOutRef)]
txOutRefs :: Tx -> [(TxOut, TxOutRef)]
txOutRefs Tx
t = (Integer, TxOut) -> (TxOut, TxOutRef)
mkOut ((Integer, TxOut) -> (TxOut, TxOutRef))
-> [(Integer, TxOut)] -> [(TxOut, TxOutRef)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Integer] -> [TxOut] -> [(Integer, TxOut)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Integer
0..] (Tx -> [TxOut]
txOutputs Tx
t) where
mkOut :: (Integer, TxOut) -> (TxOut, TxOutRef)
mkOut (Integer
i, TxOut
o) = (TxOut
o, TxId -> Integer -> TxOutRef
V1.Tx.TxOutRef (Tx -> TxId
txId Tx
t) Integer
i)
unspentOutputsTx :: Tx -> Map V1.Tx.TxOutRef TxOut
unspentOutputsTx :: Tx -> Map TxOutRef TxOut
unspentOutputsTx Tx
t = [(TxOutRef, TxOut)] -> Map TxOutRef TxOut
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(TxOutRef, TxOut)] -> Map TxOutRef TxOut)
-> [(TxOutRef, TxOut)] -> Map TxOutRef TxOut
forall a b. (a -> b) -> a -> b
$ ((Integer, TxOut) -> (TxOutRef, TxOut))
-> [(Integer, TxOut)] -> [(TxOutRef, TxOut)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Integer, TxOut) -> (TxOutRef, TxOut)
f ([(Integer, TxOut)] -> [(TxOutRef, TxOut)])
-> [(Integer, TxOut)] -> [(TxOutRef, TxOut)]
forall a b. (a -> b) -> a -> b
$ [Integer] -> [TxOut] -> [(Integer, TxOut)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Integer
0..] ([TxOut] -> [(Integer, TxOut)]) -> [TxOut] -> [(Integer, TxOut)]
forall a b. (a -> b) -> a -> b
$ Tx -> [TxOut]
txOutputs Tx
t where
f :: (Integer, TxOut) -> (TxOutRef, TxOut)
f (Integer
idx, TxOut
o) = (TxId -> Integer -> TxOutRef
V1.Tx.TxOutRef (Tx -> TxId
txId Tx
t) Integer
idx, TxOut
o)
pubKeyTxOut :: V1.Value -> PaymentPubKey -> Maybe V1.StakingCredential -> Either ToCardanoError TxOut
pubKeyTxOut :: Value
-> PaymentPubKey
-> Maybe StakingCredential
-> Either ToCardanoError TxOut
pubKeyTxOut Value
v PaymentPubKey
pk Maybe StakingCredential
sk = do
CardanoAddress
aie <- NetworkId -> Address -> Either ToCardanoError CardanoAddress
CardanoAPI.toCardanoAddressInEra (NetworkMagic -> NetworkId
C.Testnet (NetworkMagic -> NetworkId) -> NetworkMagic -> NetworkId
forall a b. (a -> b) -> a -> b
$ Word32 -> NetworkMagic
C.NetworkMagic Word32
1) (Address -> Either ToCardanoError CardanoAddress)
-> Address -> Either ToCardanoError CardanoAddress
forall a b. (a -> b) -> a -> b
$ PaymentPubKey -> Maybe StakingCredential -> Address
pubKeyAddress PaymentPubKey
pk Maybe StakingCredential
sk
Value
txov <- Value -> Either ToCardanoError Value
CardanoAPI.toCardanoValue Value
v
TxOut -> Either ToCardanoError TxOut
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TxOut -> Either ToCardanoError TxOut)
-> TxOut -> Either ToCardanoError TxOut
forall a b. (a -> b) -> a -> b
$ TxOut CtxTx BabbageEra -> TxOut
TxOut (TxOut CtxTx BabbageEra -> TxOut)
-> TxOut CtxTx BabbageEra -> TxOut
forall a b. (a -> b) -> a -> b
$ CardanoAddress
-> TxOutValue BabbageEra
-> TxOutDatum CtxTx BabbageEra
-> ReferenceScript BabbageEra
-> TxOut CtxTx BabbageEra
forall ctx era.
AddressInEra era
-> TxOutValue era
-> TxOutDatum ctx era
-> ReferenceScript era
-> TxOut ctx era
C.TxOut CardanoAddress
aie (MultiAssetSupportedInEra BabbageEra
-> Value -> TxOutValue BabbageEra
forall era. MultiAssetSupportedInEra era -> Value -> TxOutValue era
C.TxOutValue MultiAssetSupportedInEra BabbageEra
C.MultiAssetInBabbageEra Value
txov) TxOutDatum CtxTx BabbageEra
forall ctx era. TxOutDatum ctx era
C.TxOutDatumNone ReferenceScript BabbageEra
forall era. ReferenceScript era
C.Api.ReferenceScriptNone
type PrivateKey = Crypto.XPrv
addCardanoTxSignature :: PrivateKey -> CardanoTx -> CardanoTx
addCardanoTxSignature :: PrivateKey -> CardanoTx -> CardanoTx
addCardanoTxSignature PrivateKey
privKey = (Tx -> Tx)
-> (SomeCardanoApiTx -> SomeCardanoApiTx) -> CardanoTx -> CardanoTx
cardanoTxMap (PrivateKey -> Tx -> Tx
addSignature' PrivateKey
privKey) SomeCardanoApiTx -> SomeCardanoApiTx
addSignatureCardano
where
addSignatureCardano :: SomeCardanoApiTx -> SomeCardanoApiTx
addSignatureCardano :: SomeCardanoApiTx -> SomeCardanoApiTx
addSignatureCardano (CardanoApiEmulatorEraTx Tx BabbageEra
ctx)
= Tx BabbageEra -> SomeCardanoApiTx
CardanoApiEmulatorEraTx (Tx BabbageEra -> Tx BabbageEra
addSignatureCardano' Tx BabbageEra
ctx)
addSignatureCardano' :: Tx BabbageEra -> Tx BabbageEra
addSignatureCardano' (C.Api.ShelleyTx ShelleyBasedEra BabbageEra
shelleyBasedEra (ValidatedTx body wits isValid aux))
= ShelleyBasedEra BabbageEra
-> Tx (ShelleyLedgerEra BabbageEra) -> Tx BabbageEra
forall era.
ShelleyBasedEra era -> Tx (ShelleyLedgerEra era) -> Tx era
C.Api.ShelleyTx ShelleyBasedEra BabbageEra
shelleyBasedEra (TxBody (BabbageEra StandardCrypto)
-> TxWitness (BabbageEra StandardCrypto)
-> IsValid
-> StrictMaybe (AuxiliaryData (BabbageEra StandardCrypto))
-> ValidatedTx (BabbageEra StandardCrypto)
forall era.
TxBody era
-> TxWitness era
-> IsValid
-> StrictMaybe (AuxiliaryData era)
-> ValidatedTx era
ValidatedTx TxBody (BabbageEra StandardCrypto)
body TxWitness (BabbageEra StandardCrypto)
wits' IsValid
isValid StrictMaybe (AuxiliaryData (BabbageEra StandardCrypto))
aux)
where
wits' :: TxWitness (BabbageEra StandardCrypto)
wits' = TxWitness (BabbageEra StandardCrypto)
wits TxWitness (BabbageEra StandardCrypto)
-> TxWitness (BabbageEra StandardCrypto)
-> TxWitness (BabbageEra StandardCrypto)
forall a. Semigroup a => a -> a -> a
<> TxWitness (BabbageEra StandardCrypto)
forall a. Monoid a => a
mempty { txwitsVKey :: Set (WitVKey 'Witness (Crypto (BabbageEra StandardCrypto)))
txwitsVKey = Set (WitVKey 'Witness StandardCrypto)
Set (WitVKey 'Witness (Crypto (BabbageEra StandardCrypto)))
newWits }
newWits :: Set (WitVKey 'Witness StandardCrypto)
newWits = case PrivateKey
-> TxBody (BabbageEra StandardCrypto) -> KeyWitness BabbageEra
fromPaymentPrivateKey PrivateKey
privKey TxBody (BabbageEra StandardCrypto)
TxBody (BabbageEra StandardCrypto)
body of
C.Api.ShelleyKeyWitness ShelleyBasedEra BabbageEra
_ WitVKey 'Witness StandardCrypto
wit -> WitVKey 'Witness StandardCrypto
-> Set (WitVKey 'Witness StandardCrypto)
forall a. a -> Set a
Set.singleton WitVKey 'Witness StandardCrypto
wit
KeyWitness BabbageEra
_ -> Set (WitVKey 'Witness StandardCrypto)
forall a. Set a
Set.empty
fromPaymentPrivateKey :: PrivateKey
-> TxBody (BabbageEra StandardCrypto) -> KeyWitness BabbageEra
fromPaymentPrivateKey PrivateKey
xprv TxBody (BabbageEra StandardCrypto)
txBody
= TxBody BabbageEra
-> ShelleyWitnessSigningKey -> KeyWitness BabbageEra
forall era.
IsShelleyBasedEra era =>
TxBody era -> ShelleyWitnessSigningKey -> KeyWitness era
C.Api.makeShelleyKeyWitness
(ShelleyBasedEra BabbageEra
-> TxBody (ShelleyLedgerEra BabbageEra)
-> [Script (ShelleyLedgerEra BabbageEra)]
-> TxBodyScriptData BabbageEra
-> Maybe (AuxiliaryData (ShelleyLedgerEra BabbageEra))
-> TxScriptValidity BabbageEra
-> TxBody BabbageEra
forall era.
ShelleyBasedEra era
-> TxBody (ShelleyLedgerEra era)
-> [Script (ShelleyLedgerEra era)]
-> TxBodyScriptData era
-> Maybe (AuxiliaryData (ShelleyLedgerEra era))
-> TxScriptValidity era
-> TxBody era
C.Api.ShelleyTxBody ShelleyBasedEra BabbageEra
C.Api.ShelleyBasedEraBabbage TxBody (BabbageEra StandardCrypto)
TxBody (ShelleyLedgerEra BabbageEra)
txBody [Script (ShelleyLedgerEra BabbageEra)]
forall a. a
notUsed TxBodyScriptData BabbageEra
forall a. a
notUsed Maybe (AuxiliaryData (ShelleyLedgerEra BabbageEra))
forall a. a
notUsed TxScriptValidity BabbageEra
forall a. a
notUsed)
(SigningKey PaymentExtendedKey -> ShelleyWitnessSigningKey
C.Api.WitnessPaymentExtendedKey (PrivateKey -> SigningKey PaymentExtendedKey
C.Api.PaymentExtendedSigningKey PrivateKey
xprv))
where
notUsed :: a
notUsed = a
forall a. HasCallStack => a
undefined
addSignature :: PrivateKey -> Passphrase -> Tx -> Tx
addSignature :: PrivateKey -> Passphrase -> Tx -> Tx
addSignature PrivateKey
privK Passphrase
passPhrase Tx
tx = Tx
tx Tx -> (Tx -> Tx) -> Tx
forall a b. a -> (a -> b) -> b
& (Map PubKey Signature -> Identity (Map PubKey Signature))
-> Tx -> Identity Tx
Lens' Tx (Map PubKey Signature)
signatures ((Map PubKey Signature -> Identity (Map PubKey Signature))
-> Tx -> Identity Tx)
-> ((Maybe Signature -> Identity (Maybe Signature))
-> Map PubKey Signature -> Identity (Map PubKey Signature))
-> (Maybe Signature -> Identity (Maybe Signature))
-> Tx
-> Identity Tx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (Map PubKey Signature)
-> Lens'
(Map PubKey Signature) (Maybe (IxValue (Map PubKey Signature)))
forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at Index (Map PubKey Signature)
PubKey
pubK ((Maybe Signature -> Identity (Maybe Signature))
-> Tx -> Identity Tx)
-> Signature -> Tx -> Tx
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Signature
sig where
sig :: Signature
sig = TxId -> PrivateKey -> Passphrase -> Signature
signTx (Tx -> TxId
txId Tx
tx) PrivateKey
privK Passphrase
passPhrase
pubK :: PubKey
pubK = PrivateKey -> PubKey
toPublicKey PrivateKey
privK
addSignature' :: PrivateKey -> Tx -> Tx
addSignature' :: PrivateKey -> Tx -> Tx
addSignature' PrivateKey
privK Tx
tx = Tx
tx Tx -> (Tx -> Tx) -> Tx
forall a b. a -> (a -> b) -> b
& (Map PubKey Signature -> Identity (Map PubKey Signature))
-> Tx -> Identity Tx
Lens' Tx (Map PubKey Signature)
signatures ((Map PubKey Signature -> Identity (Map PubKey Signature))
-> Tx -> Identity Tx)
-> ((Maybe Signature -> Identity (Maybe Signature))
-> Map PubKey Signature -> Identity (Map PubKey Signature))
-> (Maybe Signature -> Identity (Maybe Signature))
-> Tx
-> Identity Tx
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (Map PubKey Signature)
-> Lens'
(Map PubKey Signature) (Maybe (IxValue (Map PubKey Signature)))
forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at Index (Map PubKey Signature)
PubKey
pubK ((Maybe Signature -> Identity (Maybe Signature))
-> Tx -> Identity Tx)
-> Signature -> Tx -> Tx
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Signature
sig where
sig :: Signature
sig = TxId -> PrivateKey -> Signature
signTx' (Tx -> TxId
txId Tx
tx) PrivateKey
privK
pubK :: PubKey
pubK = PrivateKey -> PubKey
toPublicKey PrivateKey
privK