diff --git a/lib/core-integration/src/Test/Integration/Framework/TestData.hs b/lib/core-integration/src/Test/Integration/Framework/TestData.hs index 525857a95ef..a867ab16058 100644 --- a/lib/core-integration/src/Test/Integration/Framework/TestData.hs +++ b/lib/core-integration/src/Test/Integration/Framework/TestData.hs @@ -97,7 +97,6 @@ module Test.Integration.Framework.TestData , errMsg403TemplateInvalidDuplicateXPub , errMsg403TemplateInvalidScript , errMsg403InvalidConstructTx - , errMsg403transactionAlreadyBalanced ) where import Prelude @@ -622,10 +621,6 @@ errMsg400ScriptNotUniformRoles :: String errMsg400ScriptNotUniformRoles = "All keys of a script must have the same role: either payment or delegation." -errMsg403transactionAlreadyBalanced :: String -errMsg403transactionAlreadyBalanced = - "The transaction is already balanced. Please send a transaction that requires more inputs/outputs to be picked to be balanced." - -------------------------------------------------------------------------------- -- Transaction metadata -------------------------------------------------------------------------------- diff --git a/lib/core-integration/src/Test/Integration/Scenario/API/Shelley/TransactionsNew.hs b/lib/core-integration/src/Test/Integration/Scenario/API/Shelley/TransactionsNew.hs index 39a9c7cbdb7..98dd66ab92e 100644 --- a/lib/core-integration/src/Test/Integration/Scenario/API/Shelley/TransactionsNew.hs +++ b/lib/core-integration/src/Test/Integration/Scenario/API/Shelley/TransactionsNew.hs @@ -28,31 +28,49 @@ import Cardano.Crypto.DSIGN.Class import Cardano.Mnemonic ( SomeMnemonic (..), mnemonicToText ) import Cardano.Wallet.Api.Types - ( ApiCoinSelection (withdrawals) + ( ApiAddress (..) + , ApiCoinSelection (withdrawals) , ApiCoinSelectionInput (..) , ApiConstructTransaction (..) - , ApiSerialisedTransaction + , ApiDecodedTransaction + , ApiSerialisedTransaction (..) , ApiStakePool , ApiT (..) , ApiTransaction + , ApiTxInputGeneral (..) + , ApiTxMetadata (..) + , ApiTxOutputGeneral (..) , ApiWallet + , ApiWalletOutput (..) , DecodeAddress , DecodeStakeAddress , EncodeAddress (..) , EncodeStakeAddress + , ResourceContext (..) , WalletStyle (..) ) import Cardano.Wallet.Primitive.AddressDerivation - ( HardDerivation (..), PaymentAddress (..), Role (..), WalletKey (..) ) + ( DerivationIndex (..) + , HardDerivation (..) + , PaymentAddress (..) + , Role (..) + , WalletKey (..) + ) import Cardano.Wallet.Primitive.AddressDerivation.Icarus ( IcarusKey ) import Cardano.Wallet.Primitive.Types.Address ( Address (..) ) import Cardano.Wallet.Primitive.Types.Coin ( Coin (..) ) +import Cardano.Wallet.Primitive.Types.Hash + ( Hash (..) ) import Cardano.Wallet.Primitive.Types.Tx ( Direction (..) , SealedTx + , TxIn (..) + , TxMetadata (..) + , TxMetadataValue (..) + , TxScriptValidity (..) , TxStatus (..) , cardanoTx , getSealedTxBody @@ -89,9 +107,9 @@ import Data.Text import Numeric.Natural ( Natural ) import Test.Hspec - ( SpecWith, describe, pendingWith ) + ( SpecWith, describe, pendingWith, shouldContain, shouldNotContain ) import Test.Hspec.Expectations.Lifted - ( shouldBe, shouldNotBe, shouldSatisfy ) + ( shouldBe, shouldNotBe, shouldNotSatisfy, shouldSatisfy ) import Test.Hspec.Extra ( it ) import Test.Integration.Framework.DSL @@ -133,7 +151,6 @@ import Test.Integration.Framework.TestData , errMsg403MinUTxOValue , errMsg403NotDelegating , errMsg403NotEnoughMoney - , errMsg403transactionAlreadyBalanced , errMsg404NoSuchPool ) @@ -145,6 +162,7 @@ import qualified Cardano.Wallet.Api.Link as Link import qualified Cardano.Wallet.Primitive.AddressDerivation.Shelley as Shelley import qualified Cardano.Wallet.Primitive.Types.TokenMap as TokenMap import qualified Data.Aeson as Aeson +import qualified Data.List.NonEmpty as NE import qualified Data.Map.Strict as Map import qualified Data.Set as Set import qualified Data.Text as T @@ -236,6 +254,16 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do Just (Cardano.TxMetaText "hello") -> pure () Just _ -> error "Tx metadata incorrect" + let txCbor = getFromResponse #transaction (HTTP.status202, Right $ ApiSerialisedTransaction signedTx) + let decodePayload = Json (toJSON $ ApiSerialisedTransaction txCbor) + let expMetadata = ApiT (TxMetadata (Map.fromList [(1,TxMetaText "hello")])) + rDecodedTx <- request @(ApiDecodedTransaction n) ctx + (Link.decodeTransaction @'Shelley wa) Default decodePayload + verify rDecodedTx + [ expectResponseCode HTTP.status202 + , expectField #metadata (`shouldBe` (ApiTxMetadata (Just expMetadata))) + ] + -- Submit tx void $ submitTx ctx signedTx [ expectResponseCode HTTP.status202 ] @@ -268,6 +296,15 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do signedTx <- signTx ctx wa apiTx [ expectResponseCode HTTP.status202 ] + let txCbor = getFromResponse #transaction (HTTP.status202, Right $ ApiSerialisedTransaction signedTx) + let decodePayload = Json (toJSON $ ApiSerialisedTransaction txCbor) + rDecodedTx <- request @(ApiDecodedTransaction n) ctx + (Link.decodeTransaction @'Shelley wa) Default decodePayload + verify rDecodedTx + [ expectResponseCode HTTP.status202 + , expectField #withdrawals (`shouldBe` []) + ] + -- Submit tx void $ submitTx ctx signedTx [ expectResponseCode HTTP.status202 ] @@ -305,6 +342,21 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do signedTx <- signTx ctx wa apiTx [ expectResponseCode HTTP.status202 ] + let txCbor = getFromResponse #transaction (HTTP.status202, Right $ ApiSerialisedTransaction signedTx) + let decodePayload = Json (toJSON $ ApiSerialisedTransaction txCbor) + let withdrawalWith ownership wdrls = case wdrls of + [wdrl] -> + wdrl ^. #amount == Quantity withdrawalAmt && + wdrl ^. #context == ownership + _ -> False + + rDecodedTx <- request @(ApiDecodedTransaction n) ctx + (Link.decodeTransaction @'Shelley wa) Default decodePayload + verify rDecodedTx + [ expectResponseCode HTTP.status202 + , expectField #withdrawals (`shouldSatisfy` (withdrawalWith Our)) + ] + -- Submit tx void $ submitTx ctx signedTx [ expectResponseCode HTTP.status202 ] @@ -329,6 +381,14 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do (`shouldBe` 0) ] + wb <- fixtureWallet ctx + rDecodedTx' <- request @(ApiDecodedTransaction n) ctx + (Link.decodeTransaction @'Shelley wb) Default decodePayload + verify rDecodedTx' + [ expectResponseCode HTTP.status202 + , expectField #withdrawals (`shouldSatisfy` (withdrawalWith External)) + ] + it "TRANS_NEW_CREATE_03b - Withdrawal from external wallet" $ \ctx -> runResourceT $ do liftIO $ pendingWith "ADP-1189: Issues with withdrawals from external wallets" @@ -377,7 +437,8 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do (`shouldBe` rewardInitialBalance) ] - it "TRANS_NEW_CREATE_04a - Single Output Transaction" $ \ctx -> runResourceT $ do + it "TRANS_NEW_CREATE_04a - Single Output Transaction with decode transaction" $ \ctx -> runResourceT $ do + let initialAmt = 3 * minUTxOValue (_mainEra ctx) wa <- fixtureWalletWith @n ctx [initialAmt] wb <- emptyWallet ctx @@ -395,8 +456,62 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do , expectField (#coinSelection . #change) (`shouldSatisfy` (not . null)) , expectField (#fee . #getQuantity) (`shouldSatisfy` (> 0)) ] - let expectedFee = getFromResponse (#fee . #getQuantity) rTx + let txCbor = getFromResponse #transaction rTx + let decodePayload = Json (toJSON $ ApiSerialisedTransaction txCbor) + let sharedExpectationsBetweenWallets = + [ expectResponseCode HTTP.status202 + , expectField (#fee . #getQuantity) (`shouldBe` expectedFee) + , expectField #withdrawals (`shouldBe` []) + , expectField #collateral (`shouldBe` []) + , expectField #metadata (`shouldBe` (ApiTxMetadata Nothing)) + , expectField #scriptValidity (`shouldBe` (Just $ ApiT TxScriptValid)) + ] + + -- After constructing tx the cbor is as expected, both wallets share common information + -- source wallet sees inputs as his, target wallet sees them as external + let isInpOurs inp = case inp of + ExternalInput _ -> False + WalletInput _ -> True + let areOurs = all isInpOurs + addrs <- listAddresses @n ctx wb + let addrIx = 1 + let addrDest = (addrs !! addrIx) ^. #id + let expectedTxOutTarget = WalletOutput $ ApiWalletOutput + { address = addrDest + , amount = Quantity amt + , assets = ApiT TokenMap.empty + , derivationPath = NE.fromList + [ ApiT (DerivationIndex 2147485500) + , ApiT (DerivationIndex 2147485463) + , ApiT (DerivationIndex 2147483648) + , ApiT (DerivationIndex 0) + , ApiT (DerivationIndex $ fromIntegral addrIx) + ] + } + let isOutOurs out = case out of + WalletOutput _ -> False + ExternalOutput _ -> True + + rDecodedTxSource <- request @(ApiDecodedTransaction n) ctx + (Link.decodeTransaction @'Shelley wa) Default decodePayload + verify rDecodedTxSource $ + sharedExpectationsBetweenWallets ++ + [ expectField #inputs (`shouldSatisfy` areOurs) + , expectField #outputs (`shouldNotContain` [expectedTxOutTarget]) + + -- Check that the change output is there: + , expectField (#outputs) ((`shouldBe` 1) . length . filter isOutOurs) + ] + + rDecodedTxTarget <- request @(ApiDecodedTransaction n) ctx + (Link.decodeTransaction @'Shelley wb) Default decodePayload + verify rDecodedTxTarget $ + sharedExpectationsBetweenWallets ++ + [ expectField #inputs (`shouldNotSatisfy` areOurs) + , expectField #outputs (`shouldContain` [expectedTxOutTarget]) + ] + let filterInitialAmt = filter (\(ApiCoinSelectionInput _ _ _ _ amt' _) -> amt' == Quantity initialAmt) let coinSelInputs = filterInitialAmt $ @@ -409,10 +524,10 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do void $ submitTx ctx signedTx [ expectResponseCode HTTP.status202 ] - eventually "Target wallet balance is increased by amt" $ do - rWb <- request @ApiWallet ctx + eventually "Target wallet balance is decreased by amt + fee" $ do + rWa <- request @ApiWallet ctx (Link.getWallet @'Shelley wb) Default Empty - verify rWb + verify rWa [ expectSuccess , expectField (#balance . #available . #getQuantity) @@ -429,6 +544,59 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do (`shouldBe` (initialAmt - amt - expectedFee)) ] + -- After signing tx the cbor is as before modulo added wtinesses, + -- and in line what was there after construction. Also as we tx was + -- accommodated in ledger output change in amount for target wallet + let expectedTxOutTarget' = WalletOutput $ ApiWalletOutput + { address = addrDest + , amount = Quantity amt + , assets = ApiT TokenMap.empty + , derivationPath = NE.fromList + [ ApiT (DerivationIndex 2147485500) + , ApiT (DerivationIndex 2147485463) + , ApiT (DerivationIndex 2147483648) + , ApiT (DerivationIndex 0) + , ApiT (DerivationIndex $ fromIntegral addrIx) + ] + } + addrsSourceAll <- listAddresses @n ctx wa + --we expect change address here with x=0 as this wallet does not participated in outcoming tx before this one + let derPath = NE.fromList + [ ApiT (DerivationIndex 2147485500) + , ApiT (DerivationIndex 2147485463) + , ApiT (DerivationIndex 2147483648) + , ApiT (DerivationIndex 1) + , ApiT (DerivationIndex 0) + ] + let addrSourceChange:_ = + filter (\(ApiAddress _ _ derPath') -> derPath == derPath') addrsSourceAll + let addrSrc = addrSourceChange ^. #id + let expectedTxOutSource = WalletOutput $ ApiWalletOutput + { address = addrSrc + , amount = Quantity $ initialAmt - (amt + fromIntegral expectedFee) + , assets = ApiT TokenMap.empty + , derivationPath = derPath + } + let txCbor' = getFromResponse #transaction (HTTP.status202, Right $ ApiSerialisedTransaction signedTx) + let decodePayload' = Json (toJSON $ ApiSerialisedTransaction txCbor') + rDecodedTxSource' <- request @(ApiDecodedTransaction n) ctx + (Link.decodeTransaction @'Shelley wa) Default decodePayload' + verify rDecodedTxSource' $ + sharedExpectationsBetweenWallets ++ + [ expectField #inputs (`shouldNotSatisfy` areOurs) -- the input is not anymore belonging to wallet + , expectField #outputs (`shouldNotContain` [expectedTxOutTarget']) + , expectField #outputs (`shouldContain` [expectedTxOutSource]) + ] + + rDecodedTxTarget' <- request @(ApiDecodedTransaction n) ctx + (Link.decodeTransaction @'Shelley wb) Default decodePayload' + verify rDecodedTxTarget' $ + sharedExpectationsBetweenWallets ++ + [ expectField #inputs (`shouldNotSatisfy` areOurs) + , expectField #outputs (`shouldContain` [expectedTxOutTarget']) + , expectField #outputs (`shouldNotContain` [expectedTxOutSource]) + ] + it "TRANS_NEW_CREATE_04b - Cannot spend less than minUTxOValue" $ \ctx -> runResourceT $ do wa <- fixtureWallet ctx wb <- emptyWallet ctx @@ -1075,24 +1243,23 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do -- update with sign / submit tx where applicable -- end to end join pool and get rewards - it "TRANS_NEW_BALANCE_01a - multiple-output transaction with all covering inputs present" $ \ctx -> runResourceT $ do - - liftIO $ pendingWith "ADP-1179: Behavior needs to be clarified" + it "TRANS_DECODE_01a - multiple-output transaction with all covering inputs" $ \ctx -> runResourceT $ do -- constructing source wallet let initialAmt = minUTxOValue (_mainEra ctx) wa <- fixtureWalletWith @n ctx [initialAmt] - -- the tx involes two outputs : + -- The normal tx was created for some wallets and they are different than the wa. + -- The transaction involves four outputs with the amounts : -- 999978 -- 999978 - -- results in two changes -- 49998927722 -- 49998927722 -- incurs the fee of -- 144600 - -- and involves one input + -- and involves one external input -- 100000000000 + -- no metadata, no collaterals, no withdrawals let serializedTxHex = "84a600818258200eaa33be8780935ca5a7c1e628a2d54402446f96236c\ \a8f1770e07fa22ba8648000d80018482583901a65f0e7aea387adbc109\ @@ -1106,21 +1273,22 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do \2b143b1ce1b68ccb62f8e8437b3089fc61d21ddfcbd4d43652bf05c40c\ \346fa794871423b65052d7614c1b0000000ba42b176a021a000234d803\ \198ceb0e80a0f5f6" :: Text - let balancePayload = Json [json|{ - "transaction": { "cborHex" : #{serializedTxHex}, "description": "", "type": "Tx AlonzoEra" }, - "inputs": [ - { "txIn" : "0eaa33be8780935ca5a7c1e628a2d54402446f96236ca8f1770e07fa22ba8648#0" - , "txOut" : - { "value" : { "lovelace": 100000000000 } - , "address": "addr1vx0d0kyppx3qls8laq5jvpq0qa52d0gahm8tsyj2jpg0lpg4ue9lt" - } - }] + + let theTxHash = Hash "\SO\170\&3\190\135\128\147\\\165\167\193\230(\162\213D\STXDo\150#l\168\241w\SO\a\250\"\186\134H" + + let decodePayload = Json [json|{ + "transaction": #{serializedTxHex} }|] - rTx <- request @(ApiConstructTransaction n) ctx - (Link.balanceTransaction @'Shelley wa) Default balancePayload + rTx <- request @(ApiDecodedTransaction n) ctx + (Link.decodeTransaction @'Shelley wa) Default decodePayload verify rTx - [ expectResponseCode HTTP.status403 - , expectErrorMessage errMsg403transactionAlreadyBalanced + [ expectResponseCode HTTP.status202 + , expectField (#fee . #getQuantity) (`shouldBe` 144600) + , expectField #withdrawals (`shouldBe` []) + , expectField #collateral (`shouldBe` []) + , expectField #metadata (`shouldBe` (ApiTxMetadata Nothing)) + , expectField #inputs + (`shouldBe` [ExternalInput (ApiT (TxIn theTxHash 0))]) ] it "TRANS_NEW_BALANCE_01d - single-output transaction with missing covering inputs" $ \ctx -> runResourceT $ do diff --git a/lib/core/src/Cardano/Wallet.hs b/lib/core/src/Cardano/Wallet.hs index dba914f1705..e561dd9cfbc 100644 --- a/lib/core/src/Cardano/Wallet.hs +++ b/lib/core/src/Cardano/Wallet.hs @@ -101,9 +101,12 @@ module Cardano.Wallet , importRandomAddresses , listAddresses , normalizeDelegationAddress + , lookupTxIns + , lookupTxOuts , ErrCreateRandomAddress(..) , ErrImportRandomAddress(..) , ErrImportAddress(..) + , ErrDecodeTx (..) -- ** Payment , getTxExpiry @@ -457,7 +460,7 @@ import Control.Monad.Trans.Except import Control.Monad.Trans.Maybe ( MaybeT (..), maybeToExceptT ) import Control.Monad.Trans.State - ( runState, state ) + ( evalState, runState, state ) import Control.Tracer ( Tracer, contramap, traceWith ) import Crypto.Hash @@ -559,7 +562,6 @@ import qualified Data.Set as Set import qualified Data.Text as T import qualified Data.Vector as V - -- $Development -- __Naming Conventions__ -- @@ -1169,6 +1171,52 @@ manageRewardBalance _ ctx wid = db & \DBLayer{..} -> do Address -------------------------------------------------------------------------------} +lookupTxIns + :: forall ctx s k . + ( HasDBLayer IO s k ctx + , IsOurs s Address + ) + => ctx + -> WalletId + -> [TxIn] + -> ExceptT ErrDecodeTx IO [(TxIn, Maybe (TxOut, NonEmpty DerivationIndex))] +lookupTxIns ctx wid txins = db & \DBLayer{..} -> do + cp <- mapExceptT atomically + $ withExceptT ErrDecodeTxNoSuchWallet + $ withNoSuchWallet wid + $ readCheckpoint wid + pure $ map (\i -> (i, lookupTxIn cp i)) txins + where + db = ctx ^. dbLayer @IO @s @k + lookupTxIn :: Wallet s -> TxIn -> Maybe (TxOut, NonEmpty DerivationIndex) + lookupTxIn cp txIn = do + out@(TxOut addr _) <- UTxO.lookup txIn (totalUTxO mempty cp) + path <- fst $ isOurs addr (getState cp) + return (out, path) + +lookupTxOuts + :: forall ctx s k . + ( HasDBLayer IO s k ctx + , IsOurs s Address + ) + => ctx + -> WalletId + -> [TxOut] + -> ExceptT ErrDecodeTx IO [(TxOut, Maybe (NonEmpty DerivationIndex))] +lookupTxOuts ctx wid txouts = db & \DBLayer{..} -> do + cp <- mapExceptT atomically + $ withExceptT ErrDecodeTxNoSuchWallet + $ withNoSuchWallet wid + $ readCheckpoint wid + -- NOTE: We evolve the state (in practice an address pool) as we loop + -- through the outputs, but we don't consider pending transactions. + -- /Theoretically/ the outputs might only be discoverable after discovering + -- outputs other pending transactions. + pure $ flip evalState (getState cp) $ forM txouts $ \out@(TxOut addr _) -> do + (out,) <$> state (isOurs addr) + where + db = ctx ^. dbLayer @IO @s @k + -- | List all addresses of a wallet with their metadata. Addresses -- are ordered from the most-recently-discovered to the oldest known. listAddresses @@ -2794,11 +2842,9 @@ data ErrSignPayment -- | Errors that can occur when balancing transaction. data ErrBalanceTx - = ErrBalanceTxTxAlreadyBalanced - | ErrBalanceTxUpdateError ErrUpdateSealedTx + = ErrBalanceTxUpdateError ErrUpdateSealedTx | ErrBalanceTxSelectAssets ErrSelectAssets | ErrBalanceTxAssignRedeemers ErrAssignRedeemers - | ErrBalanceTxNotImplemented deriving (Show, Eq) -- | Errors that can occur when constructing an unsigned transaction. @@ -2825,6 +2871,11 @@ data ErrWitnessTx | ErrWitnessTxIncorrectTTL PastHorizonException deriving (Show, Eq) +-- | Errors that can occur when decoding a transaction. +newtype ErrDecodeTx + = ErrDecodeTxNoSuchWallet ErrNoSuchWallet + deriving (Show, Eq) + -- | Errors that can occur when submitting a signed transaction to the network. data ErrSubmitTx = ErrSubmitTxNetwork ErrPostTx diff --git a/lib/core/src/Cardano/Wallet/Api.hs b/lib/core/src/Cardano/Wallet/Api.hs index c6a0f1f6c1e..fb6077fbd1c 100644 --- a/lib/core/src/Cardano/Wallet/Api.hs +++ b/lib/core/src/Cardano/Wallet/Api.hs @@ -61,6 +61,7 @@ module Cardano.Wallet.Api , CreateTransactionOld , PostTransactionFeeOld , BalanceTransaction + , DecodeTransaction , StakePools , ListStakePools @@ -177,6 +178,7 @@ import Cardano.Wallet.Api.Types , ApiCoinSelectionT , ApiConstructTransactionDataT , ApiConstructTransactionT + , ApiDecodedTransactionT , ApiFee , ApiHealthCheck , ApiMaintenanceAction @@ -528,6 +530,7 @@ type ShelleyTransactions n = :<|> CreateTransactionOld n :<|> PostTransactionFeeOld n :<|> BalanceTransaction n + :<|> DecodeTransaction n -- | https://input-output-hk.github.io/cardano-wallet/api/#operation/constructTransaction type ConstructTransaction n = "wallets" @@ -588,6 +591,13 @@ type BalanceTransaction n = "wallets" :> ReqBody '[JSON] (ApiBalanceTransactionPostDataT n) :> PostAccepted '[JSON] ApiSerialisedTransaction +-- | https://input-output-hk.github.io/cardano-wallet/api/#operation/decodeTransaction +type DecodeTransaction n = "wallets" + :> Capture "walletId" (ApiT WalletId) + :> "transactions-decode" + :> ReqBody '[JSON] ApiSerialisedTransaction + :> PostAccepted '[JSON] (ApiDecodedTransactionT n) + {------------------------------------------------------------------------------- Shelley Migrations diff --git a/lib/core/src/Cardano/Wallet/Api/Client.hs b/lib/core/src/Cardano/Wallet/Api/Client.hs index 812ba8b7d94..70fed7f1da0 100644 --- a/lib/core/src/Cardano/Wallet/Api/Client.hs +++ b/lib/core/src/Cardano/Wallet/Api/Client.hs @@ -67,6 +67,7 @@ import Cardano.Wallet.Api.Types , ApiCoinSelectionT , ApiConstructTransactionDataT , ApiConstructTransactionT + , ApiDecodedTransactionT , ApiFee , ApiNetworkClock , ApiNetworkInformation (..) @@ -194,6 +195,10 @@ data TransactionClient = TransactionClient :: ApiT WalletId -> ApiBalanceTransactionPostDataT Aeson.Value -> ClientM ApiSerialisedTransaction + , decodeTransaction + :: ApiT WalletId + -> ApiSerialisedTransaction + -> ClientM (ApiDecodedTransactionT Aeson.Value) } data AddressClient = AddressClient @@ -310,6 +315,7 @@ transactionClient = :<|> _postTransaction :<|> _postTransactionFee :<|> _balanceTransaction + :<|> _decodeTransaction = client (Proxy @("v2" :> (ShelleyTransactions Aeson.Value))) _postExternalTransaction @@ -325,6 +331,7 @@ transactionClient = , getTransaction = _getTransaction , constructTransaction = _constructTransaction , balanceTransaction = _balanceTransaction + , decodeTransaction = _decodeTransaction } fromSerialisedTx :: ApiBytesT base SerialisedTx -> ApiT SealedTx @@ -357,6 +364,7 @@ byronTransactionClient = , getTransaction = _getTransaction , constructTransaction = _constructTransaction , balanceTransaction = error "balance transaction endpoint not supported for byron" + , decodeTransaction = error "decode transaction endpoint not supported for byron" } -- | Produces an 'AddressClient n' working against the /wallets API @@ -458,3 +466,4 @@ type instance PostTransactionOldDataT Aeson.Value = Aeson.Value type instance PostTransactionFeeOldDataT Aeson.Value = Aeson.Value type instance ApiPutAddressesDataT Aeson.Value = Aeson.Value type instance ApiBalanceTransactionPostDataT Aeson.Value = Aeson.Value +type instance ApiDecodedTransactionT Aeson.Value = Aeson.Value diff --git a/lib/core/src/Cardano/Wallet/Api/Link.hs b/lib/core/src/Cardano/Wallet/Api/Link.hs index 5e340d8bfa4..97d978d4c75 100644 --- a/lib/core/src/Cardano/Wallet/Api/Link.hs +++ b/lib/core/src/Cardano/Wallet/Api/Link.hs @@ -83,6 +83,7 @@ module Cardano.Wallet.Api.Link , createUnsignedTransaction , signTransaction , balanceTransaction + , decodeTransaction -- * StakePools , listStakePools @@ -681,6 +682,21 @@ balanceTransaction w = discriminate @style where wid = w ^. typed @(ApiT WalletId) +decodeTransaction + :: forall style w. + ( HasCallStack + , HasType (ApiT WalletId) w + , Discriminate style + ) + => w + -> (Method, Text) +decodeTransaction w = discriminate @style + (endpoint @(Api.DecodeTransaction Net) (wid &)) + (notSupported "Byron") + (notSupported "Shared") + where + wid = w ^. typed @(ApiT WalletId) + -- -- Stake Pools -- diff --git a/lib/core/src/Cardano/Wallet/Api/Server.hs b/lib/core/src/Cardano/Wallet/Api/Server.hs index 5255f8cb7ab..888aa2d8064 100644 --- a/lib/core/src/Cardano/Wallet/Api/Server.hs +++ b/lib/core/src/Cardano/Wallet/Api/Server.hs @@ -92,6 +92,7 @@ module Cardano.Wallet.Api.Server , mkSharedWallet , mintBurnAssets , balanceTransaction + , decodeTransaction -- * Server error responses , IsServerError(..) @@ -136,6 +137,7 @@ import Cardano.Wallet , ErrConstructTx (..) , ErrCreateMigrationPlan (..) , ErrCreateRandomAddress (..) + , ErrDecodeTx (..) , ErrDerivePublicKey (..) , ErrFetchRewards (..) , ErrGetTransaction (..) @@ -209,6 +211,7 @@ import Cardano.Wallet.Api.Types , ApiCoinSelectionWithdrawal (..) , ApiConstructTransaction (..) , ApiConstructTransactionData (..) + , ApiDecodedTransaction (..) , ApiEpochInfo (ApiEpochInfo) , ApiEra (..) , ApiErrorCode (..) @@ -246,7 +249,9 @@ import Cardano.Wallet.Api.Types , ApiTxCollateral (..) , ApiTxId (..) , ApiTxInput (..) + , ApiTxInputGeneral (..) , ApiTxMetadata (..) + , ApiTxOutputGeneral (..) , ApiUtxoStatistics (..) , ApiWallet (..) , ApiWalletAssetsBalance (..) @@ -254,16 +259,19 @@ import Cardano.Wallet.Api.Types , ApiWalletDelegation (..) , ApiWalletDelegationNext (..) , ApiWalletDelegationStatus (..) + , ApiWalletInput (..) , ApiWalletMigrationBalance (..) , ApiWalletMigrationPlan (..) , ApiWalletMigrationPlanPostData (..) , ApiWalletMigrationPostData (..) + , ApiWalletOutput (..) , ApiWalletPassphrase (..) , ApiWalletPassphraseInfo (..) , ApiWalletSignData (..) , ApiWalletUtxoSnapshot (..) , ApiWalletUtxoSnapshotEntry (..) , ApiWithdrawal (..) + , ApiWithdrawalGeneral (..) , ApiWithdrawalPostData (..) , ByronWalletFromXPrvPostData , ByronWalletPostData (..) @@ -274,6 +282,7 @@ import Cardano.Wallet.Api.Types , MinWithdrawal (..) , PostTransactionFeeOldData (..) , PostTransactionOldData (..) + , ResourceContext (..) , VerificationKeyHashing (..) , WalletOrAccountPostData (..) , WalletPostData (..) @@ -337,7 +346,6 @@ import Cardano.Wallet.Primitive.AddressDiscovery.Sequential ( DerivationPrefix (..) , ParentContext (..) , SeqState (..) - , context , defaultAddressPoolGap , gap , mkSeqStateFromAccountXPub @@ -1060,7 +1068,7 @@ mkSharedWallet ctx wid cp meta pending progress = case getState cp of cp let available = availableBalance pending cp let total = totalBalance pending reward cp - let (ParentContextShared _ pTemplate dTemplateM) = context pool + let (ParentContextShared _ pTemplate dTemplateM) = pool ^. #context pure $ ApiSharedWallet $ Right $ ApiActiveSharedWallet { id = ApiT wid , name = ApiT $ meta ^. #name @@ -2246,6 +2254,66 @@ balanceTransaction ctx genChange (ApiT wid) body = do where nl = ctx ^. networkLayer +decodeTransaction + :: forall ctx s k n. + ( ctx ~ ApiLayer s k + , IsOurs s Address + , Typeable s + , Typeable n + ) + => ctx + -> ApiT WalletId + -> ApiSerialisedTransaction + -> Handler (ApiDecodedTransaction n) +decodeTransaction ctx (ApiT wid) (ApiSerialisedTransaction (ApiT sealed)) = do + let (Tx txid feeM colls inps outs wdrlMap meta vldt, _toMint, _toBurn) = decodeTx tl sealed + (txinsOutsPaths, collsOutsPaths, outsPath, acct) <- + withWorkerCtx ctx wid liftE liftE $ \wrk -> do + (acct, _, _) <- liftHandler $ W.readRewardAccount @_ @s @k @n wrk wid + txinsOutsPaths <- liftHandler $ W.lookupTxIns @_ @s @k wrk wid (fst <$> inps) + collsOutsPaths <- liftHandler $ W.lookupTxIns @_ @s @k wrk wid (fst <$> colls) + outsPath <- liftHandler $ W.lookupTxOuts @_ @s @k wrk wid outs + pure (txinsOutsPaths, collsOutsPaths, outsPath, acct) + pure $ ApiDecodedTransaction + { id = ApiT txid + , fee = maybe (Quantity 0) (Quantity . fromIntegral . unCoin) feeM + , inputs = map toInp txinsOutsPaths + , outputs = map toOut outsPath + , collateral = map toInp collsOutsPaths + , withdrawals = map (toWrdl acct) $ Map.assocs wdrlMap + , metadata = ApiTxMetadata $ ApiT <$> meta + , scriptValidity = ApiT <$> vldt + } + where + tl = ctx ^. W.transactionLayer @k + toOut (txoutIncoming, Nothing) = + ExternalOutput $ toAddressAmount @n txoutIncoming + toOut ((TxOut addr (TokenBundle (Coin c) tmap)), (Just path)) = + WalletOutput $ ApiWalletOutput + { address = (ApiT addr, Proxy @n) + , amount = Quantity $ fromIntegral c + , assets = ApiT tmap + , derivationPath = NE.map ApiT path + } + toInp (txin@(TxIn txid ix), txoutPathM) = + case txoutPathM of + Nothing -> + ExternalInput (ApiT txin) + Just (TxOut addr (TokenBundle (Coin c) tmap), path) -> + WalletInput $ ApiWalletInput + { id = ApiT txid + , index = ix + , address = (ApiT addr, Proxy @n) + , derivationPath = NE.map ApiT path + , amount = Quantity $ fromIntegral c + , assets = ApiT tmap + } + toWrdl acct (rewardKey, (Coin c)) = + if rewardKey == acct then + ApiWithdrawalGeneral (ApiT rewardKey, Proxy @n) (Quantity $ fromIntegral c) Our + else + ApiWithdrawalGeneral (ApiT rewardKey, Proxy @n) (Quantity $ fromIntegral c) External + joinStakePool :: forall ctx s n k. ( ctx ~ ApiLayer s k @@ -3132,14 +3200,14 @@ mkApiTransaction timeInterpreter setTimeReference tx = do , depth = Nothing , direction = ApiT (tx ^. (#txMeta . #direction)) , inputs = - [ ApiTxInput (fmap toAddressAmount o) (ApiT i) + [ ApiTxInput (fmap (toAddressAmount @n) o) (ApiT i) | (i, o) <- tx ^. #txInputs ] , collateral = [ ApiTxCollateral (fmap toAddressAmountNoAssets o) (ApiT i) | (i, o) <- tx ^. #txCollateral ] - , outputs = toAddressAmount <$> tx ^. #txOutputs + , outputs = toAddressAmount @n <$> tx ^. #txOutputs , withdrawals = mkApiWithdrawal @n <$> Map.toList (tx ^. #txWithdrawals) , mint = mempty -- TODO: ADP-xxx , status = ApiT (tx ^. (#txMeta . #status)) @@ -3202,16 +3270,19 @@ mkApiTransaction timeInterpreter setTimeReference tx = do txOutValue :: TxOut -> Natural txOutValue = fromIntegral . unCoin . txOutCoin - toAddressAmount :: TxOut -> AddressAmount (ApiT Address, Proxy n) - toAddressAmount (TxOut addr (TokenBundle.TokenBundle coin assets)) = - AddressAmount (ApiT addr, Proxy @n) (mkApiCoin coin) (ApiT assets) - toAddressAmountNoAssets :: TxOut -> AddressAmountNoAssets (ApiT Address, Proxy n) toAddressAmountNoAssets (TxOut addr (TokenBundle.TokenBundle coin _)) = AddressAmountNoAssets (ApiT addr, Proxy @n) (mkApiCoin coin) +toAddressAmount + :: forall (n :: NetworkDiscriminant). () + => TxOut + -> AddressAmount (ApiT Address, Proxy n) +toAddressAmount (TxOut addr (TokenBundle.TokenBundle coin assets)) = + AddressAmount (ApiT addr, Proxy @n) (mkApiCoin coin) (ApiT assets) + mkApiCoin :: Coin -> Quantity "lovelace" Natural @@ -3678,13 +3749,15 @@ instance IsServerError ErrConstructTx where apiError err501 NotImplemented "This feature is not yet implemented." +instance IsServerError ErrDecodeTx where + toServerError = \case + ErrDecodeTxNoSuchWallet e -> (toServerError e) + { errHTTPCode = 404 + , errReasonPhrase = errReasonPhrase err404 + } + instance IsServerError ErrBalanceTx where toServerError = \case - ErrBalanceTxTxAlreadyBalanced -> - apiError err403 TransactionAlreadyBalanced $ mconcat - [ "The transaction is already balanced. " - , "Please send a transaction that requires more inputs/outputs to be picked to be balanced." - ] ErrBalanceTxUpdateError ErrByronTxNotSupported -> apiError err403 CreatedInvalidTransaction "Balancing Byron transactions is not supported." @@ -3698,9 +3771,6 @@ instance IsServerError ErrBalanceTx where ] ErrBalanceTxSelectAssets err -> toServerError err ErrBalanceTxAssignRedeemers err -> toServerError err - ErrBalanceTxNotImplemented -> - apiError err501 NotImplemented - "This feature is not yet implemented." instance IsServerError ErrMintBurnAssets where toServerError = \case diff --git a/lib/core/src/Cardano/Wallet/Api/Types.hs b/lib/core/src/Cardano/Wallet/Api/Types.hs index e8bb6830658..f8ef6c74e54 100644 --- a/lib/core/src/Cardano/Wallet/Api/Types.hs +++ b/lib/core/src/Cardano/Wallet/Api/Types.hs @@ -162,6 +162,13 @@ module Cardano.Wallet.Api.Types , ApiBalanceTransactionPostData (..) , ApiExternalInput (..) , ApiRedeemer (..) + , ApiDecodedTransaction (..) + , ApiWalletInput (..) + , ApiTxInputGeneral (..) + , ResourceContext (..) + , ApiWithdrawalGeneral (..) + , ApiWalletOutput (..) + , ApiTxOutputGeneral (..) -- * API Types (Byron) , ApiByronWallet (..) @@ -217,6 +224,7 @@ module Cardano.Wallet.Api.Types , ApiWalletMigrationPostDataT , PostMintBurnAssetDataT , ApiBalanceTransactionPostDataT + , ApiDecodedTransactionT -- * API Type Conversions , coinToQuantity @@ -1131,6 +1139,59 @@ data ApiTransaction (n :: NetworkDiscriminant) = ApiTransaction } deriving (Eq, Generic, Show, Typeable) deriving anyclass NFData +data ApiWalletInput (n :: NetworkDiscriminant) = ApiWalletInput + { id :: !(ApiT (Hash "Tx")) + , index :: !Word32 + , address :: !(ApiT Address, Proxy n) + , derivationPath :: NonEmpty (ApiT DerivationIndex) + , amount :: !(Quantity "lovelace" Natural) + , assets :: !(ApiT W.TokenMap) + } deriving (Eq, Generic, Show, Typeable) + deriving anyclass NFData + +data ApiTxInputGeneral (n :: NetworkDiscriminant) = + ExternalInput (ApiT TxIn) + | WalletInput (ApiWalletInput n) + deriving (Eq, Generic, Show, Typeable) + deriving anyclass NFData + +data ResourceContext = External | Our + deriving (Eq, Generic, Show, Typeable) + deriving anyclass NFData + +data ApiWithdrawalGeneral n = ApiWithdrawalGeneral + { stakeAddress :: !(ApiT W.RewardAccount, Proxy n) + , amount :: !(Quantity "lovelace" Natural) + , context :: !ResourceContext + } deriving (Eq, Generic, Show) + deriving anyclass NFData + +data ApiWalletOutput (n :: NetworkDiscriminant) = ApiWalletOutput + { address :: !(ApiT Address, Proxy n) + , amount :: !(Quantity "lovelace" Natural) + , assets :: !(ApiT W.TokenMap) + , derivationPath :: NonEmpty (ApiT DerivationIndex) + } deriving (Eq, Generic, Show, Typeable) + deriving anyclass NFData + +data ApiTxOutputGeneral (n :: NetworkDiscriminant) = + ExternalOutput (AddressAmount (ApiT Address, Proxy n)) + | WalletOutput (ApiWalletOutput n) + deriving (Eq, Generic, Show, Typeable) + deriving anyclass NFData + +data ApiDecodedTransaction (n :: NetworkDiscriminant) = ApiDecodedTransaction + { id :: !(ApiT (Hash "Tx")) + , fee :: !(Quantity "lovelace" Natural) + , inputs :: ![ApiTxInputGeneral n] + , outputs :: ![ApiTxOutputGeneral n] + , collateral :: ![ApiTxInputGeneral n] + , withdrawals :: ![ApiWithdrawalGeneral n] + , metadata :: !ApiTxMetadata + , scriptValidity :: !(Maybe (ApiT TxScriptValidity)) + } deriving (Eq, Generic, Show, Typeable) + deriving anyclass NFData + -- | The response cardano-wallet returns upon successful submission of a -- mint/burn transaction. data ApiMintedBurnedTransaction (n :: NetworkDiscriminant) = ApiMintedBurnedTransaction @@ -2940,6 +3001,77 @@ instance where toJSON = genericToJSON defaultRecordTypeOptions +instance DecodeAddress n => FromJSON (ApiWalletInput n) where + parseJSON = genericParseJSON defaultRecordTypeOptions +instance EncodeAddress n => ToJSON (ApiWalletInput n) where + toJSON = genericToJSON defaultRecordTypeOptions + +instance DecodeAddress n => FromJSON (ApiWalletOutput n) where + parseJSON = genericParseJSON defaultRecordTypeOptions +instance EncodeAddress n => ToJSON (ApiWalletOutput n) where + toJSON = genericToJSON defaultRecordTypeOptions + +instance + ( DecodeAddress n + , DecodeStakeAddress n + ) => FromJSON (ApiDecodedTransaction n) + where + parseJSON = genericParseJSON defaultRecordTypeOptions +instance + ( EncodeAddress n + , EncodeStakeAddress n + ) => ToJSON (ApiDecodedTransaction n) + where + toJSON = genericToJSON defaultRecordTypeOptions + +instance + ( DecodeAddress n + , DecodeStakeAddress n + ) => FromJSON (ApiTxOutputGeneral n) + where + parseJSON obj = do + derPathM <- + (withObject "ApiTxOutputGeneral" $ + \o -> o .:? "derivation_path" :: Aeson.Parser (Maybe (NonEmpty (ApiT DerivationIndex)))) obj + case derPathM of + Nothing -> do + xs <- parseJSON obj :: Aeson.Parser (AddressAmount (ApiT Address, Proxy n)) + pure $ ExternalOutput xs + Just _ -> do + xs <- parseJSON obj :: Aeson.Parser (ApiWalletOutput n) + pure $ WalletOutput xs +instance + ( EncodeAddress n + , EncodeStakeAddress n + ) => ToJSON (ApiTxOutputGeneral n) + where + toJSON (ExternalOutput content) = toJSON content + toJSON (WalletOutput content) = toJSON content + +instance + ( DecodeAddress n + , DecodeStakeAddress n + ) => FromJSON (ApiTxInputGeneral n) + where + parseJSON obj = do + derPathM <- + (withObject "ApiTxInputGeneral" $ + \o -> o .:? "derivation_path" :: Aeson.Parser (Maybe (NonEmpty (ApiT DerivationIndex)))) obj + case derPathM of + Nothing -> do + xs <- parseJSON obj :: Aeson.Parser (ApiT TxIn) + pure $ ExternalInput xs + Just _ -> do + xs <- parseJSON obj :: Aeson.Parser (ApiWalletInput n) + pure $ WalletInput xs +instance + ( EncodeAddress n + , EncodeStakeAddress n + ) => ToJSON (ApiTxInputGeneral n) + where + toJSON (ExternalInput content) = toJSON content + toJSON (WalletInput content) = toJSON content + instance FromJSON (ApiT TxMetadata) where parseJSON = fmap ApiT . either (fail . displayError) pure @@ -3097,6 +3229,26 @@ instance DecodeStakeAddress n => FromJSON (ApiWithdrawal n) where instance EncodeStakeAddress n => ToJSON (ApiWithdrawal n) where toJSON = genericToJSON defaultRecordTypeOptions +instance DecodeStakeAddress n => FromJSON (ApiWithdrawalGeneral n) where + parseJSON obj = do + myResource <- + (withObject "ApiWithdrawalGeneral" $ + \o -> o .:? "context" :: Aeson.Parser (Maybe Text)) obj + case myResource of + Nothing -> do + (ApiWithdrawal addr amt) <- parseJSON obj :: Aeson.Parser (ApiWithdrawal n) + pure $ ApiWithdrawalGeneral addr amt External + _ -> do + (ApiWithdrawal addr amt) <- parseJSON obj :: Aeson.Parser (ApiWithdrawal n) + pure $ ApiWithdrawalGeneral addr amt Our +instance EncodeStakeAddress n => ToJSON (ApiWithdrawalGeneral n) where + toJSON (ApiWithdrawalGeneral addr amt ctx) = do + let obj = [ "stake_address" .= toJSON addr + , "amount" .= toJSON amt] + case ctx of + External -> object obj + Our -> object $ obj ++ ["context" .= String "ours"] + instance {-# OVERLAPS #-} (DecodeStakeAddress n) => FromJSON (ApiT W.RewardAccount, Proxy n) where @@ -3548,6 +3700,7 @@ type family ApiWalletMigrationPlanPostDataT (n :: k) :: Type type family ApiWalletMigrationPostDataT (n :: k1) (s :: k2) :: Type type family ApiPutAddressesDataT (n :: k) :: Type type family ApiBalanceTransactionPostDataT (n :: k) :: Type +type family ApiDecodedTransactionT (n :: k) :: Type type instance ApiAddressT (n :: NetworkDiscriminant) = ApiAddress n @@ -3596,6 +3749,9 @@ type instance ApiMintedBurnedTransactionT (n :: NetworkDiscriminant) = type instance ApiBalanceTransactionPostDataT (n :: NetworkDiscriminant) = ApiBalanceTransactionPostData n +type instance ApiDecodedTransactionT (n :: NetworkDiscriminant) = + ApiDecodedTransaction n + {------------------------------------------------------------------------------- SMASH interfacing types -------------------------------------------------------------------------------} diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiDecodedTransactionTestnet0.json b/lib/core/test/data/Cardano/Wallet/Api/ApiDecodedTransactionTestnet0.json new file mode 100644 index 00000000000..db322aa9ca3 --- /dev/null +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiDecodedTransactionTestnet0.json @@ -0,0 +1,12157 @@ +{ + "seed": 7533866823232395760, + "samples": [ + { + "withdrawals": [ + { + "amount": { + "quantity": 201, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 187, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 225, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 203, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 37, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 90, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 126, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 57, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 254, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 88, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 45, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 243, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 157, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 231, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 213, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 222, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 30, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 90, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 170, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 217, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + } + ], + "inputs": [ + { + "amount": { + "quantity": 166, + "unit": "lovelace" + }, + "address": "", + "id": "437d3f6d4b3365100a6a20890e0a061e0c29341f144d04364958943ae87c5a66", + "derivation_path": [ + "17295", + "17724", + "9797", + "8856", + "20066", + "30467", + "31008", + "30899", + "20499", + "22850", + "32148", + "14660", + "21569", + "6265", + "20600", + "23539", + "21325", + "31801", + "1944", + "1050", + "10508", + "9771", + "7107", + "19333", + "14270", + "12545" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 8, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 26, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 18, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 26, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 1, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 11, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e43", + "quantity": 27, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 9688 + }, + { + "amount": { + "quantity": 225, + "unit": "lovelace" + }, + "address": "", + "id": "69215ad1783b1e687a21e502713569037b5c1a651f3034f93bce08544d0b236f", + "derivation_path": [ + "22309", + "21731", + "20417", + "18952", + "28465", + "14795", + "12736", + "561", + "15144", + "26638", + "16348", + "19065", + "2471", + "1013", + "23763", + "31371", + "30130", + "25553", + "20484", + "4547", + "1179", + "1593", + "17602", + "1549", + "11585", + "4261" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 30, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 7, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 48, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 32, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 13, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 28, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 10, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 4, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 14, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 17, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 13, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 21606 + }, + { + "id": "4a67136d06265239431f3b6cf90b6f0ef65b6e6c2643746102113b595f5d4f70", + "index": 1 + }, + { + "id": "dd967a503d3a0717371b4324b82f58b24eb5511467b07d16db0f7c223f853e54", + "index": 0 + }, + { + "id": "7a714a521e5a4725d46333f50d3263ffc600584fcd7d43515b1c4918b21c0074", + "index": 1 + }, + { + "id": "5b695af977064723b41f266a8e7c66f378144f4a5b634b086a60ef6ffd177378", + "index": 1 + } + ], + "fee": { + "quantity": 224, + "unit": "lovelace" + }, + "outputs": [ + { + "amount": { + "quantity": 191, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "16426", + "31156", + "8562", + "31419", + "29472", + "21397", + "22123", + "30707", + "5773", + "9585", + "30878", + "27250", + "13887", + "12814", + "16483", + "28033", + "29315", + "1725", + "12320", + "30381", + "8734", + "18869", + "10709", + "5947", + "31704" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 7, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + } + ] + }, + { + "amount": { + "quantity": 247, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "26801", + "16809", + "15230", + "30479", + "308", + "3687", + "17523", + "5304", + "30449", + "31699", + "13269", + "23758", + "29594", + "32266", + "31646", + "18318", + "21432", + "7224", + "12340", + "24233", + "11315", + "17706" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 13, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 7, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 49, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 18, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 18, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 16, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 154, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "32063", + "12842", + "20688" + ], + "assets": [] + }, + { + "amount": { + "quantity": 147, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 20, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 15, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 16, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 8, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 30, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + } + ], + "script_validity": "valid", + "metadata": { + "12": { + "list": [] + } + }, + "id": "56b6d4642d6b7a791d5de126396e864049004b31231176292c53d961dbff8076", + "collateral": [ + { + "amount": { + "quantity": 124, + "unit": "lovelace" + }, + "address": "", + "id": "330cf16d43502031575d752d5e7403030fe2002f2626296daa027e43160f712c", + "derivation_path": [ + "24854", + "21020", + "781", + "20772", + "5693", + "4378", + "11287", + "521", + "22171", + "9378", + "1230", + "14936", + "6388", + "25059", + "7759", + "2409", + "865", + "16537", + "15677", + "6204", + "30335", + "28396", + "7184", + "30698" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 14, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 30, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 20, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 21, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 18, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 24, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 12, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 17, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 18468 + }, + { + "id": "4382e3992fa1146c445b696bca4c2e7368259419a0385e34e76c4d206a6c5533", + "index": 0 + }, + { + "amount": { + "quantity": 76, + "unit": "lovelace" + }, + "address": "", + "id": "33f85412470b1f396a61380240e653754e7d1d2b2f61996b44115f4e65cb6272", + "derivation_path": [ + "19347", + "2524", + "3425", + "22859", + "11244", + "23249", + "9581", + "23875", + "7758", + "5991", + "4928", + "10413", + "7053", + "6530", + "27722", + "19079", + "31064", + "19260", + "24899", + "6872", + "16966", + "17067" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 25, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 15, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 16, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 19, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 9, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 24, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 32, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 8, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 16, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 19, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 24, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 21739 + }, + { + "id": "0c2348ad1e7fbe09707801cb4a63015c3f1d5733525e71137637184b0b497890", + "index": 0 + }, + { + "id": "3a7eed451fb92b4f7173245b0d6d0d693412772908259c61136233203316646e", + "index": 0 + }, + { + "id": "48c913ec755d6a6e0b3d0b7a746f479c24250061ce755e721c574b182f02f37c", + "index": 1 + }, + { + "amount": { + "quantity": 236, + "unit": "lovelace" + }, + "address": "", + "id": "1c48ca3051634d49304d262e24543ac434183a1b0d182a565919233c254b6852", + "derivation_path": [ + "21254", + "9805", + "1774", + "13669" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 26, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + } + ], + "index": 1124 + }, + { + "amount": { + "quantity": 254, + "unit": "lovelace" + }, + "address": "", + "id": "41417c0842ed7a400f725a26277b38546e1d177c5c7d0a41d53c4707496a6d7d", + "derivation_path": [ + "17457" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 30, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 18, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 21123 + }, + { + "id": "032c2b3a762952b903762bb95bbb451ade1c066f2962ed3376552a3965406c11", + "index": 1 + }, + { + "amount": { + "quantity": 246, + "unit": "lovelace" + }, + "address": "", + "id": "d5505d0a3a17cc6e6972735f79696048122d771166a56b60f616544b5d1cc7cf", + "derivation_path": [ + "11782", + "14821", + "8733", + "31406", + "31257", + "21498", + "12582", + "5676", + "25517", + "29729", + "10072", + "23039", + "12496", + "8447", + "3620", + "9991" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 26, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 5, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 30, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 24039 + }, + { + "id": "3d537b5fba3e06217b127ed949600f647533723b994104231e4e038b616e4ea6", + "index": 1 + }, + { + "id": "391362197f095b0c190fb30c500fe7f3a263325200651e080957b803432b6b0e", + "index": 0 + }, + { + "amount": { + "quantity": 67, + "unit": "lovelace" + }, + "address": "", + "id": "1323683745191636425d043ff7bc792b7b3b941e121502393445571e0820013c", + "derivation_path": [ + "4967", + "21527", + "9633", + "4141", + "17422", + "6319", + "4897", + "21489", + "30661", + "14013", + "9836", + "24679", + "23435", + "12448", + "5089", + "30735", + "5612", + "11154", + "24603", + "19140", + "27534", + "3656" + ], + "assets": [], + "index": 1873 + }, + { + "id": "795c070f5e06a170227ca5442e2e0e5b0a7c0d5e75580c4425120bfb58090f5e", + "index": 1 + }, + { + "id": "2b0d204c7a2d431d3f62322f9b48107745743c7d777e210fb6e0543f4c0c2aea", + "index": 1 + }, + { + "id": "536b0e244ad6777a63792651601057e6675f12357a2e0a178f4d7a0c884c1935", + "index": 0 + }, + { + "amount": { + "quantity": 190, + "unit": "lovelace" + }, + "address": "", + "id": "413f103e5f381a71377f3e053d7b2e42715f377a7e491c69775bcf711d7c0f2f", + "derivation_path": [ + "4493", + "29928", + "17963", + "11856", + "9247", + "24788", + "450", + "27943", + "30245", + "21647", + "27038", + "12153", + "9669", + "19904", + "8703", + "1042", + "4145", + "10776", + "17121", + "27301", + "9705", + "15254", + "1037", + "31428", + "21209", + "26509" + ], + "assets": [], + "index": 15993 + }, + { + "amount": { + "quantity": 127, + "unit": "lovelace" + }, + "address": "", + "id": "0eb63915a11719736a032d06089ba050137e5d9a3f743331785d32493667683b", + "derivation_path": [ + "15416", + "18913", + "10891", + "7735", + "4068", + "29706", + "17961", + "12217", + "9249", + "27241", + "10220", + "10687", + "5720", + "19745", + "504", + "30657", + "18356", + "14993", + "30906", + "15427", + "18105", + "29318", + "5092" + ], + "assets": [], + "index": 31925 + }, + { + "amount": { + "quantity": 139, + "unit": "lovelace" + }, + "address": "", + "id": "1c3d482e263d5b1a7ca3747156371b6773e40517093d7d4edb176c0f235f214a", + "derivation_path": [ + "14354", + "3233", + "24564", + "11194", + "7431", + "20855", + "29892", + "6688", + "9262", + "8582", + "23985", + "2689", + "29565", + "4284", + "5924", + "6015", + "17256", + "20486", + "7447", + "6098", + "13176", + "32423", + "13384", + "18302", + "7451", + "26029", + "31307", + "7425" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 16, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 29649 + }, + { + "amount": { + "quantity": 231, + "unit": "lovelace" + }, + "address": "", + "id": "27ec0a7e697b0e203400722a182b584207603f605158160d2f1a6fcd998a4db2", + "derivation_path": [ + "19214" + ], + "assets": [], + "index": 31534 + }, + { + "id": "2c4d284c3e7352635948254f2b051b677b696228040a366c03553119746b241e", + "index": 1 + }, + { + "amount": { + "quantity": 207, + "unit": "lovelace" + }, + "address": "", + "id": "218a0e25a3f2325e0afd2e0741672433d175305d7a0b1e4928593d6f682b1838", + "derivation_path": [ + "3057", + "19168", + "15745", + "10528", + "9950", + "19171", + "20708", + "31638", + "6421", + "11568", + "8630", + "18784", + "17608", + "26602", + "32062", + "5959" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 29, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 2822 + }, + { + "id": "26587851313a1a16077e55373c552d6f63a619303a357a634e175e0526676e0a", + "index": 0 + }, + { + "id": "3f256b48a57c4f72442b5e3a6c1d76226d033229365bd54b101365747f3ba6cb", + "index": 1 + }, + { + "amount": { + "quantity": 251, + "unit": "lovelace" + }, + "address": "", + "id": "6049788a58756c3100761b43035c185c437574433541791a020d06765f657bc6", + "derivation_path": [ + "2390", + "21797", + "31495", + "23480", + "12752", + "4896", + "23512", + "29536", + "27922", + "12994", + "26328", + "11222", + "30649", + "16654", + "27829", + "1987", + "22143", + "32409", + "2959", + "3043", + "22395", + "11037", + "3513", + "13317", + "20011", + "1263", + "13513", + "26910", + "17713", + "21607" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 24, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ], + "index": 7320 + }, + { + "amount": { + "quantity": 237, + "unit": "lovelace" + }, + "address": "", + "id": "1f7d1e0e6232c21b3336db5729fdc76d830a8511282c050d236a7a0e57041c6c", + "derivation_path": [ + "26255", + "3181", + "13624", + "5597" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 30, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 28, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 15, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 6238 + }, + { + "amount": { + "quantity": 150, + "unit": "lovelace" + }, + "address": "", + "id": "450c64700c272634c845472a4c1c5d803c624e3e23e8006139465b5c210b0368", + "derivation_path": [ + "6669", + "23766", + "24920", + "11255", + "14209", + "17712", + "10379", + "15388", + "17888" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 12, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 4, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 23, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 16, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 40, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 29, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e43", + "quantity": 21, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 16465 + } + ] + }, + { + "withdrawals": [ + { + "amount": { + "quantity": 30, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 182, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 132, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 133, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 204, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 111, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 88, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 68, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 246, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 198, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + } + ], + "inputs": [ + { + "amount": { + "quantity": 11, + "unit": "lovelace" + }, + "address": "", + "id": "166645422f5b6a9e3798007c2d3f0d3e0d0239b221455a3a1e6c685c3a5c5260", + "derivation_path": [ + "8117", + "22615", + "8108", + "9570", + "2209", + "17567", + "2639", + "12971", + "14232", + "11020", + "25096", + "1529", + "31351", + "4881", + "17389" + ], + "assets": [], + "index": 27996 + } + ], + "fee": { + "quantity": 1, + "unit": "lovelace" + }, + "outputs": [ + { + "amount": { + "quantity": 214, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 14, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + } + ], + "script_validity": "invalid", + "metadata": { + "28": { + "bytes": "" + } + }, + "id": "0a1170e6e56757a2664b681e3a5e3a834068716e253e0e692801de227f56680d", + "collateral": [ + { + "amount": { + "quantity": 231, + "unit": "lovelace" + }, + "address": "", + "id": "2e1c797f37716c185d121d3ed02247116d30c53671793b592b12343b4a02705e", + "derivation_path": [ + "23108", + "18977", + "19978", + "2753", + "2499", + "19964", + "63", + "2302", + "26882", + "5834", + "24229", + "22958", + "3451", + "3636", + "11695", + "26567", + "31332", + "22501", + "18930", + "26022", + "28271", + "32608", + "18574", + "29802" + ], + "assets": [], + "index": 23834 + }, + { + "id": "bc2e7a46620604176e2d232f062d834d49683cef65615177150554000c25b153", + "index": 0 + }, + { + "id": "4a21361723541222503407a860cc1137595d139413188d571269b7109027511b", + "index": 0 + }, + { + "id": "453a504e6956646b533be75263042b0d1375610f2706750a204f64550a17551b", + "index": 1 + }, + { + "id": "33336c57d94e6a64c4312b3a126825441f254f7b296a2d0e835e1270663a2f33", + "index": 0 + }, + { + "id": "584e613a7d3d184c3b16242b2a3128672e24150a243c2ec718d5966b26a8654e", + "index": 0 + }, + { + "amount": { + "quantity": 28, + "unit": "lovelace" + }, + "address": "", + "id": "35030ed71ae7402d644a3850151e7360934f08270439207f2049242c0d625220", + "derivation_path": [ + "1007", + "6105" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 25, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 32480 + }, + { + "id": "737f3b344a739f664877ee1b3c15424e661845d8760b4765765bdc2b366346b8", + "index": 1 + }, + { + "amount": { + "quantity": 221, + "unit": "lovelace" + }, + "address": "", + "id": "16216073ed0a2776f2323c6778156075007554e87a223e647a025570573d3f49", + "derivation_path": [ + "12149", + "16818", + "8841", + "2278", + "25808", + "28836", + "26334", + "8331", + "12483", + "4201", + "6915", + "8417", + "11437", + "18761", + "7828", + "12772" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 5, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + } + ], + "index": 11974 + }, + { + "id": "45cb3f3d43f826629d370ae512465c5e6fc5310846424e201d41605c50355260", + "index": 0 + }, + { + "amount": { + "quantity": 180, + "unit": "lovelace" + }, + "address": "", + "id": "08117f2e213b7431166d106fa920dd3b074571435f0554db763a8d09737c662e", + "derivation_path": [ + "3663", + "21317", + "19035", + "17071" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 15, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 832 + }, + { + "id": "5a3804142996695e190e1d5d7b7329ac4f631e98576b3b487f4fa1197a22af57", + "index": 1 + }, + { + "amount": { + "quantity": 223, + "unit": "lovelace" + }, + "address": "", + "id": "33d8772e4c1e011b18fe38771d00c99b2b650472b8a25736077e3a380c2d308b", + "derivation_path": [ + "15944" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 24, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ], + "index": 19627 + }, + { + "amount": { + "quantity": 90, + "unit": "lovelace" + }, + "address": "", + "id": "333ce65d1589682324bd2758291d133b07e425456a1d291141165b1b6d4a1177", + "derivation_path": [ + "12807", + "3804", + "31138", + "32045", + "4343", + "23238", + "6594", + "14560", + "4404", + "25805", + "6951", + "18110", + "8321", + "22008", + "5838", + "18872", + "21045", + "24956", + "7128", + "11226", + "30429", + "15462", + "25248", + "9207", + "22156", + "11444", + "24090", + "15511", + "12753", + "3827", + "12114" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 9, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ], + "index": 16328 + }, + { + "amount": { + "quantity": 120, + "unit": "lovelace" + }, + "address": "", + "id": "71301a443c332811bbf544211003330b6d28434f1a04462f7d695d546e205891", + "derivation_path": [ + "815", + "13680", + "4835", + "18859", + "12645", + "3007", + "1478", + "13875", + "27658", + "7920", + "19871", + "29469", + "747", + "16957", + "3658", + "2560", + "19102", + "10871", + "21758", + "14818", + "25227", + "31800", + "18360", + "1178", + "6008", + "11018" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 38, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 32, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 13, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 6, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 11, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 11, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 22, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 23, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 18, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 21, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 9, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 5493 + } + ] + }, + { + "withdrawals": [ + { + "amount": { + "quantity": 194, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 20, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 225, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 77, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 40, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 203, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 24, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 180, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 21, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 139, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 218, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 246, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 249, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 135, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 204, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 80, + "unit": "lovelace" + }, + "stake_address": "" + } + ], + "inputs": [ + { + "id": "05112b40192c73692b0200580f30ee26225af71b4c645c285073274a220d3b51", + "index": 1 + }, + { + "amount": { + "quantity": 1, + "unit": "lovelace" + }, + "address": "", + "id": "127a58320062206be8222a62a1ef4b1c229b386521b46b7d2f63e10472b82dbb", + "derivation_path": [ + "15162", + "30104", + "3364", + "32747", + "10984", + "30723", + "2678", + "2466", + "8448", + "18214", + "7441", + "17583", + "27308", + "20086", + "23814", + "12353", + "23247", + "25163", + "22838", + "10793", + "4706", + "6408", + "15290", + "17389", + "12697" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 11, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 15, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 12, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 23, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 3, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 9, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 38, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e43", + "quantity": 21, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 1, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 2883 + }, + { + "id": "4af176222e5267ff0429062ec5297d030719ae1e3a361021ca6969350c94654d", + "index": 0 + }, + { + "id": "10116300a00e6f614e370f5f19723d391365a7022c7d46ef0efbfa1c177e0f66", + "index": 1 + }, + { + "id": "013d71192750151e43296b630f4549793e067445246b70164767ac69724cbf10", + "index": 0 + }, + { + "amount": { + "quantity": 155, + "unit": "lovelace" + }, + "address": "", + "id": "58d6917d44c7a51b7e034052f1987f416d204f28122b091513de6d1f3f3e392e", + "derivation_path": [ + "27169", + "10971", + "4270", + "29108", + "30352", + "8931", + "8357", + "25815" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 2, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 11, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 17, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 13, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 19, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 41, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 3, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 9, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 24, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 22, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e43", + "quantity": 8, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 1006 + }, + { + "amount": { + "quantity": 246, + "unit": "lovelace" + }, + "address": "", + "id": "487dab0e39716f2c47626927c13a0837b960436f4955090a966034435d3b6a2b", + "derivation_path": [ + "28897", + "20237", + "28246", + "32110", + "8160", + "7518", + "28434", + "13630", + "21387", + "15902", + "114", + "26441", + "25244", + "12445", + "31861", + "21620", + "25488", + "7415", + "30254", + "627", + "20876", + "24457", + "31009", + "7184", + "27539", + "12914", + "20496", + "31330", + "3838", + "32143", + "19410" + ], + "assets": [], + "index": 31327 + }, + { + "amount": { + "quantity": 71, + "unit": "lovelace" + }, + "address": "", + "id": "7d2966a359566f085001552df5250251143bed6e3fb7448636031d796f1f4617", + "derivation_path": [ + "10029", + "15537", + "3573", + "25801", + "32507", + "14330", + "10169", + "6472", + "12608" + ], + "assets": [], + "index": 11550 + }, + { + "id": "1e7755413b896a5d500a0a484961384e2005450c79234c47371aa64a796e3060", + "index": 1 + }, + { + "id": "084457312328222d284c380e411227295542907635154d6da758241a69172930", + "index": 0 + }, + { + "amount": { + "quantity": 5, + "unit": "lovelace" + }, + "address": "", + "id": "224a33140a5e2e07583c1f0f2d39210b7562003c743a7e0931687e2245261b70", + "derivation_path": [ + "1330", + "27397", + "22553", + "5230", + "4322", + "2189", + "420", + "30455", + "31059", + "19723", + "28494", + "27654", + "195", + "13599", + "20565", + "25150", + "9261", + "29052", + "20215", + "1605", + "9651", + "16697", + "22444", + "10691", + "6883", + "12950", + "13046", + "3136", + "6142", + "2869", + "23210" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 6, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + } + ], + "index": 18500 + } + ], + "fee": { + "quantity": 166, + "unit": "lovelace" + }, + "outputs": [ + { + "amount": { + "quantity": 6, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 85, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 37, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 14, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 13, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 17, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 26, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 19, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 23, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 2, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 199, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "11991", + "3829", + "23822", + "10071", + "9488", + "16577", + "2977", + "24983", + "19716", + "32250", + "16300", + "19272", + "22138", + "27386", + "11593", + "9259", + "3992", + "9669", + "17639", + "18812" + ], + "assets": [] + }, + { + "amount": { + "quantity": 132, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "15876", + "1854", + "13730", + "22793", + "32450", + "22932", + "16775", + "31316", + "22417" + ], + "assets": [] + }, + { + "amount": { + "quantity": 161, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "6520", + "22913", + "29747", + "13109", + "27276", + "3244", + "24768", + "29733", + "12103", + "22824", + "14352", + "3890", + "25636", + "22281", + "2849", + "22416", + "24750", + "21127", + "29464" + ], + "assets": [] + }, + { + "amount": { + "quantity": 229, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 161, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 24, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 21, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 12, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 28, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 24, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 37, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 24, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 103, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "25254", + "60", + "28571", + "13626", + "2340", + "31800", + "24320", + "27043", + "19951", + "2111", + "3279", + "29845", + "8265", + "12144", + "13250", + "25505", + "21807", + "30624", + "6947", + "16098", + "2989", + "5218", + "20624", + "30888", + "28651", + "2376", + "18293", + "31833", + "17066" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 23, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 21, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 8, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 19, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 25, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 36, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 17, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 67, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 10, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 18, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e42", + "quantity": 46, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 38, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 41, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "14641", + "15185", + "23566", + "11434", + "10757", + "26180", + "24957", + "15614", + "17352", + "30570", + "31071" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 15, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 7, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 7, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 11, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 102, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "6832", + "26170", + "11455", + "19869", + "15673", + "31136", + "1907", + "16229", + "31086", + "10724" + ], + "assets": [] + }, + { + "amount": { + "quantity": 129, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "18383", + "21132", + "14300", + "543", + "28870", + "5222", + "28841", + "32725", + "28448", + "10765" + ], + "assets": [] + }, + { + "amount": { + "quantity": 226, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "4812", + "30424", + "2163", + "16432", + "10625", + "8136", + "14931", + "8428", + "10573" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 15, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ] + }, + { + "amount": { + "quantity": 186, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "15599", + "15627", + "30807", + "21088", + "19959", + "10565", + "15152", + "5604", + "13301", + "5285", + "10759", + "19253", + "28333" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 10, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ] + }, + { + "amount": { + "quantity": 5, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 27, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ] + }, + { + "amount": { + "quantity": 190, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 14, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 49, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 21, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 35, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 8, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 62, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 25, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 16, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ] + }, + { + "amount": { + "quantity": 33, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "27196", + "28289", + "11698", + "7575", + "31348", + "18529", + "15823", + "10688", + "27125", + "133", + "13217", + "29213", + "17802", + "11530", + "2401", + "1797", + "31838", + "7829", + "32252", + "25789", + "11056", + "2662", + "6066", + "17452", + "30664", + "17141" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 9, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 34, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 54, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 69, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 26, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 17, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 25, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 28, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 77, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 51, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 61, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 28, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 4, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 35, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e43", + "quantity": 24, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 28, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 162, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 15, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 7, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 184, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 16, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 3, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 17, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 10, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 12, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ] + }, + { + "amount": { + "quantity": 22, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "26088", + "10372", + "735", + "10855", + "19855", + "9778", + "24491", + "5949", + "21073", + "6035", + "19416", + "9082", + "29405", + "24326", + "14453", + "9596", + "12324", + "27196", + "29753" + ], + "assets": [] + }, + { + "amount": { + "quantity": 247, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "16380", + "26192", + "19140", + "17193", + "11432", + "24424", + "1072", + "1577", + "32549", + "19329", + "10911", + "22849", + "3403", + "12422", + "6739", + "28969", + "16474", + "14633", + "1698", + "26126", + "31340", + "11749", + "9005", + "32027", + "29303", + "18986", + "20644", + "23185", + "27593" + ], + "assets": [] + }, + { + "amount": { + "quantity": 25, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 27, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 61, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 21, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + } + ] + }, + { + "amount": { + "quantity": 54, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 11, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ] + }, + { + "amount": { + "quantity": 84, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 36, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "8871", + "31002", + "19040", + "10644", + "29260", + "26522", + "30476" + ], + "assets": [] + }, + { + "amount": { + "quantity": 170, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "3011", + "13302", + "7947", + "10881", + "19557", + "2681", + "24941", + "5841", + "22158", + "22330", + "18114", + "1498", + "11675" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 25, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ] + }, + { + "amount": { + "quantity": 158, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "14210", + "3216", + "13745", + "1929", + "71", + "12939", + "27344", + "16614", + "23829", + "27333" + ], + "assets": [] + } + ], + "script_validity": "valid", + "metadata": null, + "id": "6f4b087469612700533dee1e5e5b12612d1fc121520aa9b7122c0f460658554c", + "collateral": [ + { + "id": "44e8354e273d443656d6d25b52793345272e685e150f56665f2e717e78671901", + "index": 1 + }, + { + "amount": { + "quantity": 74, + "unit": "lovelace" + }, + "address": "", + "id": "48ab4867552b2120b9606f2748730c41ad6f397b5eea5767110d12050e38331d", + "derivation_path": [ + "7769", + "24179", + "2008", + "31377", + "7098", + "3808", + "14608", + "22996", + "11048", + "124", + "15694", + "25844", + "23020", + "28171", + "13443", + "32123", + "8716", + "29835", + "3174", + "9958", + "15032" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 17, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 28, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 18, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 77, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 18, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 10493 + } + ] + }, + { + "withdrawals": [ + { + "amount": { + "quantity": 206, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 105, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 131, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 109, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 151, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 244, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 77, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 155, + "unit": "lovelace" + }, + "stake_address": "" + } + ], + "inputs": [ + { + "amount": { + "quantity": 116, + "unit": "lovelace" + }, + "address": "", + "id": "48252441c1341d0b732ee9a948026a2a112c7c6b26b6090303132150154207c3", + "derivation_path": [ + "10957", + "31624", + "14165", + "2932", + "15734", + "32240", + "25716", + "201" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 12, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 17603 + }, + { + "amount": { + "quantity": 187, + "unit": "lovelace" + }, + "address": "", + "id": "0e6821796d4e5e66645787152b7662673a7e7d0bec352aac1e254a46c30c7f44", + "derivation_path": [ + "14495", + "30430" + ], + "assets": [], + "index": 11937 + }, + { + "amount": { + "quantity": 68, + "unit": "lovelace" + }, + "address": "", + "id": "266f07385768546b165b5e36c327744c51ff4b07c6b2457d622c1133672b7a5a", + "derivation_path": [ + "31371", + "11212", + "13467", + "22723", + "1932", + "4714", + "4688", + "7381", + "24072", + "26547" + ], + "assets": [], + "index": 7633 + }, + { + "amount": { + "quantity": 162, + "unit": "lovelace" + }, + "address": "", + "id": "614f61317e4c076c1a3b1474415735043a330a781476a6685f3f3d1e591bf62a", + "derivation_path": [ + "32093", + "24986", + "24323", + "6110" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 5, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 25946 + }, + { + "id": "615c92172e6757240d7a1e5bea16a139124b2923680e48bd2801512c00121f5f", + "index": 0 + }, + { + "id": "7b15fb07102062282c4c0a2d784d393ded7e1b020ac11e163301a9487b2ea307", + "index": 1 + }, + { + "amount": { + "quantity": 211, + "unit": "lovelace" + }, + "address": "", + "id": "6307096d7a470e7757695b764c2c3621380c235d9c8020d5ff692254f6633a38", + "derivation_path": [ + "22196" + ], + "assets": [], + "index": 21078 + }, + { + "id": "49a450052e5b785c8b11243c5fb712dc3670756d0039543d186e51265e6b5a4a", + "index": 0 + }, + { + "amount": { + "quantity": 37, + "unit": "lovelace" + }, + "address": "", + "id": "7a5f6c7c7f9941f74a526b023f574f10483c79b128201f63186aff8704102a6b", + "derivation_path": [ + "29342" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 23, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 23, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 28, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 26, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 26, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 4, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 8, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 27, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e42", + "quantity": 26, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e43", + "quantity": 11, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 25, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 4801 + }, + { + "amount": { + "quantity": 109, + "unit": "lovelace" + }, + "address": "", + "id": "211a765033144065da514b668ae50d0825541ac7504372063808d61377c0d021", + "derivation_path": [ + "32103", + "17165", + "11303", + "6556", + "8688", + "5380", + "19342", + "2071", + "29812", + "867", + "30836" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 25, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 26, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 13, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 9, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 12, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 11, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 2, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 30309 + } + ], + "fee": { + "quantity": 164, + "unit": "lovelace" + }, + "outputs": [ + { + "amount": { + "quantity": 180, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "5043", + "24772", + "18839", + "20313", + "10924", + "29940", + "32592", + "20732", + "3524", + "12361", + "27068", + "2777", + "29416", + "12168", + "19844", + "4271", + "5441", + "18793", + "14777", + "27216", + "19240", + "335", + "30664", + "13478", + "6582" + ], + "assets": [] + }, + { + "amount": { + "quantity": 172, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 9, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ] + }, + { + "amount": { + "quantity": 147, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "2900", + "6307", + "8933", + "7799", + "14695", + "22114", + "9742", + "31628", + "16164", + "16463", + "4504", + "11050", + "17315", + "1531", + "19510", + "18882", + "14417", + "4856", + "26956", + "15651", + "14754", + "24510", + "18291", + "8538" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 11, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ] + }, + { + "amount": { + "quantity": 71, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 29, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 6, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 2, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 44, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 20, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 27, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 53, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 23, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ] + }, + { + "amount": { + "quantity": 118, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 4, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 27, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ] + }, + { + "amount": { + "quantity": 230, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 18, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 15, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 5, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 16, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 16, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 14, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 31, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e42", + "quantity": 22, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 15, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 24, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + } + ], + "script_validity": "valid", + "metadata": { + "17": { + "int": 0 + } + }, + "id": "821b5e940d5aca74541f2b04176b2f7e393205643dfd372362dc5c567656d80c", + "collateral": [ + { + "amount": { + "quantity": 142, + "unit": "lovelace" + }, + "address": "", + "id": "61455a44406b4fe50a1a691d1f24a853596b8d0a0f61154e4d15605676244876", + "derivation_path": [ + "28730", + "25427", + "32357", + "26257", + "2795", + "9276", + "31889", + "12847", + "15489", + "17902", + "7585", + "10904", + "23465", + "21457", + "19321", + "14937", + "1722", + "24464", + "32103", + "15467", + "28875", + "30877", + "13363" + ], + "assets": [], + "index": 2491 + }, + { + "id": "6b7a120425e94a632323151571643002101a72051904386b232605fe51434237", + "index": 0 + }, + { + "id": "433f715b2e28ea018513651d1d5f6c237307b722505dbc71247a3b7f30102d02", + "index": 1 + }, + { + "amount": { + "quantity": 196, + "unit": "lovelace" + }, + "address": "", + "id": "04f0f84a53417201a52d324a1809394c7d435c76303a37662b7c1555057d163a", + "derivation_path": [ + "23737", + "18448", + "4167", + "8028", + "12461", + "17456", + "12184", + "12651", + "4564", + "5303", + "9689", + "17732", + "13685", + "1742", + "24581" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 14, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 572 + }, + { + "amount": { + "quantity": 136, + "unit": "lovelace" + }, + "address": "", + "id": "d32fb66b650c4d239a10152e0a3d2d330e313b48704a24c0139c352250437f64", + "derivation_path": [ + "27004", + "6817", + "5057", + "3242", + "26990", + "21078", + "29070", + "28455", + "30838", + "24003", + "19701", + "2473", + "23180", + "5416", + "30183", + "14010", + "26466", + "17620", + "8923", + "21461", + "24500", + "24856" + ], + "assets": [], + "index": 10744 + }, + { + "id": "4c684064a7f14d6e1c59cb1871030364f4ce222444025b1abc2e791b27307b07", + "index": 1 + }, + { + "amount": { + "quantity": 133, + "unit": "lovelace" + }, + "address": "", + "id": "63575465797566037743452f46331663434c357317b71747658f15ae7f78a178", + "derivation_path": [ + "14468", + "20927", + "12200", + "27379", + "6401", + "27841", + "28496", + "17248", + "6576", + "4779" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 20, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 31750 + }, + { + "id": "7b7b5a4e677356422a536b124b2a0e630243097a9e4d55bd2b413b53500aed26", + "index": 1 + }, + { + "id": "0b60209d0e7c435b07531b5d4c45504524670f326922f56f230b2ab1391f500b", + "index": 0 + }, + { + "id": "7e5d37245f06bf664752749d24284a3e6a477d37ef027c3f7c6b603827025c67", + "index": 0 + }, + { + "amount": { + "quantity": 103, + "unit": "lovelace" + }, + "address": "", + "id": "523b12572a3cb567c87334191a30410d104e1c5f0355ac404e486623676ff44b", + "derivation_path": [ + "3100", + "2636", + "4255", + "16129", + "28155", + "9071", + "24572", + "17161", + "24143", + "22321", + "24616", + "6167", + "46", + "9961", + "3313", + "15336", + "7912", + "26879", + "32508", + "21695", + "28018", + "22949", + "718", + "11138", + "31551", + "21908", + "8089" + ], + "assets": [], + "index": 16087 + }, + { + "amount": { + "quantity": 125, + "unit": "lovelace" + }, + "address": "", + "id": "5e061c62300c6c4f36486e1b3f7446774778692b2326703a305e23197d227224", + "derivation_path": [ + "12354", + "12976", + "6121", + "23566", + "14770", + "688", + "16981" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 68, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 6, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 47, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 19, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 16, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 7, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 21, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 26, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 19, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e43", + "quantity": 22, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 29240 + }, + { + "amount": { + "quantity": 104, + "unit": "lovelace" + }, + "address": "", + "id": "75e249a7933419402f2b369d392531f37eba0cb838b00d1aaa117e69f34f313f", + "derivation_path": [ + "3812", + "30262", + "20875" + ], + "assets": [], + "index": 866 + }, + { + "id": "c23821015c697155370a543864707c255559446a4c1b6841597c7606117d713b", + "index": 0 + }, + { + "amount": { + "quantity": 95, + "unit": "lovelace" + }, + "address": "", + "id": "44472427216e6e64370a1247757f6ecf236457384e453d250078147e1b39cb14", + "derivation_path": [ + "2682", + "13151", + "29047", + "24539", + "16127", + "14102", + "16112", + "25817", + "21132", + "21819", + "5410", + "9921", + "23008", + "17249", + "5636", + "31056", + "25590", + "26811" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 42, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 25, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 9, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 5, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 13, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 8, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 34, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 14, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 1, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 1267 + }, + { + "id": "2a083578170da92e423f2d6f7a0a496b35731f2565510ff0000eda5f69015e6e", + "index": 0 + }, + { + "amount": { + "quantity": 12, + "unit": "lovelace" + }, + "address": "", + "id": "4a47195d104850917d656fd85f1a0e3b6e2b671dc811473f481a185125747044", + "derivation_path": [ + "25273", + "10829", + "412", + "28052", + "30377", + "4760", + "26793", + "30031", + "29585", + "3760", + "15918", + "6412", + "7025", + "26477", + "3477", + "14126", + "26990" + ], + "assets": [], + "index": 18739 + }, + { + "id": "91c110184b7a1a35f31f13a515259b6c22b96d320a1b312b5f6f4e36701bc268", + "index": 1 + }, + { + "id": "446c1264a9511b406c530f775e2712002238254949783a05495f45271a7e0222", + "index": 1 + }, + { + "id": "355d350b644f177de65b621a2a091f172a2229062712d94945ca59222f384f23", + "index": 1 + }, + { + "id": "5b5f7a0f05829e3744281ac13632d02349335a471ce133065b2c0239790a5d53", + "index": 0 + }, + { + "id": "d78859211b07ec6106497d7d636979f93767aa766be16e656c38037279456374", + "index": 0 + }, + { + "amount": { + "quantity": 28, + "unit": "lovelace" + }, + "address": "", + "id": "244d6a61587cbe492d7437fe3e400638350652af394f27755b1f517e36113166", + "derivation_path": [ + "8440", + "22022", + "19596", + "22719", + "19834", + "3751", + "11393", + "19780", + "25634", + "27657", + "32357", + "757", + "4955" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 13, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 1, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 56, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 24, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 13, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 24, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 8, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 21, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 7, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 1, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 20, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 9, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 26, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 19371 + }, + { + "id": "422f7d443253692d692ef07e590524287d37382418491c1c6043425950faee09", + "index": 1 + }, + { + "amount": { + "quantity": 53, + "unit": "lovelace" + }, + "address": "", + "id": "83cc7a9c0d51686cde905f5f3cee284b33782f1b0a251a095f39770a052e637b", + "derivation_path": [ + "3767", + "4891", + "23702", + "27350", + "23223", + "14478", + "3545" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 16, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 21, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 11426 + }, + { + "amount": { + "quantity": 167, + "unit": "lovelace" + }, + "address": "", + "id": "22497d1e339401d16d7c77285f40ae73aa154c194ccf356f23513e75cc2ce948", + "derivation_path": [ + "5909", + "17820", + "5482", + "20231" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 8, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ], + "index": 1415 + }, + { + "id": "715c8b4a130d3d135a6cec06df38192203694f2d150d42083d1f694f33666851", + "index": 1 + }, + { + "id": "4bd97b274c6511307939343a194f763060581571a76f6a6a07c1115b186c9c6f", + "index": 0 + }, + { + "id": "3f1b2174cb37491455e4072f5b0c6e485d1f36031a8255785f31306e68803e23", + "index": 1 + }, + { + "id": "0632341c525a43209a8b4a8314103aad749f5911281b2c7b6a7b1271797ba23b", + "index": 0 + } + ] + }, + { + "withdrawals": [ + { + "amount": { + "quantity": 31, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 63, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 163, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 89, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 73, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 147, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 188, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 102, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 155, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 58, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 109, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 241, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 47, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 190, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 193, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 93, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 192, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 69, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 51, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 221, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 240, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 142, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 19, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 166, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 180, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 214, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 124, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 129, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 147, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + } + ], + "inputs": [ + { + "amount": { + "quantity": 7, + "unit": "lovelace" + }, + "address": "", + "id": "73ef021de431584f7117c66b42e0fa4c041714605a8c527d250c5c5900493af9", + "derivation_path": [ + "11121", + "26329", + "20224", + "22203", + "12018", + "11863", + "23042", + "12399", + "19800", + "29756", + "19320", + "30201", + "19845", + "8233", + "21491", + "17577" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 22, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 13, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 151 + }, + { + "amount": { + "quantity": 237, + "unit": "lovelace" + }, + "address": "", + "id": "2847016427c0818d2f685a3e24100c5e0b0865321c0373ffc312441a57b77973", + "derivation_path": [ + "13012", + "4995", + "1326", + "497", + "29408", + "23630" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 11, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 26844 + }, + { + "amount": { + "quantity": 149, + "unit": "lovelace" + }, + "address": "", + "id": "604f0e04416c3e7848706ae0472f0d716652711c7f10585a71341e447d5f763e", + "derivation_path": [ + "5563", + "346", + "1108", + "1595", + "8078", + "11947", + "12917" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 28, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 9069 + }, + { + "amount": { + "quantity": 78, + "unit": "lovelace" + }, + "address": "", + "id": "76265c642529493c18fa3e44145438595e347e38462c120b080b7a53f5627e50", + "derivation_path": [ + "2675", + "1618", + "30277", + "23619", + "21891", + "31435", + "8575", + "8371", + "32684", + "28452", + "25995", + "2506", + "26291", + "8845", + "22070", + "23598", + "6911" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 17, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 5228 + }, + { + "amount": { + "quantity": 28, + "unit": "lovelace" + }, + "address": "", + "id": "72cb456b0b5f636e215c0a6e6f9dfdb92c2b7fa40f34062e3a63245a78b06dd1", + "derivation_path": [ + "22401", + "22133", + "15344", + "20153", + "27494", + "3693", + "17831", + "24938", + "29182", + "31773", + "17535", + "17256", + "2407", + "20281", + "26740", + "24483", + "10424", + "4390", + "19631", + "23848", + "16052", + "9854" + ], + "assets": [], + "index": 31567 + }, + { + "amount": { + "quantity": 134, + "unit": "lovelace" + }, + "address": "", + "id": "660b161a5f5c49223768d4336a48476d0a725d6c1235360d4b380da43549270d", + "derivation_path": [ + "9843", + "20899", + "14558", + "9701", + "5060", + "12589", + "27076", + "20764", + "4819", + "15534", + "3025", + "8137", + "3593", + "13000", + "19289", + "28028" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 22, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 24173 + }, + { + "amount": { + "quantity": 154, + "unit": "lovelace" + }, + "address": "", + "id": "3eb65e3b2f151a4059601e134b3a3d4d380d1b411b74a59681455e573a15303f", + "derivation_path": [ + "25190", + "30080", + "23802", + "16338", + "20816", + "20078", + "15564", + "1275", + "497", + "17684", + "12906", + "19657", + "8165", + "21733", + "11720", + "22205", + "16512", + "28450", + "15289", + "6990", + "23829", + "9222", + "17225", + "13605", + "30006", + "29866", + "18477", + "15340" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 27, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + } + ], + "index": 20390 + }, + { + "id": "74028419196559682808db786b075b790a3c762a436e143517176354526f7950", + "index": 0 + }, + { + "amount": { + "quantity": 254, + "unit": "lovelace" + }, + "address": "", + "id": "5f4f604d037801222c3e411826663c4e670a0a5e431f8e280b211e6e5a25311a", + "derivation_path": [ + "18581", + "17606", + "25256", + "25884", + "12651", + "1354", + "25909", + "31420", + "3126", + "27945", + "19811" + ], + "assets": [], + "index": 1300 + }, + { + "id": "1a1f102c5b09322f713f630208120230265d49565f311a3d1a6d0a1f11757f29", + "index": 0 + }, + { + "amount": { + "quantity": 33, + "unit": "lovelace" + }, + "address": "", + "id": "b86c6219215e026c142b2c2410fa5a2a015549b632464b23311bb4e12625ae3a", + "derivation_path": [ + "15477", + "23493", + "32229", + "27729", + "177", + "18046", + "8392", + "5421", + "9739", + "31007", + "589", + "25173", + "19017", + "18553", + "7208", + "9252", + "19137", + "9586", + "8988", + "5098", + "7466", + "12051", + "17073", + "26207" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 6, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ], + "index": 6573 + }, + { + "amount": { + "quantity": 195, + "unit": "lovelace" + }, + "address": "", + "id": "01272e17450ea0a022113c4c0c084159f811512434ac647f459250761aef4baf", + "derivation_path": [ + "27017", + "9197", + "1497", + "22724", + "8415", + "16017", + "16857", + "25514", + "18897", + "22984", + "21895", + "21891", + "3759", + "23756", + "15524", + "20596", + "25595", + "4549", + "12907", + "12969", + "1468", + "31152", + "17534", + "18", + "28292", + "22724", + "16062", + "25864", + "10800", + "2129", + "7695" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 17, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ], + "index": 4251 + }, + { + "amount": { + "quantity": 143, + "unit": "lovelace" + }, + "address": "", + "id": "552f742a0e4b46cb1c62c30262a61e1051124a3e247c5b1820313d137e675052", + "derivation_path": [ + "15435", + "24246", + "16364", + "28853", + "12887", + "16896", + "16082", + "2233", + "31139", + "4525", + "11063", + "19920", + "10429", + "30015" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 19, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ], + "index": 2757 + }, + { + "id": "aa855598147ebd5e526b6a334ada772d6064a3610c30785316ed2d3652535205", + "index": 1 + }, + { + "id": "290a21408d48791de8631e147b026668a02bc75459b839344834464e2b51450e", + "index": 0 + }, + { + "id": "7438792d1910767602125b5c682b7d2c3b2726581f7038005407072c0b7aec7c", + "index": 0 + }, + { + "amount": { + "quantity": 174, + "unit": "lovelace" + }, + "address": "", + "id": "2a4f08267bf24254609d364707523d60490b3a9d145d074e355d005c25790621", + "derivation_path": [ + "29135", + "17587", + "12845", + "13036", + "16598", + "14034", + "420", + "30296", + "25003", + "7978", + "22385", + "21524", + "11243", + "8793" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 19, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 28, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 4, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 39, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 22, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 57, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 3, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 20, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 18, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 18, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 19, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 6974 + }, + { + "amount": { + "quantity": 62, + "unit": "lovelace" + }, + "address": "", + "id": "7b7110444bfdc2172b59491e334d4d40707a75780c656d20034d5e53795b2a0d", + "derivation_path": [ + "10623", + "13983", + "6788", + "17494", + "29357", + "16813", + "9188", + "22744", + "14328", + "28407", + "32625", + "20328", + "18583", + "23765" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 30, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 6457 + }, + { + "amount": { + "quantity": 156, + "unit": "lovelace" + }, + "address": "", + "id": "f84c3b24393c2f3f3c700e647b7c7e6440771b3e7c93127c923836cf434b6349", + "derivation_path": [ + "13719", + "20534", + "27879", + "24239", + "24287", + "3720" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 40, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 15, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 10, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 16, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 12, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 5, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 11, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 37, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 21650 + }, + { + "amount": { + "quantity": 181, + "unit": "lovelace" + }, + "address": "", + "id": "58555a2d6c0c1824723d04fd06024f60727884c72c5343246820fa2d20542fb2", + "derivation_path": [ + "22215", + "4236", + "16247", + "8032", + "15718", + "31618", + "7764", + "31650", + "4973", + "4199" + ], + "assets": [], + "index": 4780 + }, + { + "id": "b75c29422d851b0b7d4d237e8d6b59d8020d761469641bd249d3516817525648", + "index": 1 + }, + { + "id": "46337ee250fa092a75365310031b217f521b783351250562307e2b5a5a1c0d33", + "index": 1 + }, + { + "amount": { + "quantity": 36, + "unit": "lovelace" + }, + "address": "", + "id": "161f3a5fd6aa7d0e7e6ebe7c3677066013292e117824f58ebe6a266336315355", + "derivation_path": [ + "5415" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 11, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 16066 + }, + { + "amount": { + "quantity": 73, + "unit": "lovelace" + }, + "address": "", + "id": "5f33798b2a240a074f498b2b3721a561538c2ed051543d439435054f0b05bc79", + "derivation_path": [ + "2382", + "22441", + "27458", + "10895", + "26900", + "2012", + "3629", + "25857", + "16898", + "18537", + "17827", + "32540", + "1935", + "7148", + "9419", + "29005", + "20297", + "7098", + "4889", + "9350", + "24629", + "23468", + "27523", + "10186", + "16351", + "20331", + "938", + "4155" + ], + "assets": [], + "index": 10009 + }, + { + "amount": { + "quantity": 228, + "unit": "lovelace" + }, + "address": "", + "id": "766742237e131509323e153825637c7138543f4a2ed1447f324804580b707f4a", + "derivation_path": [ + "25289", + "14606", + "8096", + "19844", + "644", + "6841", + "10546", + "32516", + "31229", + "20675", + "29228", + "11795", + "14549", + "1670", + "11886", + "16478", + "3578", + "2513", + "29413", + "22831", + "12957", + "27557", + "9283", + "23228", + "3045", + "29053" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 18, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 27 + }, + { + "amount": { + "quantity": 217, + "unit": "lovelace" + }, + "address": "", + "id": "bf638a0f780fc7b6fc1115c9015a1e7a1b004f5ebf761b23225cdc1068796720", + "derivation_path": [ + "14199", + "27108", + "20703", + "2729", + "20535", + "15671", + "24161", + "564", + "25327", + "18667", + "7725", + "16033", + "5573", + "20690", + "28437", + "22363", + "8527", + "27196", + "23989", + "21970", + "32732", + "6099", + "13431", + "5154", + "14125", + "31856", + "15349", + "18992", + "22123" + ], + "assets": [], + "index": 15298 + }, + { + "id": "3fea28591b03125b0961572d70680d863e5570247e6638e650d86b167d83376e", + "index": 1 + }, + { + "id": "a356dd5a745878427a08063c4f2a8245436f6c78755d3faf46110a3825be172b", + "index": 1 + }, + { + "id": "2d6e423d000a6168a34d404e2d982819070d597c0c72213a0a723473212a72a6", + "index": 1 + }, + { + "id": "9ea0be03795669c60a697e74205c317a3206071414282d3429085d4361a46c10", + "index": 0 + } + ], + "fee": { + "quantity": 56, + "unit": "lovelace" + }, + "outputs": [ + { + "amount": { + "quantity": 24, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "26744", + "17757", + "8712", + "23490", + "18401", + "12610", + "24376", + "9708", + "31651", + "22279", + "24248", + "31391", + "7353", + "19257", + "26715", + "23171", + "31118", + "16292", + "4381", + "4512", + "30512", + "11756", + "22351", + "10828", + "27318", + "23410", + "19514", + "15942", + "5819", + "8584" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 4, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 21, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 16, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 30, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 25, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 24, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "17282", + "3362", + "15839", + "13331" + ], + "assets": [] + }, + { + "amount": { + "quantity": 80, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "16307", + "30441", + "8480", + "7801", + "1559", + "23421", + "20718", + "14604", + "2968", + "11475", + "24325", + "16388", + "2765", + "17311", + "3764", + "14890", + "17808", + "3036" + ], + "assets": [] + }, + { + "amount": { + "quantity": 231, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 29, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 5, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 10, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 9, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 6, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 5, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 21, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 16, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 1, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 7, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 4, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 21, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 30, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 13, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 62, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "3481", + "10646", + "2185", + "7515", + "8309" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 18, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 23, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 28, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 25, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ] + }, + { + "amount": { + "quantity": 155, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "27531", + "22034", + "21578", + "5846", + "29696", + "16960", + "24850", + "26140", + "17477", + "1980" + ], + "assets": [] + }, + { + "amount": { + "quantity": 40, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 245, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "22063", + "18234", + "11949", + "15194", + "14221", + "22150", + "12415", + "2468", + "27722", + "2572", + "5408", + "8377", + "27717", + "11375", + "8945", + "18436", + "11308", + "22866", + "2656", + "10973", + "19594", + "20019", + "31790", + "30212", + "28995", + "29453", + "8752", + "490", + "14303", + "26645" + ], + "assets": [] + }, + { + "amount": { + "quantity": 105, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 13, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 233, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 8, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 9, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 25, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 4, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 8, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 19, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 3, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 11, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "17165", + "24225", + "15954", + "30420", + "15947", + "32005", + "5675", + "32490", + "16752", + "20330", + "27349", + "23093", + "32535", + "31980", + "21348", + "10902", + "7293", + "28016", + "14993" + ], + "assets": [] + }, + { + "amount": { + "quantity": 133, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "19863", + "17453", + "1188", + "23925", + "21541", + "30465", + "6977", + "19805", + "16137", + "23101", + "4407", + "4792", + "4955", + "3067" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 11, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + } + ] + }, + { + "amount": { + "quantity": 78, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "14892", + "25299", + "19521", + "23809", + "24098", + "26433" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 22, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 23, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 228, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "3257", + "2614", + "25115", + "25778", + "3779", + "9787", + "21525", + "15314", + "19039", + "12306" + ], + "assets": [] + }, + { + "amount": { + "quantity": 20, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "8190", + "20915", + "22685", + "9609", + "3539", + "23777", + "5931", + "30457", + "5788", + "15105", + "5366", + "19503", + "10607", + "14386", + "10821", + "25144", + "19370", + "28172", + "31206", + "31367", + "950", + "30323", + "11196", + "20771", + "3164", + "10428", + "14804", + "23009", + "20171", + "2085", + "9049" + ], + "assets": [] + } + ], + "script_validity": "invalid", + "metadata": null, + "id": "5f244357356315932af1187a6a357404696501e0210a6c3b554e053b3a0d2832", + "collateral": [ + { + "amount": { + "quantity": 72, + "unit": "lovelace" + }, + "address": "", + "id": "2d1a70863532f6714475734b5aed500c1039d0486b412a892b494819635a0018", + "derivation_path": [ + "16229", + "1431", + "16266", + "14901", + "13828", + "10239", + "28634", + "10320", + "31815", + "19103", + "30770", + "24613" + ], + "assets": [], + "index": 2902 + }, + { + "id": "5839374b1b02796c0d4a7207563a1c4b6a63524b68670b58d531754b511740ae", + "index": 0 + }, + { + "amount": { + "quantity": 65, + "unit": "lovelace" + }, + "address": "", + "id": "39da5ed4146c086f7c2b7c2e670f36351e2e2e0e2af44205573c59364b6e2666", + "derivation_path": [ + "17630", + "29529" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 17, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 17, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 26, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 7815 + }, + { + "id": "df17695510185f4b333a383d3a461a373a7a8d7374040e138a58451c10275571", + "index": 0 + }, + { + "amount": { + "quantity": 80, + "unit": "lovelace" + }, + "address": "", + "id": "fb423f1c0ffcce137b531d3751157b734cc1561f1924194e74004041754b020a", + "derivation_path": [ + "11774", + "2720", + "8918", + "755", + "32387", + "941", + "31154", + "25990", + "30741", + "5295", + "20145", + "23952", + "23198", + "28550", + "7397", + "30104", + "16166", + "5065", + "10664", + "24281", + "18371" + ], + "assets": [], + "index": 16620 + }, + { + "amount": { + "quantity": 135, + "unit": "lovelace" + }, + "address": "", + "id": "50405d7b725253f34a0316416446e90f254a3706e4f4690958702102293b7aa6", + "derivation_path": [ + "27524", + "27058", + "28022", + "31146", + "7381", + "21880" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 20, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 12273 + }, + { + "amount": { + "quantity": 210, + "unit": "lovelace" + }, + "address": "", + "id": "e6697dd85d48761e674f905f55003a67a6713c323a493524774b267a22393f3f", + "derivation_path": [ + "16781", + "6673", + "15482", + "22877", + "27379", + "31888", + "27046", + "9540", + "29656", + "28790", + "14695", + "16000", + "1246", + "3502", + "20175", + "6118", + "6568" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 22, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ], + "index": 28254 + }, + { + "amount": { + "quantity": 161, + "unit": "lovelace" + }, + "address": "", + "id": "3255d2061668515c5c2e2c00b80be4408c081c9eb555575121184c461b1e9e27", + "derivation_path": [ + "28394", + "4128", + "29332", + "25860", + "12827", + "23115", + "4328" + ], + "assets": [], + "index": 5332 + }, + { + "id": "371d33252e8030697c070d050c040281065760a21f631a3a172946587f452125", + "index": 1 + }, + { + "amount": { + "quantity": 137, + "unit": "lovelace" + }, + "address": "", + "id": "363d244bd7517e6518737b0f36376e4115ba054e2c6049976c4f755de5220356", + "derivation_path": [ + "1099", + "24620", + "23873", + "13919", + "30430", + "4092", + "29861", + "11516", + "22920", + "413", + "12729", + "24652", + "32080", + "18087", + "14639", + "10232", + "16943", + "18303", + "1266", + "32745", + "16448", + "3028" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 17, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 9459 + }, + { + "amount": { + "quantity": 59, + "unit": "lovelace" + }, + "address": "", + "id": "7220de5449d1382056644d46757f12034d20722c2009e917f35a616c9e1e702a", + "derivation_path": [ + "12553", + "23717", + "20744", + "2604", + "29807", + "5323", + "21238", + "660", + "7659", + "32173", + "9089", + "26149", + "28589", + "28462", + "27434", + "10464", + "31352", + "17826", + "26925", + "27678", + "10417", + "8438", + "20603" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 9, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ], + "index": 30511 + }, + { + "amount": { + "quantity": 79, + "unit": "lovelace" + }, + "address": "", + "id": "5c223d0d693903194c190691ae115c41198335cb566692294d6573422c724d0e", + "derivation_path": [ + "10849", + "2677", + "24718", + "31002", + "7272", + "2069", + "22615", + "5581", + "12418", + "19368", + "24173", + "17274" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 17, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ], + "index": 17449 + }, + { + "amount": { + "quantity": 45, + "unit": "lovelace" + }, + "address": "", + "id": "3b5d012a0879060bf68913597c294b25113c66440c1210ec1e7d3c656ef6743e", + "derivation_path": [ + "10390", + "8390", + "30055", + "31806", + "9480", + "16734", + "6593", + "23881", + "21784", + "3074", + "6788", + "1223", + "15884", + "9042", + "21038", + "17800", + "28101", + "3266", + "26853", + "16286", + "20735", + "29554" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 5, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + } + ], + "index": 15945 + }, + { + "amount": { + "quantity": 58, + "unit": "lovelace" + }, + "address": "", + "id": "5333103d54260f3b363c4a5b050e620a131b26a31f725042461bc27974705939", + "derivation_path": [ + "29514", + "11542", + "12214", + "29265", + "1215", + "9693", + "13026", + "3676", + "555", + "4486", + "20596", + "6860" + ], + "assets": [], + "index": 17324 + }, + { + "id": "33257654c0222364066d72ab416939671b4b0a4b6bd844591f77054174360ba3", + "index": 0 + }, + { + "amount": { + "quantity": 55, + "unit": "lovelace" + }, + "address": "", + "id": "230f024c00537b5569051672771e7d643e47555e353d6331543d6ff9273077ad", + "derivation_path": [ + "29772", + "12507", + "14683", + "22097", + "31211", + "21018", + "8501", + "8324", + "25007", + "13271", + "10697", + "16092", + "19196", + "2485", + "11404", + "1166", + "24514", + "1207", + "20344" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 24, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 11, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 18, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 27, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 10, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 27, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 46, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 12, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e43", + "quantity": 30, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 47, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 30055 + }, + { + "id": "95725fb2567214bb092f05677e7c5e6d322ab67304586212d8102ed7167a4253", + "index": 1 + }, + { + "id": "0e5b290c42781d562b02426036251a7b4730f8c531675b374474317f202c3bab", + "index": 0 + }, + { + "id": "3b4577acba767e4418027934682e2a0d33280665aa0c1fec4c344b3807da7160", + "index": 0 + }, + { + "amount": { + "quantity": 24, + "unit": "lovelace" + }, + "address": "", + "id": "6f6e1a3841157b496238235d3b2b062315051fd70a14e86c612f2647471c1364", + "derivation_path": [ + "17784", + "19748", + "24029", + "15168", + "20685", + "28860", + "22914", + "21178", + "30863", + "12079", + "12945", + "26909", + "32727", + "14320", + "23424", + "13928", + "29599", + "15478", + "9966", + "22452", + "8140", + "26654", + "25033", + "10255", + "19369", + "11194", + "27328" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 3, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 4, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ], + "index": 12070 + }, + { + "amount": { + "quantity": 240, + "unit": "lovelace" + }, + "address": "", + "id": "766fa6385838233c7e836f5c53405e2247778e56a43d74706d63145057656344", + "derivation_path": [ + "8702" + ], + "assets": [], + "index": 13902 + }, + { + "amount": { + "quantity": 22, + "unit": "lovelace" + }, + "address": "", + "id": "605e09680f2d30a5c2555604374a5730026b1c0c7b0658044a56e45014451f73", + "derivation_path": [ + "13686", + "13405", + "9501", + "19843", + "26927", + "24359", + "11946", + "5600", + "32656", + "9716", + "9625", + "13842", + "11012", + "17461", + "9258", + "27419", + "22346", + "27672", + "14900", + "31720", + "20544", + "19572" + ], + "assets": [], + "index": 12270 + }, + { + "id": "bed30a6566bd893c56645970a759761f104a0443766301366f550f25505b8c12", + "index": 1 + }, + { + "id": "39161f3c4457532a49478c4f66493f27036639270f7c7671eb4c5e49031d640b", + "index": 0 + }, + { + "amount": { + "quantity": 175, + "unit": "lovelace" + }, + "address": "", + "id": "1a004e3960bb5a3921ca7ea8846d590f190b6a227c7f6a20d36e0d2f474c284e", + "derivation_path": [ + "30054", + "19206", + "5162", + "6966", + "14223", + "8520", + "28345", + "24357", + "21426", + "14951", + "26682", + "19971", + "10653", + "31552", + "2633", + "18053", + "18113", + "8433", + "13630", + "21176", + "5917", + "15135", + "10086", + "5459", + "2241", + "25382", + "13961", + "20804", + "2694", + "12130" + ], + "assets": [], + "index": 13374 + }, + { + "amount": { + "quantity": 253, + "unit": "lovelace" + }, + "address": "", + "id": "4471134d75700670415c614e461b393936246b2f44555d550e25284c34367347", + "derivation_path": [ + "23491", + "21669", + "5241", + "16686", + "11594", + "847", + "9640", + "1686", + "11221", + "28443", + "18149", + "13241", + "30449", + "30264", + "21329", + "8920", + "21412", + "11449", + "32171", + "32153", + "21058" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 17, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + } + ], + "index": 17025 + }, + { + "id": "1164786a632a031f5a4a4465272b303ff903285d08c915617ec60f3c8fcb7934", + "index": 0 + }, + { + "id": "3873202b246c0e4b5a1914d75a2b0238386dd3254a52754089412b4748042f6e", + "index": 1 + }, + { + "amount": { + "quantity": 117, + "unit": "lovelace" + }, + "address": "", + "id": "6a7708f09c111c3d6a0c734d3a19fbfd256377532b04e146be3d42341f187a6f", + "derivation_path": [ + "4461", + "25108", + "1341", + "1671", + "15015", + "26750" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 12, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 10, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 1, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 20, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 15, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 10, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 4, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 12, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 5, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 9, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 8733 + }, + { + "id": "2858324848fc3c65653f1e261a235e26004067312441047a742d67fb3e017b03", + "index": 1 + } + ] + }, + { + "withdrawals": [ + { + "amount": { + "quantity": 163, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 77, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 90, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 209, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 137, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 187, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 36, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 129, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 227, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 233, + "unit": "lovelace" + }, + "stake_address": "" + } + ], + "inputs": [ + { + "id": "c819141259447c431863836b13d1706f49e7bf0831a5606265c27a51637c1b40", + "index": 0 + }, + { + "id": "741c78a93f7307052e65686c1a6904b8170645bf63205c5a493f46ec00398a78", + "index": 1 + }, + { + "id": "3d171132f560700b033a4112171425dd47165ae3094c611f570f240555743034", + "index": 1 + }, + { + "id": "59437c2fae39550f38021956794e0e612b556f352018377f2f19630c560d135e", + "index": 1 + }, + { + "id": "924ad86f0a4a46772c1c42674b8e67a44e3ccb0129645d436b28270316667af1", + "index": 0 + }, + { + "id": "51353c3e5b05ce217f49382349762f0d56afd31e3e787c2879536c552b964170", + "index": 1 + }, + { + "amount": { + "quantity": 43, + "unit": "lovelace" + }, + "address": "", + "id": "0c483e3257715a71a4706b4321701e21647563606c3f03000b096b36c5566226", + "derivation_path": [ + "25236", + "23086", + "14651", + "19720", + "17867", + "18956", + "32595", + "30707", + "23028", + "22165", + "17874", + "29334", + "25169", + "32291", + "25525", + "1632", + "25122", + "14979", + "18153", + "11702" + ], + "assets": [], + "index": 14069 + }, + { + "amount": { + "quantity": 212, + "unit": "lovelace" + }, + "address": "", + "id": "0a54182d2c944f55cc31741f3c3c2e7c5e73786f4c66577b3c69286673483c7b", + "derivation_path": [ + "25035", + "3848", + "31532", + "31108", + "21429" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 4, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 18434 + }, + { + "id": "3a40110d652f7d51643d512e442d936986470e16fe227ba1187b9b4804995e47", + "index": 1 + }, + { + "id": "4166210139667a402851523479170bb34843683e29511652501a16713e411b6b", + "index": 0 + }, + { + "amount": { + "quantity": 225, + "unit": "lovelace" + }, + "address": "", + "id": "3727122962734a7d6e0e68075f4e2f53326d24664ad376f33b7c2a3894714a28", + "derivation_path": [ + "14083", + "9654", + "13231", + "31934", + "14098", + "1636", + "348", + "14296", + "28277", + "24424", + "16600", + "26043", + "4754", + "5628", + "28350", + "8009", + "23698", + "19587", + "12102", + "1246", + "18999", + "17085", + "16621", + "14489", + "15698", + "25907", + "5031", + "23847", + "28" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 4, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ], + "index": 9488 + }, + { + "amount": { + "quantity": 91, + "unit": "lovelace" + }, + "address": "", + "id": "53699f0a45785c5b7c585f62122a586e3f22301b4b2d9e7270f6442aa5461081", + "derivation_path": [ + "14745", + "6166", + "1504", + "11158", + "18173", + "13460", + "32658", + "7838", + "27431", + "11877", + "25903", + "24212", + "19276", + "28362", + "9688", + "22061", + "8423", + "16073", + "10448", + "10017", + "19793", + "12746", + "4630", + "26103", + "16751", + "8602", + "24434" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 20, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 1894 + }, + { + "id": "e1640e81776e2161325225433af327f53e52694e6b196f5e2f4131746b40784c", + "index": 0 + }, + { + "id": "68f53375066347195c63047e7f34b9a057947d081267493510203e813a4c7345", + "index": 1 + }, + { + "id": "046262772e1c0b52527200e439466f061963fb5b3e7d087f6e283d307d394f58", + "index": 1 + }, + { + "id": "7d655f4201297d693d1a715b6010396463d2642ecd002e210a87e67b41035229", + "index": 1 + }, + { + "amount": { + "quantity": 16, + "unit": "lovelace" + }, + "address": "", + "id": "72bb482a124f8e0c111f032732706086d6060a0ba37d21215f087a4f3d603932", + "derivation_path": [ + "2243", + "30641", + "7545", + "30850", + "9836", + "16369", + "32003" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 5, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 6, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 54, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 10, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 41, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 34, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 27, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 22, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 13, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 18, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 12449 + }, + { + "id": "58143aff546d797b775f74495f78ce16135fb27874551f686164539b49063a75", + "index": 0 + }, + { + "id": "5e73385a45335b7f0be93c534993523f661c7a771a47575f732e5f346675320f", + "index": 1 + }, + { + "id": "955a41152d5d4b01646f6f7a991631567be49d059f60470831c51334267a32e2", + "index": 1 + } + ], + "fee": { + "quantity": 153, + "unit": "lovelace" + }, + "outputs": [ + { + "amount": { + "quantity": 243, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 179, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "2462", + "2273", + "30413", + "7567", + "5754", + "32749", + "14656", + "15808", + "17019", + "10404", + "15245", + "22524", + "26396", + "14305", + "28963", + "2680", + "27236", + "24632", + "24590", + "22620", + "14264", + "30662", + "11313", + "2822", + "18699", + "4056", + "23823", + "26457", + "21467", + "13875", + "8240" + ], + "assets": [] + }, + { + "amount": { + "quantity": 214, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "13248", + "13768", + "18629", + "30295", + "25293", + "15461", + "26064", + "28770", + "2723", + "29094", + "32101", + "11293", + "23197", + "15256", + "11148", + "6724", + "28070", + "8487", + "6352", + "7298", + "10485", + "25792", + "6748", + "12844", + "19348", + "3872", + "27903", + "2194", + "13571", + "1866" + ], + "assets": [] + }, + { + "amount": { + "quantity": 75, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "691", + "1166", + "5035", + "15714", + "11730", + "21839", + "29401", + "9137", + "18905", + "8489", + "667", + "31836", + "21517", + "31795", + "8945", + "1894", + "30518", + "10462", + "9138", + "4818", + "5281", + "21032", + "7219" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 10, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 30, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 7, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ] + } + ], + "script_validity": "invalid", + "metadata": null, + "id": "7d58076b2a124121ce232836023964737f6e345d41614064590c63b8013c5d4f", + "collateral": [ + { + "amount": { + "quantity": 181, + "unit": "lovelace" + }, + "address": "", + "id": "2e548e287b735dac5341033d416a71363c2273787e1e6d4e62710e1305200e64", + "derivation_path": [ + "32660", + "12695", + "7612", + "32730", + "11661", + "10343", + "11700", + "12551" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 17, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 22, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 24, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 6, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 21145 + }, + { + "amount": { + "quantity": 235, + "unit": "lovelace" + }, + "address": "", + "id": "365d57682723ac15340b59444d521e75786c105d14715561146ded124c744a12", + "derivation_path": [ + "23142", + "2029", + "2860", + "24129", + "7722", + "7792", + "1731", + "6389", + "1967", + "5481", + "145", + "1013", + "8367", + "22054", + "6488", + "14680", + "28731", + "27715", + "22558", + "3807", + "7287", + "20927", + "21117", + "23447" + ], + "assets": [], + "index": 26820 + }, + { + "amount": { + "quantity": 12, + "unit": "lovelace" + }, + "address": "", + "id": "20c44061d13eab75796fc7a478164a4f6a79544936f42a7a5414602e72667f56", + "derivation_path": [ + "7456", + "11654", + "14016", + "8678", + "17257", + "6929", + "30403", + "1852", + "479", + "26472", + "28521", + "15434", + "2348", + "31759", + "27178", + "8320", + "32251", + "11206", + "22656", + "9660", + "14083", + "18734", + "21913", + "3115", + "12274", + "31991", + "20001", + "16205", + "27125" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 12, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + } + ], + "index": 23272 + }, + { + "amount": { + "quantity": 185, + "unit": "lovelace" + }, + "address": "", + "id": "4d7d5d0e7f3954b2051230054eb72c897a01de0d09420ef16349122211496512", + "derivation_path": [ + "10286", + "31394", + "13575", + "27559", + "24", + "1896", + "11146", + "26342", + "19504", + "3097", + "31044", + "21228", + "21586", + "10409", + "3115", + "27084", + "30280", + "18200", + "19128", + "26516", + "27558", + "5991", + "22549", + "11208", + "30475" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 27, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 30, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 40, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 18, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 7, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 4, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 13, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 15, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 7, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 28, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 7316 + }, + { + "id": "6c7e7b714d61388b27327d02585f5317442d5d3a1f6e6a133a326c36741a7412", + "index": 1 + }, + { + "amount": { + "quantity": 112, + "unit": "lovelace" + }, + "address": "", + "id": "664a132e42015f5c337603312718375e5816a85ac4680d5d0f7e1d3300392347", + "derivation_path": [ + "21403", + "29330", + "6030", + "29588", + "17551", + "28890", + "28560", + "10856", + "28956", + "10252", + "14906", + "19100", + "22027", + "8815", + "14360", + "7059", + "20912" + ], + "assets": [], + "index": 14931 + }, + { + "id": "a144577437ed932f3668cf7b1632465d635500792101561e2572447c6339876b", + "index": 0 + }, + { + "amount": { + "quantity": 11, + "unit": "lovelace" + }, + "address": "", + "id": "4028521e35531b4c5e3e11872a222f040f683003644f3e4842e847baee26733d", + "derivation_path": [ + "26036", + "8770", + "11302", + "9784", + "22558", + "25921", + "4049", + "16088", + "31169", + "2493", + "2324", + "25621", + "13336", + "30105", + "23645", + "12543", + "9611", + "16401", + "14629", + "11881", + "7828", + "23850", + "27002", + "9577", + "28678", + "29333", + "1512", + "9560", + "21935", + "21698", + "155" + ], + "assets": [], + "index": 25201 + }, + { + "id": "61495c74b3225e186c1e23ff76f60c2628300f20f272667914282d3557425c7b", + "index": 1 + }, + { + "amount": { + "quantity": 147, + "unit": "lovelace" + }, + "address": "", + "id": "107a3410046d6e035c102ca21f226a74207334797f9e59161c5a3c5f3d9a6e1e", + "derivation_path": [ + "13253", + "18820", + "6478", + "28101", + "6923", + "13370", + "17215", + "13265", + "18037", + "22190", + "13445", + "10746", + "12437", + "18065", + "18740", + "18236", + "12487", + "10284" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 7, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 28987 + }, + { + "amount": { + "quantity": 227, + "unit": "lovelace" + }, + "address": "", + "id": "af5091146d16475e4b0359692b123959034c3f3926253ad535674f505d582502", + "derivation_path": [ + "29485", + "2440", + "1583", + "22526", + "30869", + "11174", + "27240", + "8720", + "21786", + "14901", + "23700", + "23398" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 4, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 3, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 15, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 35, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 39, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 12, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 29, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 3, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 22, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 30, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e42", + "quantity": 12, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 4315 + }, + { + "id": "735a2569230327324d5dc227c53900fb036b2430ac55607e1c220744694e75c7", + "index": 0 + }, + { + "id": "13774d3523686566697f113e2141293c755d78c83149142c120d618c70651f72", + "index": 1 + }, + { + "id": "6e6e427313297761563816109f2a34517a391fe973ff64527378435c570f4101", + "index": 0 + }, + { + "id": "2437332a477f5a4d7831133bd34572107a164509133b5713580c163f76106153", + "index": 1 + }, + { + "amount": { + "quantity": 57, + "unit": "lovelace" + }, + "address": "", + "id": "502d52fc6c0e6d9e28285d0138634c7947265b740a72df0743594c581a70015e", + "derivation_path": [ + "3884", + "10811", + "18232", + "8973", + "28968", + "9786", + "13213", + "9273", + "6477", + "21850", + "14295", + "32757", + "24625", + "2086", + "4123", + "24493", + "17869", + "29645", + "32465", + "23379", + "27089", + "29376", + "264", + "4003", + "14436", + "17004", + "20404", + "21788" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 4, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 19104 + } + ] + }, + { + "withdrawals": [ + { + "amount": { + "quantity": 242, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 208, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 255, + "unit": "lovelace" + }, + "stake_address": "" + } + ], + "inputs": [ + { + "amount": { + "quantity": 53, + "unit": "lovelace" + }, + "address": "", + "id": "350f5f391f1a1deb3f574119657c136f235a1b056e49322618378e0c5b41415f", + "derivation_path": [ + "1734", + "14240", + "5901", + "23717", + "22290", + "8724", + "5866", + "14776", + "5239", + "19508", + "27178", + "24002", + "2275", + "29457", + "14908", + "2022", + "26125" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 5, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 15810 + } + ], + "fee": { + "quantity": 132, + "unit": "lovelace" + }, + "outputs": [ + { + "amount": { + "quantity": 60, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 21, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 27, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 26, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 37, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 21, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 6, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 200, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "27504", + "32511", + "13565", + "31921", + "21374", + "351", + "10216", + "24505", + "29010", + "10163", + "9488", + "828" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 3, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ] + }, + { + "amount": { + "quantity": 62, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 94, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 6, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 18, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 17, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 20, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 19, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 15, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 11, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 16, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 11, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 7, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 26, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 36, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 208, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 3, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 6, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 19, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 17, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 8, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 9, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 29, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 18, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 9, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 186, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 7, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ] + }, + { + "amount": { + "quantity": 196, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "31886", + "27634", + "28349", + "30993", + "9351", + "28646", + "11695", + "2219", + "21803", + "340", + "5846", + "6866", + "17301", + "31055", + "22853", + "5638", + "17841", + "9644", + "20753", + "5383", + "16737", + "9196", + "6392", + "20965", + "11230" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 19, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ] + }, + { + "amount": { + "quantity": 52, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 24, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ] + }, + { + "amount": { + "quantity": 206, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "16420", + "28160", + "7410" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 9, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 190, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "7047", + "27536", + "20956", + "23315", + "32286", + "9480", + "4504", + "27001", + "3048", + "16202", + "26946", + "19496", + "15554", + "18997", + "17784", + "17438", + "7655", + "9735", + "5022", + "9512", + "750", + "11722", + "14557" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 4, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 23, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 16, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 13, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 28, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 7, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 27, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 18, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 9, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ] + }, + { + "amount": { + "quantity": 40, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 17, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 20, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 42, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "32210", + "3456", + "10007", + "24825", + "2776", + "25812", + "24383", + "10023", + "16037", + "30440", + "17819", + "18125", + "27044", + "17682", + "7424", + "11046", + "27209", + "23800", + "29841", + "5183", + "28002", + "5457", + "28999", + "18860", + "13065", + "4937", + "4626", + "6247", + "24945", + "20630" + ], + "assets": [] + }, + { + "amount": { + "quantity": 45, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "20289", + "2814", + "28756", + "526", + "6149", + "3695", + "476", + "6629", + "18870", + "31118", + "17130", + "7901", + "19790", + "18684", + "10812", + "3223", + "31089", + "21565", + "27434" + ], + "assets": [] + } + ], + "script_validity": "invalid", + "metadata": { + "1": { + "string": "∰" + } + }, + "id": "4c43e2986d471b57470778783e441dd7750b24c33d50730928369a0727c62827", + "collateral": [ + { + "amount": { + "quantity": 54, + "unit": "lovelace" + }, + "address": "", + "id": "6ebb740375246e4253ff5202df12436f481dd834322006489a32051133786a5e", + "derivation_path": [ + "2131", + "21217", + "10703", + "7692", + "14499", + "8194", + "28965", + "827", + "634", + "32233", + "29535", + "8667", + "21132", + "16968", + "26706", + "19152", + "6321", + "21638", + "3447", + "32235", + "14239", + "26760", + "28585", + "14061", + "5552", + "28454", + "22468" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 11, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 19, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 13, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 24, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 11, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 15, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 24, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 22, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 27, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 54, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 13, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 17, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 2, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 27353 + }, + { + "amount": { + "quantity": 160, + "unit": "lovelace" + }, + "address": "", + "id": "6526976f48a147064e7aeb56783d2e2e24c099db3e0741247b4a0f0a2c15e22b", + "derivation_path": [ + "13518", + "22989", + "19472", + "32073", + "5453", + "17232", + "26278", + "13032", + "540", + "9100", + "21786", + "30897", + "10353", + "23816", + "9307", + "6742" + ], + "assets": [], + "index": 4167 + }, + { + "amount": { + "quantity": 7, + "unit": "lovelace" + }, + "address": "", + "id": "70335fac085f02083759134f36428ed13e7e262d0e4d215f709f150148ee0726", + "derivation_path": [ + "19321", + "5516", + "7985", + "21614", + "29463", + "17494", + "19033", + "10188", + "8936", + "2678", + "691", + "9301", + "24897", + "26904", + "26370", + "32069", + "18597", + "23344", + "30873", + "20693", + "4375", + "17798" + ], + "assets": [], + "index": 21873 + }, + { + "id": "695871b20d011b4721710d5b3ed03941205b4e1406393f281c2f647a483b7014", + "index": 0 + }, + { + "id": "ff5e272a31d1206d1d3ac0713b330af669d0796b19d5285f12732a9d5b7128e6", + "index": 1 + }, + { + "amount": { + "quantity": 93, + "unit": "lovelace" + }, + "address": "", + "id": "6c06071e49914264144a276d0e416e49a80a2177633e7945215844486429af67", + "derivation_path": [ + "22210", + "27778", + "28231" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 19, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 10, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 22, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 29, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 29, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 6, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 23, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 23, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 17161 + }, + { + "amount": { + "quantity": 179, + "unit": "lovelace" + }, + "address": "", + "id": "3001762a634002311c65659a18316faf7a08b9cc102323803400214c35e6e20e", + "derivation_path": [ + "8978", + "13012", + "23404", + "22631", + "3569", + "15416", + "547", + "10892", + "10919", + "32348", + "29278" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 18, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 6, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 20, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 4, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 28, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 10665 + }, + { + "id": "2f6e22343f69440ba2585aab9b526e627506095a11064405303c5b0808093a39", + "index": 1 + }, + { + "id": "34137b6ef45353467a06645054a0c92521fc3546035efe3e823a3dcd74553eb6", + "index": 1 + }, + { + "id": "5940c03f38094ceb1f2f780c097248047f3e1f4d4a670431d27e5913074d685b", + "index": 1 + }, + { + "id": "03f5477d312270217c1b5f7c6d527ff288614e42f67f4e1f0f92415144fd5d28", + "index": 0 + }, + { + "amount": { + "quantity": 175, + "unit": "lovelace" + }, + "address": "", + "id": "1e18477e0274772c403120252e7a231b742109293b043a657f51565dee327c64", + "derivation_path": [ + "7240", + "22703", + "18981", + "16650", + "11618", + "32030", + "25401", + "17081", + "21280", + "5065", + "14433", + "12801", + "32115", + "6076", + "27975", + "3670", + "4039", + "14199", + "17999", + "28494" + ], + "assets": [], + "index": 22239 + }, + { + "amount": { + "quantity": 124, + "unit": "lovelace" + }, + "address": "", + "id": "30be3b301b771051453f4f58f45b402e7f000e71204019786330e71c08f57f18", + "derivation_path": [ + "27298", + "30004", + "10577", + "23091", + "9146", + "16565", + "28264", + "19739", + "26584", + "11935" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 13, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 245 + }, + { + "amount": { + "quantity": 97, + "unit": "lovelace" + }, + "address": "", + "id": "723b772642ef6e32044967614c4b1e7125421055524307ef02592d5e7e556190", + "derivation_path": [ + "7547", + "24748", + "30372", + "15168", + "27587", + "19282", + "15573", + "8356", + "29675", + "12173", + "31826", + "20514", + "31471", + "18930", + "26975" + ], + "assets": [], + "index": 3691 + }, + { + "amount": { + "quantity": 203, + "unit": "lovelace" + }, + "address": "", + "id": "79406e7543247d4c4c530803695d28291f63506d750b1a2b3d2370593928164a", + "derivation_path": [ + "26711", + "24695", + "260", + "17923", + "32574", + "23810", + "31082", + "24490", + "8626", + "3131", + "22982", + "9489", + "379", + "3698", + "15311", + "1065", + "29702", + "31443", + "26907" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 20, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 3920 + }, + { + "amount": { + "quantity": 154, + "unit": "lovelace" + }, + "address": "", + "id": "064d04215182581c3c1f2917c15a1167284f77846e7e024c1d634c6e04307744", + "derivation_path": [ + "26116", + "13534", + "20098", + "28658", + "14606", + "30285", + "17058", + "12154", + "9609", + "10341", + "23880", + "15684", + "25728", + "31567" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 25, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 29, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 7, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 6, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 15161 + } + ] + }, + { + "withdrawals": [ + { + "amount": { + "quantity": 66, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 17, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 162, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 137, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 64, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 39, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 102, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 98, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 250, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 217, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 190, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 200, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 188, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 51, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 116, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 46, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 254, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 66, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 194, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 119, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 71, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + } + ], + "inputs": [ + { + "amount": { + "quantity": 64, + "unit": "lovelace" + }, + "address": "", + "id": "2b0db55865ec4abd42514a152d14105dde7d37580959e72a220245177a4b5f62", + "derivation_path": [ + "23253" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 3, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 19601 + }, + { + "amount": { + "quantity": 217, + "unit": "lovelace" + }, + "address": "", + "id": "395e225bdc7aced240484b699603061c4110784266324ea638784d35436d116a", + "derivation_path": [ + "17810", + "4582", + "643", + "27945", + "20062", + "8711", + "14378", + "670", + "11721", + "1844", + "9729", + "16845", + "20681", + "28696", + "29990", + "1673", + "7392", + "21747", + "30765", + "13243", + "17956", + "4245", + "16131", + "4346", + "11595", + "30624", + "30740", + "19485", + "1399", + "26288", + "29189" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 1, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 15, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 19, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e43", + "quantity": 8, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 1263 + }, + { + "id": "49dab34278243a4d4746724203292a8d69841132684a476d7a6a440146447b07", + "index": 1 + }, + { + "amount": { + "quantity": 234, + "unit": "lovelace" + }, + "address": "", + "id": "9c9e3a2d7ea1fb39060428153d78393f44706a750b2f2202250686e4374d4000", + "derivation_path": [ + "7703", + "32500", + "5207", + "6839", + "15969", + "2100", + "1761", + "2864", + "26682", + "24280", + "17082", + "31516", + "27944", + "29791" + ], + "assets": [], + "index": 20611 + }, + { + "id": "7d151e79346927197564363c085b3b9e484078340b041f665f9a1c315d06e061", + "index": 1 + }, + { + "id": "193b0b4d053e3c7c396a0446260f5728267e4f5073e805173719927fee4733e6", + "index": 0 + }, + { + "id": "373c50660055dc371a217b09122b630c773a45794e7b4067ef1677186422497f", + "index": 0 + }, + { + "id": "37365f245ba5662e1e4f063861741d357521235e5e00350b34ebd84b431c4345", + "index": 0 + }, + { + "id": "77eb6e34674e12403fd0294f27157e36594d475b15465fd2675e22117b69e809", + "index": 1 + }, + { + "id": "675916416a4956059db61a1f5f0f3cb40a76095b7bdd4f4b49123d38404f5242", + "index": 1 + }, + { + "amount": { + "quantity": 210, + "unit": "lovelace" + }, + "address": "", + "id": "034d2e5a5a51002b6a40157331014448582a48475b167141252803122a7458d2", + "derivation_path": [ + "26071", + "21100", + "23094", + "18451", + "10475", + "8327", + "6043", + "22972", + "7335", + "3147", + "22329", + "15778", + "2431", + "11430", + "18045", + "23102", + "8556", + "26578", + "31067", + "23318", + "17149", + "27539", + "10114", + "16229", + "27322", + "28607" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 16, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ], + "index": 16419 + }, + { + "amount": { + "quantity": 250, + "unit": "lovelace" + }, + "address": "", + "id": "39e4075e09577d1d161358103f7db23b3a267845433a62787578c32e5b9b4e23", + "derivation_path": [ + "19054", + "25881", + "31900", + "31320", + "4172", + "12343", + "14059", + "10481", + "21533", + "19596", + "32731", + "16900", + "10199", + "13993", + "18136", + "19908", + "17297", + "22111" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 15, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ], + "index": 4904 + }, + { + "amount": { + "quantity": 212, + "unit": "lovelace" + }, + "address": "", + "id": "7a91076eaa7658232e8ea62614262d12277b0c3f46ea6c68456a76be21134c02", + "derivation_path": [ + "30102", + "10116", + "2953", + "21609", + "8755", + "11986", + "21135", + "5716", + "603", + "9318", + "23710", + "21391", + "29075", + "19324", + "1743", + "6352", + "22194" + ], + "assets": [], + "index": 28360 + }, + { + "amount": { + "quantity": 67, + "unit": "lovelace" + }, + "address": "", + "id": "5628246a6e64656c260d34414c650e2428783f7c59248157484c560d5c26376b", + "derivation_path": [ + "10637", + "28456", + "30025", + "24108", + "17442", + "26892", + "11262", + "23647", + "7397", + "24864", + "18303", + "4437", + "8968", + "12620", + "24009", + "9366", + "14075", + "22006", + "23210", + "3529", + "24456", + "28476", + "28628", + "6674", + "5913", + "21037", + "7296", + "3384", + "6511", + "11977", + "7976" + ], + "assets": [], + "index": 19592 + } + ], + "fee": { + "quantity": 229, + "unit": "lovelace" + }, + "outputs": [ + { + "amount": { + "quantity": 127, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "21080", + "25698", + "28004", + "10142", + "24409", + "4027" + ], + "assets": [] + }, + { + "amount": { + "quantity": 185, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 25, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ] + }, + { + "amount": { + "quantity": 201, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 138, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 91, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "10697", + "17717", + "22366", + "24511", + "31467", + "29608", + "11826", + "12570", + "5774", + "23911", + "31636", + "18080", + "21858", + "14476", + "30753", + "15496", + "29682", + "3816", + "7518", + "14170", + "30348", + "29114", + "10741" + ], + "assets": [] + }, + { + "amount": { + "quantity": 196, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 21, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + } + ] + }, + { + "amount": { + "quantity": 6, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 208, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 24, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ] + }, + { + "amount": { + "quantity": 13, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "11285", + "21311", + "22324", + "15359", + "21027", + "15108", + "28408", + "30650", + "29750", + "27138", + "23567", + "17256", + "7634", + "8413", + "22962", + "11189", + "9673", + "18817" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 10, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 90, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 29, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 14, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 29, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 24, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 16, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 56, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "15162", + "28944", + "6227", + "8346", + "7698", + "2708", + "30469", + "29476", + "12603", + "29625", + "9142", + "6481", + "5292", + "16271", + "18444", + "32561", + "19269", + "19857", + "25764", + "17567", + "1477" + ], + "assets": [] + }, + { + "amount": { + "quantity": 252, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 16, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ] + }, + { + "amount": { + "quantity": 0, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 246, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "27138" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 16, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 1, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 7, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 31, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 2, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 24, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 19, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 123, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 7, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 27, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 19, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ] + }, + { + "amount": { + "quantity": 93, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "22481", + "6607", + "31115", + "4972", + "28550", + "30503", + "14576", + "27716", + "12501", + "25770", + "1778", + "1340", + "27372", + "16155", + "27506", + "29271", + "10101", + "4296", + "25344", + "12635", + "31578", + "28807", + "6447", + "27586", + "13883", + "9041", + "20614", + "11769", + "17368", + "11728" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 28, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 12, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 30, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 10, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 16, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 10, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 21, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 30, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 23, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + } + ], + "script_validity": "valid", + "metadata": null, + "id": "de6650d5770b0ef97c3c126f3471435e69cb168c48234a724e063e639e0d7a72", + "collateral": [ + { + "id": "0fb7094f51417a635d6a0ffaee542f7a25d2370aad191257d34c4d7b45445861", + "index": 0 + }, + { + "amount": { + "quantity": 14, + "unit": "lovelace" + }, + "address": "", + "id": "df2e504f78b85f1068234a02e34370474d75430e0d7a5434725a5b0178cc43e4", + "derivation_path": [ + "12997", + "18994", + "25999", + "2718", + "27139", + "19732", + "26164", + "28486", + "26878", + "13040", + "16978", + "19902", + "11684", + "10325", + "517", + "22133" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 9, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 24, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ], + "index": 28721 + }, + { + "amount": { + "quantity": 114, + "unit": "lovelace" + }, + "address": "", + "id": "43fc61db3a67336c636926372e47761b6e4b46644f2e3a0d3d5a7f56214a2545", + "derivation_path": [ + "8308", + "18906", + "25475", + "26980", + "31726", + "19932", + "9326", + "30982", + "28132", + "16918", + "32082", + "8813", + "2712", + "9910", + "6238", + "3082", + "12518", + "19855", + "31546", + "29410", + "8494", + "4777", + "7097", + "7666", + "23108", + "25826", + "10933", + "15840", + "31331" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 21, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 5962 + }, + { + "id": "7c54101a2d2e5b341c3742516024e07de3195f5a5973b52b75b04e710c5b1db0", + "index": 0 + }, + { + "amount": { + "quantity": 253, + "unit": "lovelace" + }, + "address": "", + "id": "64434d522b4917c53e34425d5d153e616a29341b0a1f770d360d3851f271df27", + "derivation_path": [ + "16939", + "7277", + "22872" + ], + "assets": [], + "index": 25807 + }, + { + "amount": { + "quantity": 108, + "unit": "lovelace" + }, + "address": "", + "id": "5222683e2e75b66f6f1ba93d7826034c41ea4f795d681906766a29040d7f3389", + "derivation_path": [ + "8815", + "13895", + "8517", + "1869", + "19226", + "22717", + "31791", + "27245", + "14927", + "30839", + "10121", + "8058", + "7491", + "3235", + "6500", + "27402", + "402", + "6545", + "844" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 29, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 26, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 12451 + }, + { + "id": "7576642d354c7c3756854067093a4b5d494b5f5849795b2b292e41442d1c401c", + "index": 0 + }, + { + "amount": { + "quantity": 135, + "unit": "lovelace" + }, + "address": "", + "id": "d34f182b677a7c4c4d3f02093873697824201b666f0c0d55672f5f355e4ba5d6", + "derivation_path": [ + "21770" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 29, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 4, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 3, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 10, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 27156 + }, + { + "amount": { + "quantity": 230, + "unit": "lovelace" + }, + "address": "", + "id": "5f2f7c46114a012b3a130f5476207854281f327b57651f4b00e26e4d243e5502", + "derivation_path": [ + "11716", + "31223", + "29551", + "3973", + "7627", + "15389", + "2865", + "10568", + "11623", + "14087", + "27777", + "27800", + "9725", + "14519", + "18923", + "16910", + "4054", + "5129", + "4034" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 26, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 19, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 32121 + }, + { + "id": "16175106331d481f795f6f68057bcdaf48ad105992466692b898377d6838585c", + "index": 1 + }, + { + "id": "79604d7730413f2446c3765a732060400822167b4a1136091d311255383a7e4a", + "index": 0 + }, + { + "amount": { + "quantity": 235, + "unit": "lovelace" + }, + "address": "", + "id": "147d66cc321f285364121b121d23cf545e536c30540a2a843735637f4850c847", + "derivation_path": [ + "4364", + "26307", + "15193", + "10296", + "21190", + "8825", + "22217", + "4408" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 27, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ], + "index": 242 + }, + { + "amount": { + "quantity": 240, + "unit": "lovelace" + }, + "address": "", + "id": "6a19323cdfb7516d1c0e397df61b4d1c06122d3d487b273a0a6911090c1d4331", + "derivation_path": [ + "30131", + "9705", + "32270", + "28108", + "664", + "2223", + "17600", + "5029", + "2476", + "843", + "27369", + "24429", + "30099", + "18377", + "28618", + "32139", + "6155", + "12036", + "23832", + "11009", + "16988", + "30257", + "28541", + "24046", + "26699", + "19723", + "3830" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 27, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 2, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 6, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 27563 + }, + { + "amount": { + "quantity": 100, + "unit": "lovelace" + }, + "address": "", + "id": "1a63cb69090f4145b432580039333f3b2c3320444a723a0c42750d0e5724255c", + "derivation_path": [ + "20267", + "5422", + "10961", + "1466", + "3016", + "28784" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 20, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 5, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 24, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 4, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 1, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 24, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 27, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 26, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 4, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 22439 + }, + { + "amount": { + "quantity": 252, + "unit": "lovelace" + }, + "address": "", + "id": "785477023c3e861f2ce920af5a3d0c8d38626e6b373c1d6ade2103082c72d26f", + "derivation_path": [ + "15762", + "32307", + "15093", + "18139", + "26919" + ], + "assets": [], + "index": 9075 + }, + { + "amount": { + "quantity": 205, + "unit": "lovelace" + }, + "address": "", + "id": "1b2c0e61106e4e56eb6729313e6d67699b7d76e3f471d41d686a6a2a4c40535d", + "derivation_path": [ + "29025", + "28073", + "26892", + "24088", + "30510", + "17087", + "12630", + "20006", + "10431", + "696", + "16881", + "26944", + "28831", + "4790" + ], + "assets": [], + "index": 293 + }, + { + "amount": { + "quantity": 143, + "unit": "lovelace" + }, + "address": "", + "id": "6696ba7a676b701e46fe774d21684557b6ab7b56872f448bd052627127523965", + "derivation_path": [ + "12651", + "19452", + "24593", + "21833" + ], + "assets": [], + "index": 10242 + }, + { + "amount": { + "quantity": 105, + "unit": "lovelace" + }, + "address": "", + "id": "19567c8e0e7e561c603ce3402204286115db1e541b4d064a2f5c4a3dce54212d", + "derivation_path": [ + "3546", + "24855", + "31889", + "32031", + "15995", + "10132", + "26336", + "7470", + "26558", + "3494", + "17318", + "10934", + "25964", + "24354", + "17894", + "12745", + "20579" + ], + "assets": [], + "index": 31410 + }, + { + "amount": { + "quantity": 229, + "unit": "lovelace" + }, + "address": "", + "id": "5f526d49026a23330a4d63c74f1c61210d964228000b64354c3256175561033a", + "derivation_path": [ + "29926", + "17851", + "6940", + "19374", + "30979", + "11097", + "16085", + "13774", + "14523", + "15279", + "19416", + "4917", + "25170", + "5177", + "28896", + "8655", + "22419", + "29325", + "32079", + "16003", + "29422", + "29162" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 15, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 28, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 22, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 46, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 4, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 5, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 2, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 19, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 8, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 30634 + } + ] + }, + { + "withdrawals": [ + { + "amount": { + "quantity": 78, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 185, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 103, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 89, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 30, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 124, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 68, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 139, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 19, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 162, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 212, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 220, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 204, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 56, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 253, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 182, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 22, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 16, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 137, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 132, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 3, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 246, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 50, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 92, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 95, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 117, + "unit": "lovelace" + }, + "stake_address": "" + } + ], + "inputs": [ + { + "id": "37744ab149544e240d347660021d1413df4d1e623b14437a375f4c4414020363", + "index": 1 + }, + { + "id": "616c143355374b1b39e37c0f59181e6ee636b072540d07277336581f3b1e5c7a", + "index": 0 + }, + { + "amount": { + "quantity": 157, + "unit": "lovelace" + }, + "address": "", + "id": "3de9d041646713247b5e55584c55251f056f103178c019231e5e35696c090570", + "derivation_path": [ + "32382", + "25580", + "12960", + "11272", + "25169", + "21797", + "21861", + "3030", + "27675", + "31922", + "801", + "23993", + "20076", + "11395", + "20780", + "28507", + "13303", + "3329", + "1046", + "24723", + "9760", + "12056", + "20344", + "272", + "25429", + "29579", + "30412" + ], + "assets": [], + "index": 17126 + }, + { + "id": "77db444e4d852f61797b726a486d124fefa0a07971577375164604a4421b4136", + "index": 1 + }, + { + "id": "21417430074db7f862105e6d621c0e08642dec54043637285092bc6f35582d2f", + "index": 0 + }, + { + "amount": { + "quantity": 122, + "unit": "lovelace" + }, + "address": "", + "id": "422375725b45141d514c1d1a102a211975244e1d7c4e632a6b9f20582b39dc71", + "derivation_path": [ + "32394", + "10623", + "6808", + "21987", + "10626", + "10338", + "5134", + "30925", + "9325", + "2768", + "18611", + "31448", + "21365", + "21823", + "4061", + "26022", + "21282", + "6080", + "4951", + "28564", + "30700", + "17120", + "23104", + "19370", + "29545", + "2696", + "26047", + "20115" + ], + "assets": [], + "index": 32053 + }, + { + "id": "670e314d07345b223c0f470fc24235ea5a29f0226821790b1403f54166273079", + "index": 0 + }, + { + "id": "7dd94819347f5686d8114e7a11486d792830235a5336baad9e92d3bb1e57077d", + "index": 1 + }, + { + "amount": { + "quantity": 254, + "unit": "lovelace" + }, + "address": "", + "id": "0a16767e532f513f3629bf5174076a497a4103293f0f102f045676283b7a2d3b", + "derivation_path": [ + "22254", + "6180", + "29058", + "26463", + "28410", + "15539", + "18519", + "4586" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 19, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 47, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 58, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 10242 + }, + { + "amount": { + "quantity": 205, + "unit": "lovelace" + }, + "address": "", + "id": "3a66aea81d394018631e34b8772cc432cb1cba7b3a4a2519361311f217ae6a51", + "derivation_path": [ + "4523", + "12466", + "2335", + "27901", + "28490", + "16794", + "30076", + "8495", + "4718", + "2313", + "7032", + "8600", + "31926", + "8193", + "11472", + "10151", + "12588", + "3042" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 28, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 23, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 20, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 49, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 30, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 55, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 7, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 17, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 14, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 16, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 19239 + }, + { + "amount": { + "quantity": 179, + "unit": "lovelace" + }, + "address": "", + "id": "c64957b6413e55504c6f01243555295a2a68540d0e7303cdf89f034a3b427e2a", + "derivation_path": [ + "8970", + "2588", + "11441", + "30621", + "18300", + "26706", + "32747", + "21983", + "32210", + "9621", + "20959", + "13856", + "16438", + "27606", + "22805", + "2793", + "6041", + "22793" + ], + "assets": [], + "index": 25461 + }, + { + "id": "0cb508eb164231120e25da527a5b3a32151957114e38744b3c102b5c472c2053", + "index": 1 + }, + { + "amount": { + "quantity": 231, + "unit": "lovelace" + }, + "address": "", + "id": "21304e000c21507240a474253144431d411a5263681c103f4e0e3204c3897806", + "derivation_path": [ + "11182", + "8817", + "17137", + "17906", + "21183", + "10022", + "1662" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 8, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 14, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 31, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 34, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 4, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 23, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 9, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 40, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 43, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e42", + "quantity": 28, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e43", + "quantity": 2, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 16326 + }, + { + "id": "13cb413a0266a7ea1b75206e2e11700b2e69677b2f3e253895cf12466c2a2200", + "index": 0 + }, + { + "id": "683453022676153d017166214065734eb11c4e27582b18616c1f584a08933917", + "index": 0 + } + ], + "fee": { + "quantity": 9, + "unit": "lovelace" + }, + "outputs": [ + { + "amount": { + "quantity": 29, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "2922", + "6927", + "20691", + "9147", + "24087", + "2014", + "24332", + "19609", + "22732", + "133", + "31098", + "6540", + "32363", + "3856" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 25, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ] + }, + { + "amount": { + "quantity": 212, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 34, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 149, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "31244", + "7495", + "3459", + "18243", + "24409", + "24065", + "17919", + "31755", + "18363", + "6231", + "19197", + "2332", + "1939", + "17093", + "27947", + "21220", + "25810", + "21240", + "7860", + "25455", + "28188", + "9732", + "11195", + "1295", + "3897", + "5280" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 24, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ] + }, + { + "amount": { + "quantity": 199, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 17, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 33, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 6, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 30, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 27, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 8, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 15, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 27, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 26, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 3, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ] + }, + { + "amount": { + "quantity": 117, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 76, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 146, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 8, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 20, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 9, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 5, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 52, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 36, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "14958", + "24923", + "14426", + "15577", + "29649", + "17033", + "23783", + "18177", + "23370", + "13234", + "16479", + "4702", + "27829", + "23454", + "28767", + "11176", + "15871", + "585", + "26704", + "18852", + "31532", + "27774", + "30783", + "1704", + "16846" + ], + "assets": [] + }, + { + "amount": { + "quantity": 248, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 29, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + } + ] + }, + { + "amount": { + "quantity": 244, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "12468", + "17691", + "4815", + "8998", + "28671", + "14395", + "29521", + "7347", + "21459", + "20206", + "16047", + "21898", + "21816", + "13715", + "3317", + "11243", + "2455", + "25913", + "10293", + "13884", + "16393", + "13900", + "22375", + "9112", + "22749", + "655", + "7027", + "12757" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 1, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + } + ] + }, + { + "amount": { + "quantity": 227, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "29746", + "8115", + "21641", + "8145", + "30324", + "30670", + "2678", + "11658", + "10387", + "13638", + "17738", + "2417", + "13468", + "29503", + "15356", + "8170", + "10014", + "8109", + "19354", + "26740", + "10709", + "15335", + "2008", + "23716" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 18, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 1, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 24, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 21, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 46, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 18, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 22, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 4, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 29, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 2, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 168, + "unit": "lovelace" + }, + "address": "", + "assets": [] + } + ], + "metadata": { + "12": { + "list": [ + { + "bytes": "4750105a102b7a485a37fd100b6f5e0d589b2b115d6950191012a5505691e2441e3c7724634c0c240a193979683b540517375244a30139b83309c718cb" + } + ] + } + }, + "id": "1d380e71da437f64047a58e814717e7c26607c2c0d217e4d1d6773556b547f33", + "collateral": [ + { + "id": "3b043c180d0d1e1d802d42025c72b9e147204d6b3dd720302d66994a6e34194e", + "index": 0 + }, + { + "id": "5007540c7d61427a6362452398aa523a67315d73901843ac54585df74d0d643a", + "index": 0 + }, + { + "id": "4d7a30092b4601d91b13a02d2b30055bc4ac3b6e1d1fb902685a350e03736a6c", + "index": 0 + }, + { + "id": "3b3a614d22b27c060f686a1449765e7a6d3873e405032e74690816a63147774a", + "index": 1 + }, + { + "amount": { + "quantity": 153, + "unit": "lovelace" + }, + "address": "", + "id": "6903ce6b184c230a3358323d35161e47e9452d2cce514d5cd01b2a655e150d63", + "derivation_path": [ + "25617", + "5844", + "1584", + "3085", + "11083", + "26281", + "10552", + "7848", + "29719", + "24639", + "3602", + "11643", + "882", + "24645", + "29764", + "8101" + ], + "assets": [], + "index": 10543 + }, + { + "amount": { + "quantity": 114, + "unit": "lovelace" + }, + "address": "", + "id": "6a0b195fec7c77172757f378025b385e4b2a17936267424c511f3e04152f5509", + "derivation_path": [ + "14968", + "31596", + "6416", + "8532", + "11403", + "5904", + "3657", + "7982", + "17759", + "5632", + "32360", + "1382", + "11974", + "27945", + "6555", + "27333", + "26417", + "23916", + "3515", + "28235", + "30784", + "16378", + "15512", + "30064", + "18214", + "18986" + ], + "assets": [], + "index": 5168 + }, + { + "amount": { + "quantity": 201, + "unit": "lovelace" + }, + "address": "", + "id": "4b15270e502b1e11a67ae2653d113a9e350d766f7d3e44789dd24b251d3f0a77", + "derivation_path": [ + "28786" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 30, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 12898 + }, + { + "amount": { + "quantity": 76, + "unit": "lovelace" + }, + "address": "", + "id": "247d2422181e5073196d613bcd2877551e1175100f37bb650227656f53de6d2e", + "derivation_path": [ + "30544", + "28518", + "2952", + "3184", + "27670", + "18376", + "20933", + "107", + "14481", + "12983", + "3463", + "25508", + "22050", + "29989", + "27073", + "2303", + "20063", + "18257", + "22843", + "9888", + "11389", + "31207", + "9698", + "25533", + "19347" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 25, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 16, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 15093 + }, + { + "amount": { + "quantity": 150, + "unit": "lovelace" + }, + "address": "", + "id": "135e571074560673250f296405095e2266734d676b9c63c923284c00104e6a7e", + "derivation_path": [ + "31217", + "29656", + "31332", + "7333", + "26081", + "10903", + "31656", + "3027", + "10451", + "28835", + "16986" + ], + "assets": [], + "index": 20271 + }, + { + "id": "5e4a32645d4b783818631257400347750f5f081b186417507a4bf0011827da04", + "index": 1 + }, + { + "amount": { + "quantity": 148, + "unit": "lovelace" + }, + "address": "", + "id": "59152b17326d711f781b643f4561d5642e124542442f513a276c105a836d4419", + "derivation_path": [ + "25543", + "11260", + "24759", + "6126", + "7697", + "5784", + "3129", + "18430", + "21155", + "17529", + "20150", + "22908", + "8316", + "11795", + "22726", + "2262", + "14779", + "12804", + "23367", + "17643", + "30685" + ], + "assets": [], + "index": 1712 + }, + { + "amount": { + "quantity": 151, + "unit": "lovelace" + }, + "address": "", + "id": "1c31caa44b4a705d7971205e3d10727a0a46b6131415755f7b7d3b35175f8c70", + "derivation_path": [ + "13473", + "27946", + "8702", + "8341", + "2453", + "23602", + "215", + "31900", + "12254", + "12609", + "30646", + "934", + "7078", + "12636", + "5280" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 28, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 23, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 6, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 17, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 68, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 40, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 65, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 13, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 29, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 26, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 18, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 26812 + }, + { + "amount": { + "quantity": 101, + "unit": "lovelace" + }, + "address": "", + "id": "50fe6238d17879ba56215653212374041b42d4260947070a12f0791c68287268", + "derivation_path": [ + "2106", + "14453", + "20017", + "19687", + "23905", + "27857", + "29075", + "18215", + "28400", + "11145", + "10135", + "3802", + "21173", + "15598", + "21866", + "11612", + "18825", + "17498" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 23, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 29, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 51, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 45, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 30993 + }, + { + "amount": { + "quantity": 32, + "unit": "lovelace" + }, + "address": "", + "id": "4b4e253c475833008071453377334f7fe513671d0156480d10381f3d22269100", + "derivation_path": [ + "27406", + "25021", + "23692", + "29640", + "10119", + "6816", + "4718", + "13056", + "29956", + "5263", + "26870", + "26057", + "3895", + "15234", + "13234", + "5120", + "15356", + "24496", + "6034", + "10959", + "6734", + "323", + "25434", + "28275", + "31749", + "32337", + "30523", + "23492" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 7, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 20414 + }, + { + "id": "da6064635909316851dd0e235d3068467cc064e444647a75573a697926193338", + "index": 1 + }, + { + "amount": { + "quantity": 88, + "unit": "lovelace" + }, + "address": "", + "id": "6a5c77c09e581adb471a5f670e1b017e1b290d79ce65632908762172700f1177", + "derivation_path": [ + "7507", + "2128", + "26947", + "16977" + ], + "assets": [], + "index": 5542 + }, + { + "id": "080e8021762c200e5f4f1273577b7f200a16423a354168027138015571e17728", + "index": 0 + }, + { + "amount": { + "quantity": 190, + "unit": "lovelace" + }, + "address": "", + "id": "5a10024c5b69c74633655d045423771c75b43b0a0f53827f560b3b7175de771e", + "derivation_path": [ + "372", + "24674", + "25802", + "23337", + "11105", + "29635", + "32028", + "26154", + "32578", + "3645", + "10260", + "2718" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 30, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 7, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 53, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 2, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 12, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 11, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 21, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 1, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e42", + "quantity": 10, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e43", + "quantity": 26, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 9585 + } + ] + }, + { + "withdrawals": [ + { + "amount": { + "quantity": 138, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 242, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 102, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 124, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + } + ], + "inputs": [], + "fee": { + "quantity": 131, + "unit": "lovelace" + }, + "outputs": [ + { + "amount": { + "quantity": 39, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "15376", + "6519", + "28119", + "11096", + "5443", + "18586", + "24164", + "2544", + "1363", + "24536", + "23813", + "13865", + "20073", + "24627", + "1394" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 26, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 25, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e43", + "quantity": 30, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 30, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 126, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 19, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ] + }, + { + "amount": { + "quantity": 192, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "17696", + "2265", + "1002", + "28403", + "14665", + "7430", + "5651", + "3104", + "19360", + "17810", + "31201", + "4117", + "19752", + "17744", + "27389", + "19305", + "15208", + "3514", + "11853", + "30843", + "10017", + "17604", + "19681", + "15775", + "10382", + "6305", + "14324" + ], + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 36, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 5, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 6, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 1, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 12, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 120, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 214, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 19, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ] + }, + { + "amount": { + "quantity": 45, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 19, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 11, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 115, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 49, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 181, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "4172", + "4813", + "25793", + "17570", + "13353", + "30760", + "1932", + "29319", + "3122", + "8291", + "16739", + "10541", + "30418", + "20884", + "7071", + "3973", + "24572", + "16511", + "14444", + "22807" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 14, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 13, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 33, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 9, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 239, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "9675", + "22926", + "30265", + "13425", + "24670", + "3098", + "1796", + "1720", + "4587", + "30678", + "10499", + "8809", + "3621", + "28226" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 24, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 4, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 13, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 2, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 11, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 6, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 16, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 27, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 25, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 21, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 19, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 15, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 24, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 6, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 50, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 1, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ] + }, + { + "amount": { + "quantity": 253, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 254, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "28722", + "20621", + "17838", + "15870", + "12215", + "31418", + "19307" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 28, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 114, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 182, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 8, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 25, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 136, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 40, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "14270", + "484", + "23836", + "10099", + "24731" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 7, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + } + ] + }, + { + "amount": { + "quantity": 205, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 135, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "26383", + "30458", + "2270", + "14483", + "22938", + "24676", + "32195", + "13493", + "1903", + "10124", + "15457", + "26191" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 19, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ] + }, + { + "amount": { + "quantity": 126, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "1802", + "1797", + "5172", + "20851" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 11, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 6, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 12, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ] + }, + { + "amount": { + "quantity": 167, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 13, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 28, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 25, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 12, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 12, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 21, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 5, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 12, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 99, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "18853", + "19913" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 3, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 20, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 16, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 38, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e42", + "quantity": 22, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 75, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 45, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 131, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "20907", + "4865", + "5789", + "3117", + "12012", + "10472", + "17050", + "30564", + "14997", + "22769", + "31086", + "8552", + "1097", + "6475", + "7906", + "14916", + "15394", + "10709", + "16104", + "22675", + "30881", + "25973", + "6562", + "12202", + "16129", + "8420", + "20830", + "3544", + "9732" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 19, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + } + ] + }, + { + "amount": { + "quantity": 70, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 156, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 11, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + } + ] + } + ], + "script_validity": "valid", + "metadata": { + "23": { + "map": [ + { + "k": { + "string": "𢞍" + }, + "v": { + "map": [ + { + "k": { + "string": "㋆" + }, + "v": { + "list": [] + } + }, + { + "k": { + "string": "𦖛𧏚" + }, + "v": { + "bytes": "706317" + } + } + ] + } + } + ] + } + }, + "id": "034e2353534015571e453f350a478d593008637d47e310443eb9466307663648", + "collateral": [ + { + "id": "7ed6760d7b3eb90368431f5f44237b397406484535124d266b174b4a51a75a28", + "index": 1 + }, + { + "id": "5a600004637102762747523158395c2a1e164f5730681f512d5f10553e5e697e", + "index": 0 + }, + { + "amount": { + "quantity": 146, + "unit": "lovelace" + }, + "address": "", + "id": "6d6c5dd54e0b5f70df06006692fd2f76524f055c0d12391d42667c004f077103", + "derivation_path": [ + "10933", + "12724", + "13511", + "15899", + "6541" + ], + "assets": [], + "index": 14061 + }, + { + "id": "5b362fa8685c66635c112ef011240e1206a2763a1989363d6f58bbdbca020a5c", + "index": 0 + }, + { + "amount": { + "quantity": 135, + "unit": "lovelace" + }, + "address": "", + "id": "6b3f174b603e62f5020c1c23a94efc5a6d3043771b42654e617c650a2a462016", + "derivation_path": [ + "32152", + "11358", + "18404", + "31594" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 7, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 10324 + }, + { + "amount": { + "quantity": 81, + "unit": "lovelace" + }, + "address": "", + "id": "3c6f01d3492d1777505d0b484d4642677906474b2fbb35630b576b17626f5730", + "derivation_path": [ + "29070", + "28582", + "17374" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 25, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + } + ], + "index": 31524 + }, + { + "id": "65d50a11776164464a1807e6e53418684f795e15146e223241654540417f644a", + "index": 0 + }, + { + "amount": { + "quantity": 203, + "unit": "lovelace" + }, + "address": "", + "id": "2c79547076184c6eee510655866223487cb86242cb4b2b7a215b567d39322323", + "derivation_path": [ + "27663", + "7209", + "26754", + "3162", + "15674", + "10855", + "544", + "6750", + "7005", + "15880", + "2755", + "16372", + "19544", + "10345", + "752", + "11558", + "25507", + "18498", + "18350", + "6475", + "3588", + "32515", + "7664", + "25439", + "14250", + "19246", + "28188" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 1, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 10600 + }, + { + "amount": { + "quantity": 63, + "unit": "lovelace" + }, + "address": "", + "id": "2f0e7d2424bf855751855b496e5622143f034e437352462763696be055a4291d", + "derivation_path": [ + "9077", + "209", + "8262", + "24589", + "14976", + "19573", + "12278", + "23761", + "9539", + "13955", + "6881", + "20798", + "9505", + "12757", + "32767", + "31539", + "5469", + "7415", + "8708", + "28341" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 15, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 26, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 17, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 22243 + }, + { + "amount": { + "quantity": 65, + "unit": "lovelace" + }, + "address": "", + "id": "600e5e433d495e04056f4852180457715e5728006252c73e0d72475c151e6963", + "derivation_path": [ + "3674", + "24691", + "23771" + ], + "assets": [], + "index": 17724 + }, + { + "amount": { + "quantity": 226, + "unit": "lovelace" + }, + "address": "", + "id": "5a653b560404073d30d148745f567840d80b135d7c024709806d005608425d3e", + "derivation_path": [ + "21851", + "23132", + "30625", + "17813", + "14382", + "23480", + "10832", + "8251", + "17801", + "2472", + "11449", + "12447", + "31754", + "8051", + "14276" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 23, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 26, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 14555 + }, + { + "id": "1a3ce144718b2147623e3a2951766b2d71633b347b433b367423ca130815279c", + "index": 1 + }, + { + "amount": { + "quantity": 188, + "unit": "lovelace" + }, + "address": "", + "id": "390963bc1e19650c270b22f41c49e61e6c247a6f02171507f9681c6819291c18", + "derivation_path": [ + "3700", + "4021", + "16602", + "32090", + "23599", + "9105", + "25149", + "12083", + "7661", + "11518", + "19171", + "29977", + "641", + "18209", + "8984", + "12168", + "29468", + "11207", + "20446", + "32249", + "15121", + "20598", + "22764", + "7572", + "2351", + "10097" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 24, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e43", + "quantity": 9, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 54, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 10, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 5, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 26, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 8, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 24, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 19, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 2, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 13, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e43", + "quantity": 27, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 14, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 7491 + } + ] + } + ] +} \ No newline at end of file diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiExternalInputTestnet0.json b/lib/core/test/data/Cardano/Wallet/Api/ApiExternalInputTestnet0.json index 0a584fe0290..2a6e3f1d8ca 100644 --- a/lib/core/test/data/Cardano/Wallet/Api/ApiExternalInputTestnet0.json +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiExternalInputTestnet0.json @@ -1,241 +1,270 @@ { - "seed": 2716995801063548171, + "seed": 8422840658998580064, "samples": [ { "amount": { - "quantity": 254, + "quantity": 176, "unit": "lovelace" }, "address": "", - "id": "3d0122631d565f336641015fa2341c594c02664d131963c521703483c5053e3e", + "id": "060c66010a340002f535cb35697342a23a3104e7696f4224095ac1322d217248", "assets": [ { - "asset_name": "546f6b656e42", - "quantity": 11, - "policy_id": "11111111111111111111111111111111111111111111111111111111" - }, - { - "asset_name": "546f6b656e42", - "quantity": 24, - "policy_id": "33333333333333333333333333333333333333333333333333333333" - }, - { - "asset_name": "546f6b656e44", - "quantity": 40, - "policy_id": "44444444444444444444444444444444444444444444444444444444" - } - ], - "index": 3335 - }, - { - "amount": { - "quantity": 13, - "unit": "lovelace" - }, - "address": "", - "id": "4319d46a5b5118651a106080259f6359615a3e4e224e25367b469991191d09fc", - "assets": [], - "index": 6141 - }, - { - "amount": { - "quantity": 225, - "unit": "lovelace" - }, - "address": "", - "id": "5d346243624b49026f0e11617e1a1e55033e5f387f358c080f13c9420455747e", - "assets": [ - { - "asset_name": "546f6b656e41", - "quantity": 17, - "policy_id": "00000000000000000000000000000000000000000000000000000000" - }, - { - "asset_name": "546f6b656e42", - "quantity": 24, + "asset_name": "546f6b656e45", + "quantity": 58, "policy_id": "00000000000000000000000000000000000000000000000000000000" }, { "asset_name": "546f6b656e44", - "quantity": 12, - "policy_id": "00000000000000000000000000000000000000000000000000000000" + "quantity": 10, + "policy_id": "11111111111111111111111111111111111111111111111111111111" }, { - "asset_name": "546f6b656e41", - "quantity": 27, - "policy_id": "11111111111111111111111111111111111111111111111111111111" + "asset_name": "546f6b656e42", + "quantity": 6, + "policy_id": "22222222222222222222222222222222222222222222222222222222" }, { "asset_name": "546f6b656e43", - "quantity": 26, - "policy_id": "11111111111111111111111111111111111111111111111111111111" + "quantity": 28, + "policy_id": "22222222222222222222222222222222222222222222222222222222" }, { - "asset_name": "546f6b656e43", - "quantity": 16, + "asset_name": "546f6b656e44", + "quantity": 7, "policy_id": "22222222222222222222222222222222222222222222222222222222" }, { "asset_name": "546f6b656e45", - "quantity": 32, + "quantity": 1, "policy_id": "22222222222222222222222222222222222222222222222222222222" }, { - "asset_name": "546f6b656e41", - "quantity": 30, + "asset_name": "546f6b656e43", + "quantity": 1, "policy_id": "33333333333333333333333333333333333333333333333333333333" }, { - "asset_name": "546f6b656e43", - "quantity": 6, + "asset_name": "546f6b656e44", + "quantity": 20, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 11, "policy_id": "44444444444444444444444444444444444444444444444444444444" } ], - "index": 12831 + "index": 24043, + "datum": "cf1129445b24674c1d155e5f18901176ee4b62755d5e653fdd1259b1322d2c7c" }, { "amount": { - "quantity": 114, + "quantity": 2, "unit": "lovelace" }, "address": "", - "id": "2e77654128742a474f012f5c263010117b7a711f352c3d316e3c0356351d33ec", + "id": "d02481907e49204843a25b4621cb1cb955cf417760b7c55b62007e6f75104eb4", "assets": [], - "index": 24366 + "index": 29744 }, { "amount": { - "quantity": 254, + "quantity": 11, "unit": "lovelace" }, "address": "", - "id": "1b5955612409c2a63bfc6c2c5d291c2c1d2950b43c0613162a74221430717a6a", + "id": "47a8224966160f01cdda724e5a79a2336df81c4d4f22e34c062369902a4c0028", "assets": [], - "index": 21856 + "index": 1205, + "datum": "2a7d565c411d7e1e084e195d16d62a0c7a20707a107d7b57527b7ab526066a75" }, { "amount": { - "quantity": 127, + "quantity": 153, "unit": "lovelace" }, "address": "", - "id": "242f78572d5536218a3a07769078502b087de90d607d3a1a320850e25b614244", + "id": "3e1e727607705b441fc04f695903430d7e0d673af86e527b3e7e64044c0a4c73", "assets": [ { - "asset_name": "546f6b656e43", - "quantity": 25, - "policy_id": "00000000000000000000000000000000000000000000000000000000" + "asset_name": "546f6b656e42", + "quantity": 30, + "policy_id": "44444444444444444444444444444444444444444444444444444444" } ], - "index": 3899 + "index": 16971, + "datum": "19353c72460e7a0d599f2b59115d51fb1b343bde3d205747640c4794273a0691" }, { "amount": { - "quantity": 189, + "quantity": 167, "unit": "lovelace" }, "address": "", - "id": "529977637071b46c56123d5b091f3325657a40293c70553b3b38190e46067016", + "id": "30385a1018304f544d333c296e238e1d9a1bb52656726d627b7b190c47003e15", "assets": [ - { - "asset_name": "546f6b656e41", - "quantity": 5, - "policy_id": "00000000000000000000000000000000000000000000000000000000" - }, { "asset_name": "546f6b656e44", - "quantity": 8, + "quantity": 30, "policy_id": "00000000000000000000000000000000000000000000000000000000" }, { - "asset_name": "546f6b656e45", - "quantity": 6, - "policy_id": "00000000000000000000000000000000000000000000000000000000" + "asset_name": "546f6b656e43", + "quantity": 5, + "policy_id": "22222222222222222222222222222222222222222222222222222222" }, { "asset_name": "546f6b656e44", - "quantity": 24, - "policy_id": "11111111111111111111111111111111111111111111111111111111" - }, + "quantity": 18, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 25251, + "datum": "24306a2607bfec04852dd572fb506718d5d84f6657773a6c572d3461cd598c15" + }, + { + "amount": { + "quantity": 253, + "unit": "lovelace" + }, + "address": "", + "id": "1a6faa382a4b780d1572bb3045474a4c3a237f254a0f7a0b73741274091bf052", + "assets": [ { - "asset_name": "546f6b656e41", - "quantity": 11, - "policy_id": "22222222222222222222222222222222222222222222222222222222" + "asset_name": "546f6b656e43", + "quantity": 20, + "policy_id": "00000000000000000000000000000000000000000000000000000000" }, { - "asset_name": "546f6b656e42", - "quantity": 4, - "policy_id": "22222222222222222222222222222222222222222222222222222222" + "asset_name": "546f6b656e41", + "quantity": 10, + "policy_id": "33333333333333333333333333333333333333333333333333333333" }, { "asset_name": "546f6b656e43", - "quantity": 17, - "policy_id": "22222222222222222222222222222222222222222222222222222222" - }, - { - "asset_name": "546f6b656e44", - "quantity": 16, - "policy_id": "22222222222222222222222222222222222222222222222222222222" + "quantity": 27, + "policy_id": "33333333333333333333333333333333333333333333333333333333" }, { "asset_name": "546f6b656e45", - "quantity": 24, - "policy_id": "22222222222222222222222222222222222222222222222222222222" - }, - { - "asset_name": "546f6b656e42", - "quantity": 12, + "quantity": 23, "policy_id": "33333333333333333333333333333333333333333333333333333333" }, { "asset_name": "546f6b656e45", - "quantity": 21, + "quantity": 13, "policy_id": "44444444444444444444444444444444444444444444444444444444" } ], - "index": 24380 + "index": 28289, + "datum": "2b64336922169a2510005b3d4933904326a4472d29cd2b502d604015445972d5" }, { "amount": { - "quantity": 83, + "quantity": 151, "unit": "lovelace" }, "address": "", - "id": "7293597736457d2132117d53af4326097f265011526d455d67bcfe23aa216276", + "id": "2d4704726f6e4c6276e0627637671c5c3b3460376d3456376726674a39372090", "assets": [], - "index": 1204 + "index": 29384, + "datum": "1d2191f96d2415302b5d737173141d1c4d7c7a230a6c416d1906143d0320f311" }, { "amount": { - "quantity": 179, + "quantity": 159, "unit": "lovelace" }, "address": "", - "id": "59147f470d24430635522e5e01aa6571174e1611685832966bd52954661412b8", + "id": "2f04b9d3196d0b324c152a6066232e26320e0a44a0ac28660c572d633d284d13", "assets": [ { "asset_name": "546f6b656e43", - "quantity": 24, + "quantity": 15, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 29, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 25, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e43", + "quantity": 5, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 23, "policy_id": "33333333333333333333333333333333333333333333333333333333" } ], - "index": 27579 + "index": 24001, + "datum": "15187a5f1601214c143932f5983f9d6d163866292e33df131f0116327acc7444" }, { "amount": { - "quantity": 135, + "quantity": 150, "unit": "lovelace" }, "address": "", - "id": "e25b7f21276c2a24301d3a355332673d5c16d86e2d071d7a52386c620f725324", + "id": "681519ef5a6544792f05071d2f4c050b6a6b7f2968783d7fde6f0a92666d4729", "assets": [ { "asset_name": "546f6b656e41", "quantity": 21, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 14, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 12, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 4, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 2, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 11, "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 20, + "policy_id": "44444444444444444444444444444444444444444444444444444444" } ], - "index": 22631 + "index": 23951, + "datum": "3e03730afd1a39132e6a021c49396e03712e341c0a2d1a456b5ff75a725e0a5c" + }, + { + "amount": { + "quantity": 202, + "unit": "lovelace" + }, + "address": "", + "id": "6e53e96fea1d720b457b365a244ce8300ab702380eb829480f2b3d5c2a325106", + "assets": [], + "index": 27795, + "datum": "777e506a3f44427d2c146a4e379b1c5e5212305a39475c1a091d6576724b6c27" } ] } \ No newline at end of file diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiTxInputGeneralTestnet0.json b/lib/core/test/data/Cardano/Wallet/Api/ApiTxInputGeneralTestnet0.json new file mode 100644 index 00000000000..68f927d3ee1 --- /dev/null +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiTxInputGeneralTestnet0.json @@ -0,0 +1,228 @@ +{ + "seed": -1708654607137581765, + "samples": [ + { + "id": "840b334b43335226181859097865cf736970247855393d4e3c6b6a3b2d1b7e45", + "index": 0 + }, + { + "amount": { + "quantity": 162, + "unit": "lovelace" + }, + "address": "", + "id": "4c1cba3e08a91e442b6c436b734d5e161c674a4545529d716b223a484f328b62", + "derivation_path": [ + "17125", + "18173", + "14014", + "7555", + "10855", + "14013", + "9946", + "31377", + "22343", + "9174", + "24703", + "7943", + "11738", + "15349", + "28338", + "20394", + "31190", + "6148" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 12, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 11, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 79, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 19, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e43", + "quantity": 18, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 9, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 12, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 8, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 12, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 31396 + }, + { + "id": "67e557032b43ff01c15346360f5b7ae3d0520226554619292f0d1b3d3b2f156e", + "index": 1 + }, + { + "id": "59ff310409270109781e1755374c5fa70c6c5c66192c52274f41706d001e5501", + "index": 1 + }, + { + "amount": { + "quantity": 68, + "unit": "lovelace" + }, + "address": "", + "id": "0f1a627352102c4d4d0ebb3ba01937175d59643d3c6a186e5e492b566b673d02", + "derivation_path": [ + "29124" + ], + "assets": [], + "index": 22717 + }, + { + "amount": { + "quantity": 230, + "unit": "lovelace" + }, + "address": "", + "id": "7d5f5e32683d79ca2068391336012e1e526922423f7527434416665b2071053c", + "derivation_path": [ + "23118", + "9814", + "17884", + "23471", + "2112", + "22357", + "18646", + "19199", + "21684", + "17176", + "23245", + "14429" + ], + "assets": [ + { + "asset_name": "546f6b656e42", + "quantity": 4, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 9, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e42", + "quantity": 2, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + } + ], + "index": 22045 + }, + { + "id": "2b1ef1744b4921010458257f7c6bea045b28661cdd4b4455245403616d4118cf", + "index": 1 + }, + { + "id": "5149333ecb5c92366e6d135e3915740fcd140826571e5a756df21f5e79455641", + "index": 0 + }, + { + "id": "6244924533715121146e024f6323f116154d5cd90d0428423f0a6bfc5d2b4a73", + "index": 0 + }, + { + "amount": { + "quantity": 157, + "unit": "lovelace" + }, + "address": "", + "id": "46fc0e42041c8b2e3f32274d91168210112653405ef60e092c0301c2594f1551", + "derivation_path": [ + "214", + "18637" + ], + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 32, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 30, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e45", + "quantity": 28, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 24, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 12, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e44", + "quantity": 16, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 28, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 49, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e42", + "quantity": 8, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 23, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e45", + "quantity": 23, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ], + "index": 16395 + } + ] +} \ No newline at end of file diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiTxOutputGeneralTestnet0.json b/lib/core/test/data/Cardano/Wallet/Api/ApiTxOutputGeneralTestnet0.json new file mode 100644 index 00000000000..bbed7151bae --- /dev/null +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiTxOutputGeneralTestnet0.json @@ -0,0 +1,284 @@ +{ + "seed": -6422875769636208967, + "samples": [ + { + "amount": { + "quantity": 157, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "18076", + "1401", + "16839", + "29882" + ], + "assets": [ + { + "asset_name": "546f6b656e45", + "quantity": 10, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 31, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "12782", + "17346", + "31989", + "28039", + "16936", + "136", + "17283", + "9495", + "3181", + "17291", + "32092", + "12528", + "5617", + "5958", + "18329", + "5081" + ], + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 17, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + } + ] + }, + { + "amount": { + "quantity": 21, + "unit": "lovelace" + }, + "address": "", + "derivation_path": [ + "25631", + "5510", + "13534", + "30491", + "19060", + "23803", + "16340", + "3461", + "2433", + "19273", + "24382", + "9115", + "31514", + "10457", + "17133", + "16973", + "23464", + "24567", + "32742", + "11736", + "28530", + "14440" + ], + "assets": [] + }, + { + "amount": { + "quantity": 215, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 88, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e43", + "quantity": 5, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 22, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e44", + "quantity": 28, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e42", + "quantity": 10, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 16, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e41", + "quantity": 8, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e42", + "quantity": 26, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e43", + "quantity": 22, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e45", + "quantity": 1, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 6, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 165, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 20, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 8, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e44", + "quantity": 33, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e42", + "quantity": 34, + "policy_id": "11111111111111111111111111111111111111111111111111111111" + }, + { + "asset_name": "546f6b656e41", + "quantity": 8, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e44", + "quantity": 6, + "policy_id": "22222222222222222222222222222222222222222222222222222222" + }, + { + "asset_name": "546f6b656e45", + "quantity": 3, + "policy_id": "33333333333333333333333333333333333333333333333333333333" + }, + { + "asset_name": "546f6b656e41", + "quantity": 34, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e42", + "quantity": 18, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e43", + "quantity": 6, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 1, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 66, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 103, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e41", + "quantity": 12, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 17, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + }, + { + "amount": { + "quantity": 2, + "unit": "lovelace" + }, + "address": "", + "assets": [] + }, + { + "amount": { + "quantity": 45, + "unit": "lovelace" + }, + "address": "", + "assets": [ + { + "asset_name": "546f6b656e44", + "quantity": 21, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e45", + "quantity": 6, + "policy_id": "00000000000000000000000000000000000000000000000000000000" + }, + { + "asset_name": "546f6b656e41", + "quantity": 28, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + }, + { + "asset_name": "546f6b656e44", + "quantity": 26, + "policy_id": "44444444444444444444444444444444444444444444444444444444" + } + ] + } + ] +} \ No newline at end of file diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiWithdrawalGeneralNetworkDiscriminantTestnet0.json b/lib/core/test/data/Cardano/Wallet/Api/ApiWithdrawalGeneralNetworkDiscriminantTestnet0.json new file mode 100644 index 00000000000..c41283ff7e5 --- /dev/null +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiWithdrawalGeneralNetworkDiscriminantTestnet0.json @@ -0,0 +1,80 @@ +{ + "seed": 6259355950075141976, + "samples": [ + { + "amount": { + "quantity": 201, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 182, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 8, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 9, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 187, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 159, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 24, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 0, + "unit": "lovelace" + }, + "stake_address": "" + }, + { + "amount": { + "quantity": 131, + "unit": "lovelace" + }, + "context": "ours", + "stake_address": "" + }, + { + "amount": { + "quantity": 117, + "unit": "lovelace" + }, + "stake_address": "" + } + ] +} \ No newline at end of file diff --git a/lib/core/test/unit/Cardano/Wallet/Api/Malformed.hs b/lib/core/test/unit/Cardano/Wallet/Api/Malformed.hs index 58733c3361d..3c19454a806 100644 --- a/lib/core/test/unit/Cardano/Wallet/Api/Malformed.hs +++ b/lib/core/test/unit/Cardano/Wallet/Api/Malformed.hs @@ -62,6 +62,7 @@ import Cardano.Wallet.Api.Types , ApiPostRandomAddressData , ApiPutAddressesData , ApiSelectCoinsData + , ApiSerialisedTransaction , ApiSharedWalletPatchData , ApiSharedWalletPostData , ApiSignTransactionPostData @@ -1276,6 +1277,30 @@ instance Malformed (BodyParam ApiSignTransactionPostData) where ) ] +instance Malformed (BodyParam ApiSerialisedTransaction) where + malformed = jsonValid ++ jsonInvalid + where + jsonInvalid = first BodyParam <$> + [ ("1020344", "Error in $: parsing Cardano.Wallet.Api.Types.ApiSerialisedTransaction(ApiSerialisedTransaction) failed, expected Object, but encountered Number") + , ("\"hello\"", "Error in $: parsing Cardano.Wallet.Api.Types.ApiSerialisedTransaction(ApiSerialisedTransaction) failed, expected Object, but encountered String") + , ("{\"transaction\": \"\", \"random\"}", msgJsonInvalid) + , ("{\"transaction\": 1020344}", "Error in $.transaction: parsing 'Base64 ByteString failed, expected String, but encountered Number") + , ("{\"transaction\": { \"body\": 1020344 }}", "Error in $.transaction: parsing 'Base64 ByteString failed, expected String, but encountered Object") + ] + jsonValid = first (BodyParam . Aeson.encode) <$> + [ + ( [aesonQQ| + { "transaction": "!!!" + }|] + , "Error in $.transaction: Parse error. Expecting Base64-encoded format." + ) + , ( [aesonQQ| + { "transaction": "cafecafe" + }|] + , "Error in $.transaction: Deserialisation failure while decoding Shelley Tx. CBOR failed with error: DeserialiseFailure 0 'expected list len or indef'" + ) + ] + instance Malformed (BodyParam (PostTransactionOldData ('Testnet pm))) where malformed = jsonValid ++ jsonInvalid where diff --git a/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs b/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs index 9d4cf9ae7eb..ca032fb5bf4 100644 --- a/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs +++ b/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs @@ -83,6 +83,7 @@ import Cardano.Wallet.Api.Types , ApiConstructTransaction (..) , ApiConstructTransactionData (..) , ApiCredential (..) + , ApiDecodedTransaction (..) , ApiDelegationAction (..) , ApiEpochInfo (..) , ApiEra (..) @@ -137,7 +138,9 @@ import Cardano.Wallet.Api.Types , ApiTxCollateral (..) , ApiTxId (..) , ApiTxInput (..) + , ApiTxInputGeneral (..) , ApiTxMetadata (..) + , ApiTxOutputGeneral (..) , ApiUtxoStatistics (..) , ApiVerificationKeyShared (..) , ApiVerificationKeyShelley (..) @@ -148,16 +151,19 @@ import Cardano.Wallet.Api.Types , ApiWalletDelegationNext (..) , ApiWalletDelegationStatus (..) , ApiWalletDiscovery (..) + , ApiWalletInput (..) , ApiWalletMigrationBalance (..) , ApiWalletMigrationPlan (..) , ApiWalletMigrationPlanPostData (..) , ApiWalletMigrationPostData (..) + , ApiWalletOutput (..) , ApiWalletPassphrase (..) , ApiWalletPassphraseInfo (..) , ApiWalletSignData (..) , ApiWalletUtxoSnapshot (..) , ApiWalletUtxoSnapshotEntry (..) , ApiWithdrawal (..) + , ApiWithdrawalGeneral (..) , ApiWithdrawalPostData (..) , Base (Base16, Base64) , ByronWalletFromXPrvPostData (..) @@ -174,6 +180,7 @@ import Cardano.Wallet.Api.Types , PostMintBurnAssetData (..) , PostTransactionFeeOldData (..) , PostTransactionOldData (..) + , ResourceContext (..) , SettingsPutData (..) , SomeByronWalletPostData (..) , VerificationKeyHashing (..) @@ -544,6 +551,10 @@ spec = parallel $ do jsonRoundtripAndGolden $ Proxy @(ApiT StakePoolMetadata) jsonRoundtripAndGolden $ Proxy @ApiPostRandomAddressData jsonRoundtripAndGolden $ Proxy @ApiTxMetadata + jsonRoundtripAndGolden $ Proxy @(ApiDecodedTransaction ('Testnet 0)) + jsonRoundtripAndGolden $ Proxy @(ApiTxInputGeneral ('Testnet 0)) + jsonRoundtripAndGolden $ Proxy @(ApiTxOutputGeneral ('Testnet 0)) + jsonRoundtripAndGolden $ Proxy @(ApiWithdrawalGeneral ('Testnet 0)) jsonRoundtripAndGolden $ Proxy @ApiMaintenanceAction jsonRoundtripAndGolden $ Proxy @ApiMaintenanceActionPostData @@ -1157,6 +1168,20 @@ spec = parallel $ do } in x' === x .&&. show x' === show x + it "ApiDecodedTransaction" $ property $ \x -> + let + x' = ApiDecodedTransaction + { id = id (x :: ApiDecodedTransaction ('Testnet 0)) + , fee = fee (x :: ApiDecodedTransaction ('Testnet 0)) + , inputs = inputs (x :: ApiDecodedTransaction ('Testnet 0)) + , outputs = outputs (x :: ApiDecodedTransaction ('Testnet 0)) + , collateral = collateral (x :: ApiDecodedTransaction ('Testnet 0)) + , withdrawals = withdrawals (x :: ApiDecodedTransaction ('Testnet 0)) + , metadata = metadata (x :: ApiDecodedTransaction ('Testnet 0)) + , scriptValidity = scriptValidity (x :: ApiDecodedTransaction ('Testnet 0)) + } + in + x' === x .&&. show x' === show x it "ApiPutAddressesData" $ property $ \x -> let x' = ApiPutAddressesData @@ -2091,6 +2116,51 @@ instance Arbitrary (ApiRedeemer n) where , ApiRedeemerRewarding <$> arbitrary <*> arbitrary ] +instance Arbitrary (ApiTxInputGeneral n) where + arbitrary = oneof + [ ExternalInput <$> arbitrary + , WalletInput <$> arbitrary + ] + +instance Arbitrary (ApiWithdrawalGeneral (t :: NetworkDiscriminant)) where + arbitrary = ApiWithdrawalGeneral + <$> fmap (, Proxy @t) arbitrary + <*> arbitrary + <*> oneof [pure External, pure Our] + +instance Arbitrary (ApiWalletInput n) where + arbitrary = ApiWalletInput + <$> arbitrary + <*> arbitrary + <*> arbitrary + <*> arbitrary + <*> arbitrary + <*> arbitrary + +instance Arbitrary (ApiWalletOutput n) where + arbitrary = ApiWalletOutput + <$> arbitrary + <*> arbitrary + <*> arbitrary + <*> arbitrary + +instance Arbitrary (ApiTxOutputGeneral n) where + arbitrary = oneof + [ ExternalOutput <$> arbitrary + , WalletOutput <$> arbitrary + ] + +instance Arbitrary (ApiDecodedTransaction n) where + arbitrary = ApiDecodedTransaction + <$> arbitrary + <*> arbitrary + <*> arbitrary + <*> arbitrary + <*> arbitrary + <*> arbitrary + <*> arbitrary + <*> arbitrary + instance Arbitrary StakeAddress where arbitrary = do header <- elements [ BS.singleton 241, BS.singleton 224 ] @@ -2826,6 +2896,26 @@ instance Typeable n => ToSchema (ApiConstructTransaction n) where instance ToSchema ApiMultiDelegationAction where declareNamedSchema _ = declareSchemaForDefinition "ApiMultiDelegationAction" +type ApiTxInputsGeneral (n :: NetworkDiscriminant) = [ApiTxInputGeneral n] + +type ApiTxOutputsGeneral (n :: NetworkDiscriminant) = [ApiTxOutputGeneral n] + +type ApiWithdrawalsGeneral (n :: NetworkDiscriminant) = [ApiWithdrawalGeneral n] + +instance Typeable n => ToSchema (ApiTxInputsGeneral n) where + declareNamedSchema _ = declareSchemaForDefinition "ApiInputsGeneral" + +instance Typeable n => ToSchema (ApiTxOutputsGeneral n) where + declareNamedSchema _ = declareSchemaForDefinition "ApiOutputsGeneral" + +instance Typeable n => ToSchema (ApiWithdrawalsGeneral n) where + declareNamedSchema _ = declareSchemaForDefinition "ApiWithdrawalsGeneral" + +instance Typeable n => ToSchema (ApiDecodedTransaction n) where + declareNamedSchema _ = do + addDefinition =<< declareSchemaForDefinition "TransactionMetadataValue" + declareSchemaForDefinition "ApiDecodedTransaction" + -- | Utility function to provide an ad-hoc 'ToSchema' instance for a definition: -- we simply look it up within the Swagger specification. declareSchemaForDefinition :: Text -> Declare (Definitions Schema) NamedSchema diff --git a/lib/shelley/src/Cardano/Wallet/Shelley/Api/Server.hs b/lib/shelley/src/Cardano/Wallet/Shelley/Api/Server.hs index 1a7e05748e0..55ff65c1fb6 100644 --- a/lib/shelley/src/Cardano/Wallet/Shelley/Api/Server.hs +++ b/lib/shelley/src/Cardano/Wallet/Shelley/Api/Server.hs @@ -64,6 +64,7 @@ import Cardano.Wallet.Api.Server , balanceTransaction , constructTransaction , createMigrationPlan + , decodeTransaction , delegationFee , deleteTransaction , deleteWallet @@ -315,6 +316,7 @@ server byron icarus shelley multisig spl ntp = :<|> postTransactionOld shelley (delegationAddress @n) :<|> postTransactionFeeOld shelley :<|> balanceTransaction shelley (delegationAddress @n) + :<|> decodeTransaction shelley shelleyMigrations :: Server (ShelleyMigrations n) shelleyMigrations = diff --git a/specifications/api/swagger.yaml b/specifications/api/swagger.yaml index 77e5ff44d86..1bd0a80cad9 100644 --- a/specifications/api/swagger.yaml +++ b/specifications/api/swagger.yaml @@ -1211,6 +1211,29 @@ x-transactionWithdrawals: &transactionWithdrawals stake_address: *stakeAddress amount: *amount +x-ours: &ours + type: string + enum: ["ours"] + description: | + Used when withdrawal or output is ours. + +x-transactionWithdrawalsGeneral: &transactionWithdrawalsGeneral + description: | + A list of withdrawals from stake addresses. Withdrawal belonging to the wallet + is underlined. + type: array + minItems: 0 + items: + type: object + additionalProperties: false + required: + - stake_address + - amount + properties: + stake_address: *stakeAddress + amount: *amount + context: *ours + x-softIndex: &softIndex type: integer minimum: 0 @@ -1309,6 +1332,85 @@ x-transactionResolvedInputs: &transactionResolvedInputs type: integer minimum: 0 +x-transactionInputsOutsideWallet: &transactionInputsOutsideWallet + description: | + A transaction input not belonging to a given wallet. + type: object + required: + - id + - index + properties: + id: *transactionId + index: + type: integer + minimum: 0 + +x-transactionInputsInsideWallet: &transactionInputsInsideWallet + description: | + A transaction input belonging to a given wallet. + type: object + required: + - id + - index + - address + - amount + - derivation_path + properties: + address: *addressId + amount: *amount + assets: *walletAssets + id: *transactionId + derivation_path: *derivationPath + index: + type: integer + minimum: 0 + +x-transactionInputsGeneral: &transactionInputsGeneral + type: array + minItems: 0 + items: + oneOf: + - <<: *transactionInputsOutsideWallet + title: tx inputs without source not belonging to a given wallet + - <<: *transactionInputsInsideWallet + title: tx inputs belonging to a given wallet + +x-transactionOutputsOutsideWallet: &transactionOutputsOutsideWallet + description: | + A transaction output not belonging to the wallet + type: object + required: + - address + - amount + properties: + address: *addressId + amount: *amount + assets: *walletAssets + +x-transactionOutputsInsideWallet: &transactionOutputsInsideWallet + description: | + A transaction output not belonging to the wallet + type: object + required: + - address + - amount + - derivation_path + properties: + address: *addressId + amount: *amount + assets: *walletAssets + derivation_path: *derivationPath + +x-transactionOutputsGeneral: &transactionOutputsGeneral + type: array + minItems: 0 + items: + oneOf: + - <<: *transactionOutputsOutsideWallet + title: tx outputs not belonging to a given wallet + - <<: *transactionOutputsInsideWallet + title: tx outputs belonging to a given wallet + x-transactionResolvedCollateral: &transactionResolvedCollateral description: A list of transaction inputs used for collateral type: array @@ -2256,6 +2358,39 @@ components: metadata: *transactionMetadata script_validity: *txScriptValidity + ApiInputsGeneral: &ApiInputsGeneral + <<: *transactionInputsGeneral + description: | + Inputs that could be external or belong to the wallet. + + ApiOutputsGeneral: &ApiOutputsGeneral + <<: *transactionOutputsGeneral + description: | + Outputs that could be external or belong to the wallet. + + ApiWithdrawalsGeneral: &ApiWithdrawalsGeneral + <<: *transactionWithdrawalsGeneral + description: | + Withdrawals that could be external or belong to the wallet. + + ApiDecodedTransaction: &ApiDecodedTransaction + type: object + required: + - id + - fee + - inputs + - outputs + - withdrawals + properties: + id: *transactionId + fee: *amount + inputs: *ApiInputsGeneral + outputs: *ApiOutputsGeneral + collateral: *ApiInputsGeneral + withdrawals: *ApiWithdrawalsGeneral + metadata: *transactionMetadata + script_validity: *txScriptValidity + x-txBody: &txBody oneOf: - <<: *serialisedTransactionBase64 @@ -4758,6 +4893,17 @@ x-responsesSignTransaction: &responsesSignTransaction application/json: schema: *ApiSignedTransaction +x-responsesDecodedTransaction: &responsesDecodedTransaction + <<: *responsesErr400 + <<: *responsesErr404WalletNotFound + <<: *responsesErr406 + <<: *responsesErr415UnsupportedMediaType + 202: + description: Accepted + content: + application/json: + schema: *ApiDecodedTransaction + x-responsesSubmitTransaction: &responsesSubmitTransaction <<: *responsesErr400 <<: *responsesErr404WalletNotFound @@ -5526,6 +5672,24 @@ paths: schema: *ApiSignTransactionPostData responses: *responsesSignTransaction + /wallets/{walletId}/transactions-decode: + post: + operationId: decodeTransaction + tags: ["Transactions New"] + summary: Decode + description: | +

status: unstable

+ + Decode a serialized transaction. + parameters: + - *parametersWalletId + requestBody: + required: true + content: + application/json: + schema: *ApiSerialisedTransaction + responses: *responsesDecodedTransaction + /wallets/{walletId}/addresses: get: operationId: listAddresses