From d63982e8592a2f4bec73e780306971dc27e8da84 Mon Sep 17 00:00:00 2001 From: paolino Date: Thu, 1 Feb 2024 18:03:23 +0000 Subject: [PATCH 1/9] Add DRep module --- lib/primitive/cardano-wallet-primitive.cabal | 1 + .../Cardano/Wallet/Primitive/Types/DRep.hs | 149 ++++++++++++++++++ 2 files changed, 150 insertions(+) create mode 100644 lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs diff --git a/lib/primitive/cardano-wallet-primitive.cabal b/lib/primitive/cardano-wallet-primitive.cabal index 4bc0ced4cda..be67195d232 100644 --- a/lib/primitive/cardano-wallet-primitive.cabal +++ b/lib/primitive/cardano-wallet-primitive.cabal @@ -164,6 +164,7 @@ library Cardano.Wallet.Primitive.Types.Coin Cardano.Wallet.Primitive.Types.Coin.Gen Cardano.Wallet.Primitive.Types.DecentralizationLevel + Cardano.Wallet.Primitive.Types.DRep Cardano.Wallet.Primitive.Types.EpochNo Cardano.Wallet.Primitive.Types.EraInfo Cardano.Wallet.Primitive.Types.ExecutionUnitPrices diff --git a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs new file mode 100644 index 00000000000..0e301266f26 --- /dev/null +++ b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs @@ -0,0 +1,149 @@ +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE QuasiQuotes #-} + +module Cardano.Wallet.Primitive.Types.DRep + ( DRep (..) + , DRepKeyHash (..) + , DRepScriptHash (..) + , VoteAction (..) + , encodeDRepKeyHashBech32 + , decodeDRepKeyHashBech32 + , encodeDRepScriptHashBech32 + , decodeDRepScriptHashBech32 + ) +where + +import Prelude + +import Control.DeepSeq + ( NFData + ) +import Data.ByteString + ( ByteString + ) +import Data.Text + ( Text + ) +import Data.Text.Class + ( FromText (..) + , TextDecodingError (TextDecodingError) + , ToText (..) + ) +import Fmt + ( Buildable (..) + ) +import GHC.Generics + ( Generic + ) + +import qualified Codec.Binary.Bech32 as Bech32 +import qualified Codec.Binary.Bech32.TH as Bech32 + +newtype DRepKeyHash = DRepKeyHash { getDRepKeyHash :: ByteString } + deriving (Generic, Eq, Ord, Show) + +instance NFData DRepKeyHash + +newtype DRepScriptHash = DRepScriptHash { getDRepScriptHash :: ByteString } + deriving (Generic, Eq, Ord, Show) + +instance NFData DRepScriptHash + +data DRep = + DRepFromKeyHash DRepKeyHash | DRepFromScriptHash DRepScriptHash + deriving (Eq, Generic, Show, Ord) + deriving anyclass NFData + +-- | Encode 'DRepKeyHash' as Bech32 with "drep" hrp. +encodeDRepKeyHashBech32 :: DRepKeyHash -> Text +encodeDRepKeyHashBech32 = + Bech32.encodeLenient hrp + . Bech32.dataPartFromBytes + . getDRepKeyHash + where + hrp = [Bech32.humanReadablePart|drep|] + +-- | Decode a Bech32 encoded 'DRepKeyHash'. +decodeDRepKeyHashBech32 :: Text -> Either TextDecodingError DRepKeyHash +decodeDRepKeyHashBech32 t = + case fmap Bech32.dataPartToBytes <$> Bech32.decodeLenient t of + Left _ -> Left textDecodingError + Right (hrp', Just bytes) + | hrp' == hrp -> Right $ DRepKeyHash bytes + Right _ -> Left textDecodingError + where + textDecodingError = TextDecodingError $ unwords + [ "Invalid DRep key hash: expecting a Bech32 encoded value" + , "with human readable part of 'drep'." + ] + hrp = [Bech32.humanReadablePart|drep|] + +-- | Encode 'DRepScriptHash' as Bech32 with "drep_script" hrp. +encodeDRepScriptHashBech32 :: DRepScriptHash -> Text +encodeDRepScriptHashBech32 = + Bech32.encodeLenient hrp + . Bech32.dataPartFromBytes + . getDRepScriptHash + where + hrp = [Bech32.humanReadablePart|drep_script|] + +-- | Decode a Bech32 encoded 'DRepScriptHash'. +decodeDRepScriptHashBech32 :: Text -> Either TextDecodingError DRepScriptHash +decodeDRepScriptHashBech32 t = + case fmap Bech32.dataPartToBytes <$> Bech32.decodeLenient t of + Left _ -> Left textDecodingError + Right (hrp', Just bytes) + | hrp' == hrp -> Right $ DRepScriptHash bytes + Right _ -> Left textDecodingError + where + textDecodingError = TextDecodingError $ unwords + [ "Invalid DRep Script hash: expecting a Bech32 encoded value" + , "with human readable part of 'drep_script'." + ] + hrp = [Bech32.humanReadablePart|drep_script|] + +instance Buildable DRep where + build = \case + DRepFromKeyHash keyhash -> build $ encodeDRepKeyHashBech32 keyhash + DRepFromScriptHash scripthash -> build $ encodeDRepScriptHashBech32 scripthash + +-- | Vote action. +data VoteAction + = Abstain + | NoConfidence + | VoteTo !DRep + deriving (Eq, Generic, Show, Ord) + deriving anyclass NFData + +instance ToText VoteAction where + toText Abstain = "abstain" + toText NoConfidence = "no confidence" + toText (VoteTo (DRepFromKeyHash keyhash)) = + encodeDRepKeyHashBech32 keyhash + toText (VoteTo (DRepFromScriptHash scripthash)) = + encodeDRepScriptHashBech32 scripthash + +instance FromText VoteAction where + fromText txt = case txt of + "abstain" -> Right Abstain + "no confidence" -> Right NoConfidence + _ -> case decodeDRepKeyHashBech32 txt of + Right keyhash -> + Right $ VoteTo $ DRepFromKeyHash keyhash + Left _ -> case decodeDRepScriptHashBech32 txt of + Right scripthash -> + Right $ VoteTo $ DRepFromScriptHash scripthash + Left _ -> Left $ TextDecodingError $ unwords + [ "I couldn't parse the given vote action." + , "I am expecting either 'abstain', 'no confidence'" + , "or bech32 encoded drep having prefixes: 'drep_script'" + , "or 'drep_script'."] + +instance Buildable VoteAction where + build = \case + Abstain -> "abstaining" + NoConfidence -> "casting no confidence" + VoteTo drep -> "voting to " <> build drep From 42fdef7408a530d46ad62cebaac5d5ac937ae327 Mon Sep 17 00:00:00 2001 From: paolino Date: Thu, 1 Feb 2024 18:04:58 +0000 Subject: [PATCH 2/9] Add Conway certificates to Types --- .../Wallet/Primitive/Ledger/Read/Block.hs | 2 +- .../Wallet/Primitive/Types/Certificates.hs | 37 ++++++++++++++++++- 2 files changed, 36 insertions(+), 3 deletions(-) diff --git a/lib/primitive/lib/Cardano/Wallet/Primitive/Ledger/Read/Block.hs b/lib/primitive/lib/Cardano/Wallet/Primitive/Ledger/Read/Block.hs index 62af0bb0341..ee9c5c5a10b 100644 --- a/lib/primitive/lib/Cardano/Wallet/Primitive/Ledger/Read/Block.hs +++ b/lib/primitive/lib/Cardano/Wallet/Primitive/Ledger/Read/Block.hs @@ -87,7 +87,7 @@ pickWalletCertificates pickWalletCertificates xs = partitionEithers $ do x <- xs case x of - W.CertificateOfDelegation cert -> pure $ Left cert + W.CertificateOfDelegation _ cert -> pure $ Left cert W.CertificateOfPool cert -> pure $ Right cert _otherCerts -> [] diff --git a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/Certificates.hs b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/Certificates.hs index 3e51449523c..aa9b249d5f2 100644 --- a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/Certificates.hs +++ b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/Certificates.hs @@ -8,6 +8,7 @@ module Cardano.Wallet.Primitive.Types.Certificates ( DelegationCertificate (..) , dlgCertAccount , dlgCertPoolId + , dlgCertVote , StakeKeyCertificate (..) , PoolCertificate (..) , getPoolCertificatePoolId @@ -31,6 +32,9 @@ import Cardano.Slotting.Slot import Cardano.Wallet.Primitive.Types.Coin ( Coin ) +import Cardano.Wallet.Primitive.Types.DRep + ( VoteAction + ) import Cardano.Wallet.Primitive.Types.EpochNo ( EpochNo ) @@ -76,6 +80,8 @@ data DelegationCertificate = CertDelegateNone RewardAccount | CertDelegateFull RewardAccount PoolId | CertRegisterKey RewardAccount + | CertVoteFull RewardAccount VoteAction + | CertDelegateAndVoteFull RewardAccount PoolId VoteAction deriving (Generic, Show, Eq, Ord) instance NFData DelegationCertificate @@ -85,12 +91,24 @@ dlgCertAccount = \case CertDelegateNone acc -> acc CertDelegateFull acc _ -> acc CertRegisterKey acc -> acc + CertVoteFull acc _ -> acc + CertDelegateAndVoteFull acc _ _ -> acc dlgCertPoolId :: DelegationCertificate -> Maybe PoolId dlgCertPoolId = \case CertDelegateNone{} -> Nothing CertDelegateFull _ poolId -> Just poolId CertRegisterKey _ -> Nothing + CertVoteFull _ _ -> Nothing + CertDelegateAndVoteFull _ poolId _ -> Just poolId + +dlgCertVote :: DelegationCertificate -> Maybe VoteAction +dlgCertVote = \case + CertDelegateNone{} -> Nothing + CertDelegateFull _ _ -> Nothing + CertRegisterKey _ -> Nothing + CertVoteFull _ vote -> Just vote + CertDelegateAndVoteFull _ _ vote -> Just vote data StakeKeyCertificate = StakeKeyRegistration @@ -165,24 +183,39 @@ instance Buildable PoolRetirementCertificate where data NonWalletCertificate = GenesisCertificate | MIRCertificate + | CommitteeHotKeyAuthorization + | CommitteeColdResignation + | DRepRegistration + | DRepDeregistration deriving (Generic, Show, Read, Eq) instance ToText NonWalletCertificate where toText GenesisCertificate = "genesis" toText MIRCertificate = "mir" + toText CommitteeHotKeyAuthorization = "committee hot key registration" + toText CommitteeColdResignation = "committee resignation" + toText DRepRegistration = "DRep registration" + toText DRepDeregistration = "DRep deregistration" instance FromText NonWalletCertificate where fromText "genesis" = Right GenesisCertificate fromText "mir" = Right MIRCertificate + fromText "committee hot key registration" = + Right CommitteeHotKeyAuthorization + fromText "committee resignation" = Right CommitteeColdResignation + fromText "DRep registration" = Right DRepRegistration + fromText "DRep deregistration" = Right DRepDeregistration fromText _ = Left $ TextDecodingError - "expecting either 'genesis' or 'mir' for NonWalletCertificate text value" + "expecting one of 'genesis', 'mir', 'committee hot key registration'\ + \, 'committee resignation', 'DRep registration' or \ + \'DRep deregistration' for NonWalletCertificate text value" instance NFData NonWalletCertificate data Certificate - = CertificateOfDelegation DelegationCertificate + = CertificateOfDelegation (Maybe Coin) DelegationCertificate | CertificateOfPool PoolCertificate | CertificateOther NonWalletCertificate deriving (Generic, Show, Eq) From af96842f8ce382a918a0046c25486ba06b6e3b1b Mon Sep 17 00:00:00 2001 From: paolino Date: Thu, 1 Feb 2024 18:07:20 +0000 Subject: [PATCH 3/9] Add Conway certificates to Read features --- .../Ledger/Read/Tx/Features/Certificates.hs | 99 ++++++++++++++----- 1 file changed, 72 insertions(+), 27 deletions(-) diff --git a/lib/primitive/lib/Cardano/Wallet/Primitive/Ledger/Read/Tx/Features/Certificates.hs b/lib/primitive/lib/Cardano/Wallet/Primitive/Ledger/Read/Tx/Features/Certificates.hs index abc1c3d4dd0..c37ef7e4e80 100644 --- a/lib/primitive/lib/Cardano/Wallet/Primitive/Ledger/Read/Tx/Features/Certificates.hs +++ b/lib/primitive/lib/Cardano/Wallet/Primitive/Ledger/Read/Tx/Features/Certificates.hs @@ -40,10 +40,18 @@ import Cardano.Slotting.Slot ( EpochNo (..) ) import Cardano.Wallet.Primitive.Types.Certificates - ( PoolCertificate (..) + ( Certificate (..) + , NonWalletCertificate (..) + , PoolCertificate (..) , PoolRegistrationCertificate (..) , PoolRetirementCertificate (..) ) +import Cardano.Wallet.Primitive.Types.DRep + ( DRep (..) + , DRepKeyHash (..) + , DRepScriptHash (..) + , VoteAction (..) + ) import Cardano.Wallet.Primitive.Types.Pool ( PoolId (PoolId) , PoolOwner (PoolOwner) @@ -87,6 +95,7 @@ import GHC.Stack import qualified Cardano.Ledger.Api as Ledger import qualified Cardano.Ledger.BaseTypes as SL import qualified Cardano.Ledger.Credential as SL +import qualified Cardano.Ledger.DRep as Ledger import qualified Cardano.Ledger.Shelley.API as SL import qualified Cardano.Wallet.Primitive.Types.Certificates as W import qualified Cardano.Wallet.Primitive.Types.Coin as Coin @@ -124,25 +133,29 @@ fromConwayCert fromConwayCert = \case Ledger.RegPoolTxCert pp -> mkPoolRegistrationCertificate pp Ledger.RetirePoolTxCert pid en -> mkPoolRetirementCertificate pid en - Ledger.RegTxCert cred -> mkRegisterKeyCertificate cred - Ledger.UnRegTxCert cred -> mkDelegationNone cred - Ledger.RegDepositTxCert _ _ -> error "TODO: Conway, ADP-3065" - Ledger.UnRegDepositTxCert _ _ -> error "TODO: Conway, ADP-3065" - Ledger.DelegTxCert _ _ -> error "TODO: Conway delegation, ADP-3065" - {- - Ledger.DelegStakeTxCert delegator pool -> - W.CertificateOfDelegation - $ W.CertDelegateFull - (fromStakeCredential delegator) - (fromPoolKeyHash pool) - -} - Ledger.RegDepositDelegTxCert {} -> error "TODO: Conway, ADP-3065" - Ledger.AuthCommitteeHotKeyTxCert _ _ -> error "TODO: Conway other, ADP-3065" - Ledger.ResignCommitteeColdTxCert _ _ -> error "TODO: Conway other, ADP-3065" - Ledger.RegDRepTxCert {} -> error "TODO: Conway other, ADP-3065" - Ledger.UnRegDRepTxCert _ _ -> error "TODO: Conway other, ADP-3065" + Ledger.RegTxCert cred -> mkRegisterKeyCertificate Nothing cred + Ledger.UnRegTxCert cred -> mkDelegationNone Nothing cred + Ledger.RegDepositTxCert cred coin -> + mkRegisterKeyCertificate (Just $ fromLedgerCoin coin) cred + Ledger.UnRegDepositTxCert cred coin -> + mkDelegationNone (Just $ fromLedgerCoin coin) cred + Ledger.DelegTxCert cred delegatee -> + mkDelegationVoting Nothing cred delegatee + Ledger.RegDepositDelegTxCert cred delegatee coin -> + mkDelegationVoting (Just $ fromLedgerCoin coin) cred delegatee + Ledger.AuthCommitteeHotKeyTxCert _ _ -> + CertificateOther CommitteeHotKeyAuthorization + Ledger.ResignCommitteeColdTxCert _ _ -> + CertificateOther CommitteeColdResignation + Ledger.RegDRepTxCert {} -> + CertificateOther DRepRegistration + Ledger.UnRegDRepTxCert _ _ -> + CertificateOther DRepDeregistration _ -> error "impossible pattern" +fromLedgerCoin :: HasCallStack => SL.Coin -> W.Coin +fromLedgerCoin (SL.Coin c) = Coin.unsafeFromIntegral c + mkShelleyCertsK :: ( Foldable t , CertificatesType era ~ t (ShelleyTxCert era') @@ -178,17 +191,49 @@ mkPoolRetirementCertificate pid (EpochNo e) = , retirementEpoch = W.EpochNo $ fromIntegral e } -mkRegisterKeyCertificate :: SL.Credential 'SL.Staking crypto -> W.Certificate -mkRegisterKeyCertificate = - W.CertificateOfDelegation +mkRegisterKeyCertificate + :: Maybe W.Coin + -> SL.Credential 'SL.Staking crypto + -> W.Certificate +mkRegisterKeyCertificate deposit = + W.CertificateOfDelegation deposit . W.CertRegisterKey . fromStakeCredential -mkDelegationNone :: SL.Credential 'SL.Staking crypto -> W.Certificate -mkDelegationNone credentials = - W.CertificateOfDelegation +mkDelegationNone + :: Maybe W.Coin + -> SL.Credential 'SL.Staking crypto + -> W.Certificate +mkDelegationNone deposit credentials = + W.CertificateOfDelegation deposit $ W.CertDelegateNone (fromStakeCredential credentials) +mkDelegationVoting + :: Maybe W.Coin + -> SL.Credential 'SL.Staking crypto + -> Ledger.Delegatee crypto + -> W.Certificate +mkDelegationVoting deposit cred = \case + Ledger.DelegStake pool -> + W.CertificateOfDelegation deposit + $ W.CertDelegateFull (fromStakeCredential cred) (fromPoolKeyHash pool) + Ledger.DelegVote vote -> + W.CertificateOfDelegation deposit + $ W.CertVoteFull (fromStakeCredential cred) (fromLedgerDRep vote) + Ledger.DelegStakeVote pool vote -> + W.CertificateOfDelegation deposit + $ W.CertDelegateAndVoteFull (fromStakeCredential cred) + (fromPoolKeyHash pool) (fromLedgerDRep vote) + +fromLedgerDRep :: Ledger.DRep crypto -> VoteAction +fromLedgerDRep = \case + Ledger.DRepAlwaysAbstain -> Abstain + Ledger.DRepAlwaysNoConfidence -> NoConfidence + Ledger.DRepCredential (SL.ScriptHashObj (SL.ScriptHash scripthash)) -> + VoteTo (DRepFromScriptHash (DRepScriptHash $ hashToBytes scripthash)) + Ledger.DRepCredential (SL.KeyHashObj (SL.KeyHash keyhash)) -> + VoteTo (DRepFromKeyHash (DRepKeyHash $ hashToBytes keyhash)) + fromShelleyCert :: ( Ledger.ShelleyEraTxCert era , Ledger.ProtVerAtMost era 8 @@ -197,12 +242,12 @@ fromShelleyCert => Ledger.TxCert era -> W.Certificate fromShelleyCert = \case Ledger.DelegStakeTxCert delegator pool -> - W.CertificateOfDelegation + W.CertificateOfDelegation Nothing $ W.CertDelegateFull (fromStakeCredential delegator) (fromPoolKeyHash pool) - Ledger.RegTxCert cred -> mkRegisterKeyCertificate cred - Ledger.UnRegTxCert cred -> mkDelegationNone cred + Ledger.RegTxCert cred -> mkRegisterKeyCertificate Nothing cred + Ledger.UnRegTxCert cred -> mkDelegationNone Nothing cred Ledger.RegPoolTxCert pp -> mkPoolRegistrationCertificate pp Ledger.RetirePoolTxCert pid en -> mkPoolRetirementCertificate pid en Ledger.GenesisDelegTxCert {} -> W.CertificateOther W.GenesisCertificate From 06be740cc2726152e0595c46e13fed0c1e10fa50 Mon Sep 17 00:00:00 2001 From: paolino Date: Thu, 1 Feb 2024 18:17:13 +0000 Subject: [PATCH 4/9] Add bottom implementations for wallet code on Conway certificates --- lib/wallet/api/http/Cardano/Wallet/Api/Types/Certificate.hs | 3 ++- lib/wallet/src/Cardano/Wallet.hs | 1 + lib/wallet/src/Cardano/Wallet/DB/Pure/Implementation.hs | 3 +++ lib/wallet/src/Cardano/Wallet/DB/Store/Delegations/Layer.hs | 2 ++ 4 files changed, 8 insertions(+), 1 deletion(-) diff --git a/lib/wallet/api/http/Cardano/Wallet/Api/Types/Certificate.hs b/lib/wallet/api/http/Cardano/Wallet/Api/Types/Certificate.hs index 73e4dd0510b..3590a9e7478 100644 --- a/lib/wallet/api/http/Cardano/Wallet/Api/Types/Certificate.hs +++ b/lib/wallet/api/http/Cardano/Wallet/Api/Types/Certificate.hs @@ -241,7 +241,7 @@ mkApiAnyCertificate -> W.Certificate -> ApiAnyCertificate n mkApiAnyCertificate acct' acctPath' = \case - W.CertificateOfDelegation delCert -> toApiDelCert acct' acctPath' delCert + W.CertificateOfDelegation _ delCert -> toApiDelCert acct' acctPath' delCert W.CertificateOfPool poolCert -> toApiPoolCert poolCert W.CertificateOther otherCert -> toApiOtherCert otherCert where @@ -286,3 +286,4 @@ mkApiAnyCertificate acct' acctPath' = \case else DelegationCertificate $ JoinPoolExternal (ApiRewardAccount rewardKey) (ApiT poolId') + toApiDelCert _ _ _ = error "mkApiAnyCertificate: conway certificates not supported" diff --git a/lib/wallet/src/Cardano/Wallet.hs b/lib/wallet/src/Cardano/Wallet.hs index 5e7d377858e..1891b131eda 100644 --- a/lib/wallet/src/Cardano/Wallet.hs +++ b/lib/wallet/src/Cardano/Wallet.hs @@ -3792,6 +3792,7 @@ instance ToText WalletFollowLog where , " within slot " , pretty slotNo ] + _ -> "Conway certificate not supported in the logs" MsgCheckpoint checkpointTip -> "Creating checkpoint at " <> pretty checkpointTip MsgDiscoveredTxs txs -> diff --git a/lib/wallet/src/Cardano/Wallet/DB/Pure/Implementation.hs b/lib/wallet/src/Cardano/Wallet/DB/Pure/Implementation.hs index 7f1b7b7c5b9..ac00d3257f4 100644 --- a/lib/wallet/src/Cardano/Wallet/DB/Pure/Implementation.hs +++ b/lib/wallet/src/Cardano/Wallet/DB/Pure/Implementation.hs @@ -349,6 +349,9 @@ mPutDelegationCertificate cert slot = alterModelNoTxs' CertDelegateFull {} -> stakeKeys CertRegisterKey {} -> Map.insert slot StakeKeyRegistration stakeKeys + CertVoteFull {} -> error "Vote certificates not supported in DB" + CertDelegateAndVoteFull {} -> + error "Vote certificates not supported in DB" } mIsStakeKeyRegistered diff --git a/lib/wallet/src/Cardano/Wallet/DB/Store/Delegations/Layer.hs b/lib/wallet/src/Cardano/Wallet/DB/Store/Delegations/Layer.hs index a8250a8b60f..b4772dfab20 100644 --- a/lib/wallet/src/Cardano/Wallet/DB/Store/Delegations/Layer.hs +++ b/lib/wallet/src/Cardano/Wallet/DB/Store/Delegations/Layer.hs @@ -77,6 +77,8 @@ putDelegationCertificate cert sl = case cert of CertDelegateNone _ -> [Deregister sl] CertDelegateFull _ pool -> [Delegate pool sl, Register sl] CertRegisterKey _ -> [Register sl] + CertVoteFull{} -> error "Conway certificates are not supported in the DB" + CertDelegateAndVoteFull{} -> error "Conway certificates are not supported in the DB" -- | Arguments to 'readDelegation'. data CurrentEpochSlotting = CurrentEpochSlotting From e9e96f0c8ff74bbc2a86eb18332528eceefe7a69 Mon Sep 17 00:00:00 2001 From: Pawel Jakubas Date: Mon, 5 Feb 2024 11:17:39 +0100 Subject: [PATCH 5/9] apply review suggestions --- .../Ledger/Read/Tx/Features/Certificates.hs | 30 +++-- .../Wallet/Primitive/Types/Certificates.hs | 51 +++---- .../Cardano/Wallet/Primitive/Types/DRep.hs | 35 ++--- .../api/http/Cardano/Wallet/Api/Types.hs | 124 ++---------------- .../Cardano/Wallet/Api/Types/Certificate.hs | 2 +- lib/wallet/src/Cardano/Wallet.hs | 6 +- .../Cardano/Wallet/DB/Pure/Implementation.hs | 9 +- .../Wallet/DB/Store/Delegations/Layer.hs | 5 +- .../test/unit/Cardano/Wallet/Api/TypesSpec.hs | 26 ++-- .../test/unit/Cardano/Wallet/DB/Arbitrary.hs | 3 +- specifications/api/drep-voting.md | 2 +- specifications/api/swagger.yaml | 31 +++-- 12 files changed, 112 insertions(+), 212 deletions(-) diff --git a/lib/primitive/lib/Cardano/Wallet/Primitive/Ledger/Read/Tx/Features/Certificates.hs b/lib/primitive/lib/Cardano/Wallet/Primitive/Ledger/Read/Tx/Features/Certificates.hs index c37ef7e4e80..2cdb7bdc2e2 100644 --- a/lib/primitive/lib/Cardano/Wallet/Primitive/Ledger/Read/Tx/Features/Certificates.hs +++ b/lib/primitive/lib/Cardano/Wallet/Primitive/Ledger/Read/Tx/Features/Certificates.hs @@ -48,9 +48,9 @@ import Cardano.Wallet.Primitive.Types.Certificates ) import Cardano.Wallet.Primitive.Types.DRep ( DRep (..) + , DRepID (..) , DRepKeyHash (..) , DRepScriptHash (..) - , VoteAction (..) ) import Cardano.Wallet.Primitive.Types.Pool ( PoolId (PoolId) @@ -144,13 +144,13 @@ fromConwayCert = \case Ledger.RegDepositDelegTxCert cred delegatee coin -> mkDelegationVoting (Just $ fromLedgerCoin coin) cred delegatee Ledger.AuthCommitteeHotKeyTxCert _ _ -> - CertificateOther CommitteeHotKeyAuthorization + CertificateOther AuthCommitteeHotKey Ledger.ResignCommitteeColdTxCert _ _ -> - CertificateOther CommitteeColdResignation + CertificateOther ResignCommitteeColdKey Ledger.RegDRepTxCert {} -> - CertificateOther DRepRegistration + CertificateOther RegDRep Ledger.UnRegDRepTxCert _ _ -> - CertificateOther DRepDeregistration + CertificateOther UnRegDRep _ -> error "impossible pattern" fromLedgerCoin :: HasCallStack => SL.Coin -> W.Coin @@ -216,23 +216,25 @@ mkDelegationVoting mkDelegationVoting deposit cred = \case Ledger.DelegStake pool -> W.CertificateOfDelegation deposit - $ W.CertDelegateFull (fromStakeCredential cred) (fromPoolKeyHash pool) + $ W.CertVoteAndDelegate (fromStakeCredential cred) + (Just $ fromPoolKeyHash pool) Nothing Ledger.DelegVote vote -> W.CertificateOfDelegation deposit - $ W.CertVoteFull (fromStakeCredential cred) (fromLedgerDRep vote) + $ W.CertVoteAndDelegate (fromStakeCredential cred) + Nothing (Just $ fromLedgerDRep vote) Ledger.DelegStakeVote pool vote -> W.CertificateOfDelegation deposit - $ W.CertDelegateAndVoteFull (fromStakeCredential cred) - (fromPoolKeyHash pool) (fromLedgerDRep vote) + $ W.CertVoteAndDelegate (fromStakeCredential cred) + (Just $ fromPoolKeyHash pool) (Just $ fromLedgerDRep vote) -fromLedgerDRep :: Ledger.DRep crypto -> VoteAction +fromLedgerDRep :: Ledger.DRep crypto -> DRep fromLedgerDRep = \case Ledger.DRepAlwaysAbstain -> Abstain Ledger.DRepAlwaysNoConfidence -> NoConfidence Ledger.DRepCredential (SL.ScriptHashObj (SL.ScriptHash scripthash)) -> - VoteTo (DRepFromScriptHash (DRepScriptHash $ hashToBytes scripthash)) + FromDRepID (DRepFromScriptHash (DRepScriptHash $ hashToBytes scripthash)) Ledger.DRepCredential (SL.KeyHashObj (SL.KeyHash keyhash)) -> - VoteTo (DRepFromKeyHash (DRepKeyHash $ hashToBytes keyhash)) + FromDRepID (DRepFromKeyHash (DRepKeyHash $ hashToBytes keyhash)) fromShelleyCert :: ( Ledger.ShelleyEraTxCert era @@ -243,9 +245,9 @@ fromShelleyCert fromShelleyCert = \case Ledger.DelegStakeTxCert delegator pool -> W.CertificateOfDelegation Nothing - $ W.CertDelegateFull + $ W.CertVoteAndDelegate (fromStakeCredential delegator) - (fromPoolKeyHash pool) + (Just $ fromPoolKeyHash pool) Nothing Ledger.RegTxCert cred -> mkRegisterKeyCertificate Nothing cred Ledger.UnRegTxCert cred -> mkDelegationNone Nothing cred Ledger.RegPoolTxCert pp -> mkPoolRegistrationCertificate pp diff --git a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/Certificates.hs b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/Certificates.hs index aa9b249d5f2..a17974fdfce 100644 --- a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/Certificates.hs +++ b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/Certificates.hs @@ -33,7 +33,7 @@ import Cardano.Wallet.Primitive.Types.Coin ( Coin ) import Cardano.Wallet.Primitive.Types.DRep - ( VoteAction + ( DRep ) import Cardano.Wallet.Primitive.Types.EpochNo ( EpochNo @@ -78,10 +78,8 @@ import GHC.Generics data DelegationCertificate = CertDelegateNone RewardAccount - | CertDelegateFull RewardAccount PoolId | CertRegisterKey RewardAccount - | CertVoteFull RewardAccount VoteAction - | CertDelegateAndVoteFull RewardAccount PoolId VoteAction + | CertVoteAndDelegate RewardAccount (Maybe PoolId) (Maybe DRep) deriving (Generic, Show, Eq, Ord) instance NFData DelegationCertificate @@ -89,26 +87,20 @@ instance NFData DelegationCertificate dlgCertAccount :: DelegationCertificate -> RewardAccount dlgCertAccount = \case CertDelegateNone acc -> acc - CertDelegateFull acc _ -> acc CertRegisterKey acc -> acc - CertVoteFull acc _ -> acc - CertDelegateAndVoteFull acc _ _ -> acc + CertVoteAndDelegate acc _ _ -> acc dlgCertPoolId :: DelegationCertificate -> Maybe PoolId dlgCertPoolId = \case CertDelegateNone{} -> Nothing - CertDelegateFull _ poolId -> Just poolId CertRegisterKey _ -> Nothing - CertVoteFull _ _ -> Nothing - CertDelegateAndVoteFull _ poolId _ -> Just poolId + CertVoteAndDelegate _ poolIdM _ -> poolIdM -dlgCertVote :: DelegationCertificate -> Maybe VoteAction +dlgCertVote :: DelegationCertificate -> Maybe DRep dlgCertVote = \case CertDelegateNone{} -> Nothing - CertDelegateFull _ _ -> Nothing CertRegisterKey _ -> Nothing - CertVoteFull _ vote -> Just vote - CertDelegateAndVoteFull _ _ vote -> Just vote + CertVoteAndDelegate _ _ voteM -> voteM data StakeKeyCertificate = StakeKeyRegistration @@ -183,34 +175,33 @@ instance Buildable PoolRetirementCertificate where data NonWalletCertificate = GenesisCertificate | MIRCertificate - | CommitteeHotKeyAuthorization - | CommitteeColdResignation - | DRepRegistration - | DRepDeregistration + | AuthCommitteeHotKey + | ResignCommitteeColdKey + | RegDRep + | UnRegDRep deriving (Generic, Show, Read, Eq) instance ToText NonWalletCertificate where toText GenesisCertificate = "genesis" toText MIRCertificate = "mir" - toText CommitteeHotKeyAuthorization = "committee hot key registration" - toText CommitteeColdResignation = "committee resignation" - toText DRepRegistration = "DRep registration" - toText DRepDeregistration = "DRep deregistration" + toText AuthCommitteeHotKey = "auth_committee_hot_key" + toText ResignCommitteeColdKey = "resign_committee_cold_key" + toText RegDRep = "reg_DRep" + toText UnRegDRep = "unreg_DRep" instance FromText NonWalletCertificate where fromText "genesis" = Right GenesisCertificate fromText "mir" = Right MIRCertificate - fromText "committee hot key registration" = - Right CommitteeHotKeyAuthorization - fromText "committee resignation" = Right CommitteeColdResignation - fromText "DRep registration" = Right DRepRegistration - fromText "DRep deregistration" = Right DRepDeregistration + fromText "auth_committee_hot_key" = Right AuthCommitteeHotKey + fromText "resign_committee_cold_key" = Right ResignCommitteeColdKey + fromText "reg_DRep" = Right RegDRep + fromText "unreg_DRep" = Right UnRegDRep fromText _ = Left $ TextDecodingError - "expecting one of 'genesis', 'mir', 'committee hot key registration'\ - \, 'committee resignation', 'DRep registration' or \ - \'DRep deregistration' for NonWalletCertificate text value" + "expecting one of 'genesis', 'mir', 'auth_committee_hot_key'\ + \, 'resign_committee_cold_key', 'reg_DRep' or \ + \'unreg_DRep' for NonWalletCertificate text value" instance NFData NonWalletCertificate diff --git a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs index 0e301266f26..018b4022c8d 100644 --- a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs +++ b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs @@ -5,10 +5,10 @@ {-# LANGUAGE QuasiQuotes #-} module Cardano.Wallet.Primitive.Types.DRep - ( DRep (..) + ( DRepID (..) , DRepKeyHash (..) , DRepScriptHash (..) - , VoteAction (..) + , DRep (..) , encodeDRepKeyHashBech32 , decodeDRepKeyHashBech32 , encodeDRepScriptHashBech32 @@ -52,7 +52,7 @@ newtype DRepScriptHash = DRepScriptHash { getDRepScriptHash :: ByteString } instance NFData DRepScriptHash -data DRep = +data DRepID = DRepFromKeyHash DRepKeyHash | DRepFromScriptHash DRepScriptHash deriving (Eq, Generic, Show, Ord) deriving anyclass NFData @@ -105,45 +105,46 @@ decodeDRepScriptHashBech32 t = ] hrp = [Bech32.humanReadablePart|drep_script|] -instance Buildable DRep where +instance Buildable DRepID where build = \case DRepFromKeyHash keyhash -> build $ encodeDRepKeyHashBech32 keyhash DRepFromScriptHash scripthash -> build $ encodeDRepScriptHashBech32 scripthash --- | Vote action. -data VoteAction +-- | A decentralized representation ('DRep') will +-- vote on behalf of the stake delegated to it. +data DRep = Abstain | NoConfidence - | VoteTo !DRep + | FromDRepID DRepID deriving (Eq, Generic, Show, Ord) deriving anyclass NFData -instance ToText VoteAction where +instance ToText DRep where toText Abstain = "abstain" toText NoConfidence = "no confidence" - toText (VoteTo (DRepFromKeyHash keyhash)) = + toText (FromDRepID (DRepFromKeyHash keyhash)) = encodeDRepKeyHashBech32 keyhash - toText (VoteTo (DRepFromScriptHash scripthash)) = + toText (FromDRepID (DRepFromScriptHash scripthash)) = encodeDRepScriptHashBech32 scripthash -instance FromText VoteAction where +instance FromText DRep where fromText txt = case txt of "abstain" -> Right Abstain "no confidence" -> Right NoConfidence _ -> case decodeDRepKeyHashBech32 txt of Right keyhash -> - Right $ VoteTo $ DRepFromKeyHash keyhash + Right $ FromDRepID $ DRepFromKeyHash keyhash Left _ -> case decodeDRepScriptHashBech32 txt of Right scripthash -> - Right $ VoteTo $ DRepFromScriptHash scripthash + Right $ FromDRepID $ DRepFromScriptHash scripthash Left _ -> Left $ TextDecodingError $ unwords - [ "I couldn't parse the given vote action." + [ "I couldn't parse the given decentralized representative (DRep)." , "I am expecting either 'abstain', 'no confidence'" , "or bech32 encoded drep having prefixes: 'drep_script'" , "or 'drep_script'."] -instance Buildable VoteAction where +instance Buildable DRep where build = \case - Abstain -> "abstaining" + Abstain -> "abstain" NoConfidence -> "casting no confidence" - VoteTo drep -> "voting to " <> build drep + FromDRepID drep -> "delegating voting to " <> build drep diff --git a/lib/wallet/api/http/Cardano/Wallet/Api/Types.hs b/lib/wallet/api/http/Cardano/Wallet/Api/Types.hs index f52df7e0cc4..4c5029b5c4b 100644 --- a/lib/wallet/api/http/Cardano/Wallet/Api/Types.hs +++ b/lib/wallet/api/http/Cardano/Wallet/Api/Types.hs @@ -193,10 +193,6 @@ module Cardano.Wallet.Api.Types , ApiDecodeTransactionPostData (..) , fromApiDecodeTransactionPostData , toApiDecodeTransactionPostData - , ApiVoteAction (..) - , DRep (..) - , DRepKeyHash (..) - , DRepScriptHash (..) -- * API Types (Byron) , ApiByronWallet (..) @@ -441,6 +437,9 @@ import Cardano.Wallet.Primitive.Types.Address import Cardano.Wallet.Primitive.Types.AssetId ( AssetId (..) ) +import Cardano.Wallet.Primitive.Types.DRep + ( DRep + ) import Cardano.Wallet.Primitive.Types.Hash ( Hash (..) ) @@ -1233,83 +1232,6 @@ newtype ApiEncryptMetadata = ApiEncryptMetadata deriving (FromJSON, ToJSON) via DefaultRecord ApiEncryptMetadata deriving anyclass NFData -newtype DRepKeyHash = DRepKeyHash { getDRepKeyHash :: ByteString } - deriving (Generic, Eq, Ord) - -instance NFData DRepKeyHash - -instance Show DRepKeyHash where - show p = "(DRep key hash " <> show (encodeDRepKeyHashBech32 p) <> ")" - --- | Encode 'DRepKeyHash' as Bech32 with "drep_vkh" hrp. -encodeDRepKeyHashBech32 :: DRepKeyHash -> T.Text -encodeDRepKeyHashBech32 = - Bech32.encodeLenient hrp - . Bech32.dataPartFromBytes - . getDRepKeyHash - where - hrp = [Bech32.humanReadablePart|drep_vkh|] - --- | Decode a Bech32 encoded 'DRepKeyHash'. -decodeDRepKeyHashBech32 :: T.Text -> Either TextDecodingError DRepKeyHash -decodeDRepKeyHashBech32 t = - case fmap Bech32.dataPartToBytes <$> Bech32.decodeLenient t of - Left _ -> Left textDecodingError - Right (hrp', Just bytes) - | hrp' == hrp -> Right $ DRepKeyHash bytes - Right _ -> Left textDecodingError - where - textDecodingError = TextDecodingError $ unwords - [ "Invalid DRep key hash: expecting a Bech32 encoded value" - , "with human readable part of 'drep_vkh'." - ] - hrp = [Bech32.humanReadablePart|drep_vkh|] - -newtype DRepScriptHash = DRepScriptHash { getDRepScriptHash :: ByteString } - deriving (Generic, Eq, Ord) - -instance NFData DRepScriptHash - -instance Show DRepScriptHash where - show p = "(DRep script hash " <> show (encodeDRepScriptHashBech32 p) <> ")" - --- | Encode 'DRepScriptHash' as Bech32 with "drep_script" hrp. -encodeDRepScriptHashBech32 :: DRepScriptHash -> T.Text -encodeDRepScriptHashBech32 = - Bech32.encodeLenient hrp - . Bech32.dataPartFromBytes - . getDRepScriptHash - where - hrp = [Bech32.humanReadablePart|drep_script|] - --- | Decode a Bech32 encoded 'DRepScriptHash'. -decodeDRepScriptHashBech32 :: T.Text -> Either TextDecodingError DRepScriptHash -decodeDRepScriptHashBech32 t = - case fmap Bech32.dataPartToBytes <$> Bech32.decodeLenient t of - Left _ -> Left textDecodingError - Right (hrp', Just bytes) - | hrp' == hrp -> Right $ DRepScriptHash bytes - Right _ -> Left textDecodingError - where - textDecodingError = TextDecodingError $ unwords - [ "Invalid DRep Script hash: expecting a Bech32 encoded value" - , "with human readable part of 'drep_script'." - ] - hrp = [Bech32.humanReadablePart|drep_script|] - -data DRep = - DRepFromKeyHash DRepKeyHash | DRepFromScriptHash DRepScriptHash - deriving (Eq, Generic, Show) - deriving anyclass NFData - --- | Vote action. -data ApiVoteAction - = Abstain - | NoConfidence - | VoteTo !DRep - deriving (Eq, Generic, Show) - deriving anyclass NFData - -- | Input parameters for transaction construction. data ApiConstructTransactionData (n :: NetworkDiscriminant) = ApiConstructTransactionData @@ -1319,7 +1241,7 @@ data ApiConstructTransactionData (n :: NetworkDiscriminant) = , encryptMetadata :: !(Maybe ApiEncryptMetadata) , mintBurn :: !(Maybe (NonEmpty (ApiMintBurnData n))) , delegations :: !(Maybe (NonEmpty ApiMultiDelegationAction)) - , vote :: !(Maybe ApiVoteAction) + , vote :: !(Maybe (ApiT DRep)) , validityInterval :: !(Maybe ApiValidityInterval) , referencePolicyScriptTemplate :: !(Maybe (ApiT (Script Cosigner))) , encoding :: !(Maybe ApiSealedTxEncoding) @@ -2269,39 +2191,6 @@ instance ToJSON ApiStakeKeyIndex where instance FromJSON ApiStakeKeyIndex where parseJSON val = ApiStakeKeyIndex <$> parseJSON val -instance ToJSON ApiVoteAction where - toJSON Abstain = "abstain" - toJSON NoConfidence = "no_confidence" - toJSON (VoteTo drep) = case drep of - DRepFromKeyHash keyhash -> - String $ encodeDRepKeyHashBech32 keyhash - DRepFromScriptHash scripthash -> - String $ encodeDRepScriptHashBech32 scripthash -instance FromJSON ApiVoteAction where - parseJSON t = - parseAbstain t <|> parseNoConfidence t <|> parseKeyHash t <|> parseScriptHash t - where - parseKeyHash = withText "DRepKeyHash" $ \txt -> - case decodeDRepKeyHashBech32 txt of - Left (TextDecodingError err) -> fail err - Right keyhash -> - pure $ VoteTo $ DRepFromKeyHash keyhash - parseScriptHash = withText "DRepScriptHash" $ \txt -> - case decodeDRepScriptHashBech32 txt of - Left (TextDecodingError err) -> fail err - Right scripthash -> - pure $ VoteTo $ DRepFromScriptHash scripthash - parseAbstain = withText "Abstain" $ \txt -> - if txt == "abstain" then - pure Abstain - else - fail "'abstain' is expected." - parseNoConfidence = withText "NoConfidence" $ \txt -> - if txt == "no_confidence" then - pure NoConfidence - else - fail "'no_confidence' is expected." - instance ToJSON ApiMultiDelegationAction where toJSON (Joining poolId stakeKey) = object [ "join" .= @@ -2432,6 +2321,11 @@ instance FromJSON (ApiT (Hash "TokenPolicy")) where instance ToJSON (ApiT (Hash "TokenPolicy")) where toJSON = toTextApiT +instance FromJSON (ApiT DRep) where + parseJSON = fromTextApiT "DRep" +instance ToJSON (ApiT DRep) where + toJSON = toTextApiT + instance FromJSON WalletPutPassphraseData where parseJSON = fmap WalletPutPassphraseData . variants "PutPassphrase data" diff --git a/lib/wallet/api/http/Cardano/Wallet/Api/Types/Certificate.hs b/lib/wallet/api/http/Cardano/Wallet/Api/Types/Certificate.hs index 3590a9e7478..03ed8a939d6 100644 --- a/lib/wallet/api/http/Cardano/Wallet/Api/Types/Certificate.hs +++ b/lib/wallet/api/http/Cardano/Wallet/Api/Types/Certificate.hs @@ -279,7 +279,7 @@ mkApiAnyCertificate acct' acctPath' = \case else DelegationCertificate $ RegisterRewardAccountExternal (ApiRewardAccount rewardKey) - toApiDelCert acctM acctPath (W.CertDelegateFull rewardKey poolId') = + toApiDelCert acctM acctPath (W.CertVoteAndDelegate rewardKey (Just poolId') Nothing) = if Just rewardKey == acctM then WalletDelegationCertificate $ JoinPool (NE.map ApiT acctPath) (ApiT poolId') diff --git a/lib/wallet/src/Cardano/Wallet.hs b/lib/wallet/src/Cardano/Wallet.hs index 1891b131eda..72c62e68804 100644 --- a/lib/wallet/src/Cardano/Wallet.hs +++ b/lib/wallet/src/Cardano/Wallet.hs @@ -573,11 +573,11 @@ import Cardano.Wallet.Read.Tx.CBOR ( TxCBOR ) import Cardano.Wallet.Shelley.Transaction - ( _txRewardWithdrawalCost - , mkTransaction + ( mkTransaction , mkUnsignedTransaction , txConstraints , txWitnessTagForKey + , _txRewardWithdrawalCost ) import Cardano.Wallet.Transaction ( DelegationAction (..) @@ -3781,7 +3781,7 @@ instance ToText WalletFollowLog where [ "Discovered end of delegation within slot " , pretty slotNo ] - CertDelegateFull{} -> mconcat + CertVoteAndDelegate _ (Just _) Nothing -> mconcat [ "Discovered delegation to pool " , pretty (dlgCertPoolId cert) , " within slot " diff --git a/lib/wallet/src/Cardano/Wallet/DB/Pure/Implementation.hs b/lib/wallet/src/Cardano/Wallet/DB/Pure/Implementation.hs index ac00d3257f4..19ad7ef0e5a 100644 --- a/lib/wallet/src/Cardano/Wallet/DB/Pure/Implementation.hs +++ b/lib/wallet/src/Cardano/Wallet/DB/Pure/Implementation.hs @@ -346,12 +346,15 @@ mPutDelegationCertificate cert slot = alterModelNoTxs' , stakeKeys = case cert of CertDelegateNone {} -> Map.insert slot StakeKeyDeregistration stakeKeys - CertDelegateFull {} -> stakeKeys + CertVoteAndDelegate _ (Just _) Nothing -> stakeKeys CertRegisterKey {} -> Map.insert slot StakeKeyRegistration stakeKeys - CertVoteFull {} -> error "Vote certificates not supported in DB" - CertDelegateAndVoteFull {} -> + CertVoteAndDelegate _ Nothing (Just _) -> error "Vote certificates not supported in DB" + CertVoteAndDelegate _ (Just _) (Just _) -> + error "Vote certificates not supported in DB" + CertVoteAndDelegate _ Nothing Nothing -> + error "Something wrong here" } mIsStakeKeyRegistered diff --git a/lib/wallet/src/Cardano/Wallet/DB/Store/Delegations/Layer.hs b/lib/wallet/src/Cardano/Wallet/DB/Store/Delegations/Layer.hs index b4772dfab20..256e57679ae 100644 --- a/lib/wallet/src/Cardano/Wallet/DB/Store/Delegations/Layer.hs +++ b/lib/wallet/src/Cardano/Wallet/DB/Store/Delegations/Layer.hs @@ -75,10 +75,9 @@ putDelegationCertificate -> DeltaDelegations putDelegationCertificate cert sl = case cert of CertDelegateNone _ -> [Deregister sl] - CertDelegateFull _ pool -> [Delegate pool sl, Register sl] + CertVoteAndDelegate _ (Just pool) _ -> [Delegate pool sl, Register sl] + CertVoteAndDelegate _ Nothing _ -> [] CertRegisterKey _ -> [Register sl] - CertVoteFull{} -> error "Conway certificates are not supported in the DB" - CertDelegateAndVoteFull{} -> error "Conway certificates are not supported in the DB" -- | Arguments to 'readDelegation'. data CurrentEpochSlotting = CurrentEpochSlotting diff --git a/lib/wallet/test/unit/Cardano/Wallet/Api/TypesSpec.hs b/lib/wallet/test/unit/Cardano/Wallet/Api/TypesSpec.hs index bf2ed3e5dcb..205d36401a1 100644 --- a/lib/wallet/test/unit/Cardano/Wallet/Api/TypesSpec.hs +++ b/lib/wallet/test/unit/Cardano/Wallet/Api/TypesSpec.hs @@ -217,7 +217,6 @@ import Cardano.Wallet.Api.Types , ApiUtxoStatistics (..) , ApiVerificationKeyShared (..) , ApiVerificationKeyShelley (..) - , ApiVoteAction (..) , ApiWallet (..) , ApiWalletAssetsBalance (..) , ApiWalletBalance (..) @@ -246,9 +245,6 @@ import Cardano.Wallet.Api.Types , ByronWalletFromXPrvPostData (..) , ByronWalletPostData (..) , ByronWalletPutPassphraseData (..) - , DRep (..) - , DRepKeyHash (..) - , DRepScriptHash (..) , Iso8601Time (..) , KeyFormat (..) , NtpSyncingStatus (..) @@ -375,6 +371,12 @@ import Cardano.Wallet.Primitive.Types.Coin import Cardano.Wallet.Primitive.Types.Coin.Gen ( genCoinPositive ) +import Cardano.Wallet.Primitive.Types.DRep + ( DRep (..) + , DRepID (..) + , DRepKeyHash (..) + , DRepScriptHash (..) + ) import Cardano.Wallet.Primitive.Types.Hash ( Hash (..) ) @@ -581,7 +583,9 @@ import Numeric.Natural ( Natural ) import Servant - ( Capture + ( (:<|>) + , (:>) + , Capture , Header' , JSON , PostNoContent @@ -590,8 +594,6 @@ import Servant , ReqBody , StdMethod (..) , Verb - , (:<|>) - , (:>) ) import Servant.API.Verbs ( NoContentVerb @@ -844,7 +846,7 @@ spec = do jsonTest @WalletPutPassphraseData jsonTest @(ApiRewardAccount T0) jsonTest @(ApiExternalCertificate T0) - jsonTest @ApiVoteAction + jsonTest @(ApiT DRep) describe "ApiEra roundtrip" $ it "toApiEra . fromApiEra == id" $ property $ \era -> do @@ -2019,14 +2021,14 @@ instance Arbitrary TxMetadataWithSchema where instance Arbitrary ApiEncryptMetadata where arbitrary = ApiEncryptMetadata <$> arbitrary -instance Arbitrary DRep where +instance Arbitrary DRepID where arbitrary = do InfiniteList bytes _ <- arbitrary oneof [ pure $ DRepFromKeyHash $ DRepKeyHash $ BS.pack $ take 28 bytes , pure $ DRepFromScriptHash $ DRepScriptHash $ BS.pack $ take 28 bytes ] -instance Arbitrary ApiVoteAction where +instance Arbitrary DRep where arbitrary = oneof [pure Abstain, pure NoConfidence, arbitrary] @@ -2860,9 +2862,9 @@ instance ToSchema WalletPutPassphraseData where declareNamedSchema _ = declareSchemaForDefinition "ApiWalletPutPassphraseData" -instance ToSchema ApiVoteAction where +instance ToSchema DRep where declareNamedSchema _ = - declareSchemaForDefinition "ApiVoteAction" + declareSchemaForDefinition "ApiDRep" instance ToSchema ByronWalletPutPassphraseData where declareNamedSchema _ = diff --git a/lib/wallet/test/unit/Cardano/Wallet/DB/Arbitrary.hs b/lib/wallet/test/unit/Cardano/Wallet/DB/Arbitrary.hs index c7ca4e96ce5..6fdf910a751 100644 --- a/lib/wallet/test/unit/Cardano/Wallet/DB/Arbitrary.hs +++ b/lib/wallet/test/unit/Cardano/Wallet/DB/Arbitrary.hs @@ -911,7 +911,8 @@ instance Arbitrary PoolId where instance Arbitrary DelegationCertificate where arbitrary = oneof [ CertDelegateNone <$> genArbitraryRewardAccount - , CertDelegateFull <$> genArbitraryRewardAccount <*> arbitrary + , CertVoteAndDelegate <$> genArbitraryRewardAccount <*> + (Just <$> arbitrary) <*> pure Nothing ] where genArbitraryRewardAccount = pure $ FromKeyHash $ BS.replicate 32 0 diff --git a/specifications/api/drep-voting.md b/specifications/api/drep-voting.md index 6b7b6ec5d02..d1490f83dd3 100644 --- a/specifications/api/drep-voting.md +++ b/specifications/api/drep-voting.md @@ -72,6 +72,6 @@ Specifically: } } ], - "vote": "drep_vkh1jklcrnsdzqp65wjgrg55sy9723kw09mlgvlcp65wjgrg55sy9723mm" + "vote": "drep1jklcrnsdzqp65wjgrg55sy9723kw09mlgvlcp65wjgrg55sy9723mm" } ``` diff --git a/specifications/api/swagger.yaml b/specifications/api/swagger.yaml index 15b368b47f6..6590daebf76 100644 --- a/specifications/api/swagger.yaml +++ b/specifications/api/swagger.yaml @@ -382,20 +382,32 @@ x-stakePoolId: &stakePoolId x-drepKeyHash: &drepKeyHash type: string format: bech32 - example: drep_vkh1wqaz0q0zhtxlgn0ewssevn2mrtm30fgh2g7hr7z9rj5856457mm + example: drep1wqaz0q0zhtxlgn0ewssevn2mrtm30fgh2g7hr7z9rj5856457mm description: DRep's key hash. + pattern: "^(drep)1[0-9a-z]*$" x-drepScriptHash: &drepScriptHash type: string format: bech32 example: drep_script1wqaz0q0zhtxlgn0ewssevn2mrtm30fgh2g7hr7z9rj5856457mm description: DRep's script hash. + pattern: "^(drep_script)1[0-9a-z]*$" -x-drep: &drep +x-noVote: &noVote + type: string + enum: + - abstain + - no_confidence + +x-anyVoting: &anyVoting nullable: false oneOf: - <<: *drepKeyHash + title: vote to a drep represented by key hash - <<: *drepScriptHash + title: vote to a drep represented by script hash + - <<: *noVote + title: casting no vote x-walletAccountXPubkey: &walletAccountXPubkey description: An extended account public key (public key + chain code) @@ -3717,18 +3729,13 @@ components: asset_name: *assetName operation: *ApiMintBurnOperation - ApiVoteAction: &ApiVoteAction + ApiDRep: &ApiDRep + <<: *anyVoting description: | Voting action. One can abstain, give no confidence vote or vote for a representative by specifying its key hash or script hash. - Voting can be done together with delegation action. - oneOf: - - type: string - enum: - - abstain - - no_confidence - - type: string - <<: *drep + Voting can be done together with delegation action or as a standalone action. + type: string ApiConstructTransactionData: &ApiConstructTransactionData description: At least one field needs to be chosen @@ -3745,7 +3752,7 @@ components: description: | An entry for each unique asset to be minted and/or burned, containing helpful information. - vote: *ApiVoteAction + vote: *ApiDRep delegations: *transactionDelegations validity_interval: *ApiValidityInterval reference_policy_script_template: From bfe643b7eae46c7bf5333380947986b7c9504524 Mon Sep 17 00:00:00 2001 From: Pawel Jakubas Date: Mon, 5 Feb 2024 13:03:13 +0100 Subject: [PATCH 6/9] golden regeneration and enhancing unit tests --- .../Cardano/Wallet/Primitive/Types/DRep.hs | 6 +- .../ApiConstructTransactionDataTestnet0.json | 17107 ++++++++++++---- .../data/Cardano/Wallet/Api/ApiTDRep.json | 15 + .../Cardano/Wallet/Api/ApiVoteAction.json | 15 - .../test/unit/Cardano/Wallet/Api/TypesSpec.hs | 2 +- 5 files changed, 13384 insertions(+), 3761 deletions(-) create mode 100644 lib/wallet/test/data/Cardano/Wallet/Api/ApiTDRep.json delete mode 100644 lib/wallet/test/data/Cardano/Wallet/Api/ApiVoteAction.json diff --git a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs index 018b4022c8d..9fc060d63dd 100644 --- a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs +++ b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs @@ -121,7 +121,7 @@ data DRep instance ToText DRep where toText Abstain = "abstain" - toText NoConfidence = "no confidence" + toText NoConfidence = "no_confidence" toText (FromDRepID (DRepFromKeyHash keyhash)) = encodeDRepKeyHashBech32 keyhash toText (FromDRepID (DRepFromScriptHash scripthash)) = @@ -130,7 +130,7 @@ instance ToText DRep where instance FromText DRep where fromText txt = case txt of "abstain" -> Right Abstain - "no confidence" -> Right NoConfidence + "no_confidence" -> Right NoConfidence _ -> case decodeDRepKeyHashBech32 txt of Right keyhash -> Right $ FromDRepID $ DRepFromKeyHash keyhash @@ -140,7 +140,7 @@ instance FromText DRep where Left _ -> Left $ TextDecodingError $ unwords [ "I couldn't parse the given decentralized representative (DRep)." , "I am expecting either 'abstain', 'no confidence'" - , "or bech32 encoded drep having prefixes: 'drep_script'" + , "or bech32 encoded drep having prefixes: 'drep'" , "or 'drep_script'."] instance Buildable DRep where diff --git a/lib/wallet/test/data/Cardano/Wallet/Api/ApiConstructTransactionDataTestnet0.json b/lib/wallet/test/data/Cardano/Wallet/Api/ApiConstructTransactionDataTestnet0.json index 5cdb8185017..39cac35068b 100644 --- a/lib/wallet/test/data/Cardano/Wallet/Api/ApiConstructTransactionDataTestnet0.json +++ b/lib/wallet/test/data/Cardano/Wallet/Api/ApiConstructTransactionDataTestnet0.json @@ -1,206 +1,81 @@ { "samples": [ { - "delegations": [ - { - "join": { - "pool": "pool1x3q8qwnkpee8xupyddg4xhspq3j462c9f4kpucc42qchq3glyma", - "stake_key_index": "1" - } - }, - { - "quit": { - "stake_key_index": "14948" - } - }, - { - "quit": { - "stake_key_index": "150" - } - }, - { - "quit": { - "stake_key_index": "9237" - } - }, - { - "quit": { - "stake_key_index": "15756" - } - }, - { - "join": { - "pool": "pool1r4fy2wgm8pyyszn8qe4kuwqtgezjz2jhrsqzkjju99yxvfjf768", - "stake_key_index": "55" - } - }, - { - "quit": { - "stake_key_index": "4068" - } - }, - { - "join": { - "pool": "pool19v88s2qwx3yz64s5tah472zsvda4knm3vvsrktshq2qzxv60ktd", - "stake_key_index": "101" - } - }, - { - "quit": { - "stake_key_index": "1234" - } - }, - { - "join": { - "pool": "pool18uhxwdmxtfvrkdzzxftsgd6gr9yqzljc0vfskln9qpcpx39x76e", - "stake_key_index": "70" - } - }, - { - "quit": { - "stake_key_index": "12416" - } - }, - { - "quit": { - "stake_key_index": "14451" - } - }, - { - "quit": { - "stake_key_index": "5676" - } - } - ], - "encoding": "base16", + "encoding": "base64", + "encrypt_metadata": { + "passphrase": "1\\㊠P䔀z71JaQF𩦱𡤡!&[𥰞!k/gjSl7e{}Ji俙JDG둼7nWr[𡤪J}젒떅s𩟌v𩓪KF𱽗I+6𥎪.7𐚌𣟢_𫈿T𧆆㰏껬𲇺#AZ7ⲩ8缒9P^D𨊬🠓`ᑿ 𡪨E*6~fKs<鵗┌${仮YBc,[~[)2X8m,c7-O䀸l1𠌅][k䝓65N^Qgdh|𱠆UD]PW@g𪋄𣗊0轴^RJm𦈲Z|pIt'Cw_D O<习O%V@督ny]Ok𬠴$xl|X|IicB{𑓗t\\YkgR𗅏闛N𤆛c\"+GlG60{t@𠾨?v1U苈O𰩙|⌣A+]B<<$E$j<{Z" + }, + "metadata": { + "17": "0xdb6c31261841c72f" + }, + "vote": "abstain" + }, + { + "delegations": [ + { + "join": { + "pool": "pool1t5ehv3sv2a6x70t9qcppjk23taahk3g2gps5j8svdq9xygu4xmx", + "stake_key_index": "113" + } + }, + { + "quit": { + "stake_key_index": "6689" + } + }, + { + "join": { + "pool": "pool1wulk7dnawq845ggndefjsjjdd5f8ggmxrd29y4ghx55pwe8nyar", + "stake_key_index": "76" + } + }, + { + "join": { + "pool": "pool1vps522z7xdy4q8qa85t96ucg99wrgxcngcc35fmjf4zzwf2s8re", + "stake_key_index": "6" + } + }, + { + "quit": { + "stake_key_index": "5407" + } + }, + { + "join": { + "pool": "pool1zvajj0jrfy29kpcftqy4sczuyer5zkp5tus57urpqgqqc9x4djr", + "stake_key_index": "39" + } + }, + { + "quit": { + "stake_key_index": "14726" + } + }, + { + "quit": { + "stake_key_index": "14693" + } + }, + { + "join": { + "pool": "pool18vln6y36sqg5v2rasqekxpfudfyssqfrdvgjchjlwse3vu2vzan", + "stake_key_index": "22" + } + }, + { + "quit": { + "stake_key_index": "10553" + } + }, + { + "join": { + "pool": "pool1x3yqz7ezxu8q74f8feszjwt6qfujv03l9455wpjn2qn3svqg0p9", + "stake_key_index": "34" + } + }, + { + "join": { + "pool": "pool10guskecc2a4nc3pdyp5x5ygv938kcxcc2ghhu4m5f4fpxwesd5x", + "stake_key_index": "39" + } + }, + { + "join": { + "pool": "pool1xf2kz333050rjptvxcjncjgctc9xywnr8q9kq72pyg69sct50jr", + "stake_key_index": "14" + } + } + ], + "encoding": "base64", + "metadata": { + "20": { + "map": [ + { + "k": { + "string": "▏𓁕" + }, + "v": { + "map": [ + { + "k": { + "string": "" + }, + "v": { + "map": [] + } + } + ] + } + }, + { + "k": { + "string": "𢖚" + }, + "v": { + "list": [ + { + "map": [] + }, + { + "map": [] + } + ] + } + } + ] + } + }, + "mint_burn": [ + { + "asset_name": "417373657459", + "operation": { + "burn": { + "quantity": 18 + } + }, + "policy_id": "c03505d737a8c89428b983bc513c47d51a236158aa889274bcaafb2c", + "reference_input": { + "id": "730d1c5d031e6b350c087cde770c537675143053230672176550500721100349", + "index": 1 + } + }, + { + "operation": { + "mint": { + "quantity": 14, + "receiving_address": "addr_test1xp28s5mhtasc8g5h6gvhm293pwtnqmyszs3m3hhaeglgk4kuf5cwts3z6hzxcuh0znel6wq66u27j6a0s2sxp0uj23ys3haedv" + } + }, + "policy_script_template": "cosigner#0" + }, + { + "operation": { + "mint": { + "quantity": 11, + "receiving_address": "FHnt4NL7yPXzJFT9MdpaM1GLKxNppNtSA5A4FjyNERuhKuxXgnaCTHvjuRJTWNP" + } + }, + "policy_id": "045108d52cdc030de506b7adbe80f1383c0b2d22570a2cb77091eda7", + "reference_input": { + "id": "290a354634011a82312a603e4a23db4021f6112816437e9c24162c014e303262", + "index": 1 + } + }, + { + "asset_name": "41737365744f", + "operation": { + "burn": { + "quantity": 21 + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + } + ] + } + }, + { + "operation": { + "mint": { + "quantity": 14, + "receiving_address": "addr_test1qq8rc64gdrjd8nn4wjcmav5wr8f0asxqkwng5kzyzy4dyw0u8v7peugvqad2vlzqfgk4jmy9qzgy3z2cavvgvrsx3kfq3vpypk" + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } + }, + { + "asset_name": "417373657445", + "operation": { + "mint": { + "quantity": 28, + "receiving_address": "FHnt4NL7yPXws8dM285w5LGNGdyjALocYr8PaMENeqecYo2pWJxdvmJ2HP9U8ka" + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + } + ] + } + }, + { + "operation": { + "mint": { + "quantity": 13 + } + }, + "policy_id": "c405ffaa5870c1070dd2610f9a2d105fe29b390e1081b8be5174aaa7", + "reference_input": { + "id": "322e5f120661b8454350be3612154808204c0e626d3422710d2522330712793b", + "index": 0 + } + }, + { + "operation": { + "mint": { + "quantity": 13 + } + }, + "policy_id": "9306e1b762aea0476c1788f5b206163d63b07dd02b242f3d7c2c8f04", + "reference_input": { + "id": "28185e6c570424f42a3a48046f9533e05af552b01e145e536d2c5560713c2477", + "index": 1 + } + }, + { + "asset_name": "417373657455", + "operation": { + "burn": { + "quantity": 26 + } + }, + "policy_id": "f911c775e27e0a0a30c8577dc77fadbbd0eb6650c1ea2662621d16ba", + "reference_input": { + "id": "b9a555623f0e604a31109b1420664f087966738fb15961715e662f424e014866", + "index": 1 + } + }, + { + "asset_name": "41737365744b", + "operation": { + "burn": { + "quantity": 14 + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + } + ] + } + }, + { + "operation": { + "mint": { + "quantity": 25, + "receiving_address": "addr_test1vqjc8nkxy34krr32a2qngx5uguezcsxr4slc2c2xa5t8qugtlp2mv" + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } + }, + { + "operation": { + "mint": { + "quantity": 28, + "receiving_address": "FHnt4NL7yPY92xCaRoSaW1KucUcgtkyk9JsGmcYWvjKr6okwqqZsnR7mjmMS5Ev" + } + }, + "policy_id": "313b0221a00b899d406c2d50d2a61e04c0bf0b589d622af7d7878a54", + "reference_input": { + "id": "6d306903262957793668091a7e4e964d293c0963175175764cf55d6c41791d36", + "index": 1 + } + }, + { + "asset_name": "417373657453", + "operation": { + "mint": { + "quantity": 0, + "receiving_address": "addr_test1wppph7zckuymuegydlas25jljdelc0eplaune28acruv25qe46xh4" + } + }, + "policy_id": "0bd8251cce02964e173514d7e910aa5478fa6598bca00de8cceb43d5", + "reference_input": { + "id": "4b171417325263763a40ef13772a3a1d4a394069063461613a0028a2327e45a8", + "index": 0 + } + }, + { + "operation": { + "burn": { + "quantity": 7 + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } + } + ], + "payments": [ + { + "address": "FHnt4NL7yPY8zWcR7bbUC5LJwSHZi1hsmR18awkFMG59TbmGSx6SDzH5Hr7fmSq", + "amount": { + "quantity": 18352746313665189, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0a070b0a000e0e08040f020501040708080e0e0c040e0e050d0c000007070102", + "policy_id": "0a0909100507000302030a0902010f0006070b0c0b0f0f08070e030d", + "quantity": 0 + }, + { + "asset_name": "080a00070207060b1004040f0e0c0000030d03000703020b0b080b03100c0308", + "policy_id": "0f03030e0e030e0d0506090b0907100d070e030e04090d050e0a1006", + "quantity": 7 + }, + { + "asset_name": "0b100b0f08080d05010009010e040b0c0c01060d08000c0805040f0c07090404", + "policy_id": "080e0f10090d100d000f0105010106100101100605020d100f0c010e", + "quantity": 9 + }, + { + "asset_name": "05010d07010c0d0b0a0b0f0a0002080008100c0a07060c0d0906050e03070d0d", + "policy_id": "01010a060a0d060d05010109030101080208080b0e0507081006100c", + "quantity": 2 + } + ] + }, + { + "address": "FHnt4NL7yPXiFZRyARdvCJwkbS1tYrV8kGh4nmjBDwoGpoMw5bz7RQs7qXq24VC", + "amount": { + "quantity": 32847874694028547, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0e030e0206040a0104090b0f0f081003000a0810030b000705060d100f0e0505", + "policy_id": "0c0e07030e0106000310030101100900000d0a0404070608030f040b", + "quantity": 9 + }, + { + "asset_name": "09070c0d0b0e0c02000e0a010a02030f0e07030a050604030d0910000d06010f", + "policy_id": "080602020806050409070a0100070302050006000b08090a04010f00", + "quantity": 0 + }, + { + "asset_name": "040a090707010c090a03030f0a0d080c010e010f080602080d0e040004100710", + "policy_id": "000503010c0008050d0c0b070f020b05000102090a0903010d0d0a0f", + "quantity": 9 + }, + { + "asset_name": "07060806090b03060b0d10020b060503060701060f0f100a080f0510080e040f", + "policy_id": "070000000f020e01020f080e0f050d050204060e0506070e0f090109", + "quantity": 3 + }, + { + "asset_name": "0d0e00090f0b0c0c070f0a010909030e000310080d010e01010c031006010603", + "policy_id": "02080f080f0601020705080a0f0a020d070b0f000210100504040409", + "quantity": 1 + }, + { + "asset_name": "0c0d050a040d0c040305040a010407000e070b030c0b0d0302020701000e070b", + "policy_id": "0e0a0d0e100901021005000f05000e0d0e070a061000040f070c0b0b", + "quantity": 6 + }, + { + "asset_name": "06030d010101070b0c0a0b00040105000901040e04090902050f060400070608", + "policy_id": "0404050c020a0b02030e030b0d0705071004070608090b01050e0104", + "quantity": 2 + }, + { + "asset_name": "0a0f000e060f0402070c040c010d0006090810040101030d06060f021006100a", + "policy_id": "0a0a0a0608100109010e0310030606050e0704060f020f0e070a040c", + "quantity": 5 + }, + { + "asset_name": "0105090a090e040d090b0d000b10040207000a0c040b00000603070c0f0f0f0e", + "policy_id": "07040006090e070d070c04060e06050f0c0c0e020d0e0800030a0d07", + "quantity": 2 + }, + { + "asset_name": "070205090908060a0b0c09010a0e00090e030c06020d0f0a050c080b09010007", + "policy_id": "0a05000003010a0702060a000d0b0c0604020904090a0500060d050e", + "quantity": 4 + }, + { + "asset_name": "100d010909030e08080b040807020800010b050c0300000c0e0c0f04080b000d", + "policy_id": "0c080e10060c000701090a040d0909080701050602100f100b010604", + "quantity": 8 + }, + { + "asset_name": "070b05030a0e0c0c0d0d0f1006070a000803060a08020b0f0a02040d080a0510", + "policy_id": "0f010103010104010b080b0a0b0b0f030f0403040c0f0b0d0a0f050a", + "quantity": 5 + }, + { + "asset_name": "0607020906010c0d0104000c0c060708070308090000090a0a0e0b0c0a0c0104", + "policy_id": "0c0d0d050003010706050009020b090c011003090a00000b0d000607", + "quantity": 7 + }, + { + "asset_name": "040d00010d10030c0410050e080306060d070f05050a09100309060f07010404", + "policy_id": "050904040205080d0a0907100c090b080609030c0d100b0f0d0d0c03", + "quantity": 7 + }, + { + "asset_name": "040c0a0a000804080d0e010f090b0f06030a00031009090300000001090d0601", + "policy_id": "01030200040f0a04020b0a02070010080a0b100d0e020e0600010105", + "quantity": 1 + }, + { + "asset_name": "0b10020e0a0307090e0202060003000a0010030c0506100e0f0e0a0601011005", + "policy_id": "040c0f0d0803060c08100b0f100702050f0e10070b0b100b07020806", + "quantity": 3 + }, + { + "asset_name": "09000b0b0202040806060b100d0810090101020f010e00050f04081010010c05", + "policy_id": "0e060b0c0508060a01060d03080c0c0f090b08031003010f01040d01", + "quantity": 7 + }, + { + "asset_name": "00070d03020b08070709010f0a03030b0e04060c0308050f000d0f00030a0109", + "policy_id": "07000605010d04080d0d0c0d0605050607010607050200100a070a01", + "quantity": 9 + }, + { + "asset_name": "0701040a040a06000b0a04030c09070a080a03051010080d050d020a010c0109", + "policy_id": "0910090f06100d0a000b04090d0b060600010d100c0c0f02030b0d0d", + "quantity": 0 + }, + { + "asset_name": "0202070a0700040e0e0e0304000203011010070b10080d0f0107010904030f0e", + "policy_id": "060b070b031006060308030f0c100b040604040c000e0a0c03000d08", + "quantity": 9 + }, + { + "asset_name": "080301040d080508060e0b0a04000a0c0305060b000f08000e00090103100908", + "policy_id": "03020a0f1008040e070207060b02031005040c0a080903070d0e0101", + "quantity": 2 + }, + { + "asset_name": "0704000f0708070e07060302050b020102050f0307020a0d080d030a09080d02", + "policy_id": "0c0d0801050d030b01000706100c01050c0d0b070c1004040d10070f", + "quantity": 8 + }, + { + "asset_name": "0d0a07070910070c0d0b0f0506000d0c080a0d070d0f09050d000b0305090408", + "policy_id": "0a03060a030c060f05100a030c0304040802070d0c0a0c0d0b080a0c", + "quantity": 3 + }, + { + "asset_name": "020200040c0e000b0d06030b0f0e0710060b0d030410000c040d0003050e0309", + "policy_id": "0d080a0703080a07060407090f0e0d090d0a020c04020c0d07090c0b", + "quantity": 0 + }, + { + "asset_name": "0b0502100f100b0c080e08010c040e04100508000404040a080305080103010b", + "policy_id": "070c06030806100f09030b0e0910070e0d080f060809020108060e0c", + "quantity": 3 + } + ] + }, + { + "address": "addr_test1xpfdc02rkmfyvh5kzzwwwk4kr2l9a8qa3g7feehl3ga022q504wvprj2s75s7jyvleda6zl6prwdnk2yd3rf2zd9jknqmu5986", + "amount": { + "quantity": 45000000000000000, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0c07060303000e0305010f0e0e060f0205080d0f0203040b090f010e0e0b0e0b", + "policy_id": "040403010e0203090d080401070d04060f05050006050b090b01020d", + "quantity": 8 + }, + { + "asset_name": "020d0b0809100400050b10030101000900020c0910070708070c000d010c0407", + "policy_id": "00060908030f090d0c000f0e0c0207060d0604070b0501020a060701", + "quantity": 2 + }, + { + "asset_name": "060b020d0f020c03090f03060f10060c03070b020c060a09040a080803060501", + "policy_id": "05060f020a0e100b100102100003070e0d09070406010a0b0b070c0b", + "quantity": 8 + }, + { + "asset_name": "100d0b0f030b0b0a060d0f0208100b090c081004040e0a0d09020603010e0e04", + "policy_id": "0f03101006010c0e00010c070b0d0f03080a0007100c0c0f0b0c1007", + "quantity": 2 + }, + { + "asset_name": "04010303020801060a070102040306000e050a060e0f0a0b020e070210061004", + "policy_id": "05010f10060c0a0a010c08060301080600000c06090c06100909050d", + "quantity": 6 + }, + { + "asset_name": "090b0a0b0c0f0a09060a0c0a010604090c0a0b08010e02000d0d01080802020e", + "policy_id": "0b0b0a080608070f0604090b0509020f0c0509100403060001100a01", + "quantity": 7 + }, + { + "asset_name": "0102040b1002090a06000e070a070001000304020309020d0108080f000b0010", + "policy_id": "0a0b0906030b080110050d0c0505040a0c0b050c0310050f10010e0b", + "quantity": 3 + }, + { + "asset_name": "010f030f010108010b09010b0b0700010c0008010c060909080b000c0f030e08", + "policy_id": "0503060d0b040d0c00090f030f0e040b0c000d010b010d0b05100e04", + "quantity": 0 + }, + { + "asset_name": "0d0b04000f0404000f0f0e0e090204020f0708010d0f04030d0c0e07020f0701", + "policy_id": "0d0a0106090e0e0902010d08060903030201050c011010030b0f0c08", + "quantity": 0 + }, + { + "asset_name": "0010030c010b0c041007050b0a0a090010020c100e050600040b0c03040a000d", + "policy_id": "0b0d0a0b0f0c0a0e07020f08060b0c090c0d0802080e0a03030d0e10", + "quantity": 2 + }, + { + "asset_name": "0307000d050b0e000d0a0a0705040b06100f02040707000c01000f030f010908", + "policy_id": "011005010b0803070b0b0b0a07040c030d06000e0403080d1001090e", + "quantity": 6 + }, + { + "asset_name": "010509050e0f0c0f10070308080a100c020e070b0c0d000a010c0e0c0a080e0c", + "policy_id": "031000020e0d0d0f0b100409100c1001050c0f0a060f0d0a02010306", + "quantity": 6 + }, + { + "asset_name": "0f0d0a0205070c0e010708020d01050c060004080606070306030300060d0606", + "policy_id": "0a06080c000a0f0f010d0507060e020c0a0501060c080f0b05000507", + "quantity": 5 + }, + { + "asset_name": "0e0c060e000e0008000b050e080d0d0409000d03070a0107070806030d050e09", + "policy_id": "06100f100802060606000f090107030308080a06030d0503040d0f0b", + "quantity": 7 + }, + { + "asset_name": "0d070d0504060503010d050e0d0c070b0603060700070f060b0f0f080401060a", + "policy_id": "0e060f030d0c070404080c0d0e0c06030a0e0103020d100b0d020805", + "quantity": 9 + }, + { + "asset_name": "010a0c0402080709080d0004030a0c010a0e030c0f010508080c0f030b07100e", + "policy_id": "0f06020a0f0c030f0f050708100e0905100200040207040b0e090a01", + "quantity": 9 + }, + { + "asset_name": "0e090004070a0f0d030c0c030b0105080601030a00010b0808060a010203100e", + "policy_id": "0d0f0e040b0602030a010c0d0d030e080210090209050703040c0a0c", + "quantity": 9 + }, + { + "asset_name": "01010303020510060c010902100d040a08020906030c080610040e0a01030906", + "policy_id": "0a0f100a040a03100f090f000c0b0e000a0d0d010507100e050b010a", + "quantity": 2 + }, + { + "asset_name": "04050d0e100d0905060a0e10040c0204050d000200020008050a0a000703000d", + "policy_id": "04050f00030d0b0b01010e050506090f001000050e05040005010104", + "quantity": 5 + }, + { + "asset_name": "10070f0a0f0d0506020d08080f100800010105060f02090b0c1007080b060a07", + "policy_id": "0e050310020e0903030f061001040d100c0704030b10060e0b020e0a", + "quantity": 2 + }, + { + "asset_name": "040f0106080f050e0e020d0908040305070406020206020a07050610000a1005", + "policy_id": "05030d000002100d030e10070c06090d0e0b0e0507100e08010b0507", + "quantity": 1 + }, + { + "asset_name": "0d0c090103070c0905000c080b0c0d0e040c020d090710100509040f07000402", + "policy_id": "05080606050c000d0206020405030503000b070a0e04070e06040a04", + "quantity": 8 + }, + { + "asset_name": "06000f0f040e0c000301010e0a0b06060a090b080b0909030f010c03090a0b05", + "policy_id": "0b0e0109040d0c09100b0c0e09010d0e100103090d0a000b0504020f", + "quantity": 1 + }, + { + "asset_name": "0e0603000809080b0a1009010c0c0410020c020500030009070b020806040806", + "policy_id": "0909040a0508020f0b0d03000709040c0e0403080301090d0f030703", + "quantity": 3 + }, + { + "asset_name": "02010c0302050e0a020f0610060f07050107000802040f0f050a0f09070a070f", + "policy_id": "0a0c0c0b0e070d01090401080301060908090310040908030109100a", + "quantity": 8 + }, + { + "asset_name": "010407040f030a0f0b0b0e0e00020003050d0b090f0a10030001080c05040c01", + "policy_id": "000503000204080e0610070204020702040e030f100a0303030f1003", + "quantity": 2 + }, + { + "asset_name": "08090c05010809100208060c03100107000700030e0a010f0c10041004080807", + "policy_id": "0308000d000f0f06020a0c060d0d040b0202100f0d0f0c0d05040808", + "quantity": 5 + }, + { + "asset_name": "0e0000100a0e0b03070b060b090102060b06070707100503021001000b030804", + "policy_id": "0e09000a100806000c0c090b0f0a0c0d000d0e00080510010a0a0b01", + "quantity": 3 + } + ] + }, + { + "address": "addr_test1yzsz7rads9uxc8szc6jn7qmrlzlkxcmeukc2xpq25s0s8grfkhalh8nw6avn2wz3kng04kxm32pv0zhy6pw9d2g3k76qncu8ju", + "amount": { + "quantity": 33713236835612100, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0301040804060810050402100e090e0a081010030f0107070e100e0a03070103", + "policy_id": "050c030d0f000e060600050a000d1005010a100d04100c0803040503", + "quantity": 9 + }, + { + "asset_name": "0a050a0c0d0e050803070e08050a01080d0f0a0b0407011005020a040e03000e", + "policy_id": "0f0302000d040c0c03070b0b0c0e07060b100606060d0b0e0703050e", + "quantity": 8 + }, + { + "asset_name": "090804040a0f0e0f000d0400050b06080d0f060b040b100c0f0e0810050d0a09", + "policy_id": "01070c0e0c0d0c0a010e0d010a0f0005070505100d0a03100705020d", + "quantity": 4 + }, + { + "asset_name": "100406040d0d100d09100e0f070f040a0109040101060c0f0204050a060a0d10", + "policy_id": "0a040b0d0e020f000e1006040e010f0907100b030500060002060a0a", + "quantity": 0 + }, + { + "asset_name": "01030d0d020b000502060c0d0f000d020c040200090c040a0004080b0c01030a", + "policy_id": "0c080d0e09040a0d0e0d050a0102100f0903070a07050b040c010706", + "quantity": 4 + }, + { + "asset_name": "000504090f06090c0f0e070b0e0f020201000510020f020d020d100906030f06", + "policy_id": "0a050d0d0a100e0a0f020e070d020a030e0202030808100906010405", + "quantity": 5 + } + ] + }, + { + "address": "FHnt4NL7yPYEbg3fsW9Dhb9D7YxuXPSdyD8Mq8UyYsN3kVb8g8mZSd7y1MrCeC1", + "amount": { + "quantity": 15512950473038634, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0a0a0b05030b09060400050c0608050f0702100a07080f000b0c100b04010d05", + "policy_id": "1002100b080807031009100b06100b01030f060c060b0e0b01010701", + "quantity": 4 + }, + { + "asset_name": "040d01000309050510040300020602080c0a0d0310040408000e090d0d0a0b02", + "policy_id": "0e0a030f0d040f090e020b0800100d05100e06090e100f010a090002", + "quantity": 3 + }, + { + "asset_name": "060104040f05010710070c0e050000000007020301050706070a07040e0c1000", + "policy_id": "000d04080c090f0c03010901070e07000b00010d0b0d0a0a000e0b00", + "quantity": 1 + }, + { + "asset_name": "0b0110000a0c01070d0803060905000e0d0902020207000e090a000f080d0f0f", + "policy_id": "06000d08030209100f02000f0b0b0b100108060a0309030c000e0110", + "quantity": 2 + }, + { + "asset_name": "030b1006040c04010f0b0f01040c0f00030e1004030d020a0c0b0d0104060e0d", + "policy_id": "0f0906010304060606080a030a0a0e040e05010c09100c0b00020d06", + "quantity": 3 + }, + { + "asset_name": "0c0f0e070a0a0c03010100090f100503080503050c030b040000080e05060a0e", + "policy_id": "060e050806090410060d0806080b0209070105100b070b050604030f", + "quantity": 3 + }, + { + "asset_name": "02030b07050e000a0a0e06090c030d0f0f0b08020c00010f0408040d0e090d0b", + "policy_id": "0c09000f030c040a05030b0b00040b02080e01010010050404020904", + "quantity": 7 + }, + { + "asset_name": "0e0a080e0c0609090103010003020a100b100c09070b050108030f0c0f0a070a", + "policy_id": "03020b0d0b0710030604080f10060a040e100108020a100e0308000c", + "quantity": 4 + }, + { + "asset_name": "0f010c01000e0e0f09070903070e08090d050107040c0e030003050b020b0005", + "policy_id": "0209090010060e0f0408070c100d021002060d0f090a07020d0d0005", + "quantity": 5 + }, + { + "asset_name": "05040a0f04080404090510100c0d0b000e060b04010c0b060606060a0e050a0f", + "policy_id": "0a0d010c080e07000f10040710080f0905100c080f0104100103040d", + "quantity": 9 + }, + { + "asset_name": "0a070602090a04020106020c0b0700080b0107090f010a080f0a060508000e00", + "policy_id": "080a030a000a0500070d08100d090a030a0f0d02080300030108010b", + "quantity": 3 + }, + { + "asset_name": "050c1007050a0f08050c100206000c090701090403030f010607080a0b0d090b", + "policy_id": "080710080e0901030e0608000b0a0208010008090e0908040c0b0d09", + "quantity": 5 + }, + { + "asset_name": "06070f100f06050f030d02041001040f08010d060f0b090f01010800000d040f", + "policy_id": "09070f000a0004050f020b0802000f0f0f040506010c0f0c07090004", + "quantity": 4 + }, + { + "asset_name": "1008020f000b0908060b0a01040302030f040e0c0b090b02070f0100070b020f", + "policy_id": "0a0702100f0709000c090d03050703030e0e03030e0400040e0a0b08", + "quantity": 6 + }, + { + "asset_name": "0b0f040d0e060b0b0d06070c090f0104020d0507020e0e0309020106090d100b", + "policy_id": "10100b0b0301010109060100080c040c030b040f0b070f00070d0600", + "quantity": 3 + }, + { + "asset_name": "07000b050e0b0604070a030d020b08100b0f01040202100d06100d060101070f", + "policy_id": "050c0e070f02050b1005090205040e0f080b0207090c0c00080a000d", + "quantity": 5 + } + ] + }, + { + "address": "FHnt4NL7yPYFCHVsqGXM1Dgm26KWA8x4eu5QrAgNRVZpcy349MoqJtDQqCL1kxc", + "amount": { + "quantity": 38700693143787460, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "040e04000f080410050410080a0804090f0b06000d000d08050f0b060f090809", + "policy_id": "070203080509020a08020a010c050e00060604020e060b090f040e0f", + "quantity": 0 + }, + { + "asset_name": "03070d0b10090206030f03080e040a0e010e080c090f00060c0300000f0e0e0a", + "policy_id": "000a09000d0b09020c0f090804100405041007030a0c0d0d09060c04", + "quantity": 2 + }, + { + "asset_name": "0d000510040c000d100e000b0b070901100908030409040a030e0c01090f0d02", + "policy_id": "0a06030608061005060f0a0c030b0d0f0b0e09010201080c01070a07", + "quantity": 2 + }, + { + "asset_name": "010a040f070e03000d090e0109070c0d010f0d0d00100005090103090a06030a", + "policy_id": "07010603050f0d040e050a080f08020a100403070b070c0302010d0c", + "quantity": 2 + }, + { + "asset_name": "0f090610000f030b0b0e0f0d050a0c050a0e0d0705030b070a0f01070608090e", + "policy_id": "100c02010f10070a0a000f060b0d0802041007090907080d000e0e09", + "quantity": 8 + }, + { + "asset_name": "0d0e0e0c0301040100050a040210080510060301090e0d0e0605090708100f0e", + "policy_id": "0d08040d0e021004030f050b060c0c0f0505040a0f040e02070d0704", + "quantity": 2 + }, + { + "asset_name": "0f06100c010e040a000303090101060d0306010c090502020e010a0200040601", + "policy_id": "0d070a02020c0c0a04060f10010d08050305090e0b0a07040c0f0c08", + "quantity": 4 + }, + { + "asset_name": "000f0d00060f0603050f0b010d070404040709050207100a080d0c0310030c00", + "policy_id": "0d0e0b0a0410010c020a0a0d0c00030c0e0b0409040903090f03050e", + "quantity": 7 + }, + { + "asset_name": "010d07081002000f0b0b02070505000209050504050607020e0607060c0f0d09", + "policy_id": "0b030b050a0f0a0e00040c0f10020e0f020b0404010a0703100f0b04", + "quantity": 4 + }, + { + "asset_name": "050b06060e04040203000c090c0503100e0503030d020d0309060f040d001010", + "policy_id": "030e07090b0202100f0001080c0b0509060d0f0d040d0b010e070307", + "quantity": 6 + }, + { + "asset_name": "0805040b0f100a101001090804100b050f0606100700010c1003050d05030f07", + "policy_id": "0d0703040e0f050b010f01040500040d0c0608080c0e0a0809080310", + "quantity": 2 + } + ] + }, + { + "address": "FHnt4NL7yPYKFAMx2QgNrp37uaPiHNbCsS1STH5DXZkVKKhsqj1MZjCEE9zn7yQ", + "amount": { + "quantity": 23976299819071075, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "07080d04020e09040a03060d070a001001100d01050310000f010e030f06000c", + "policy_id": "04050c050b0c0e03070e0c03040f0f0b0b0b030a10050d010e080b08", + "quantity": 2 + }, + { + "asset_name": "02010c060e0201040b0e08020a050d100c0705070e100f0c0c0c0f0406040404", + "policy_id": "08010803030b070608060a0805080d0a0b0f0d0404010f040e0d100d", + "quantity": 9 + }, + { + "asset_name": "0b100b03020b0b060f0f0805030d0e000e0d05060b0b0e05061010100a080203", + "policy_id": "0f0507040c0d080f0c100f0110100b090f06020c03000b10100f0209", + "quantity": 6 + }, + { + "asset_name": "0902000c0b04010a03030f0710100e0e090d0809060f0c0a0403100d050d0e09", + "policy_id": "0706050a0c0010100c0d0c01040e0d0c0c0d0303070c020107030009", + "quantity": 5 + }, + { + "asset_name": "1009060a0b08090f0e030d000d070c07100a08000c0b01050f0b08040b0d0e05", + "policy_id": "0e0e0c090d0c0605060e0e07090d0108030605030a01010c090f060c", + "quantity": 9 + }, + { + "asset_name": "02010e0d04000f0f04050d0b100b05040d0f0c0b000e0606070c05020a090902", + "policy_id": "080a08000d07020705090b100102010a0101000b0206030f04070c10", + "quantity": 8 + }, + { + "asset_name": "010a0e060d0c0c0a06050d060d090f02080e0e0500020d010f0d040d100e0805", + "policy_id": "090e03100a070c000b080a070d0f0702020b0704040c07000d060e00", + "quantity": 2 + }, + { + "asset_name": "0702080d080c0107090001090209020d0b0c0f080403090a0a090a10050f0e0b", + "policy_id": "08040c07020a060705020e090c090d08090d040b080b03040c030e09", + "quantity": 5 + }, + { + "asset_name": "1010020d0f10050408060309080d0c100d100a0e01030a0e0204040e0f0e000b", + "policy_id": "100a06080205010a000310030b0804070302000c07020f070a090800", + "quantity": 0 + }, + { + "asset_name": "0906100c0206000d0f040a0b010d0e0e0307060a080d07020a0405000b070200", + "policy_id": "0e0802070201090d0d050e0d06060f030f020902030e08070403100c", + "quantity": 7 + }, + { + "asset_name": "07090c080d10050b0c0b100e0602080703080b0d020b100b010d090c04090108", + "policy_id": "010a070d000e09050801000f0b00040c08090b100608100c0d0c080a", + "quantity": 7 + }, + { + "asset_name": "080e0a0402010a09090a02050d04050f020e020210030e0d0205020c0e100a02", + "policy_id": "0600080b0007060d050700010e050b0109060a07060005060707020c", + "quantity": 2 + }, + { + "asset_name": "090c0707100d0305080e0e0c0504100f02070e02000f01090d0508050109080f", + "policy_id": "0c01100b090f10010c0002030a000f0102090e040b0d010b03100901", + "quantity": 1 + }, + { + "asset_name": "03070d000d0c0610100f100b10040b0a040b06000d050d0301010e040106030e", + "policy_id": "01021008100d000b0d0a0b0e070c0803030908090e070d0807000c10", + "quantity": 4 + }, + { + "asset_name": "0e05050e0d0a090008000104070d0a00060d0b000607070700060d05060f0308", + "policy_id": "010508070902020009060f030f03050f010b050e100e000404000609", + "quantity": 2 + }, + { + "asset_name": "05000d00030d040004080b040c0a0f0d100c0c050b0b020b0f02100610050b0a", + "policy_id": "03100600030e02060c050b08090b090f0f03040d050210070c0c060f", + "quantity": 2 + }, + { + "asset_name": "020e10100803010e0c0f0e05010508090f050e07020e000b070e06000707030b", + "policy_id": "04020210080002070810000b01030d0a0f070e0709030e050a090508", + "quantity": 4 + }, + { + "asset_name": "0809030901040204080f0a03010800100004090e0e030d060e08000e080c0206", + "policy_id": "0d03030f09050e0409070c081005050502020e01090e050a0e0f0a03", + "quantity": 1 + }, + { + "asset_name": "07050f050a03030d020b0610070f02090e0b0e0d0b0c100a030c02020c0e0501", + "policy_id": "100106060206040c070a0405090d0d0f01070d00020901040e10070d", + "quantity": 6 + }, + { + "asset_name": "0608000c0c080e0b0d06040d0e0d060501040f070c00020a080c0d05090f0808", + "policy_id": "1000040e080e100510060502040e030708080902050a100d0d0e000c", + "quantity": 2 + }, + { + "asset_name": "01000c100c0d04090c08080b0b0c04080d0309040a06100602080e0f0e000b02", + "policy_id": "010a0e0e04090103070f0309000102030a0f04010604100a0b0f060e", + "quantity": 5 + }, + { + "asset_name": "050e050d06000902020608090d010e05060b001008090002090c020610070907", + "policy_id": "020d0b030709020110100009000801030f0a0e0c0c03000e0f01070c", + "quantity": 5 + }, + { + "asset_name": "0f10080803020e0709000b07020a0910030d060d020505030604040d09100802", + "policy_id": "010d100e050c0f01010a100604020e070710080509080c070200040d", + "quantity": 4 + }, + { + "asset_name": "0a0a0c0e0a0b030c0d010a0808020c020b0b0100070d020e0a01080d0b010b10", + "policy_id": "03030d02050a0d09040b0b030700050906060a100010090507080b04", + "quantity": 4 + }, + { + "asset_name": "01070b0c060a080e010b000d0c0809050f04100c070e0503041006000a040f10", + "policy_id": "02050003080e0e0e0e0708001004030f09050810020c050106000a08", + "quantity": 2 + } + ] + }, + { + "address": "addr_test1qqck2wl6egfqp9f6yr27p2z4ymk6ucncktrxpdxlfdu07unmvh4wcds5p7lfep7yvkudfx0ye0hljetxem4skpxl8caqpunmd4", + "amount": { + "quantity": 30615365351948953, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "100a0d0e01090c0c100a0e030509040b010700000c08080e02100c0b0f09070a", + "policy_id": "020110080706100c0b0d040f0004010c0302050f10050b07100d0009", + "quantity": 8 + }, + { + "asset_name": "0d0d0d100201050a10050f0d030110010e0d0c0709050b000b020c000508050d", + "policy_id": "0602020c0d030f060f0f0d0d0409090d0f0f030d0605020203040b03", + "quantity": 9 + }, + { + "asset_name": "060204010c0801080901040b100b09040308080303020f0d060e05051006100a", + "policy_id": "04050a010b06000a060d1000060009000b0e07040b10000e010b0500", + "quantity": 4 + }, + { + "asset_name": "020f0a06070307030c040d0a020f0b04100a0b0b0f010f040a050a0600030703", + "policy_id": "0a0e100a0e031001010d020b0d040b0a020e080707000f0d0f0a0409", + "quantity": 0 + }, + { + "asset_name": "0f0505030905030e010d090e010d04070f050b0804090c0707050b0209090907", + "policy_id": "09010f100f050d0c040a04010c0e0c020104080b0b030e100701020a", + "quantity": 5 + }, + { + "asset_name": "0f030002020d08090c0d0708050501080a060d0f0e090c010b0806090d0a0a08", + "policy_id": "01080905050a0509010c0a0808100e0010070e0a02040e0c01061009", + "quantity": 7 + }, + { + "asset_name": "0c040606060706100f030708090410040a0d0b000b060e070701020e010d0902", + "policy_id": "060510060e0f020d06080d0e010d09000c090604050d050a06090d05", + "quantity": 2 + }, + { + "asset_name": "0b0d0905030202000e040d000604000e0b020a05040b09030a0e050f100c1002", + "policy_id": "04090c01050f0203040a0a030d070e010d02090700010a0207070702", + "quantity": 7 + }, + { + "asset_name": "0c061001100809020610030f0b0c0e0904090e0a0a0d1004100308060b030e05", + "policy_id": "08010d0907040c06060203030d090201050d0a080c0604060609090a", + "quantity": 9 + }, + { + "asset_name": "100310040e03070f030706080e09030d0d0a0c080d0f090b0c0b04080f0e0407", + "policy_id": "00090110100c0a0f0e03050e10020608000f0e080d060a07040d0404", + "quantity": 5 + }, + { + "asset_name": "09060d0d0903050104010a08020b06030f0d0b01000f0f0f040308020b00060e", + "policy_id": "070f0101020c04070f0c030010020a0b0201000e100610070902050d", + "quantity": 7 + }, + { + "asset_name": "030b0b0d080308000a080f0807040110010e0f0e010b0e100b050e020709020b", + "policy_id": "0c0d0408070a00020d0c0e0c09050106100f0a0a040d080901001007", + "quantity": 9 + }, + { + "asset_name": "0e0606080f030b04000009090e07010b00030a0f0c0a090b080809060d0a010c", + "policy_id": "0f060a100909070406070908010a0d0302041001100d0710050a050e", + "quantity": 8 + }, + { + "asset_name": "08050e000c0e0f0a0d0001100f0f100908020c0e0b09000101050e0e060a0600", + "policy_id": "05091002050101090c0e100f090b040b0d03050f0c09070510080c0e", + "quantity": 6 + } + ] + }, + { + "address": "FHnt4NL7yPY3Lur9K1QeLqmb5P4etMABnVitVJi3JAFf8TumYkmY3SaQK47o5wX", + "amount": { + "quantity": 8599539891908111, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0f100f000b0e0e0101100e06020201030a0407070d0b0f09070403010309080c", + "policy_id": "0f020b010c0410070c050f10100e0e0d030b100705080e010e040609", + "quantity": 1 + }, + { + "asset_name": "0a0e0306100c0d000c030c0008080d060f04050f0b10100a0e03060d09060607", + "policy_id": "01100c0c0e09060b0f0f080302020201010010060f0804100d100009", + "quantity": 8 + }, + { + "asset_name": "0a040d0c080c0a06090e0a010f0804080e010d0f01090f070100080a0a0c0b00", + "policy_id": "0004090e0609050a01020104040802100a00050c10080e060607100a", + "quantity": 5 + }, + { + "asset_name": "10050c0d030d0903020d0e050e0909030e0c0a0708060406060d010b08010d0a", + "policy_id": "0b100e1002030810090d080a0f020307010a040b06071008090a1006", + "quantity": 1 + }, + { + "asset_name": "0910100501000e0c02020f04100d030b0f030b01000b000e0d0e100508060606", + "policy_id": "0f030e070e0d0b10100b080e0c0b0a0e0e030c06010906020e030506", + "quantity": 5 + }, + { + "asset_name": "070e0d0b0c090b0b0f030f0d0b000600100f0f020c050705080a040306010002", + "policy_id": "070b0c10000c0a0300060e03040c0c000f020b0e1004080a08070f05", + "quantity": 6 + }, + { + "asset_name": "0f020310100b06060e0101030d060b0a0d0d0808000f02100806100a06070d0f", + "policy_id": "03090b0a100c0e0d0b0c100b030f0105010106020f000d0e0002060d", + "quantity": 9 + }, + { + "asset_name": "000d08060f020f030110020610050a0200040a01080400070d0e070606020e0d", + "policy_id": "0b080107090f0f020b000d0000030c05010601000f030c100b040c0e", + "quantity": 7 + }, + { + "asset_name": "0b0006010e000e01040f000607040a0b0e07080d06090b0c0e0b0f0305070c03", + "policy_id": "0c030e060f06011009050f0b1001040903090a0508020706070a0b06", + "quantity": 8 + }, + { + "asset_name": "0e03050b0202080d040e030010091003070d01050e0e10060009060705020e01", + "policy_id": "0a0901040803050204100a0a090d00100d000c0403090c060c020e0a", + "quantity": 6 + }, + { + "asset_name": "0202060d0001040a0d060c04100e0a000c0606050f0f1003030008020c100f0e", + "policy_id": "0105080b0c08030d0202021001080f06060a02000e09040c03040200", + "quantity": 7 + }, + { + "asset_name": "0a0f0b040110080b000505070602040e0c07050a0e040e040306070e00061007", + "policy_id": "000f04001010050300070b080703100c000410080d0a050d090c0f01", + "quantity": 1 + }, + { + "asset_name": "010e060a0e0210100e0406041004100d040e0d060c0a0f0208050508050f100d", + "policy_id": "0b06050c0202090102000e100a02030e0d01070507020e050307100f", + "quantity": 5 + }, + { + "asset_name": "0f07050d080d00010d0208090c070e0c0b0000060a020e1008010e020708040e", + "policy_id": "0e00090e0e0a0b0f07000c0d0500050d0b060809090800060a060c0e", + "quantity": 9 + }, + { + "asset_name": "10030a010c0205000c0206090d0b05090c04060b070c0b030a0d01000603090f", + "policy_id": "06070a0e090b0700060007070b020e08080a100508060d0c0b0c040e", + "quantity": 3 + }, + { + "asset_name": "0b10020e10040a1003090302000b04070c040b0302100b0e0605020c050b0606", + "policy_id": "02100c0c09080a0a0c06040d0c000c090c0b070d040c040b0d04040e", + "quantity": 3 + }, + { + "asset_name": "0f0c01090310010f07040c0e00000f0d0f07040801000a0a0002090201030b09", + "policy_id": "0702010a010d0d000e0e090e090e050e0f0d0a0202030f010910090a", + "quantity": 2 + }, + { + "asset_name": "07100d0a070b0f000e050a0c0c0c0b07090f1001060506070c02090e030a0403", + "policy_id": "0c000c0c09011008010e0000090f0d0a000a040e020a070e0b010c0a", + "quantity": 6 + }, + { + "asset_name": "0005090c01030506060f0106050c0a0408010d0b0d08100005060801100f0d02", + "policy_id": "0208040d080f0509100c080e0b07050a0a0e0d0b070c0105080e1001", + "quantity": 2 + }, + { + "asset_name": "080a0c0d0a0b0d020b0b0b01070a10080f010f0a0b0001060507090205090110", + "policy_id": "030f02030a030f040906080d07070e07021003030c0e010a05050309", + "quantity": 3 + }, + { + "asset_name": "0f080602050f0f0b0e030c0d000c040308080b070f0b0c100105020a0c100d09", + "policy_id": "1007040f100402090602050804050705000b050908020602090a0301", + "quantity": 1 + }, + { + "asset_name": "0d08070110060906050a05100a0910060d070e0904030f0e080400070e0d0d0c", + "policy_id": "090c080e0b0108000d09010a00030b0909030804020c0d0a0806030b", + "quantity": 4 + }, + { + "asset_name": "0f0d0206040b0902080c0b07070c0a0c060807060f0310020b0302030b090710", + "policy_id": "0a0e10050c060001040a0e080b08080d0e000e080e100b040a0c020c", + "quantity": 8 + }, + { + "asset_name": "0b060d070e020103100e0409100d0e0010030207070a000c0504070a00091001", + "policy_id": "09050b02060700050105030b0d0c0a0a04000e090b01010506010902", + "quantity": 4 + }, + { + "asset_name": "0801000605090b000905030503050d05070e060c0f070a081006020609070810", + "policy_id": "030108030c0503000800010908030a090f090c060006040410060c09", + "quantity": 9 + }, + { + "asset_name": "030b0b0c0b10000007030b0c030106090b0705100d02070c06090d0e06070605", + "policy_id": "030f0206000e070900000d0e0309000e0807040e01000d050a0a0010", + "quantity": 7 + }, + { + "asset_name": "060306100a0a030e040b0e09050f0d080103000610010004000f010306080a05", + "policy_id": "060b0a040b1007000807000301040410050f0407050e0406060e0801", + "quantity": 3 + } + ] + }, + { + "address": "FHnt4NL7yPXmT3cKTuv56YvRi6rFXqbS2ujtGKQdwQvMa9a4XDBpnbwpXiBVGj8", + "amount": { + "quantity": 45000000000000000, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "060603080e0a020e000202010c03000b09090f050e06060d020e040d0c080105", + "policy_id": "010c030f0f060d0e0d10050a0809051003000f1006080e0103010f03", + "quantity": 7 + }, + { + "asset_name": "080a04080b05080b050f0d0510100307080b000c0f0b050906100e0c100c0b04", + "policy_id": "0f030208100b0901030901100c02000407000e060010040b04060209", + "quantity": 1 + }, + { + "asset_name": "020b020a03020a100d0b0b0709030c08060c0e0d0b000f05040e07010d0e0702", + "policy_id": "0104040a00070207080303030e01030d010809000e050804010f010a", + "quantity": 2 + }, + { + "asset_name": "0d030e100c020608030c0b080a070e000504010d0202000804020d0d07090304", + "policy_id": "080d010f03060b000a0b0f030c051006040d06010d060304040e0210", + "quantity": 2 + }, + { + "asset_name": "0c060e0005020910100403100b0604020f01080e04080706070d060f0706040d", + "policy_id": "10000a10000d020c0b01060b050909100110080a0305080c080b0a0b", + "quantity": 4 + }, + { + "asset_name": "0e0103100d0a01041002020c020a0a010d04090e0500010c0a06000c0a0e0305", + "policy_id": "0a0e00060601090104010e03060c06090c000003060c0503080f000d", + "quantity": 0 + }, + { + "asset_name": "0e0a0209070304090d0f0d05080a06100500090c030f10090c0e0301040d0b03", + "policy_id": "100a0e1002030a030602011004020a020f05100a0204000002010009", + "quantity": 3 + }, + { + "asset_name": "0e0d0e020f0e0d04080700000d080d04090803080b0b010708000b0b090f010b", + "policy_id": "0205040e08010a0f10100c040e0305080e0f0b08090e080a0210020d", + "quantity": 5 + }, + { + "asset_name": "0f09000a100b000e0409040d100b070508010d090e060903010a100e0610020a", + "policy_id": "080904000b0e0c050e010701010e070e0d0b050b050d080105000101", + "quantity": 1 + }, + { + "asset_name": "1010010909100c0c03000104000d0a060f0c09050e1009060304020402070d00", + "policy_id": "0f0a0e0405060a0009040806050e0c0d0209100b020d0f0d09070b06", + "quantity": 0 + }, + { + "asset_name": "0b0c0e0d02070c0b050b0b03070b09000900030b090f0303020d0702040e0702", + "policy_id": "01060c04050c080e0b0104040e0a0e100007010c090a070a0108100b", + "quantity": 5 + }, + { + "asset_name": "050d0010080e080c0b0a0c0d030a050603090c01040008070c0907000604010d", + "policy_id": "07100d0704100200070f0d0e0e010405080000060b00070210000705", + "quantity": 6 + }, + { + "asset_name": "00100803080e010a04010202070404020d08100b071007080201000d10070a04", + "policy_id": "0d050c090a0d0210060d070c0008000e09020a040b01030b00000406", + "quantity": 4 + }, + { + "asset_name": "1001040c0b051001000501010509040c100109000b0b0f080b01040302090b10", + "policy_id": "000d010c030706060703020f0b06070e0f07040b0a0803050c050c0b", + "quantity": 1 + }, + { + "asset_name": "0a03010f0901030e00070910020f0a010b0d0d0f020a05090b000c0300070808", + "policy_id": "100f0e0e080c030010040a03080a08080e030b0b0605080a08030908", + "quantity": 3 + }, + { + "asset_name": "0c0d0a070f0e0d03050a0600080b0d0f00060004090c0b030008000b02050408", + "policy_id": "09100a04000d0a00010109030f0c10080f010a06000e02100e050104", + "quantity": 4 + }, + { + "asset_name": "0c030d10090708000e0310070a0b090000060a0d0e08060205020c0a0d040f07", + "policy_id": "020a0209000b0f0300000110080c040f0b04020801000d0107070006", + "quantity": 4 + }, + { + "asset_name": "0d05000b0b040b070f03100404000909100c0401040c0f0c070f0c100c0b010a", + "policy_id": "0204100004040a020408090e0d05040a100210020607080b0d07070e", + "quantity": 6 + }, + { + "asset_name": "0c06100d09000f10020b05090b040a0206010c0f100b040910020f0c05050502", + "policy_id": "090404050b090805020f0c0802070205010410030e06050106030c03", + "quantity": 3 + }, + { + "asset_name": "02080207090407100a0e081003050503050f060d100205100f0f040a0a0c0109", + "policy_id": "0c0c0905040a030f0f0606051004070c050a03020e080007050a050a", + "quantity": 6 + }, + { + "asset_name": "030908010d050a080f040d00010907040c040e040d0407090409040e08080f0b", + "policy_id": "0004050e0f00020706060f040c050d020509050a030e00080d0f0f04", + "quantity": 1 + }, + { + "asset_name": "0b0d080d0b0e0b100c060c000a080008020d0210030f0805030a0708050e0b00", + "policy_id": "0e100404010d02020905100b0c09080501070d10070e0e030b100b09", + "quantity": 8 + }, + { + "asset_name": "08000e0f040c03040507050b0f0b0d09020b04070c0b08050b10080e0d03090b", + "policy_id": "0e0007080c081001000807080f02090e040c0c0701030f0a060f0f09", + "quantity": 9 + }, + { + "asset_name": "080e00050d0d01030706000b03010e100206090c0706020e0f0c0704010c0101", + "policy_id": "0b050d03080a0902031008070c06000a090c090f0800050c10040d0b", + "quantity": 4 + } + ] + }, + { + "address": "addr_test1zp9q302d38p3jmplfp7xlz5gmwfe7ffw97pe8rx86fkyr4hecxltehdlqlaav5cw5sg347clvhgp586azqggxjx3sq9sp0r3gp", + "amount": { + "quantity": 30480912478705772, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "00040c05030c0e060707020803070e0e0b03070006040e050c000b050e0a0001", + "policy_id": "020c0709060f0f02010006070909081005080e0c0d06030404070010", + "quantity": 6 + }, + { + "asset_name": "0f0f070b050d0e000307060301090f0a0d05060300000b090e030a080001050e", + "policy_id": "02060c0402100e07050e09070d0b030202030b0307020e060d070203", + "quantity": 5 + }, + { + "asset_name": "010201060305010c00080d040c0710070f02050705070c0204100f0403030d07", + "policy_id": "0d0b08050a030e0a01090a01010010040907040c0704070e050e0c00", + "quantity": 2 + }, + { + "asset_name": "0805070e0a020c040d0a02090d060107090a10060d0f0d020f060a0c03040804", + "policy_id": "0c1004060810040705080a090203040c070f070e020d0802010e0505", + "quantity": 0 + }, + { + "asset_name": "0b020c08001009080e0e020109080d100b080b06020d05070b0608050e080b0a", + "policy_id": "03090e090f0809060907090d0704050c01100c0a0307090c0e050503", + "quantity": 2 + } + ] + }, + { + "address": "addr_test1vpwr7j0zhlfvjj6f8znnnysqxzhpe4gah0vhcmcx42ncvpcfqdy0q", + "amount": { + "quantity": 42198789689743394, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0d080b03090a0b0a09040f0d080d07030910020d050e070109100f100e070a01", + "policy_id": "0207010b0c0404020f05010b0a10090c09020b0b040f010a030f070f", + "quantity": 0 + }, + { + "asset_name": "06060c020002090e060a0c10030f02000e010e0007030b0007040709060b0e02", + "policy_id": "0b0d060e0000100109070a08030200010700030710090f030d020210", + "quantity": 7 + }, + { + "asset_name": "070d0b050303030907030f0703030f0602060a0b060901010601080003080005", + "policy_id": "020b05030d0c0009000a0a050507000a0e0308070d0e0c060b00020f", + "quantity": 1 + }, + { + "asset_name": "0a0d08080b00040b0907000a0103050f0b070f0000040309080c02061000030a", + "policy_id": "000301010c0a070e0a02090d07010e060f030b0505070f0f0906100e", + "quantity": 6 + }, + { + "asset_name": "0e0d06010201100b08010a100c030e090710020703010b050e0806070c05010e", + "policy_id": "09030807040409080b0f05011005010c0b0f09060905070608020d0a", + "quantity": 3 + }, + { + "asset_name": "02100d07010305030509100300020c050610091007100b0b09040f060a02010b", + "policy_id": "030201080d090a0a00070e01030d010c0e0102040a090d000d081000", + "quantity": 4 + }, + { + "asset_name": "0104000a02090b0203030a10040a0b060308010a030103050e030a070c000102", + "policy_id": "1009030b0c0a050b000a0b05090d07030e0f04030b09090103030e01", + "quantity": 5 + }, + { + "asset_name": "0a0d040a0e0201020c000e010c0c1006060d0f060210080504030a0205090c00", + "policy_id": "10040f02040f090e09000a0d1008080e010d0e0c0e05010f0805080b", + "quantity": 7 + }, + { + "asset_name": "0a00040d0c01081001060e0404090c02090c0610000805030e0a050e0b0e0702", + "policy_id": "0e0a0c080a0a10050c070402030602070e00050e0805030d0302070b", + "quantity": 4 + }, + { + "asset_name": "0a0b060c0e0d0408040f100c010b0d080608000f100f020f10021002040f0f02", + "policy_id": "0207060d0c0b070207080b000107060b060c000804000b040b0d0b0b", + "quantity": 5 + }, + { + "asset_name": "08080e060b040b050f0a050d0f000e0a02050c020102000405060e0e02000c00", + "policy_id": "0008050508070d04090810100703010e09010f0f100307100203020b", + "quantity": 2 + }, + { + "asset_name": "0107000e0e0b070100040104070b060b0e100803010c020a090c0e1008100500", + "policy_id": "0f060609090f0e0802020d0f050f04070a050005060b070804000d07", + "quantity": 8 + }, + { + "asset_name": "0d0e000807080f0e0a0b01010f00040b06050b0d02050d0d0304090901090f0b", + "policy_id": "0c090500080d0f080a0a020d0b0307100f0e0f0e01060e0c0c06020e", + "quantity": 5 + }, + { + "asset_name": "03100601100e0b0d0b000b0610060400080b0c0b0d080a000f0a080703040700", + "policy_id": "100c100e070309100a0c070f06070e030e0d07070104030905030a00", + "quantity": 4 + }, + { + "asset_name": "0a080f060300100f08100e020b0008040a0a0a0005100a10030e0f0c020a050f", + "policy_id": "0009010e04040b010a10100710080e090b030c020a060f0404040a05", + "quantity": 4 + }, + { + "asset_name": "09060f08070e090302060a061007090d080a0c0a060f0e08030406070f090b00", + "policy_id": "03000801030d02090107050905080c020b0c0201060208030c010c04", + "quantity": 5 + }, + { + "asset_name": "070f07040b100510090f0d0c00000d0b040b07070d050d100208090201100c0b", + "policy_id": "010903090f0f0b020c0a0c0303080a030f100804100f01050203020e", + "quantity": 3 + }, + { + "asset_name": "0e0a0c09060d0909080a0b0407100702080f090101040503080510090b0e0b00", + "policy_id": "00030e0a0e1002030408000e060b01040e06040f0900031008060c0c", + "quantity": 4 + } + ] + }, + { + "address": "addr_test1zprh03s43npcn9qktwkvrunk6xcs8ex2ypux0944t3ep6j0smlwye3es7wervfl5ujma3h7h0ger7uc7kx0dtt640svswcayvt", + "amount": { + "quantity": 8818234786748532, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0302021001030d0a0703080d060d040f070207010f0204030f070c0904070603", + "policy_id": "05070d0e0b070e070d090e09070d0310080d0900020f0e0e0a00100c", + "quantity": 6 + }, + { + "asset_name": "09010c0e02080c070104000e0104050f040d010e100010080f040a0b03040b01", + "policy_id": "050f10070009090a10070601060e0a09100009010f10090103030400", + "quantity": 2 + }, + { + "asset_name": "0f0302050007040110000c0705090f020a04010f08010406050d07000b0d0a0a", + "policy_id": "0b0002100104000d0a000408020f0d10030f090a050408100f000805", + "quantity": 4 + }, + { + "asset_name": "030303100906070105030a0a0e10020c070e10040b0c090005090b0a07050104", + "policy_id": "0d09010a090c01040f100b0d0d060c0a0d0c010800070e0000050207", + "quantity": 0 + }, + { + "asset_name": "0e0c0e0f0f081003090b020e0b0d020e0d0b02000006050c02030707060c040f", + "policy_id": "090b0d02050d0b020109050a070300050a0d0b00070e080109060108", + "quantity": 5 + }, + { + "asset_name": "0b01050203070c0e01070b0b0b0d0e0a0d0b040c0002070b000f03100e07030c", + "policy_id": "0b00000a0304010604070d040d01010206090f05040d0905050d0105", + "quantity": 7 + }, + { + "asset_name": "0c0e10010e080007000c03050f100c090b0d07100f0a0f000e070c0f0d0a070d", + "policy_id": "070804010d01050d040c01100c07030d0a03030f080c02090c0b090e", + "quantity": 3 + }, + { + "asset_name": "08050e0403020c000b0400090b0110010606000a010a100c10060102040e0809", + "policy_id": "05090202090b0b0b000f050b0d0704000405060c0c10000b0909000d", + "quantity": 3 + }, + { + "asset_name": "0e030f040b03060d0d0701090e0c0a100801050f0504060008020e000a06040f", + "policy_id": "1005030c0f00090f04050c090f00050f04030a020a03010c0f05040d", + "quantity": 2 + }, + { + "asset_name": "0c0d0210090b080f040c0602070b100a0d060c0b020b0d060d050a08090f070a", + "policy_id": "070e0a0a0c050d0f030905000c0b070610010a050c090f0c09010d06", + "quantity": 3 + }, + { + "asset_name": "0a10080a0c0c06020a090f0703070510030d060410080706090a0b0d05000903", + "policy_id": "02020f0a000607000f1006020f0f010505030f000004040b100f0e04", + "quantity": 8 + }, + { + "asset_name": "04050e040d010f0a08000d040b0e0b0d100407060f010d020209030c0f080801", + "policy_id": "07060a0b060704020f04040e0b08030103030e020708030704010705", + "quantity": 0 + }, + { + "asset_name": "050d0f05050809040e07030c030e0505050a06040f070d070e0c0f06040a0303", + "policy_id": "080701060509020e000703090a0d08020607000a0107000303020602", + "quantity": 7 + }, + { + "asset_name": "0d0200040d07010a090d0e0b09001008000f0e0d0801080d0a0e0e060f060a0f", + "policy_id": "0d050e0d0d060b0209010d03020b09020c0105070c0b040c04060409", + "quantity": 8 + } + ] + }, + { + "address": "addr_test1vpy43yhajld6v7d4ur3qvulrjana8nlmlptuhhtzu5sq97glaxvlt", + "amount": { + "quantity": 4594945896840628, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "1006090c0b010301020d0c0e0a0f100309000f0708000f0d040305050c0d0306", + "policy_id": "0e03040e0108050a0d0f080e060006100d010307070a08060505100f", + "quantity": 7 + }, + { + "asset_name": "0610100b0a0f0a030c10020e0a0606100808000f0c0f0b0f0b0f01031009090c", + "policy_id": "040b0b0f020506021002050d0c090a10000e040d10040f0d010c0c03", + "quantity": 5 + }, + { + "asset_name": "0806020c0903000c05070009050a0e0c060403100a0a06090f000c02090f070d", + "policy_id": "040f0c10091005010b0f10010a00000b02070d020d0a051006060805", + "quantity": 7 + }, + { + "asset_name": "010f0501050b0c100106030401010e0010100a080d0105020800040904050503", + "policy_id": "0d0d0d0e0c04020f0804100400070e0e08050f100f070b0b0607090e", + "quantity": 1 + }, + { + "asset_name": "090d040e0d020e0c0b0d070802070e0408090a0e0c0a03040d0c0b0d0808030e", + "policy_id": "0b010e0b090d0e090610000b050d080401030c0f100f0c0105030102", + "quantity": 6 + } + ] + }, + { + "address": "addr_test1zzupzrfw3vn90hv2ch3aqfkwj4ydhtts9v5l5d2qa8nzautc98p4c3m258585f3y8m3mvuy7cxhyx70ulg646umv0kaq07af75", + "amount": { + "quantity": 45000000000000000, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0309020809030f0c06020e03010c00060c1004000101000c060500100604080d", + "policy_id": "0c0c0e090e011001020d04090c080b0b000a0c040e000700060b020e", + "quantity": 6 + }, + { + "asset_name": "0c07000c0709000a050d010e0f01030407030b0f0b050900031009100d08090d", + "policy_id": "0c06060607100b0b080c0c0808090602080406020e0801050b0f030a", + "quantity": 4 + }, + { + "asset_name": "020f090b0f0f05090f0100060b0302020c0e040e0b090b010c0305010c09080f", + "policy_id": "040c0b0d0f0b0e0a08060e010210020f08090f0f09010705000a0000", + "quantity": 2 + }, + { + "asset_name": "070f040d070206010c0e020707040c04010d060a020c10020a0d05060804060d", + "policy_id": "05010102050e090206040506090f0e0c0e08050b02070a010d0e0803", + "quantity": 7 + }, + { + "asset_name": "1006020c06030105090a0d0e0403040b0d0b0307010c0f0c0b0a100e0a0e0f05", + "policy_id": "07090c1000070000020409050b060e010a0504030f0d000605000908", + "quantity": 5 + }, + { + "asset_name": "0c0d050b03050a020907030e0e0d0302020d0309080200060f030b0f01060e06", + "policy_id": "030f040b031002051006070e100f0708030508100b0308020a090b0f", + "quantity": 4 + }, + { + "asset_name": "10080806030407000a090a0e000f0e070303040d0c0d100c10080d02100a0706", + "policy_id": "090a0b0d0d0506100c01040a02030d0f0b0c0c0a08000b000d070d06", + "quantity": 4 + }, + { + "asset_name": "040a100805020401100d06080a0c10100f030505020d040f0e0d040f0b0d070e", + "policy_id": "0d0c040b03050f01000f0e00020a07040c0003000d01100401080703", + "quantity": 8 + }, + { + "asset_name": "0c0e080f0f0600070b100c0d06010907051003050c060f00010a060c0b0e0d0e", + "policy_id": "0903030406040101050f0d091007040f0f00060f10100405070b0e0f", + "quantity": 9 + }, + { + "asset_name": "0110090006060a0b0603020f00040a0f070d0d0d0703030e0b0f010c0600050e", + "policy_id": "0a060900000f0302100f0f0f02020b0e0704060102040e010e0e060a", + "quantity": 6 + }, + { + "asset_name": "0a00040a0709090d0603080c0d030f060104000a0e060b1007080c0a0e060102", + "policy_id": "040304060c1004040710010a0c070d0707060e00090f0f0d05010c0e", + "quantity": 1 + }, + { + "asset_name": "010c0f0406050c0d01080b0e100c100c0a0e0709030304040204080510070a07", + "policy_id": "040107060b070c010605070002040b100c0c090c050005070d0a0d0a", + "quantity": 8 + }, + { + "asset_name": "0c0b00080c0405100a03030c0b0b0c030a050c09080202080b0f0f0208000b02", + "policy_id": "0f0e00020b01080c07100c07090e0c10010000010a0c03090e060e06", + "quantity": 6 + }, + { + "asset_name": "0e0809050c000701090f090b0c0408090b0a0c0c0b080b050510070504070e0f", + "policy_id": "050e0709060601010c0e0e0f0f040b0d0103000f0c010a0d05060a0e", + "quantity": 2 + }, + { + "asset_name": "080903090103080a10070c0007070a00030a0305050907090c0d040c06010402", + "policy_id": "10060d0a0b050a06020b0205090b0e09030e06010e010e0d00020d07", + "quantity": 2 + }, + { + "asset_name": "0810070008100d030c0301040309100a04020a0c071007000a06010910040404", + "policy_id": "0c070f050710040f09030a0f0c020308050806050407080f030c0710", + "quantity": 8 + }, + { + "asset_name": "030f02050b0d0e08080509040f031000000810030d04080305010a0f0105010a", + "policy_id": "0610020808070d030d040c08040f0b070501010a00020d040e09030a", + "quantity": 6 + }, + { + "asset_name": "03030b08050508060700060d020500070b030000080602010307000d010f0a02", + "policy_id": "01070008090f02000f050905050d0c0308080f09060f0609100c0403", + "quantity": 2 + }, + { + "asset_name": "070c10060106010004080506050b0801030d0b09050e0a10090404070c020e07", + "policy_id": "0c0807010205090a010f02030b0c03080c080406080b000703010500", + "quantity": 0 + } + ] + }, + { + "address": "addr_test1xquqguvgml2tnltrm9alkp0c9ffzfe6hsj79wnghadqfj7duxcvvnhf0dpp03tezkdur3rvhpp9al98wwctjlaqddrsq339knh", + "amount": { + "quantity": 34034660601133105, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "080b0b0f0a100f08100f100b0b0601071004030907100a0b0b01030e0309060e", + "policy_id": "020c0c0c09030f040c010a070a060005080d010f04030c0a0b0e0903", + "quantity": 2 + }, + { + "asset_name": "010b0101050c0505010301070f060310000b10100200100d09050c0e0306020b", + "policy_id": "0e0a0d0608030d070305040d06050108030d100b100e0f000601020a", + "quantity": 7 + }, + { + "asset_name": "0a03100d0b090d050d0e0405040d0c0203010308080c050710010509100c050b", + "policy_id": "0a0b02030d02010e070d0d0602101006050710030f0707030106000c", + "quantity": 3 + }, + { + "asset_name": "0c00070009010e0a00060b06060f100f0c07010806040a0b040d080e01050a04", + "policy_id": "030906030010090a0a040204080b0f040a01060f0b0e0c060c0f0c00", + "quantity": 2 + }, + { + "asset_name": "0b1003030e030f0102000a060f0a0c0b00000e010f0c100b05100e000b050309", + "policy_id": "07010e090f0810030c100f0c0e05060c070103030b000b0e04020b0c", + "quantity": 0 + }, + { + "asset_name": "02100f0804100306010403010b100504080b02000005060104100e000c020a04", + "policy_id": "0f02050a0f0a0609040a0904070701040d0e07020b0f0a0400080100", + "quantity": 9 + }, + { + "asset_name": "0e000e06080c0b0c0d0c0e07090c060407051009030e030108000e09040f0900", + "policy_id": "0a040e09060904100810090a02090b0103020c0f0010050f030e0507", + "quantity": 8 + }, + { + "asset_name": "0c0b05010f0b100d0c010c100502020b0b0a0a1003060a010507030306050510", + "policy_id": "05060f030f000e04020a050d0b0807080d10070c000d060905030810", + "quantity": 6 + }, + { + "asset_name": "0000020d060c0b0209050c0a07020702020903000a0d10100b0a0004080e0e10", + "policy_id": "0507020210100310061000090a0d0907090d0607080c0c000f050002", + "quantity": 1 + }, + { + "asset_name": "02050a000e09100c100d09080209050b0208060a0f0206100103040908090f00", + "policy_id": "0b060f0b071001070a0305020903060304020f0b1010020a07090c05", + "quantity": 9 + }, + { + "asset_name": "040a010f030205010a030f0a1000060307070c020c02090107020c0808000c07", + "policy_id": "0705010b0303100f090a050e090b0601060b0704030103020e040a0a", + "quantity": 9 + }, + { + "asset_name": "0e010f0a0f060b050a0f0909000f0701050d0100020c0e020209080e0f080401", + "policy_id": "07000f08000d0a0706040a030f0b0d070909080100070a0906080705", + "quantity": 4 + }, + { + "asset_name": "0e020503070c0c070c0c0208020409070f0d00090e000a0502010802020a090f", + "policy_id": "06050700020603010d0e080b010a00100d0c0c05080709100e0e020b", + "quantity": 0 + }, + { + "asset_name": "080f0f0c06060b03040d0f0b0d080c0d100b020501100e0e06070a0004040306", + "policy_id": "10100103050d0c0d0f0a0a09020f02010008060b0a100509100e1003", + "quantity": 7 + }, + { + "asset_name": "02080b10090d080b0d0f05020c0805070c010f0a06030f09010d07030c0d020c", + "policy_id": "0808060a0e0a0c0a0f050d01100610100406010910040306000e0b08", + "quantity": 7 + }, + { + "asset_name": "00090b03040f1006040c0e0f0c0f060a060b0a060b0b0105040910010c010903", + "policy_id": "07040407080c040c00090d020c0e080407090a0300000a06050e0b00", + "quantity": 7 + }, + { + "asset_name": "0908000c02090b0f030e0b0609060f060a0d0b0f100303090f020f080d0d0407", + "policy_id": "0407020810060810060d0f00080a080e100b05060b050e0109050d07", + "quantity": 1 + }, + { + "asset_name": "000c071002060c05070a1004020e020e0a0a0f10001010020c0306090b020504", + "policy_id": "0e0f0004030d02050d0a030b0e0e030c09070a0c0107010c000e0b0f", + "quantity": 7 + }, + { + "asset_name": "060c100b050d040d04000f0900030d060a0b010e0c020d0602050d010a040d0c", + "policy_id": "000c05050d08030c040b0e0c000110010b09070e060c040f05060602", + "quantity": 1 + }, + { + "asset_name": "100c040d0f0502090c030606031007080504040c0d0d0f0b0f101002060a0c04", + "policy_id": "080a0403100405080f0f030e070b1004100d0d04050c0805010e020e", + "quantity": 2 + }, + { + "asset_name": "0b0800070c03000809100b100805010b060e0e0910050902030f0c0f02030300", + "policy_id": "0a100d0707060a0b01100d030c0a0f03020e07090a05050c08040c0f", + "quantity": 5 + } + ] + }, + { + "address": "FHnt4NL7yPXrMfHonfnjnjbqBKPfFHDNBz1Hbx9YP139U23wnoHf22Azkpdfdhf", + "amount": { + "quantity": 44082785817567111, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "000a100e000b07030c0d0200090d020d060a03060b070f0f10020b0403060206", + "policy_id": "050c0508040c08091005020b0e0f080307080c080308080e0f0e0004", + "quantity": 7 + }, + { + "asset_name": "05070a010a050a0d0207020803060609040a030706080f0710010a000103100a", + "policy_id": "090c050c040e0410060c0c0c060b0c0c0204060e0304100106030b02", + "quantity": 0 + }, + { + "asset_name": "08020f0b0f040805080a05100310070a080f08030e0d04030c0b080608050200", + "policy_id": "010402020a080f0a0f07100b04040e000f0e100a0e0a0b010d0b0309", + "quantity": 0 + }, + { + "asset_name": "0500060b0d050209090f0e0c05050b0103030508070201090a08000609100302", + "policy_id": "0f0e030704060c0c04050c0a08020f050c020203010d040a0f0a080d", + "quantity": 7 + }, + { + "asset_name": "0c0e0c06030d0f03071010060b000607100902080309030b0a020b09100a010c", + "policy_id": "0910080b090906080e100801070010010203090408000b040a0e0306", + "quantity": 6 + }, + { + "asset_name": "080d0e050a0705070d0e0d080f060200040f010f0b0900010d0104040e0d0007", + "policy_id": "0c060b0f0d10080e0a0c0c0809010505020d01040e0a070001020f05", + "quantity": 2 + }, + { + "asset_name": "070406100d0c0d0510030e06030c0f010f0a0400020b050a010c030d0f0a0a0f", + "policy_id": "00041009000f040b100a040d0b020306010c090c0f090d08030e080c", + "quantity": 0 + }, + { + "asset_name": "010703010a0410080c060d02080d040d080708031008020a04080a010100060b", + "policy_id": "04080f0e0e0408030b0f0f0a100e0810040d040107050f0f100e010e", + "quantity": 3 + }, + { + "asset_name": "1002090b070810090d0c0b070b060f090a050b100a070c0b090e0e100b02100f", + "policy_id": "01090f030b0700100a100106050808020b090802080e0e0a0b000e0e", + "quantity": 5 + }, + { + "asset_name": "040604010c01070f0f0f0a03080a100909040f0e0a03020002020d040d0b010c", + "policy_id": "0e090e010d100e0a09090610090c0b00020705070e051007040b000e", + "quantity": 4 + }, + { + "asset_name": "0a0c100d050b000e030e09090502040104030d080f0f0a080a07040c0a04100b", + "policy_id": "0e05010903000a0b0e0c09070f060d0e0a0602010d03030c0110090e", + "quantity": 6 + }, + { + "asset_name": "0107090d00100505090e0a0a0105000e0f000c0a060a0600040403050d061003", + "policy_id": "0e020e0b0c01060d100e08020d0a0e00000c08090f0c031010100d06", + "quantity": 1 + }, + { + "asset_name": "080e040100010c0c01100d08061003020e010d0c010c0a0c0d090b080a100801", + "policy_id": "0605090f0e080a060c04020c07060402090a0306090b050406010a0b", + "quantity": 7 + }, + { + "asset_name": "09050301050c08060b01060107070201070d0a09060506031004020308070d0e", + "policy_id": "0f000710040e0e080210080c03071009080503000e0300010c040f0d", + "quantity": 1 + } + ] + }, + { + "address": "FHnt4NL7yPXx1Yw9wVsW564QqKLi7aTzLZGWY6gffWnPDT7E2xtKDurW4ciEfi5", + "amount": { + "quantity": 27338027687109485, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0c00090100080401080c0800010508020e0a0a01000f05050909000008080d02", + "policy_id": "0f090f04040c070a0a0b070c0405080b0c0d0c0a0d0b100b0e0a0d10", + "quantity": 3 + }, + { + "asset_name": "0302090409010e000d090a100d090a0f0904070803090e090504000f00080807", + "policy_id": "010d070400010d0205040210030d0207080e08020110100b05010403", + "quantity": 3 + }, + { + "asset_name": "0a01100100070a0a04090c00000a06030f0e0b0b0a0800090602040307050502", + "policy_id": "0c0d020f0301000c0a0c0b070e0f040d100608060901080207090008", + "quantity": 4 + }, + { + "asset_name": "0a0c0c020110070d020010080b090a06020f0d04000a060a0b0702050e070c0d", + "policy_id": "02020103060e00060f040409070b00080d030c0e0b0600040e0f0608", + "quantity": 2 + }, + { + "asset_name": "0902080d000c0f020500030b05020e060e0a0b05050e0b070604040407100f0d", + "policy_id": "10040a10020e100e08060f0e100308040a10000d050b000a090c0f0e", + "quantity": 2 + }, + { + "asset_name": "09030409000b01010c0300010c090f050c0c020b060b00080102030e0f0c0d00", + "policy_id": "0e0a090e09050708070a081008010d0d100a000d03090e0b01010b0d", + "quantity": 0 + }, + { + "asset_name": "0f030107101009030e0f060b0009000c00030807030505020502100d09050c06", + "policy_id": "0d020b0b030809060f01060c0e0407030b10070d0f010c07040f0c09", + "quantity": 8 + }, + { + "asset_name": "0a1000041010100a02030a10060c0809100202100e0806060906100604080910", + "policy_id": "0703010a0e03050c0e0402090b0b0d070807050d0909070d0d0d0e0d", + "quantity": 2 + } + ] + } + ], + "vote": "abstain" + }, + { + "delegations": [ + { + "join": { + "pool": "pool1qvn5z5ty2p23jarlggwrjdezt5ervefrwp2yu83ewugsye55af9", + "stake_key_index": "11" + } + }, + { + "quit": { + "stake_key_index": "6807" + } + }, + { + "quit": { + "stake_key_index": "5749" + } + }, + { + "quit": { + "stake_key_index": "8393" + } + }, + { + "join": { + "pool": "pool1tdmjgwttfftjq6jrxss8y6p6y5j4cycrtyxy5kzhgenr2z93utk", + "stake_key_index": "45" + } + }, + { + "quit": { + "stake_key_index": "15056" + } + }, + { + "quit": { + "stake_key_index": "8192" + } + }, + { + "quit": { + "stake_key_index": "5629" + } + }, + { + "quit": { + "stake_key_index": "10415" + } + }, + { + "join": { + "pool": "pool1fda9wspwwy8kzccdfam8vmnyp9yr7zmxp4qz2lrlqfuxz0yxzar", + "stake_key_index": "45" + } + } + ], + "encoding": "base64", + "metadata": { + "10": 0 + }, + "payments": [ + { + "address": "FHnt4NL7yPY5Eprx7LrMPHewpweCHMZsbdPVLMWUqLJXPa2SLWdAgoSJpbwKF84", + "amount": { + "quantity": 2313435982998217, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0a04070a0710060e00030d0d0b00020508030209050e1002090b07090a0c0e10", + "policy_id": "0c0506080d0f0f040b0708010605010d01100904050c0c060c0c0d05", + "quantity": 2 + }, + { + "asset_name": "0a02060a020806040e0a0f0007010610100a01060a0c0d0a001005020f0c0a0c", + "policy_id": "0806030b0001090b07060a050e031007100100020306010e0503040b", + "quantity": 3 + }, + { + "asset_name": "090e030508080607010503040a090b0310050c0f0f030a0a070805060b060a03", + "policy_id": "060905080d071010011004050c0a0c0f0a0d0d0601040906070e0e04", + "quantity": 8 + }, + { + "asset_name": "040e0a0b0a0810070a0c0c0e000c080d0f02030b090500030d1003040902000a", + "policy_id": "02090c080d0f0001070103030d020b10080604040e0a060c07050108", + "quantity": 5 + }, + { + "asset_name": "0406060f0508030507100d03060f040710060b050b070200080308100607030a", + "policy_id": "100d080e0a0103040d0a0d10010e0e01010f06060d080c0708100402", + "quantity": 4 + }, + { + "asset_name": "10030107030d0501010b0d04030f01020e0e0a0501050b0d0f09010f010b070d", + "policy_id": "0d0100000e0210100e0a100f0408010c030c0005070b09080e09020b", + "quantity": 0 + }, + { + "asset_name": "0103050e0a02020c0a0a0e0e0b030d0204050d0a0f0e090a0c050609000e0b03", + "policy_id": "0c000f05100a0800090a0c08050e0c05000a0e0c0b090a0003060c0e", + "quantity": 7 + }, + { + "asset_name": "060e01100905020f090f0d04010908030f020e0d1004030f080c0a02040a0f00", + "policy_id": "050003080d00100508000505070f0c08010d03090008010e0b0f0a00", + "quantity": 9 + }, + { + "asset_name": "030f0c010f0d0802050302010b070306010009050f0d080e0d090f08050b0506", + "policy_id": "020c00090407020e0d09061010020b030b100e070c04050506080f06", + "quantity": 3 + }, + { + "asset_name": "0b0702050b0a0000090c000b090c0d0c0a0d0d090a100e030203030806060207", + "policy_id": "07060a02020a0d090301030a000a0010060c0c050e10080d080a0208", + "quantity": 3 + } + ] + }, + { + "address": "FHnt4NL7yPXuujgiypGTcWWEgvXabmEo5Dj3tixvbZUbzdJuzA3NwB3fQ23bWzj", + "amount": { + "quantity": 30728669889930196, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "020d00020a02030f06100e1008100706010c05020d0d0100060808010a090604", + "policy_id": "0e0e080e0c03100e0f07030f0e0301080f0e0502020f0f0507020906", + "quantity": 2 + }, + { + "asset_name": "00070f0f100b070b060106090a0301040708060c0a0900020f0d01080504000c", + "policy_id": "020d0d090a050d0d0502050c1004070c04010a0b0e080a0c08060905", + "quantity": 8 + }, + { + "asset_name": "0206100b0a06100b0b080d060b010c10050005030e0804100f050a0406060e07", + "policy_id": "061001000c070c0c05060905000a080d080a0f040d0a0f020210060d", + "quantity": 5 + }, + { + "asset_name": "09040c060b0b05040908030f0808060b0b0a0c0e0a0206080b0e10040a000d10", + "policy_id": "03000807070804090707060d04000400000505080e03020c0c060404", + "quantity": 4 + }, + { + "asset_name": "081003020109070e090c05010e020e0a030407010f0a080f0e060801010b0f01", + "policy_id": "040e050403090c0b0a0e050204010b04070d0b0000010600090d0906", + "quantity": 9 + }, + { + "asset_name": "050808100e0e1007090200030f07040e06020a040902030f0b0509060d100409", + "policy_id": "060e0a100503070b01030300100801020a061007090f060b10020308", + "quantity": 6 + }, + { + "asset_name": "060c0d0805100d030b100c060a0310080d09050c0607040402060302010e0d10", + "policy_id": "0d0f04070b040906000c0d0107030110060d0c0a0a0f0c0105070910", + "quantity": 4 + }, + { + "asset_name": "0b0e070f060d04040107060c0c060104010c03000b0a1009090c0f070002030f", + "policy_id": "0210100d10060f0a020a020608030f0c070002050001100b0e0a1005", + "quantity": 9 + }, + { + "asset_name": "0e0b0209020802100710090506080d050108090c0b0302030e090a000e08030d", + "policy_id": "090c0010030407100b0802020f020b040e060c02070d0409020e0710", + "quantity": 3 + }, + { + "asset_name": "010b000b0e0d0b0708010d070f03040a0f01080a0108070b0310020c050c0000", + "policy_id": "0506030001030d0f0e0e0c090e0100061007000a04060d050d0f0501", + "quantity": 6 + }, + { + "asset_name": "090a02070d030e0f0e07090d010b09040503070e00010505040c0c0f0d060a05", + "policy_id": "0d06030a0507050f010c100b0b0903050d06090b0602020a03050905", + "quantity": 0 + }, + { + "asset_name": "0c01010c0f010c0b000b0b0f0e090d000f0d0e02010a07060505000700051009", + "policy_id": "04100105020509030a10010a05020a0b0609000f090c060408010c0e", + "quantity": 7 + }, + { + "asset_name": "060f0407000801090d060c0305070709010c0b0a0d0806100d040406100b0301", + "policy_id": "03100f0204100b0b0103030a0c0e0009000e08070f000f0c0b030f01", + "quantity": 0 + }, + { + "asset_name": "0a030e020304070d0c0d060f0b010d070010070403020f08020f0a080e090309", + "policy_id": "06090505070f091007100e0f0908060a050f0506080b00100b0f000b", + "quantity": 4 + }, + { + "asset_name": "050c080f000d0e0b000009030f0f060703080910080f020e0600000d0b000e03", + "policy_id": "0a0e050909060900050c0d0500010101060d020a0b101009010d0b06", + "quantity": 5 + }, + { + "asset_name": "04070e070909081008010e0b000806060d040e0800010e071004030e02090c0a", + "policy_id": "0b06090c0601010b0f0a02050405020a0e0d0902090a09080c080b10", + "quantity": 9 + }, + { + "asset_name": "060e070306050a020b011000010006090306100b010d04080d0f080c0c0b0b09", + "policy_id": "030e0308040e08040e0e0c0a0f0e060e10050b050507060d080f050b", + "quantity": 6 + }, + { + "asset_name": "050a060f080c060c0b0b080808010f0b0e0c10060100040f06000c020409070f", + "policy_id": "030b0503080f010a0e070602090e0c070b0e0d080f1003020400100c", + "quantity": 5 + }, + { + "asset_name": "0c060b0e010e03030002030b0f100c06030a0b0906020f060a090f0c03050c00", + "policy_id": "0b0d0f0b04080c10080f0c080b100a01010b02070600090b0e090a06", + "quantity": 1 + }, + { + "asset_name": "050004050d0208000e1006100302040f0f0009080010050a010a02000d0d0609", + "policy_id": "000507050300040e00000c0d090d0e040208040b000905000e01040e", + "quantity": 6 + }, + { + "asset_name": "07080e0a0a040b0c0a000208050a050d06030a0503040007060710010f020405", + "policy_id": "0e0e0b0b0c01020707090c0307080708000a0d07040c0c030a030504", + "quantity": 8 + } + ] + }, + { + "address": "addr_test1wpfdc02rkmfyvh5kzzwwwk4kr2l9a8qa3g7feehl3ga022qez7f2d", + "amount": { + "quantity": 45000000000000000, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0d080406000e0e010407010f0e0800020909030d0709060d0904070805060e0a", + "policy_id": "0e0b090d0d0204020e100d0208080a030004030c0c0a0a020206060f", + "quantity": 3 + }, + { + "asset_name": "010d0f0e0903010e0e10010f070103050a0b010e020c0f0c100c0a040c040507", + "policy_id": "030d080808010d010e0201060309070e0206000b07031002060b030c", + "quantity": 8 + }, + { + "asset_name": "10090d0c040a090b060d050b0b0e100404000701050a0809030508070d00020a", + "policy_id": "0c0f090a000c030c040904010402080608060b0f0b030b0d0d0f0a02", + "quantity": 4 + }, + { + "asset_name": "03100c0705080102041006060705090104050a0d000001000e04090202020e0c", + "policy_id": "101001030003100500100a040f09050c070f0b070f05040e01040203", + "quantity": 2 + }, + { + "asset_name": "000f0c07010004030404060c0f0606060a010201100d0f07060803060e0e0d06", + "policy_id": "0601000a080b0e0c0e0b0c040d0303040a0e060c050f0903040c0e0d", + "quantity": 4 + }, + { + "asset_name": "060b0b100600040f020e030d030a05080f0b0a0f0d0b090204050e0a030a0c10", + "policy_id": "1002080208070a00040a0c05080e0d050a05060b050b0f0b060d0a00", + "quantity": 3 + }, + { + "asset_name": "020d0502080c000a0e06080009060c0e040d02100301070500050f100808040a", + "policy_id": "05050602021010100e0509020c0a020f09100910020d0b07020e070d", + "quantity": 2 + }, + { + "asset_name": "0205050e050204020a070d09030c000407070a08100a0a0c080d040b0507090c", + "policy_id": "0a0b020100010403020c07090a0f080b0d0a0b000503100f100b0b04", + "quantity": 1 + }, + { + "asset_name": "09090606040d04060a040c10070c09080d0f0d010a0509020b050b0c0d020c0f", + "policy_id": "00080c080b0d0a1004050c0000030d0f0c0d0d05040610030a080c0c", + "quantity": 1 + }, + { + "asset_name": "07010b02060110050a030310060d0803030c0705070807060c0610100e09020f", + "policy_id": "10050c0d0706080f08060905020f0f090d0a0d000205020b0c090105", + "quantity": 5 + }, + { + "asset_name": "0100070a0f0c020c10020310090a08000c0e0907020e040d10040c0f10070308", + "policy_id": "07100f0a02020e0d0e00000f0b02090e030d01040e04000e08080608", + "quantity": 8 + }, + { + "asset_name": "070e0f05060b0d0b010101050c030d010d091010060b0b0a080006030e0a0901", + "policy_id": "0e020a0c0000100f0a000c0f100f0a030e06080e010a01090b03100f", + "quantity": 5 + }, + { + "asset_name": "0b01030c0c0c080d10040704080c0d0700100810070f0e0b0d00070c0300050b", + "policy_id": "0405080e0b010403010f10020802080d100d00010205030606090a10", + "quantity": 3 + }, + { + "asset_name": "0e01010b010d0e0c00041010040a02060e09030b0a0010070a040d0503020510", + "policy_id": "020d0f0c07050d0c030a0710090308050c0b010e0f020c02080b0102", + "quantity": 9 + }, + { + "asset_name": "0d0403040f0b060c0c030401060b0302060a04010f02040f0d04030903090e10", + "policy_id": "010f000d0c0e0602020a1006060b060709010906040a090b07010504", + "quantity": 5 + }, + { + "asset_name": "0a0d0b08020c050f0005000a08020c0407020c030f0006030c05000403100c02", + "policy_id": "0e10090a090b0110000403090a03100f080d0701020e100b030c0f0b", + "quantity": 3 + }, + { + "asset_name": "020d100909060e050d0104080702010e07080b0e0e0200000e020b0a0904080f", + "policy_id": "0b010801020b0d0a0f0e0004010c0f04030b06100d0209050b040500", + "quantity": 0 + }, + { + "asset_name": "000c0e0e000e000d0f080a0f0c020f0c090a0102070a0d080804040d0a0b060b", + "policy_id": "07090e000f08010d0d020906090c04090c0c070709100301060b0c07", + "quantity": 6 + }, + { + "asset_name": "0803060b080f00081005070b060c0505090e05050c080a0d0e0e050d01000702", + "policy_id": "0b0d010a030602100c010004080c09090300030c0e06060b020c010d", + "quantity": 3 + }, + { + "asset_name": "0f1008060b0b10010800050e030d090a100e040a0a06010208100d030b000d08", + "policy_id": "0e00100e051007040b050e0c0b0f05100d030e0b0901040c01100a07", + "quantity": 7 + }, + { + "asset_name": "0c0f040d0c0e00000d020c0810040408080400060508081002000602050b0d05", + "policy_id": "0d0a04090d0600081001060b010c0810090d0d0310030c080e020503", + "quantity": 2 + }, + { + "asset_name": "0b0401010b0a0a09070c0004000e030c030e020a0704010e0902070c08091005", + "policy_id": "0808070f0a04010a040d000d0a070103020206060908060f01030c07", + "quantity": 4 + }, + { + "asset_name": "00000e0d0e020b0f001005060003030606000107100902060907000e0e080f0c", + "policy_id": "02010d1010040f0010030d0e040b00040b0e040a0a060809030c0a04", + "quantity": 9 + }, + { + "asset_name": "08030c0d100b0004000a0f050b050c02090b0f0f07040201020d080d0d07060c", + "policy_id": "02090b0408050b0a020203060c08020a10040500080b01070a080400", + "quantity": 6 + } + ] + }, + { + "address": "addr_test1zzclwt5ztwlxul3hcsgv6rr56f2ml8nwn204wv0pgsduswffjkfux7yjq8rtder0kg4l60quwwugr3gsht4fx8wnthfq3pmuxu", + "amount": { + "quantity": 9360457705721757, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0c0101020d0d040b050b0b080c00090a0e0003040e0c060007040e0909100703", + "policy_id": "0307030a071005020505000a050803000c0d07000d0e08030c0c100f", + "quantity": 2 + }, + { + "asset_name": "010606030110100e100f00080807040e040b01080907070f0c09100b0d080c0b", + "policy_id": "0009070809000b0b100607090a0104090a0d07090e090e0104070505", + "quantity": 9 + }, + { + "asset_name": "06040d060f020b010f09010500070b10090c030e0f090003071002040e0e0806", + "policy_id": "0b070f040710100104000c020e090f080810080f03090f1010090806", + "quantity": 4 + }, + { + "asset_name": "0f0d090a00090e0f020a0f0b02090a0a010d0406090d060f06060f0c02060d0b", + "policy_id": "0200051004030a030c0204090c000a070b0a01070d000005030d1005", + "quantity": 4 + }, + { + "asset_name": "070a0e030101020c09060907010007030400100d061008040c01010a020f0510", + "policy_id": "060c100d060f0204061000100104070f0000090e0c0d070e03080b0b", + "quantity": 3 + }, + { + "asset_name": "0806040a0c0f010f0801020604090b070f0000100104030d100706100302040b", + "policy_id": "010c090609030c060c1000010c0a03030506040b060c030f0d051004", + "quantity": 4 + }, + { + "asset_name": "000204060b0004010c0809040a0e0e0a06000702070f0100010801010f020100", + "policy_id": "080009090b080a06080e0107030f0c0410100a0a01060f04000e080b", + "quantity": 1 + }, + { + "asset_name": "02080b06030e01050102070d0f070c070701010709080502100d090301080902", + "policy_id": "08080d0f0b020510040c0d0d0101060f021008020400090207060f0d", + "quantity": 8 + }, + { + "asset_name": "06010c0210050309070f0910100903010f020900090d100c0c08050a0f030e02", + "policy_id": "0409000f0d0100031004060a01080109090100040d040b020b020f0e", + "quantity": 7 + }, + { + "asset_name": "0703080f100b0404010a040e000c01060f0b0a010a02060d020602090d0c010e", + "policy_id": "06030f0202080106091007040803080310030c0e0e0b040a0f000e00", + "quantity": 4 + }, + { + "asset_name": "100f030f0e0e090610010b090b0a0b0904000d00090b070e0607040803020400", + "policy_id": "02040f0c010b0303060a0e0d0e0b030e060f100b02010c040502030b", + "quantity": 0 + }, + { + "asset_name": "080d10090e100109030a000d010804020f0c070f100509080f0f06090c000605", + "policy_id": "0405070b0c0a0d0e0c0e02000e080a0b10010d01070c0e0b09020203", + "quantity": 0 + }, + { + "asset_name": "0f100306000e0e0a090310070e080e0f0b090808030e0002050f0b0b0f04010f", + "policy_id": "0d0f070410050f0f0a0210020e0604080c020b10050304030908000e", + "quantity": 0 + }, + { + "asset_name": "030b0707040c0d070f080c0d0e0506050f0f05060a0c0e02020a0d060b100209", + "policy_id": "01020a0406000410070308080f0d010a0201010e100002020c09000e", + "quantity": 4 + }, + { + "asset_name": "0910070d09000300040f0d0704060a0201020f0210050b0b0f05030e0d0e0907", + "policy_id": "080c010c020209060d0a040f0909000a0c0902000c01000600090c0c", + "quantity": 7 + }, + { + "asset_name": "0410100904010407010a0110060802060a0802000708090502050504100d0c09", + "policy_id": "020f0210090c0b060408040802030d0d040d01011005090d0c090110", + "quantity": 9 + }, + { + "asset_name": "01010e040a0802090c0b080f100a000610050a080808040e1010000e0d060d0d", + "policy_id": "05030407030a0705050c02000f03040d02080a00080f090c060b0b02", + "quantity": 3 + }, + { + "asset_name": "07080e0b020a010f05060b100f00100c0f0910030c0c0a040d060f0608030b09", + "policy_id": "0a0b0906091004100d05030c0e070d0f0c070a03100c070304060a04", + "quantity": 7 + }, + { + "asset_name": "02070e01090c090a090b040103030d0e030804000305100407080310100b010d", + "policy_id": "100e0a0c0a0608050f0005040c060c01060008010c08080e0c010b04", + "quantity": 7 + }, + { + "asset_name": "030600100c0d06000e000b07020010050f0d100602010c0e0d050f030c010801", + "policy_id": "07070a0101020b010a01080407040c0701080a08040809090700060d", + "quantity": 7 + }, + { + "asset_name": "0503040c040b040702000709060c0e08050b100f000e0e000a0001040a070808", + "policy_id": "050d080803100600010606050600100906090b0307070e0d010c0a0b", + "quantity": 9 + }, + { + "asset_name": "0d0e0e0303020a01040c0307020b020402010e04070d0d0c0e100e010b0e0c03", + "policy_id": "09010e03010807031003050d010f03010504000a08010f0a02080400", + "quantity": 4 + }, + { + "asset_name": "0708100c01060c040d07070a0902060e0f010f0409010e06000a0b00030d0f04", + "policy_id": "10100f090a010e000b0f0f02010c0305050e000e04040108100a000b", + "quantity": 6 + }, + { + "asset_name": "03100c020406000b10040201030a00080209030f0d100d0710010c08060d0d0b", + "policy_id": "0d03000b070909090a090a030310050d0c0e06050e0a08050a00100d", + "quantity": 8 + }, + { + "asset_name": "090f0a0b06050d0f0d05060904040f0c0f0d0d06000e0307060609080606100e", + "policy_id": "05040c090e080c000d0a0f050a000a080e040e0f0e10010a090d0310", + "quantity": 1 + } + ] + }, + { + "address": "FHnt4NL7yPY4T8Cok5N7izNpb4ny4FKWt2Yk354ZkEBdTPA8d2p6RbmQ6ZHHXAm", + "amount": { + "quantity": 38763853014497689, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0610010e000d030a070c10050f0206020b0b031007021004060208090002040a", + "policy_id": "0b0501040a050a02040c02080a0c0004060b0b0b040a0d0d00070a08", + "quantity": 0 + }, + { + "asset_name": "0c0e03040d0c1007020803090a00030f0503040a0c0404030407050d09070a05", + "policy_id": "0d050d080d0e0903040b03051006010b0a090a0e051003100c040f05", + "quantity": 9 + }, + { + "asset_name": "1006020509040b0c10000f0601090b01070f05050d0108080500000e0a090800", + "policy_id": "01000a0808080d090710030705090b0608010a0b0e00080a020a0a10", + "quantity": 6 + }, + { + "asset_name": "04090b080d0c0f070906040f07040902000b0a000a0f0f0a0c030d0f0d00010c", + "policy_id": "080f0d070f06050a080e03050c08010b0901050702070e0e0e100b10", + "quantity": 7 + }, + { + "asset_name": "0f10080509010a060708000c090a00040e0a0008070d0c0a0e06000408050008", + "policy_id": "05020d0606070109040b080506010d03090c0f0d0b0d070c0110030f", + "quantity": 4 + }, + { + "asset_name": "0b0e0e04020809050710000501070f0f0b02060a0c0a090c060e0a09050a0a0d", + "policy_id": "0a0f0e0007080c0c050c03090c010e0d0d100503030f050a0d0e0d05", + "quantity": 9 + }, + { + "asset_name": "06080d0f101003070b060404060c1005090d0b0d000f010a000d0d0c0c0f0003", + "policy_id": "030c0b0a090e0d010e0a0e05050c06000406090402000c0a020a0809", + "quantity": 3 + }, + { + "asset_name": "030c090b0b0f060d0306030c060e030b0a0e0605090405000403010a0e000f03", + "policy_id": "0f10030d020f0e0d07050c0a070d020d020a090f080706040d070f0e", + "quantity": 4 + }, + { + "asset_name": "0c000f070f000a100c0409080208100e0e0d040c08070b0d0d0f0e090110020f", + "policy_id": "0c1007060e0a0d0309090b050d01030601070d00070b0103080a0e01", + "quantity": 1 + }, + { + "asset_name": "08000a0f1004060e020600000f02000e0604020d0706020c03100e100d0a010a", + "policy_id": "070705010b010e0d02060d0c0b0c0908050f0e0d050c0f080b060606", + "quantity": 0 + }, + { + "asset_name": "0a060f10080206090007040f0f0a0e0008030d050e090c020e01020d070a090e", + "policy_id": "0800060a0a0b0e0f05040d07100408000701030e010c0505080c0b07", + "quantity": 3 + }, + { + "asset_name": "0906090c0a0a000007050c01060c0f10080b0101040e020f0f03010c0b001010", + "policy_id": "0a100c0d0b0e00020b0d000c0f0e03010e0810050f0807030807060e", + "quantity": 8 + }, + { + "asset_name": "030d000f050c0c0e0b0e0d060d060e06080200090e040f000a070c0503040f09", + "policy_id": "0e091007090f0b0f0d0b0103080300060706040f0e0a0604100a0004", + "quantity": 9 + }, + { + "asset_name": "01030b100b0a0f0f03100a060406080707020c050c0c0b0b0f091002000f0d10", + "policy_id": "030e0a000b09010a0f01010c0800020d0f0104080a0b090104080e06", + "quantity": 5 + } + ] + }, + { + "address": "addr_test1wqrrs5see573llela35fa60jy8pqmtsqpel88lyp5taqchgj6tl2x", + "amount": { + "quantity": 0, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "040c040b0f0c000e050f010c0d0d0900070c060d000c0e090403090b02020202", + "policy_id": "0104090e020a060f060f00090a0900070f091000070e05060c090508", + "quantity": 6 + }, + { + "asset_name": "0e100f0105100e030e060c07050b0102050908090b0e02030d0f0d01070f0d0a", + "policy_id": "0f0b100e020b0409090c0b0607090d0a0601020a0f030b0d0d0d0706", + "quantity": 2 + }, + { + "asset_name": "030c0d0f0106000502060c0e03010e070309040d100c05020101100008100701", + "policy_id": "0a07060b0e060409040d0d020b0c09070d080e0f0d0206030f04100b", + "quantity": 1 + }, + { + "asset_name": "0c010e0f060e0006030400030f0b020e0410030408100904020a0e07090d0406", + "policy_id": "0e051002060e030e000702100609020d040b0e0a070a010305090a0c", + "quantity": 1 + }, + { + "asset_name": "09030d05040c020f0e021010050c0610090e0e060c0a00000d0b060a0e0e0e0b", + "policy_id": "100d020f0a0e0a0e070c0705041000080d0e000506060a0200010f06", + "quantity": 2 + }, + { + "asset_name": "0a040001090b0b0f000b0e0f080405090601080604070605060e0b0d0e06040f", + "policy_id": "0107050f090e0310050e050110010f100e060c1002050a0d08070e07", + "quantity": 3 + }, + { + "asset_name": "1003080f030c09070e0802020b060c100702040f0f0c000e0d0b0f080f0e0f0f", + "policy_id": "010c050308010a010b0003090a0a0b020e100a040e00010c0e080104", + "quantity": 9 + }, + { + "asset_name": "01010f0a100c0d0201010e0b060a0c010204030c0800060f0a0310000e050608", + "policy_id": "03000803070100040f0e0e0f01000b0a07050a0d0509020010030a04", + "quantity": 3 + }, + { + "asset_name": "0308100c03040e02081000060a020b0609030700050a100b06050203070d0a02", + "policy_id": "0e08060d0100090a0001070f0c0b0a10020f0b020500040607050602", + "quantity": 3 + }, + { + "asset_name": "0e000d07000d05020c0a091003080d060d05010d0e0409070b10090d08050b02", + "policy_id": "1004020c030b040a0f0909060304050a0c0908060309050c060c0902", + "quantity": 6 + }, + { + "asset_name": "0f0b050510000e0f0e100100030d100a071005000c08030b0f0205010b0e0d04", + "policy_id": "090d080e06050009050c070a0a0601000e06060a0c03090c10000d03", + "quantity": 9 + }, + { + "asset_name": "0900020804030007080008100a010c0809010c050b000410070b0e0b0f0a0002", + "policy_id": "0908070801000c0c100805100a0d0a010e020c060e0b02000e040f0b", + "quantity": 5 + }, + { + "asset_name": "02070008000306070b00020a0f0e0b0a02080109050b0e080609040a020f0805", + "policy_id": "000004100b0a06060e1005080d02040d030a0d05080b070c0b000d01", + "quantity": 0 + }, + { + "asset_name": "10080309000a0604000a0c000703040500000a0c050b0f050303000c0a10010c", + "policy_id": "0f0b0f0410070502071009040e0606000d0708060405060306010c01", + "quantity": 0 + }, + { + "asset_name": "0e04000d04100c050a10020b050a0e0f0b100a0408070d000a03000700040a03", + "policy_id": "0e000e020c000501070b0f08020905020d000a040e020209070f080b", + "quantity": 3 + }, + { + "asset_name": "05080d0f0f0a0b020a09060801080902040c0b0100000309070b0800100d000a", + "policy_id": "100d0e070303010e000a040f03040807080b090b10050e040708060c", + "quantity": 1 + }, + { + "asset_name": "070d0e00010c0b100c00070b0f0d00070d0f08090e0d00030301000f0f080a0f", + "policy_id": "0c010d030d090d090c050e0a0e0a00040b000f0c0d090602040c0a10", + "quantity": 3 + }, + { + "asset_name": "070e0908090e0a0e0f0507050701010e090d00020a10090c030a090c01000200", + "policy_id": "040c0e05010f07060a0d0c0a03060d0c0006020c0201010d0f030d04", + "quantity": 2 + } + ] + }, + { + "address": "addr_test1vza9r4nncvtt2az3m8rrq6tn2383upma9hxdfwp2z7qgytsqa43sy", + "amount": { + "quantity": 36627356937673470, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0e020c04010d0506080009030e0207040a0b000202080a0d050704050d040b03", + "policy_id": "0b06100900070e0a0709040e0f02020b010709080106040500080809", + "quantity": 6 + }, + { + "asset_name": "0c0509040f10051010091002100d0f050d050400040a0d010906060f09020c00", + "policy_id": "1007020610080f040e0c04090d0e0a0d02050207000f07100f070300", + "quantity": 6 + }, + { + "asset_name": "100b0c030a0107050b08040e0e020f06070304090b01100f030e0e0607081006", + "policy_id": "08100d010d070b070e0500040701010e03090d0b0505010708100e0b", + "quantity": 2 + }, + { + "asset_name": "0709090f0a05100b050e0304030e0c02080b0508010e09030005020b070a0d03", + "policy_id": "0f0c0f0b0909060004020705000d0c010e06090b09020f0e01090100", + "quantity": 3 + }, + { + "asset_name": "0d000202000b0602070803060b090201080f0b0f0b0d060f000800040200060b", + "policy_id": "0d0603100600100d02021003000d0c06100500070a0d0208000e1009", + "quantity": 0 + }, + { + "asset_name": "1006010b02010e0e050c0f0d0603020f040f04060404071003100c0c02090e10", + "policy_id": "000e051009021000000c0e0d090f090c0807100b10060710100d0708", + "quantity": 5 + }, + { + "asset_name": "02090e10080705080e02010c08000d00010b0d0d050e0907020406050a020d0b", + "policy_id": "030b0d0d070d02030503050c0b0005100b05100d03090f07090d0d0c", + "quantity": 9 + }, + { + "asset_name": "050809090a030e09090c0c010c09050906000806100e01080c0f070c02080004", + "policy_id": "090d0c0c0d0c100d000d090e0006030402040701060c0503080c030f", + "quantity": 8 + }, + { + "asset_name": "0c030202070a100a100606100a07070b03070009040d00060e07100808020c01", + "policy_id": "070b0b030f080a0b020d050c080b010d0b070107080d080108070c0c", + "quantity": 5 + }, + { + "asset_name": "020b0200020a0d03030f0c0f0506060d080602020e0008090a090408020c0108", + "policy_id": "0a080f060b0710070a0b090306070c050e080910000a0f0708031006", + "quantity": 4 + }, + { + "asset_name": "0e050c021003040a060410030d09050302070901100d0e000109070507090603", + "policy_id": "07020c0b040409060902090d01070b0b0a040b08020c0e0c0a070510", + "quantity": 9 + }, + { + "asset_name": "0610100809100801030b000907090b08090d010e0005070a09070b0601031009", + "policy_id": "0f03090e1004030d05060404050e0e00050b0b0e0006071000070302", + "quantity": 6 + }, + { + "asset_name": "0d060b0c04060c0a100209060a0e04030d0302050403080e0e0805060f0f1008", + "policy_id": "0a0602080309040707100704060c0109070205080f03090504101003", + "quantity": 9 + } + ] + }, + { + "address": "addr_test1wzvyr040dpjmq7wnz324g3235tf54dm900fwptuy3h0zxasw4m74c", + "amount": { + "quantity": 30787370982605879, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0402080c0e090f000f090a08000e0e040d0d0a0f0b00040f06030b02030a0606", + "policy_id": "070510060a05100508010507070a0707040a0e080600080701090c04", + "quantity": 5 + }, + { + "asset_name": "100e0f0a020c0c09050b02100806020f1009010f07050c0e0f1003030903050a", + "policy_id": "04080c0707100010070708090c050e0601100e100405080406030101", + "quantity": 1 + }, + { + "asset_name": "06000d0c0a03080c0202020a100505090b0d0a040b0e0601080b10080109090a", + "policy_id": "0c01040c00070203010e0d0e0101040b01100d0c05050d01060f060b", + "quantity": 1 + }, + { + "asset_name": "000b0c0f0e0c010d0d1007030b10070208010409050901030b0a0b060c0c010b", + "policy_id": "0802100e0c010c090706030f01090e000310020b0d0e100a040e0f06", + "quantity": 6 + }, + { + "asset_name": "0901080c060802030d0c0f0d0f0e0010090e0c0204050d0e0106040f0a000a0a", + "policy_id": "0c0a0b0009030a0704010a040f030710010d020d0e03080409070d02", + "quantity": 6 + }, + { + "asset_name": "0f0f0f03090e0f0f080704090705000c090c070f020c010a050a050904040008", + "policy_id": "000905040c0a0e08050a030d0b0203060c050f060c0005060b0b040d", + "quantity": 8 + }, + { + "asset_name": "040c080d070301090a0b0d03020c0a0d05090304080a06020a000c0b0f01070f", + "policy_id": "040a0c0b0402030a000a0c06050a0f0e0100000602090006050e0c06", + "quantity": 4 + }, + { + "asset_name": "0b05090e00060f09060310100907080a0c0d0a06010b060505040a0d0300000a", + "policy_id": "0f0a06040e04040b01080507000a0d060610020f090606050e0b0804", + "quantity": 5 + }, + { + "asset_name": "010c040c0b0e050e10070203050e020d03080a070a0d050c030e0e060906060a", + "policy_id": "030c01090d03040b0d010307060406080600070f010e0c0d090e050a", + "quantity": 8 + }, + { + "asset_name": "0405060d0d0e070704060b07030808020110050a000f04030408000d0a070f08", + "policy_id": "0b080d02000404100c030b0207000907020d0c080d0d03040b050a09", + "quantity": 3 + }, + { + "asset_name": "0e01020d0f0204000107050400020c10010d0d010309030f050c040e08050810", + "policy_id": "080f0d03041001020e0a0c08020e10060a050803030a0f06000d030e", + "quantity": 5 + }, + { + "asset_name": "050d040b08070d0e010b040d0e0c10010e0b0f020e0d0c0301090307010d0b10", + "policy_id": "000e0604000a06080200070002060206040e070d020e050a0b040b0a", + "quantity": 9 + }, + { + "asset_name": "0d0702040e0f050805040b0d00030910100e0e0e03040e00060d050306090508", + "policy_id": "100c07050b050c0d00010d0e0f080a050a050c070d060e100d070a01", + "quantity": 1 + }, + { + "asset_name": "07000d080e02010e090c060805020b0806051001000e090f0507070207050102", + "policy_id": "090a0a020e090d000a020d0a0a03030d080a05100810070a05080e0a", + "quantity": 0 + }, + { + "asset_name": "1008050e0601050702040d05070a0f050b0e0808000b06030c0e0d0e05080300", + "policy_id": "0b0a02100a05100a02060e0510090e080204000a000b10030e0f0408", + "quantity": 2 + }, + { + "asset_name": "07010e04030b070d090709101007030809000d04050b020d030200000c0a100f", + "policy_id": "0803070008020608050404060304040b0006060401050406040f0b04", + "quantity": 6 + }, + { + "asset_name": "0f0e0f0a070801070510000605000f0205020e0007000d010e00070b03100e0a", + "policy_id": "0e0e041005020b040a10041007000d0d0f05100b02030d01070e0909", + "quantity": 7 + }, + { + "asset_name": "0e0d081000030803000a0d04080204010e1005020f0e0607070b100b10060b05", + "policy_id": "0c070e08070d0c030e000b02070b03000d0d0d0a050f020302050b06", + "quantity": 6 + }, + { + "asset_name": "0902030d0503080d0d0805070b060109010a0e060f0908040a02070e0401020f", + "policy_id": "100a070c08010c0600030d060108050e080210050b04030b000d0507", + "quantity": 6 + }, + { + "asset_name": "10070007050e03100a0e0f0005100007080d1006060202030e0201050c0c0d07", + "policy_id": "0206090104020c000c0a0e0e0601090a0e050a02010601050f0f0f10", + "quantity": 6 + }, + { + "asset_name": "0f0f03050e050e0a0a0e020810070a03080402010b000a04020b0b0d0908020c", + "policy_id": "04030c010a060402020d05011000010b0d000a0e0303050a07070a0b", + "quantity": 2 + }, + { + "asset_name": "030104080d02010a020a0c0c0d0f0e100b0d100104090305010f021009080c09", + "policy_id": "070303030f020e0905030f04030c03070001020f0b080f0810070804", + "quantity": 1 + }, + { + "asset_name": "0c03000b020d0b050708030f010108100305020f06050f08080e080e04050000", + "policy_id": "020c090d060e050100030504010f05070a0a00071006071000050a00", + "quantity": 8 + }, + { + "asset_name": "09050d0704090a070c0d02080b050c02070504000b0f02081008100d08070c0a", + "policy_id": "0d0c0b00010408030400050600090c05050a0a00070f0f0a0b020702", + "quantity": 6 + }, + { + "asset_name": "0b070706060006050403030a020703010c0e0605070d010a0706060d07080b0f", + "policy_id": "0307070f0003090b0305020401020b030e0d0700050b0f1002070208", + "quantity": 1 + } + ] + }, + { + "address": "addr_test1xpl8044k9zjnq8ezjnwswtvuv44car9csu5dggfgtxw5sktqrhjc2f45ejwrqxtcxcscnsfsd77fl47vww8avvre6ycsdryvu0", + "amount": { + "quantity": 0, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0e020e101007030b0d100d0b0707010e0b10020810060c06000407020d041003", + "policy_id": "010a0808090b0402030d0100030e07020907050903080f060f070c0f", + "quantity": 3 + }, + { + "asset_name": "060f0f080b0903090302070201000009011010010c0c0e04040505030a070308", + "policy_id": "06080a100b0b050c05100b0405070b000d1004080c100e0b1004030c", + "quantity": 2 + }, + { + "asset_name": "030f0c070a100f0d0d0c090100070c08090b0410040803080a0209040f0f0301", + "policy_id": "0d061006050c0f0804060d010e01060700000a0a0f03060e00100f00", + "quantity": 6 + }, + { + "asset_name": "06000508000110000310070e041003040b0a10060b050104000e010310101002", + "policy_id": "0b07070e0e10080f07080c03070c040807080108060710070f060207", + "quantity": 6 + }, + { + "asset_name": "0e03000a070b05050a0c07060804090b0e030c0805050f000b0e0409040a0f02", + "policy_id": "02020f01030f0e02090407040a0f0a0d0f0a080a100703020e000a07", + "quantity": 8 + }, + { + "asset_name": "100b0b0f0808010f01030806090a070b02010102060c0f0300100b04050d0d07", + "policy_id": "08030f09080a0c00060f0d070902000603040807060d0e0c0610020e", + "quantity": 8 + }, + { + "asset_name": "000006010f0d0c0d070e0b090a0b0b080c030c090508100a0c0f07100e070e08", + "policy_id": "0809090f1004090404000e04001005100005050d08030b00100d0d0f", + "quantity": 6 + } + ] + }, + { + "address": "addr_test1zrsnjyhk7tvzjuzpnpw7ud9zwz2svzf7f53qln2k4h4wngxjvykct89tqgvtwz3qnrev63rxwwtsft0t5jhg0s3humkqtjdwpd", + "amount": { + "quantity": 10023948132495022, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0d090b0c040f080e02050c0000080f030801060c0506040204010b0d0e0d0f0f", + "policy_id": "0a0a0a0400100103020e1003070c10060a020510060d0a0d060f0004", + "quantity": 0 + }, + { + "asset_name": "080c010e0f06090d040a010a0a0c0d0a03070b03010b070e0d060e0d060b0a00", + "policy_id": "0f060909090f0a0e0210010202100c090d020e0a09000f0d0b0b0b03", + "quantity": 6 + }, + { + "asset_name": "1004090d0c0e060e080e0607050d08050f090f05060e090b000e0f0e0f0d0004", + "policy_id": "05030c0f0f0203020d0b020607030c0204020f000b0006010d000f0d", + "quantity": 3 + }, + { + "asset_name": "0d080b0c080008030610020c0a04090809001002060c0a0e0e0702050b070f0d", + "policy_id": "0b040e020c06011001080a04080e01030e07100a020c100802030e0c", + "quantity": 7 + }, + { + "asset_name": "0a0f0f0c0d07030e080103060e10090700010b08090502080b02060d060c0809", + "policy_id": "070a0c0b0d0d0f050005010f0a0a04000f0b0a0f0600070703020707", + "quantity": 7 + } + ] + }, + { + "address": "addr_test1zpfdc02rkmfyvh5kzzwwwk4kr2l9a8qa3g7feehl3ga02292ukgaayf5eultc835c9hy75qg53ejgevtt58e6m87qu8q2dsqam", + "amount": { + "quantity": 24944048109851665, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "05060a0b0501050106090e0d000e000c090a0e04080b0900000f0006030a010a", + "policy_id": "040701000b020310010309080a070510040d0f0e0f07050f06030909", + "quantity": 6 + }, + { + "asset_name": "0b050401090b070004060f030205090f0c0106050b020b07040e0000080b0c0c", + "policy_id": "0e100200010d01090a050a040504010e01070700040c090d0e020a0f", + "quantity": 5 + }, + { + "asset_name": "0301030e0f090a070a080f0e0a1009090800050c0d04060e080c000b0e06030c", + "policy_id": "0b060b05000008060b0e080a0f0806000a100710080a0d01090d060c", + "quantity": 3 + }, + { + "asset_name": "05000e0a0d050b010210090505000605040c09000301040d08020f0300030301", + "policy_id": "100908091007050304100c070c000d0f0e0d060b0e100f0407100402", + "quantity": 5 + }, + { + "asset_name": "04030000050c0d010907020f0e03030602060110080710070303060801080005", + "policy_id": "0d060401060201090d01010b05030c06100b090f09100f060704010f", + "quantity": 8 + }, + { + "asset_name": "0a000504030a0d0f04000b0c02020e0006050e000b0e0400010408100e040f0a", + "policy_id": "07100004061000000a04100f0206100a020201030610070005030e03", + "quantity": 5 + } + ] + }, + { + "address": "FHnt4NL7yPXjbQsrmVEJFwf8C3fjGScYvETyKaXyoyr5mbHuM9xWzCrfQX41Are", + "amount": { + "quantity": 0, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0208030e020407100601050407000b050e1007050b0302060705010108060c0c", + "policy_id": "02020d050d0e030d090500020b04080c0d0908100a0d09010c030a07", + "quantity": 4 + }, + { + "asset_name": "0d0201100b0905070c1006030d0b0f00080b1004060900020c0f000a080d0302", + "policy_id": "100a05050608080d090200050507100a00100e06020f0e0f07100708", + "quantity": 1 + }, + { + "asset_name": "080e09000e02020e100e100d0e03040c0f0806100802100e0c0b070303040909", + "policy_id": "0704030d040a0306090a0f0001031007040e060b080b090d0308030a", + "quantity": 7 + }, + { + "asset_name": "000f0405080a090a0d0608080a0403050a000f0507070b0f080307090f01000a", + "policy_id": "030b0e0a0e0010030c0e0304050910070803060d0a060b0e0f0d0705", + "quantity": 7 + }, + { + "asset_name": "060705050a0a0804080a02040107010901050f020e0805100500080c0601000c", + "policy_id": "10100c0b09020205060f01000f0f0f0904071007050e000b070a0107", + "quantity": 7 + }, + { + "asset_name": "0a0b050c0e010405060c0a0b0e0d0e0809090b0b100e05080e07090003000a02", + "policy_id": "010107030f080c02050d0c0e0c0305070908010d02030605090f0e06", + "quantity": 5 + }, + { + "asset_name": "050f0807080f0a0d0b0607050c030c0307050d0306030700030e06060e0e0501", + "policy_id": "0e040b040f09040f0b060d0f02010710080b08050910080906070700", + "quantity": 1 + }, + { + "asset_name": "0b10060705080e0f0e030f0a0b06080602090c0a00070a050c0307010c071002", + "policy_id": "050e01080a0b000c080e0e0e0d0207090f04090e020d0901050d1007", + "quantity": 0 + }, + { + "asset_name": "0b020b01060d060c0d0e0f0d06100b100b0a0c0d000c0c040a0600040f0b0601", + "policy_id": "0b0f0905050c010d09010503100b0610080903060b0a04090e04080c", + "quantity": 8 + }, + { + "asset_name": "0d02050b00100d04040e060c0e050d0e09090605080402070c07060607030b02", + "policy_id": "0d0b0e06040c0d07090a0c050a0e05070a080f0c0f0d050707040a06", + "quantity": 4 + }, + { + "asset_name": "04060f0e0d050e0d0e030108080c0c020f08020b02020b03030a0f08000a1003", + "policy_id": "0f0b100c010806000e08040d0f060d060701050e0200040406050e02", + "quantity": 0 + }, + { + "asset_name": "0a0a0e100a0c0b0a0c0a000b01020906050c08090c080000100c0e0001000c0c", + "policy_id": "0b090d0f0d0f0f06061001060d05080002000b070f0303080c0c0804", + "quantity": 3 + }, + { + "asset_name": "080a040c070d0606030d10090d070f0d06010a030b0a0f10040c0c0e10040f01", + "policy_id": "05010e07070e0d0f03080f03090700090a0c100d000f031005010b0e", + "quantity": 2 + }, + { + "asset_name": "0b060a0509100d0c0e030a0a0104010d0a0a080c04050e08080a060710000e01", + "policy_id": "0b030b0d010c06020607100806000b0500080f0e0b0e02070207010b", + "quantity": 7 + }, + { + "asset_name": "0b0e0f0d0b08040200050a0b080d0f010910050a100d0d0f040b0b090a040b06", + "policy_id": "010f100b020704010902000c10070e10070604080c0c0108010a0d09", + "quantity": 4 + }, + { + "asset_name": "0a040c0c071003011010070309090f020100070a050803030e0103060a04100d", + "policy_id": "0904071002100907030e100800020b0c0101040e0b070a0d010a0001", + "quantity": 7 + }, + { + "asset_name": "090c0d0c0400080f04090801070f0f0901030009050b0406040e0d0b0f060c05", + "policy_id": "080309020d0502060c0b0604040a0d0b0c050a050b010b0001100705", + "quantity": 6 + }, + { + "asset_name": "0a060602070f03020b0d0702020c0b070b030002010c10070600000a0d080003", + "policy_id": "0b071009100204070b020d0f0b0105030a010f060701050c080b0b04", + "quantity": 4 + }, + { + "asset_name": "02040c0a0e030e090c0f020102000c010409010b080909060a0f030709020703", + "policy_id": "0e02000609020c0f07050d04090a060d0f0a020f0a0d100a03061002", + "quantity": 6 + }, + { + "asset_name": "060305060e03030507050d100e0905030d0b0f06001008080e0e0f0200090604", + "policy_id": "0b09030704050c0105040c070a00010f1008100c0800060c01000f09", + "quantity": 0 + }, + { + "asset_name": "00040203050b050104030e0f100f0a0301090008070406070a06010f10070e0b", + "policy_id": "0b0e000a0e060d0b0e02040b070e09020f0e0308020d08040f000706", + "quantity": 3 + }, + { + "asset_name": "02040c0f000905061006100a0909040903060300040f0c090600080702030005", + "policy_id": "0a0108040f081001090e0c030501050710090e0c100f0a0307100708", + "quantity": 2 + }, + { + "asset_name": "0d02040810090a0b070d04010f0208000a0f07090f0f09030000100d020b020e", + "policy_id": "0c0609050e0e0e070a070a0310010c000a01100c050e0e0401030b0b", + "quantity": 2 + }, + { + "asset_name": "06060b0d01080c03080307070e020a00090c0d0d080d0907080b0d0d030e0c00", + "policy_id": "0d070b0a03060808060603040906060610000f0306080b0e0c03000c", + "quantity": 8 + } + ] + }, + { + "address": "addr_test1xpg30wazy3p3wdd5shd82cthfr7z5wzjkqm6seja0rj0ghgvnmt8xz2dzlsku8m03a8rtz60a93yqfu635ym56w4zszs5ga3hf", + "amount": { + "quantity": 30922684509886852, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0b0b020b040b0b080005070a0907050e0e0b0c010d0c0003010610010f0d1009", + "policy_id": "07100f0a0b0d0c0b0e070110040c050d01100b0a0f03060908080510", + "quantity": 2 + }, + { + "asset_name": "060e020b08100a0807050907090e0f0f100104070f001002000b0b0003080505", + "policy_id": "050d05070c0d030f080f050d0e100e020d0808070b0c050e050e0510", + "quantity": 8 + }, + { + "asset_name": "010e0d03010e000702000710030e02040a04040b100e020a00090109030b0106", + "policy_id": "04020c0105040c040f080c0a0f0700050e0803040c070f0a07060209", + "quantity": 6 + }, + { + "asset_name": "0f02070b0c060710011005070c03050d0e07050f0b100e0c090502090e020b06", + "policy_id": "041004010a0d010208050b040e060c0f0206061001040708070d0303", + "quantity": 2 + }, + { + "asset_name": "0a0a04020d0d0f10060c0c0b0a0b050509090f00080b000e0f04010107010a0b", + "policy_id": "09030b00040e0e0301070f060c030c0609000f020101040106001005", + "quantity": 5 + }, + { + "asset_name": "070202080d030907030d100007040c06020d0c0a060b01040b0705000d010003", + "policy_id": "060a010b010d09020509080c0e020b0701040a02091001080c030804", + "quantity": 8 + }, + { + "asset_name": "0e060700030c09010b020c08090f07020a02010b02050d0b100e020d0910040e", + "policy_id": "0605010910100b010f0f0d020d06090d0b020a08000f0a0503070006", + "quantity": 6 + }, + { + "asset_name": "02040c0e00100a0c00070505050f0908020903090b090f050000101005010d04", + "policy_id": "080d090a050b0f0e000b050d0e03030a10030f0a0000070a0006050d", + "quantity": 3 + }, + { + "asset_name": "0d020802070407040b0a06090a07100a0003030b070405020402030803080c10", + "policy_id": "040e0f0e0d0c01000402010308040f070b08030e040e020a0b070803", + "quantity": 9 + }, + { + "asset_name": "0f0604100500050709090a001001100501030900100c0a06050701100a030900", + "policy_id": "030b0b0d0d090a090f03010708100e030b0607050d08040501000c0a", + "quantity": 6 + }, + { + "asset_name": "100a09050c01050900060c0b000a04050f060702050300050b0606080e010604", + "policy_id": "0d04010608040d0c08090c010b0d0006080309090b0f0f0c09101004", + "quantity": 6 + }, + { + "asset_name": "070f070507040d0e060d0103030e0d0d080e030b01060a060a0000060c0b060e", + "policy_id": "0f0a0c06100a050d0e0602100f0c0a060c07100f0e050103080a0705", + "quantity": 2 + }, + { + "asset_name": "040c00030c020b0e0d0a0306101005020e050907070a030d02100808040b0204", + "policy_id": "040e0a070e0005020a0a0305081007000e070f08070e060c07100200", + "quantity": 0 + }, + { + "asset_name": "0c030910030c07090d0507050a090d10050e060f0f070f08020a03050b05050f", + "policy_id": "000a100909060e0804070d0b010503040f0a04070c0f0c020f060706", + "quantity": 4 + }, + { + "asset_name": "0a0e0f020f10000e05050a00070e040d030f020a0c06080f010e070f0b0b1005", + "policy_id": "08030304030a0e0908080d0002090c0910070a0c0c0508050c001006", + "quantity": 7 + }, + { + "asset_name": "08090c0604090c0f100e0e090b0c0d0b0a07100801070b06100d080b01000008", + "policy_id": "020702040c030a0500020901080f060e050301020a1004050807020b", + "quantity": 5 + }, + { + "asset_name": "000a050b0d0e0d06090a0c050400080707080c0009060b0c0d100d0302040910", + "policy_id": "0f0e0d040403070009030f0b03090106000008090a000d09000d0008", + "quantity": 2 + }, + { + "asset_name": "030e0509020b03090c030c10090c0b0b0101100c0e0f08061010100d03080603", + "policy_id": "0a040501040904060b020807010c10070d080c1003090004050f0e0b", + "quantity": 9 + }, + { + "asset_name": "0407060b0d0c0b04020e07050304030f010b040905030d0c0e09000c020d030f", + "policy_id": "040f000a010804080e0c0b060202080906040910060a05050309010f", + "quantity": 3 + }, + { + "asset_name": "0f0a0b030d0207060c0302000c070a100d0e0d080c03000c0a050d03060e0908", + "policy_id": "030a0c000910080c0f100c10020409100c020d000203100805050d02", + "quantity": 7 + }, + { + "asset_name": "0d071007100700020402040805020d04050d0e010d0c050c030d0f0902030405", + "policy_id": "04000308040506000c020a02020a0c09010e0a0a060609010c060c07", + "quantity": 8 + }, + { + "asset_name": "090a050b0309020a0d0c0e0d0d080f060b0c040a0f09100f09030a000104000c", + "policy_id": "05090d0e000f06100b091002050705070a0c03100e0f020f07100709", + "quantity": 6 + }, + { + "asset_name": "0800050c02010703100f000307060f040b0d05080e0a0101080d0b1010050709", + "policy_id": "0f031008040802080a010d00030201020e030007020c0a00060d1009", + "quantity": 7 + } + ] + }, + { + "address": "addr_test1zrjj9remldudeagttptltxtx80lnz7hk45utf63vcr54c7azzfrjrgvgk3jzrc75vmyz0xuzgw2t2qwex30482y08z2q4h3kj9", + "amount": { + "quantity": 40662696431194303, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0a010e0004010a060109010805050d0c0c100905020403070f0406080f10020e", + "policy_id": "0e01000d0910010f07080a08060f0300090c04020c050a0b03071009", + "quantity": 2 + }, + { + "asset_name": "0e090e0a0c090c09020c100d06090b0500090109080c0d0d0b04090c04000f09", + "policy_id": "0e08000405071008070f01101010010907010c0a0c0b0e02080f0901", + "quantity": 4 + }, + { + "asset_name": "01040f03040405040e10010a0702010006050e0d0809040c0b0f0304040a0e0f", + "policy_id": "0b040f000f0700100f0608070808040408010a050f0a0603020a0d0a", + "quantity": 2 + }, + { + "asset_name": "080a030701080f0908100408070d0009100e01090d0e0c020d0f010b0b080f03", + "policy_id": "0c0a10030a010a0d0f0301000e0c020c0907080b0307000700060201", + "quantity": 3 + }, + { + "asset_name": "0c040c05031004020c060809080d07070e080005090e08100910000607060b07", + "policy_id": "0504090104040f09090b080a1003080f060c090d081002010d010610", + "quantity": 7 + }, + { + "asset_name": "0302030a00090e10000a0c10040d07060e0101040502020c0802100200100908", + "policy_id": "0105060008100406060a030401050a00000201040102000c0e0a010c", + "quantity": 3 + }, + { + "asset_name": "03090d10041002040c010d090909050d0e040f0e080f0907030f0707040f0102", + "policy_id": "0a080b00100e0d0d010e0e0c0106030f06060a0a0a0901060a0b0801", + "quantity": 4 + }, + { + "asset_name": "0303060a0f050910030c100a040d0d0f050110000c030e09060f07100e070009", + "policy_id": "080806100b0c0b0f0e0808030b030e090b10030403030d0a000d0f0e", + "quantity": 0 + }, + { + "asset_name": "020c0f070a050e05100e00080f0a010f03070f09050104000610060808020b06", + "policy_id": "0505020a030207010d0d040908050c0502080b010d02040901020010", + "quantity": 3 + }, + { + "asset_name": "0602000a0c0b03040300070b0d0404050b0f01090e0e060d09040c0800020304", + "policy_id": "02100e040b04090b070e05070e0f0b0a020b030b00080910090f0004", + "quantity": 5 + }, + { + "asset_name": "0304030d070f0e0c100b0b040d0f0d020e000200040d0d0a00020c0f04080f07", + "policy_id": "050a07000110070602010f0400100400090b0b020305090f0e0c050b", + "quantity": 5 + }, + { + "asset_name": "0f0a00010b0b030a100e09041009060a0c0009070a040d0b070f0e080a0d090e", + "policy_id": "10060003000f080b0e0d030c02010f020a0a030b0f06100c08030300", + "quantity": 3 + } + ] + }, + { + "address": "addr_test1zpd979qvmla0ma7l5t5xeadawv89sefw5mk2nq2dfs6mk399gek5zl234quxdrnz6zxg83pcapq0kayts08egyge29zsl0n4xu", + "amount": { + "quantity": 45000000000000000, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "060401010f02050f080f05090b080a01030a04070c0e02030e100500100c0306", + "policy_id": "0a0d040c09100c05010d0901050e0e0b040b000a0400000802020709", + "quantity": 2 + }, + { + "asset_name": "020203030f090d040d0d0e0709040b090a010608020b0d0910070f0e0d010004", + "policy_id": "0208040604000f010106040a07040a08010a060a03090007010f0100", + "quantity": 0 + }, + { + "asset_name": "090c0e0c0a000b0f090106010e0e090c040c05000a100708030403020b020b04", + "policy_id": "0a0f0a040303020c0c020108060f030b0f0d0602020808070a0f090e", + "quantity": 6 + }, + { + "asset_name": "0703070e0505030c0c0e0f000a0f0707000d070c0e0c04020006010b0f0d0300", + "policy_id": "0b0f0903080f050d01030f0a060110070b020b070d00010e020b100c", + "quantity": 5 + }, + { + "asset_name": "0b0200080104060b070c0d010b0d040c020b0a020e04070a0b090207090c0904", + "policy_id": "010b0b020b0b060b030c0c04000406010f0e0a040907100500000b05", + "quantity": 0 + }, + { + "asset_name": "100b100a040507060a01060e0c0c030200040b1000090110020b06050c0b000f", + "policy_id": "0d0b0e0a0f100a0d0f100d0108060d0b0707040e080710050d060110", + "quantity": 8 + }, + { + "asset_name": "0f0b0a0a0b0e02100d0710020b070c020b0e00100b010e1004050c060f0a0908", + "policy_id": "0c0a0a030f0b0d000905100d0f090e060b0f0103040107010a0c0200", + "quantity": 8 + }, + { + "asset_name": "030d080d09010e060e040805041001090f0c04010a0d09090510030906000307", + "policy_id": "030e020c010f04100e060a0c090003100e0b0a01010d0c0d10050605", + "quantity": 1 + }, + { + "asset_name": "0d050704040a08081000090a01010a040b0c060f020d0c10020a0b050a000f0a", + "policy_id": "0e060b100e02050e0e0002080d030100050c01020e080e0e0503070e", + "quantity": 7 + }, + { + "asset_name": "0906000904050d0003050a04080c050801050c0f0300040f04090400010c0604", + "policy_id": "0b0105020a100d04020e07020f07060405090109090202020200020e", + "quantity": 8 + }, + { + "asset_name": "060d0b0008070002090c050c0310020e02060c0e07030f020709000e090d080b", + "policy_id": "0004030e1008090103100c08080d09070710030501020b0d0d030e00", + "quantity": 3 + }, + { + "asset_name": "010a060a03060f0d08100a0c080a0f0a090e0701030c070402000f0902060a05", + "policy_id": "040a0b050403000c08060b080c0207010a000b08060501030907080e", + "quantity": 4 + }, + { + "asset_name": "0c0e0d0e0d0e1007050b031005080406070b07020b090701030a030405000e0c", + "policy_id": "0504020b0b030703050305030c05000f030304000a00010101090306", + "quantity": 7 + }, + { + "asset_name": "080f020e100606090a071000090d100708010e0906060b0e060d0d00070b010d", + "policy_id": "0d010f000d0b01060a060e000f050f070310030d0402030105020b0b", + "quantity": 5 + }, + { + "asset_name": "0e050d0b0e0d0f0c0507070f0b070f05090f0707040c061002100b050f040605", + "policy_id": "030100050e0000050a0c08020c000b100a0609060e0304020e080f08", + "quantity": 4 + }, + { + "asset_name": "0b040c04030a0c07010b0d0e03050b0a000700070d0102050809050f09080f0e", + "policy_id": "0e0902080c01050f0004010f090c060b09020d050508090310010206", + "quantity": 0 + } + ] + }, + { + "address": "addr_test1xp9ywf73qegmha68u2ky5n92v46wewcagyf0h2j7ralyqz2jms758dkjge0fvyyuuadtvx47t6wpmz3unnn0lz36755qp63xjq", + "amount": { + "quantity": 37284694870269194, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0a010d070e050b000905010f0a0a060d1000000d0e020c0e0a030f0210010701", + "policy_id": "061000070e000b0e0b0804070b0d080003070c0809080906020c080e", + "quantity": 5 + }, + { + "asset_name": "0d040b000a02090c0f0b060d00100709030407000f050a0f100f0d090110050a", + "policy_id": "0e0606040e100e0d0f040b0a020709080e1007100b09080e00080609", + "quantity": 4 + }, + { + "asset_name": "010c0e0a0603040d06090804040c08000d09080a040e0200001009070a090e10", + "policy_id": "10030d020d06100b080406030f0a0c0d0d0b050c0707080a040c0a00", + "quantity": 1 + }, + { + "asset_name": "0b100307020f07100b0b070e10090b0a0b1008100a0a05030f04020a05100410", + "policy_id": "050902010c020b0a00050f0d0e070f0c070c100100100a0409000200", + "quantity": 4 + }, + { + "asset_name": "0f050c08040510050b0f0e030d000106030907020e0d0001000f01080e020f02", + "policy_id": "070e05050f060b0205070e010f0909010e07070e0601070f0a000e08", + "quantity": 9 + }, + { + "asset_name": "090f0700060900030307050c000d0f021004050806000c01100c050c03030c07", + "policy_id": "0a0601050f040b09070f060a03050c0a0b010900070502090e000c0a", + "quantity": 9 + }, + { + "asset_name": "1003030a080909080b0f020f0f100b020b10000c0f0010090b000e0b09040008", + "policy_id": "010e0a0a0c0b01020f04060705060a070000020308060c0e09020a00", + "quantity": 1 + }, + { + "asset_name": "0c03040c060e0900070a0007070301060501030207000f0a0c0d0c000c0e0d10", + "policy_id": "09100e0209100e0b050810020f000e0a09010201070508040607090c", + "quantity": 4 + }, + { + "asset_name": "04000e09010f01060e0d0d0d0d000b0e0b00050610030f100b0f0b0d0e070a03", + "policy_id": "0f0c0d0008060f060b0f0700080306090e0b0b030c020f0c100e0408", + "quantity": 0 + }, + { + "asset_name": "02010d000d0c0004040309060901080e0a100b060b0c0d0a0601080d0e030d03", + "policy_id": "010b010c060b07090e0f070304070809090310000c0a090f0a0e0d0e", + "quantity": 2 + }, + { + "asset_name": "0000070210090607070b04100d1004050706000a0a04080c0d030709080a0105", + "policy_id": "0e050c060c010600060e00010a0c020d0d100b0f03030c0000100707", + "quantity": 1 + }, + { + "asset_name": "09000e0f03010405020a0f0f0f0b060b0d040c020a0605080305070d060a0809", + "policy_id": "0c040e06010401070b0f030e0b0a1003050b0a0f0107020201050d06", + "quantity": 8 + }, + { + "asset_name": "0801050b040d0f030c0404030a03070f080707010b0b10020f0404080d0a0109", + "policy_id": "070f060d02060c0e0d0e020f0a031001010a090d0f0800020e090304", + "quantity": 9 + } + ] + }, + { + "address": "addr_test1vz03fatwyekrgswqkkqhya798jzfnwxuh63h870gjv8enrgcgxd0w", + "amount": { + "quantity": 1834438543719867, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0e0c080700090b03040203050605010109070709040610080309100f09000e05", + "policy_id": "0808080e0c050d030c0a0705030a0f0f0e0a03020f0f0d0a0b0b000c", + "quantity": 2 + }, + { + "asset_name": "02050d0101050608100f00040d0e03050c02010c06000700060107000a0a0b09", + "policy_id": "01020f0d0e020e0e070e0f06080d080e020610060a10040608080110", + "quantity": 4 + }, + { + "asset_name": "06100d030c0c0b030e00010a0e09080109020609000f0708090e010c0203000d", + "policy_id": "0109000e04060e080c08030b00020302080d010500090f100f05040a", + "quantity": 0 + }, + { + "asset_name": "0b0a070c010006010b000f10050b010a05070f00080406070a050e0c0e030f10", + "policy_id": "0702051004070d0c01000c020c0006050204070c040904010b0e0e08", + "quantity": 3 + }, + { + "asset_name": "100007020f03060e01100802040401020f0c010d000f0e0a10060a050c0f0a0a", + "policy_id": "0500071005030c0f0002090b0f0b0e0f0c0a03000b0e0c020d050508", + "quantity": 6 + }, + { + "asset_name": "0910090a0c030107070a06020708040f0c0509050b0d0b0404060c030a03020b", + "policy_id": "0f030f10090f01070a0e080f0408080f04080c0c080b0606090c0d02", + "quantity": 7 + }, + { + "asset_name": "020207070206030a0a050b0c0501030d080400060d070d0f030f060d0904050d", + "policy_id": "0f0b0f08050903060305050a04030e0e060e02030b06000f0c0b0701", + "quantity": 5 + }, + { + "asset_name": "0904070e0608050a0e070a090e070608030a0b010c01030b0f060e010c031007", + "policy_id": "100a0b0c06030a080d0b0b0f0605010a07080c0c000c04000f040a10", + "quantity": 4 + }, + { + "asset_name": "030c080a08050402080e00020e0a0c090908100b04010b0608030e03010b0308", + "policy_id": "0a000a0b080c08030703090c0310030c020602090c0e03100c100e02", + "quantity": 6 + }, + { + "asset_name": "030a0c0f071004100a070a0b010e0a09090d090304010d0a0d090c000e060407", + "policy_id": "100d070c0f0405010b0c0f05080d08060805030d080600060f010605", + "quantity": 6 + }, + { + "asset_name": "0808080805040f0b0c090b0901070e0300000303060c0e08010909000e0e0a0f", + "policy_id": "0a0f000103050105030c1004100d0e01070e0c080d08080d01010f05", + "quantity": 9 + }, + { + "asset_name": "03080f0d0c0a050005030700010a0e050401010104060d0201080e0905040809", + "policy_id": "01020a080105030a1008040e04090a01020a08081010011005060601", + "quantity": 7 + }, + { + "asset_name": "0e050d02090d04090d030d1009100102050f0e02070a0e0a0f0c0b0d01061001", + "policy_id": "000f0c0902070f0e091006010409040f100b010b0c1003000d0c0e0c", + "quantity": 6 + }, + { + "asset_name": "010f10070c010c09000009030f0b0503050a02070b0c09000407000f04100e0d", + "policy_id": "0903080c0f08050e0904000e0d0e0a07060901030c0905070a0b030c", + "quantity": 4 + }, + { + "asset_name": "0c0909050502000d070a0207050d0d0e0505080903040c0f04050d0a0a0e0b0c", + "policy_id": "060f09050a10050b0b03040e0a0a0d0c060a030f0f0f0f0103030808", + "quantity": 4 + }, + { + "asset_name": "0909040c0910100e050c080000030e060c080801030a000e0e06030603080201", + "policy_id": "00070b0e10090c0a05100804020d0d0c0f030d0109050c040900020e", + "quantity": 8 + }, + { + "asset_name": "080d0d0301030b040903080c0005070b00000a09020806080a0b05010e100307", + "policy_id": "0f0f090d0b0b0f070607060f0b0c090d0f0b0b0e0608040209010a02", + "quantity": 3 + }, + { + "asset_name": "07070e0a0c080c0c040a0f0c0c010a050300030201020402060e00050d08010e", + "policy_id": "0510050d010b0e0803080504000f070a0c01050e0f0a060106010409", + "quantity": 6 + }, + { + "asset_name": "0c100d02060b0b0e10050b0206090f0b0403090a020e03050f100f0708071008", + "policy_id": "06050d0b0e030e0e0e000f0508070e0604010a0e0f090a0b08040f04", + "quantity": 9 + }, + { + "asset_name": "080e0205100a0d0205050600080909030d050d0307000107010d04090f080d05", + "policy_id": "100d0d0b100408090b0000020507090c090b0a030a0d03090909000b", + "quantity": 8 + }, + { + "asset_name": "000b0107100e000805060b0c050b0309090f07100303000b0a0901070e00040b", + "policy_id": "010e0b0f080c0103050f070501060907010e06030e0f0e0d03050910", + "quantity": 7 + }, + { + "asset_name": "08000c0d0e0e0d0e02080408020a060c010d050f0f070a0b0104010508050b0d", + "policy_id": "070d10010e0f0401050c02070300050408060d090b0604060d0d0b0a", + "quantity": 1 + }, + { + "asset_name": "03100206070c040507060209070b04020a090108090a0e09100c02090a0f030e", + "policy_id": "0a0b09060c10060b050204050c080c060c09050f0a0e08010b0f100c", + "quantity": 6 + } + ] + }, + { + "address": "addr_test1wr2yzgn42ws0r2t9lmnavzs0wf9ndrw3hhduyzrnplxwhncaya5f8", + "amount": { + "quantity": 33997445905226521, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0605020f0b020a05100c07080e05080905021005010800030c000110040c0f0b", + "policy_id": "0c06090a00080404000d090d0e010f08020610070e0a060703060f00", + "quantity": 5 + }, + { + "asset_name": "03020a090b040a02020901070b020a0b0b0a080f0a0a030e01030d0b10070f03", + "policy_id": "040e0c06030d040904000801090c0a00060202070808051006070f04", + "quantity": 7 + }, + { + "asset_name": "0103040104081009090403000e0308100308100d01050104090f090c0c100a03", + "policy_id": "0603000a07080b01030110020b030e010900020d02100d030f0b070c", + "quantity": 2 + }, + { + "asset_name": "040a0a0504010e060d06050705030e050c09090202060d01050a010a090c000f", + "policy_id": "050208040a050e080b090a050c0200030e080e0a010f08000009080e", + "quantity": 4 + }, + { + "asset_name": "0b0807070106070201010f0605030f040c09040e04060d0e08090e0003040f0c", + "policy_id": "0b0100010f080a010e000d05010f0901070e0f0d0905071006070f07", + "quantity": 4 + }, + { + "asset_name": "0c0a0f00070b0b0b0b100a0d0104030c0f0d0303060d0c0e0c030302070c0c00", + "policy_id": "0109100d06070c030d0b0405040c0f0c0e08000d0805060301090e0a", + "quantity": 5 + } + ] + }, + { + "address": "FHnt4NL7yPXttr9FHHXXqJzXMBKxgDTuB4RumYXJspn32RGs97aGoo9z3JTxJPF", + "amount": { + "quantity": 0, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0c090e070600020f00050204000e0f06100a020d0109000605010c0a0808050e", + "policy_id": "0d0d030f0b100e000403060a040a08030508030801070a0509000008", + "quantity": 9 + }, + { + "asset_name": "0c060e0e03010b0f0d0c000309030b03010a0d080c0910070d030210060d040a", + "policy_id": "1009080610060308090002020f07040e050d04040d01000e070f020c", + "quantity": 8 + }, + { + "asset_name": "030f090b02060e090c0d0707070d090108000401050f070e0e0c0c08000b0c04", + "policy_id": "0d020f0b060b00020f0a0d0c100402050200080e0e0d0f090b050f10", + "quantity": 4 + }, + { + "asset_name": "0008070a090a100f0b0a050f000f010608080701090d01020f06080f0f07050b", + "policy_id": "09060a050a07030c04020301100a0a0e090c100e0e0f0900000e100b", + "quantity": 8 + }, + { + "asset_name": "050e03090201070b0d0601090d0a0d0f0d05020d0f0a02020808020b10020f0f", + "policy_id": "0b0f0a0d08090108010f020b06050508090f0e0606080a0809020209", + "quantity": 1 + }, + { + "asset_name": "02020c070b04010c0c010d04030f090f01070e080e08010e0e0d030c0b050b02", + "policy_id": "0c0804060303010b0304060c0b0f030210070b080001040f02040506", + "quantity": 6 + }, + { + "asset_name": "080e060002070e0f090a0008040e090e0e0e10080a0e0d0a00100a030709070e", + "policy_id": "0a080903030f02080f060a09000e0606010b02030b080d0d0c0d1004", + "quantity": 4 + }, + { + "asset_name": "0e0d010f0b070200000008010a06040500020a0607100f010c00030700090501", + "policy_id": "070009090708040d0a05100b0b0e090b0500040e05030701030b010d", + "quantity": 2 + }, + { + "asset_name": "010e0e0e0f030b0b041005000e0906040d0a0a0b01030f080305100b0a100305", + "policy_id": "090a030109090f0d080101020a0606080f05040a0e07060905050106", + "quantity": 7 + }, + { + "asset_name": "01090f100f010c0e05040b0c050f030010040a02060a090b0a0805010e101010", + "policy_id": "0d040609010f0c0d020709060e0c07100d05070f0e0b0206100a090e", + "quantity": 0 + }, + { + "asset_name": "0e040b100e0409090f0f06090f050f050e060c070002080b0b050f0a10070908", + "policy_id": "0210040e0c07100c05090d010b01100007080c020a070d0904000609", + "quantity": 9 + }, + { + "asset_name": "080e030f0e0d050c050e01100c0d0e0a070707100e0c060d06100b02070e0a0e", + "policy_id": "0a06050a0e06020a09010c050c0d08001005001003100607050d0e10", + "quantity": 8 + }, + { + "asset_name": "0f06100e070e030e0d030901000105010010040e0b0f040d0b000e100b0a0605", + "policy_id": "100d0f000c100e080c090e04060d01060d0a090b0300010210100908", + "quantity": 4 + }, + { + "asset_name": "05010f0f02010108030905020006030d090e0e0607050a0707060e07060e0601", + "policy_id": "080b0702000101100902030b0b04010609010d090a10090706020b08", + "quantity": 6 + }, + { + "asset_name": "0c080f03060502030a070f0c0405100d01090e080e090e0e080509040b080d00", + "policy_id": "0907080b000d0c000e0c0c0c0f0b0e08080d0b0e09040d05050c0f04", + "quantity": 9 + }, + { + "asset_name": "1010040d0403070600090f00010b090108090810030a040c0b090508060d0701", + "policy_id": "0d0e09060201050704000e070408030f0f0a0e030f0910100b0c0d0a", + "quantity": 5 + } + ] + }, + { + "address": "FHnt4NL7yPXvuoVdNVUXquot2vJUMXCDhNCswF5zxVBN5mNLkuwdLQcAMc4hFq3", + "amount": { + "quantity": 10771192368312943, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "030d0b03070e04080e010e0c0e0e100b0e0f030202090b05050604040a000f0b", + "policy_id": "070e011002030810090807060a020d07021006000d08030103040900", + "quantity": 7 + }, + { + "asset_name": "0709020f07040e0e0607020305000107020c050b0d0905090d02010e01080d00", + "policy_id": "0f020007010107010b03080d0d000b0310100c040f0a0c0d020e0b0d", + "quantity": 2 + }, + { + "asset_name": "0005030f0d0d0f0d100a0a020102040b0e05090c000f0c030403010205000b01", + "policy_id": "0208020205080f0a09010309070e050d081001010d10070b0a020404", + "quantity": 7 + }, + { + "asset_name": "0b08010600020107090b0e00070602080e0f0e03060c09040105030c0e080b0e", + "policy_id": "09010f0c0d0f0f090608010a030d050d0f040e010506080308080605", + "quantity": 0 + }, + { + "asset_name": "030c0b0b0a090705030d030907030b0a0f080d060d020f05100101000606030e", + "policy_id": "040c0703000c0f0307040f000c0d0b0d010e040f0c0c0d0d0408070d", + "quantity": 6 + }, + { + "asset_name": "0710090c09100f0d05050b0a050f0610000302060702080a0d000c090a040b10", + "policy_id": "0d070605100606060c060e0d020e08020405090605040d000e010305", + "quantity": 9 + }, + { + "asset_name": "020602100d0d0b0d010a0708010410020608020705090a030d05010d0701090f", + "policy_id": "04040d0a040a0d090203050410100f070c03100d030106070a020101", + "quantity": 3 + }, + { + "asset_name": "0f000d0d080102050a0b0d100d030102060b0907070a0f0a0f0b090d0c01010b", + "policy_id": "010f0e07060b05050c0a090e030f0e010c07100b040407090e080206", + "quantity": 4 + }, + { + "asset_name": "03010d060805060c060a090c07080304021006080e0206030d07050e0f010506", + "policy_id": "0f0d02090610100e070210090102020d040a0c0304020c07100c030b", + "quantity": 2 + } + ] + }, + { + "address": "FHnt4NL7yPXxkt5ajNqSmgcWdGyQsMC4GFsC4H3KqmQXhVLa1k8EAc8NMyjyVHQ", + "amount": { + "quantity": 45000000000000000, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0a0705050b090c100e050b0604100b070e050c0b10080603060b0b08090a0e06", + "policy_id": "050506060e0a0a010402040c000f09050b090d0b0e080d040a030d0f", + "quantity": 6 + }, + { + "asset_name": "040e0d10010a090f020706000a02040e0c0700090e1005070e02100e0d0b0903", + "policy_id": "0c03010c0304060a0d0001060e01000d0c0b0f0109020d090d0b0109", + "quantity": 6 + }, + { + "asset_name": "02010f05040d030d0b000c100808070b0f0c0b10060a060e0000010906100706", + "policy_id": "07080a0b0302100d0904020e020902100701030a0a040c101009090f", + "quantity": 1 + }, + { + "asset_name": "050a10000101060909090c0b070904000e03010b060e0b06010109040d0b0408", + "policy_id": "0003050d080a0809030f0701100d000d0b040203030504070803010f", + "quantity": 3 + }, + { + "asset_name": "0d01070005010007030b000602020d0f08070f0f0d05040d0509090f00040b05", + "policy_id": "0210070008080d040c0a0a10000405010e0504080d070507040e030e", + "quantity": 2 + }, + { + "asset_name": "1004020a0c0b030f030e0d0a0a011005060e000b07020e0b0300000f06090d06", + "policy_id": "0d0c020a030a0b00030d0b02080a10000b010f0602030b0907100c0b", + "quantity": 5 + }, + { + "asset_name": "080f03080a0b0a0d0e07070f080d0e00000f04041004080d060504020c020000", + "policy_id": "01010f00080f04000d05030b070f0c0e0001080e09070c0004100803", + "quantity": 8 + }, + { + "asset_name": "0f07090600010d100c060d0802040a10001008060709040201100d0c050f0c04", + "policy_id": "030c07010a0e0904080e020e0f01050c04020603000e030e070e0802", + "quantity": 7 + }, + { + "asset_name": "070301000702020804040a0e0d0705100b0f0d0605090c0d0c0504100110040f", + "policy_id": "030a090f0e0e1003010b0d100d030906050f0604000d030f09060203", + "quantity": 5 + }, + { + "asset_name": "0d09040f0e0d0c000f000f030c0508060c09010c0d100f070d020b080f03050f", + "policy_id": "020c06020f040d040e07020e020810040404090d0a0f0307040f100e", + "quantity": 9 + } + ] + }, + { + "address": "addr_test1qrrnqfs699z8cnrzmwe594rmsljw94f2cqzgssg3ddxy9q6e42nqtakjggct0jvneyruzjm64pdaezcmzgj997vz9mysecjzsh", + "amount": { + "quantity": 12979144054013338, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0f0b0f0602080e080e0107030d030706070c0f01060e0a0510000009070c0c04", + "policy_id": "090c0408010c080a08060c030f0b090108030c080e05091000031001", + "quantity": 0 + }, + { + "asset_name": "0910080e0d0d0d0e06060406100409090d0504010c040e0d0f0c0e020007070f", + "policy_id": "01100a0c090d090c020c070401040a020b010a0500060b0907020d0c", + "quantity": 2 + }, + { + "asset_name": "100e0707100a05010903030b020a0c0a0d05070301100907030b10010c030f0a", + "policy_id": "0f050a10100c100f060401020f020a06010d040c070902010f0f0a0a", + "quantity": 2 + }, + { + "asset_name": "0809000207070807090306090f04061010010a0d07030c040901080c0c090c02", + "policy_id": "09030c010e0f010f000b050a0d1010060d070f0209030606080d0400", + "quantity": 2 + }, + { + "asset_name": "040b0c0d0e04070a09030c080207011008090805070d0b060f000c0605100306", + "policy_id": "0509070703070f030501070e09080804080d0f010e0b07060f0f100d", + "quantity": 7 + }, + { + "asset_name": "090a0f0a05060110090d0609090a000b02010f0f090806030102050b080f0105", + "policy_id": "040b020f010f050f0e100c05000b050f0604020204040d10070b0301", + "quantity": 8 + }, + { + "asset_name": "0f0d04020d0404000a0e0c080c0b0f0300090c071009000b0307030105070001", + "policy_id": "020d03050102060509070b0c0d1004020b0e00030c000c0f020d0d0c", + "quantity": 0 + }, + { + "asset_name": "04000a0002040c050b040e0003021005080e030b08040e06060b0d0102000608", + "policy_id": "100f0105090c080d040a0509050d07010d06000b060701000a09040e", + "quantity": 6 + }, + { + "asset_name": "100d05040d070a05080a0d10050e050f0b0f09050f100c0a0906001004030910", + "policy_id": "0e1007070605100f0504040a03050e0f050c00100202070304040c09", + "quantity": 8 + }, + { + "asset_name": "05090d100f08060c060c01090503100b030d10050201020c0e0a050401040709", + "policy_id": "03080e07090e020e0e0a09060802060e0609050d0303010b01070d08", + "quantity": 0 + }, + { + "asset_name": "06050806080a0805070e050b0304010b020110040e01020c080c0102080d0b07", + "policy_id": "09070e07020b10010a10050f0c0f090f010a0d0306040d090f0f0c07", + "quantity": 0 + }, + { + "asset_name": "050b00100d06080300100a0f0100080d0c05000f04050a0b0d020b0f0d0e100e", + "policy_id": "0b020d0f01030a0c08000e0a0a0202020b090600080e0e090e010e07", + "quantity": 1 + }, + { + "asset_name": "1001090e0f0409090110080f0a0608090d0d000b020b080a06010e0604070310", + "policy_id": "0b000510030e070a100a0a01050a0b10050f1003030d0b0e09060309", + "quantity": 5 + }, + { + "asset_name": "090d09040c060b030c0204040403060003080d0e0c00060f0b0309030007070f", + "policy_id": "070f06070d07020c0a090c0502050f0e0b000505040b0d01040c0a0a", + "quantity": 4 + }, + { + "asset_name": "060a0105070e0609080e0d0b100d020e040103070e070001000c041001020a0f", + "policy_id": "0a090c0d060e08050b0505010806040f090c0e0d050c060a0a0b0605", + "quantity": 5 + }, + { + "asset_name": "080e0b01040a0409000e0408070800020e070c0c0d090c08020c060e050e0a0b", + "policy_id": "0e070a0c0803010a030206010f0d1005100909060604050c0c070608", + "quantity": 4 + }, + { + "asset_name": "090d0f0f1001050d0c060009040b090f0404020e010504050f0b000102000809", + "policy_id": "100400020e100d0106000806100b000e10031008000f0f000d0b0104", + "quantity": 1 + }, + { + "asset_name": "0410030b0509000007080104090608040f0009050c10050104060d050d0c0209", + "policy_id": "090a0b06040d100708010c04030b070c0005090d100e050e0e0f0b0b", + "quantity": 1 + }, + { + "asset_name": "0d0a040402011007080f0b07050b0b00060b060c0f040b050a090d020610030c", + "policy_id": "0801020a0b0a06040f06040c070a0a040a100b040903090c100f0905", + "quantity": 9 + }, + { + "asset_name": "030404070c03020200060e080303050a020502030e01000d0e05010e00090502", + "policy_id": "0e0f0a000b0b1007000d090b0b0405010f10020d0609030f0100100b", + "quantity": 0 + }, + { + "asset_name": "10050306050f0c0b100501090b0f010f040d1006090806040b0a08100b0c0a0d", + "policy_id": "01050a000603060f030510000806000e0f060c070c0d0f050f00020b", + "quantity": 9 + }, + { + "asset_name": "020a0304060e0c060b0c06040f05030f0a0e050209080b03070e00060e060e0e", + "policy_id": "0505030506100a0f0c000e05090e0a020f100103030c100f02000b02", + "quantity": 2 + }, + { + "asset_name": "03040d0e04020306060d0d0f0e07020107070f000f000f070a000b040f030707", + "policy_id": "060702040700010a0c060c0f0909080c100005060a0b040910100f03", + "quantity": 5 + }, + { + "asset_name": "020b0f0e0f0b0b010a010c040907100a060b0b04050c0c020c000408050b0100", + "policy_id": "09080701050e000005020c070b0803030708090906030504060c0a02", + "quantity": 5 + } + ] + }, + { + "address": "addr_test1qq96nfp79jg4qqllq8ans8zztfk3ymngzuxn45fac3gkzdupthxjzhmm6x52lzare8jcvuanfvz9d7ffcnqmtqrgdamqxt3q90", + "amount": { + "quantity": 32040306888249854, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0a03040c10010e06090b0d020808060005080a0c0f1008040a01040906010008", + "policy_id": "080e10010101020b050d050e010b0e080903100003050a0d070e0302", + "quantity": 5 + }, + { + "asset_name": "070d0807030d000000030906040a0e05090a0106000302020b010f0900060110", + "policy_id": "030d050f030509040704080e090f070a010607050308100f05091002", + "quantity": 1 + }, + { + "asset_name": "090100030f04070e0f04010101090e070e050e070a0a0b0c0f00060908100b0c", + "policy_id": "0305020501100a0a03020b0406030d0a1007080e0c020b0c03020202", + "quantity": 3 + }, + { + "asset_name": "030607030b04010c070b090f000b0b1004050700090202070d000d0a0a100c06", + "policy_id": "000e0b02090b090c0104100a02060f0000010202070a03080f0f0400", + "quantity": 8 + }, + { + "asset_name": "050a0d0000090f000604090006070702100e0f05050608060b08030a0506060a", + "policy_id": "01101001020f03080d0b010505040c0d0f081008060b09041004070c", + "quantity": 1 + }, + { + "asset_name": "05090f01070e0e010c060b0e100106030d0c00000f010810050e090c10060810", + "policy_id": "040f00020e0904060e0f0f030e0c020d041010020d050e0b0b06020f", + "quantity": 0 + }, + { + "asset_name": "030f0c080d0d080a0f0902030a070806030e0d0c0b0d010704040f040b04010b", + "policy_id": "100f040e0f0406030a05090b0d0c0c03060a010a010803000a09090c", + "quantity": 2 + }, + { + "asset_name": "00060d0104000a040d080e0d0e0304000b04020d0d0a0a0e02090c0a0f080110", + "policy_id": "070f06040a100c000a04000a100410060c020907090a0d070f040109", + "quantity": 2 + }, + { + "asset_name": "0f070a080502020601070202100f0b080c0e100501070906030d1003010b0802", + "policy_id": "0707090000080e0e0d0609100007050e000d030e09070e0102060809", + "quantity": 1 + }, + { + "asset_name": "0d0c0c0c06030003010a000a01020c0f0c0c010f0e010c0601030c0c020a0106", + "policy_id": "0d1000080a0d040a060c0a000f0100090a0d0e09040005010e0d0802", + "quantity": 4 + }, + { + "asset_name": "000f02030a0b10030807090a0b09050e04040003020c09090d080d0c07090902", + "policy_id": "0904070609080b060b0c0b0e0e060c03050910030e0b0c040e0d0508", + "quantity": 9 + }, + { + "asset_name": "000e0d0901020d0906000a0a070a000f00020406050a070f07040e0f00030d0f", + "policy_id": "0702080f011010080f0407090c0b100f0c04010201050a0b010c070e", + "quantity": 2 + }, + { + "asset_name": "0c0608100a07040900050d0a070603040b040905050f0f0308030310090b0903", + "policy_id": "010d060f0c09100e040e0603090b050000020f0f030405080c01000e", + "quantity": 1 + }, + { + "asset_name": "0500000f0e020910050a0702080a0a00060609080a06010c0b0f10060a070f0f", + "policy_id": "0209080b100403070710040808020807020c03100106090b070f070a", + "quantity": 1 + }, + { + "asset_name": "0b0c030d0d0000060d0d100306050f06100d070b000d0602100c070a0a070107", + "policy_id": "09000c010a02070608100d0a0705090b0102040e0201020f0f0f0a04", + "quantity": 5 + }, + { + "asset_name": "070d020a090e10000c0a07050a100e0904100f070202050a01010205060b020d", + "policy_id": "07030c030a1006000804080a0105100010030a0601060e02010e0002", + "quantity": 3 + }, + { + "asset_name": "0300010e0902010e0e0703040a100b0c0303020f0e0c0b0e02020d0c0b0c0d07", + "policy_id": "000004010e100a0b03090b0b0402080e0e0f0e050e080208070a0a07", + "quantity": 5 + }, + { + "asset_name": "0b040909090d0e02070901100a0b10020c090c02040c06030c100f0c0801100a", + "policy_id": "0c100b0a050b04080806020d0f060708000b090d08040008030f0b10", + "quantity": 5 + }, + { + "asset_name": "0906010a000b0d0c050a060704010c040b0c0b08080f06080b06010e060f0f07", + "policy_id": "06090e0e0e020b09050d0f070f100e0101100c0f0f050a0a05050b0f", + "quantity": 7 + } + ] + }, + { + "address": "FHnt4NL7yPXzjTDs54edHfeWrisComtBLH7TcZRjyThbir9dXcGRieSCEP51kyt", + "amount": { + "quantity": 30972111964803369, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0b060b10040b000b0b08020c0c0b100a0e0f0c010b0c06050a06001004010510", + "policy_id": "03080a100c081006040e04060d0e021001070e0b060c0101070a0c00", + "quantity": 3 + }, + { + "asset_name": "0b07070c090e060f0a0b0c060d0200040e0c010c080c060801020500020a050d", + "policy_id": "0a050008000e020806060b0f0a020f0a0c050d050e040d050109050c", + "quantity": 9 + }, + { + "asset_name": "0f010a040d0b1010070b07090a080b030d0d10030c0d07000c090d0b00001009", + "policy_id": "010a050510060d09030a0d050e06040a030a0101010408070e020707", + "quantity": 5 + }, + { + "asset_name": "10000d0f040e0a08020d040e0f070c0306020f0b08040d000a01070e100d0f03", + "policy_id": "0003050e100b040c04000b03010d0b03090c020b0805090e04070206", + "quantity": 8 + }, + { + "asset_name": "03060d0c0b040f000c08060c0d08020b0209070a030c02060f01000f0d0e0507", + "policy_id": "070f000f03050e0e0f0c0205100207090d0a0b0c000809001001050e", + "quantity": 7 + }, + { + "asset_name": "0f0303040a050e0d050302050100020b060809070b09090a0f09000f08010d02", + "policy_id": "050c100201070d090d0a0f030e0b020706080a040d0f04040f01020a", + "quantity": 3 + }, + { + "asset_name": "0b0b020c05060908030510070104070c080e00100e030c000e050a0606030406", + "policy_id": "020b0e01090f03090500100c080b0b0603000f10070d0b03060f0910", + "quantity": 4 + }, + { + "asset_name": "06070504030210080108040204010f0c10060c010a030507080c08010a0a020b", + "policy_id": "09020301050003040e05040108050c0d0501070f0f091007070a0100", + "quantity": 5 + }, + { + "asset_name": "06080d050d0f0b0c0d0e050d070a0c0e0b0306050e08070b0b0f0b030c070110", + "policy_id": "0b070707000709010d00030c060d000708020d0c0302100c09020703", + "quantity": 5 + }, + { + "asset_name": "000d09000c0d01030d10060e0f0903040d03020b04080f00080b050300080806", + "policy_id": "040806010f08010304020b0100100e030700000f0b0909100b0f050e", + "quantity": 6 + }, + { + "asset_name": "0c090e0e0a1009050900070507040f0f040f0f0d04070b0c000209050d0f040b", + "policy_id": "0d071009080210000f080d0d080a06051007010e0b040c1009020309", + "quantity": 2 + }, + { + "asset_name": "0d0d0b060d080f0f090b050302040305060f020e0c080e0701010a01080c0606", + "policy_id": "0f0f030108030808070a0210030c100b0c0c100505000b0f090c070c", + "quantity": 1 + }, + { + "asset_name": "000c040110020c08060d0f000700050901020a0f0007050a06030f0d100e0101", + "policy_id": "0a070308060f09070f09070c100c090f0c06090d060409100b060c01", + "quantity": 0 + }, + { + "asset_name": "1002070a08010106100b050305100c0008090d050c0002030b07040702090604", + "policy_id": "090301040d00071001060a06100501070c020e0b0e0b06040c04070a", + "quantity": 9 + }, + { + "asset_name": "08060f0c05070a0c0b0f02100e0e0c0c030b03020708010001000d050807070b", + "policy_id": "0e000a040007000409050d0b090a040909030c0510100d0702000b0c", + "quantity": 2 + }, + { + "asset_name": "0f020600020e040b0c0b0e0a041009060e0000100a10100d0e0b100e05070f0a", + "policy_id": "0a030d03050c000901040e0b080d03070e000d070e0f060a09010810", + "quantity": 1 + }, + { + "asset_name": "0d0010020b05090f0f09060d010a100309020f070a0f0404040e0d04020e1008", + "policy_id": "08030405010807070b000b040a0d07050e0f0e050b0d070c0709040c", + "quantity": 0 + }, + { + "asset_name": "0d050a0d080a040d09020b030f0a0a0c07000700100b0e000c0c020210070a04", + "policy_id": "0701040d090102000c0603040d080d09020202090d0508000e0b0c02", + "quantity": 9 + }, + { + "asset_name": "09050408100d0410070108100503010600080a080d0b080f041008080706060e", + "policy_id": "0806090c0c080b0e0b0d050303030b03070a01020c0f060b0b030b06", + "quantity": 1 + }, + { + "asset_name": "0e04010704000e100f0d000d0f10090403030502030408030f010302070e0f0b", + "policy_id": "07080b1001020b0e00020f0e040803040b0d03000d090f100a01070a", + "quantity": 6 + }, + { + "asset_name": "0d07010d070c0e0000030e0c020b08040a050f0b0c0e020408080d1000050c0b", + "policy_id": "0a0c0904030e0009040a0f000500080c04010b0807070f0e0c020e0c", + "quantity": 3 + }, + { + "asset_name": "090d000c0d1010020d0c02070a06000c000001100205050610000210030b0f0b", + "policy_id": "04080b0904100b10080003070b060c04040b030a0c07100406070b01", + "quantity": 1 + }, + { + "asset_name": "020f000e01020e1001080b0805000a0a060c050e0f070810030d030807080d07", + "policy_id": "050d09040800090d010d100f0d0d040a0e000d040f020b0f0e070605", + "quantity": 0 + }, + { + "asset_name": "1000081010040801031000090501030f03030d0101070607060b0405080c0a05", + "policy_id": "0f0b0704070e070a020f0d040e060d0b0d01000a0a0a090c010d0e08", + "quantity": 6 + }, + { + "asset_name": "090b070e0806090701030b0706080c0f08040408070f0f0d030e0101100b0d0e", + "policy_id": "0b07000f0a000a0a0a050d0f0c030d070e10080e0e03040c06040f04", + "quantity": 7 + }, + { + "asset_name": "0a020e020e0b0f0a090709050106040f010d0a10000b0f01070b0e0304100901", + "policy_id": "0d0c000d0503100810001004070e07070d0900040a0b08060307030e", + "quantity": 2 + }, + { + "asset_name": "0c0c06031003030d0c0d0a0c05080f0e0d070a000a100f0b02070f0704050a10", + "policy_id": "0410060610060f030f0c0500100e000a100d080805090805090b090b", + "quantity": 1 + } + ] + }, + { + "address": "FHnt4NL7yPXxsuYSP7ak3pbSeCPtnDnGrN2Sqdzyy1ZnQZNRVR7uXUFQpT5na5d", + "amount": { + "quantity": 39690237147441109, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "000208040a10100c080c010c01040204030c0e0c0c060309100e0c030e010d10", + "policy_id": "06080e0303020603060508030f0505080e0d0b09020d080301000f01", + "quantity": 8 + }, + { + "asset_name": "0d07090a0b090a06050b0103060d100202020604040a050610080200010f0604", + "policy_id": "040a0c0f0f0d100f0d0c050a03080d05080905020902050609070200", + "quantity": 5 + }, + { + "asset_name": "040a0c0b0b0e0c04020303060709020408080b080604070807080b020e020005", + "policy_id": "050a070a0b02000c0a04080a000706000c0709060b040009060d0f01", + "quantity": 2 + }, + { + "asset_name": "0b030008030a010a0000090e0e0e0c0a060005100c030c070a040b0c0f0a0d02", + "policy_id": "080d0c0b000a03000f0404060b05050b0a040601030f070a060a0a0d", + "quantity": 6 + }, + { + "asset_name": "06060f000d090e030d01000002080c0c0b0c02080e0f0d0803080c0f0e070108", + "policy_id": "0b030601010c000a0e070e060f030f061009070f100a10030d080708", + "quantity": 7 + }, + { + "asset_name": "00030f0c060405040e0701090606090c00050e070e030d0e0f090d1002081000", + "policy_id": "071003020e01030600050c0f0e03060d100b0f000c08010f0c090110", + "quantity": 9 + }, + { + "asset_name": "0002040a000a050f050e000b0106080a0902010a060608060f10010a00070f06", + "policy_id": "0e0b020d0102000605020905080d0510000c03090f0b080206100b06", + "quantity": 4 + }, + { + "asset_name": "0510070f100b0a0c06050c030f0d050402090b100610000a09090e0d000d0c05", + "policy_id": "0f08000301070f010f06010f030c080a0e0a0c0409020e0907020508", + "quantity": 4 + }, + { + "asset_name": "0a0807000901020e030a0905030e0d00070d0708030b080b000107000d01000e", + "policy_id": "0e0610100c080b08100d070205040207020d0a0908060e030c100401", + "quantity": 6 + }, + { + "asset_name": "0a0a070e000b03020203050d0d0001070306030807050410000b0d0b10000b05", + "policy_id": "07030d0500020b050b010508060c02020a09030004040600070b010d", + "quantity": 5 + }, + { + "asset_name": "050b060f0703040207060405070902000802050c100d0e0f010702090c08100f", + "policy_id": "0c0d05080d01100b0b050c020e0506080c000c05030b04080a0e0107", + "quantity": 7 + } + ] + } + ], + "vote": "abstain", + "withdrawal": "self" + }, + { + "delegations": [ + { + "join": { + "pool": "pool1tg5n6zc7y3uyw46f23yqugqj0ccyc4srzgjq2v6qgfhqwgu8g96", + "stake_key_index": "66" + } + }, + { + "join": { + "pool": "pool1vsuz6dfftvcxjsjuvv09yypdpf3zxtqafdwpq6rupdpxzuya8yl", + "stake_key_index": "101" + } + }, + { + "join": { + "pool": "pool1qs0ny0cwp3ph6nq5z9z3kjfsyqt3yhgcd3d9vk2er335yz97vvm", + "stake_key_index": "101" + } + } + ], + "encoding": "base64", + "encrypt_metadata": { + "passphrase": "{h{𐺈s6\\!`1kDP6𩓼q?ଘ𥘗X2})&𩈪Y_𒾺rTWjt" + }, + "metadata": { + "4": { + "bytes": "472540191d0f8d3358516c31726f19321c1d56212b55063650550c7e47b832e07ca65eb400" + } + }, + "mint_burn": [ + { + "asset_name": "41737365744b", + "operation": { + "mint": { + "quantity": 18, + "receiving_address": "addr_test1xzgelvm956zmqhfu0amhxy468fnqq8v2303f429um9a873wpjh4dnre0weyluc3zu380ausm6sdpw7vycargzkz2xnqstqjny6" + } + }, + "policy_id": "15581b1ecfd923bb318a8c57e9f3b6ec3675f68cb9f74fa908c9d4cc", + "reference_input": { + "id": "20502a30435d5b51653d49534a73380416b8685100b65f74091f55617e5d4541", + "index": 1 + } + }, + { + "operation": { + "mint": { + "quantity": 17 + } + }, + "policy_id": "3adfe136c156152a00ff5b088dbfe6c62dae28c0549b968e90552dd8", + "reference_input": { + "id": "77741858471a0d9015636f62545131262b447041a50926074941a31203844e47", + "index": 0 + } + }, + { + "operation": { + "mint": { + "quantity": 2 + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } + }, + { + "asset_name": "41737365744d", + "operation": { + "mint": { + "quantity": 7, + "receiving_address": "FHnt4NL7yPY67BBBNKLRq8nQ3buPxidGiGfjAJw4kPPn5Rvqnwajh1XD1uge9hb" + } + }, + "policy_script_template": "cosigner#0" + }, + { + "asset_name": "41737365744e", + "operation": { + "mint": { + "quantity": 8, + "receiving_address": "FHnt4NL7yPXoBvQmQukGaWqUaUVkpV2QCandA3d8RqBRXRqUcUwmV8AWA1HmNNg" + } + }, + "policy_script_template": "cosigner#0" + }, + { + "operation": { + "burn": { + "quantity": 18 + } + }, + "policy_id": "18379297e82f7e628f51984cb01c24546593ef93a878ffd426703cf1", + "reference_input": { + "id": "22135d7a773c75b813323a4179703265661c4f4d7f187a366a71551289705e55", + "index": 1 + } + }, + { + "asset_name": "417373657447", + "operation": { + "burn": { + "quantity": 23 + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } + }, + { + "asset_name": "41737365744e", + "operation": { + "mint": { + "quantity": 8 + } + }, + "policy_id": "102747a5a9a82ffb56c49f0265dba339e5b363df444723e221667214", + "reference_input": { + "id": "da1700253b16154433f6490a131e02654a352319147873447e09a14442035fd9", + "index": 0 + } + }, + { + "operation": { + "mint": { + "quantity": 25, + "receiving_address": "FHnt4NL7yPXn2a36LR8wdtYygfzYUcATB6tnN412ZGztDtbY26nYmsEyowaAVBj" + } + }, + "policy_id": "a120aeec86be9f9648e7b71fab397b22e8dbec774105bb561643006a", + "reference_input": { + "id": "08656d5ad1608486505d215c054051160bc7366389e006614c4c7a3f6d6a771b", + "index": 0 + } + }, + { + "operation": { + "mint": { + "quantity": 21, + "receiving_address": "FHnt4NL7yPXgtShBd8bSabVYqWQdonoNUPAVhbvc32V1yjH5YzJoh8dNBkWUxBE" + } + }, + "policy_script_template": "cosigner#0" + } + ], + "payments": [ + { + "address": "FHnt4NL7yPY9dnUGxyEc1vU9hb2rUaiv9XAMginNyKa3nDC7rV2oawB8SocSCvX", + "amount": { + "quantity": 45000000000000000, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0e0e0f0301030f0a0a030002050906061008040400000a03060a0e060c040601", + "policy_id": "0c0409010a0110100a02100a0d0e070c0008030b01010205040c090c", + "quantity": 1 + }, + { + "asset_name": "05040a0310090e0d030c0704050f1010080a060f0304020c030c0b0f0e030a00", + "policy_id": "0703030503020d02000407010d0d02080c0f0d0f0d0e100e0e020501", + "quantity": 4 + }, + { + "asset_name": "01070b0f030508100f08020e000501080e0c0a1006060405080a0e0407020b0e", + "policy_id": "0c0c0c0a03040102020703090d0b0704010d040201060a0d10040f08", + "quantity": 4 + }, + { + "asset_name": "0507090b0b050d03030701070f010f0700020109100409090f0a04040b100b0a", + "policy_id": "100d0603010e0d0b0b08020f0c0b010900000b10101009050b0c0c0b", + "quantity": 1 + }, + { + "asset_name": "080c0b040c0e080b00070800090d0f0303020e100204020b10090109100d0209", + "policy_id": "0501060e05070305090606021007000c08100f100d050203040a0207", + "quantity": 2 + }, + { + "asset_name": "03010e0a070c06061007090d0d04100401020f06090c040c05000d0802000a0f", + "policy_id": "0f02060e0d0006010e04090d0507090005070110010e0605050a0d09", + "quantity": 7 + }, + { + "asset_name": "0c100c010a0a0c100700040c03070203080c02060f070f0c0507100907010f04", + "policy_id": "08000b0e07040a0a100501010b0f000907010104000c060510090b02", + "quantity": 8 + }, + { + "asset_name": "06060a0a100a0010020b010608080f000c0b1007080406100f0b060d01080602", + "policy_id": "0a0a0c0010090c0d030106020b0c09090c01100600040b040c010c10", + "quantity": 5 + }, + { + "asset_name": "080f09000b0c05090810080f100b07030c04020c010603030e02080102010d0b", + "policy_id": "050d070e0a03080501081002050d0905040f040505030810100a0404", + "quantity": 1 + }, + { + "asset_name": "0c03100f0803000d0103000b0e0506000c070a020908000a0805070302030a0e", + "policy_id": "06030008050609000b020109030604100f0e0a0a0c10080b00100a02", + "quantity": 1 + }, + { + "asset_name": "0c08030b0902020b100d0810040b0208030f0d05050f07060e02030504020d04", + "policy_id": "01080d0202100f050010100c03080402080c0e06090d0409010e0a01", + "quantity": 3 + }, + { + "asset_name": "00031006060b08090e06070f0e0e0c100d0f100b0b0a0f06040208000b050c0a", + "policy_id": "04090b01000b000810000e0d1003050a04060c030f010d0510000703", + "quantity": 4 + }, + { + "asset_name": "000407030c0a0f090402000f0f090e040809000a06060c0d0d030f01030c070f", + "policy_id": "0800050a0f010f0b000f010301060c090f010a0107071001080e0809", + "quantity": 3 + }, + { + "asset_name": "0f0e1003100602050b0a100b0d02090d08090505080c0a011001010a020d1000", + "policy_id": "0906080e0a09030a020401080b0405070806040a070a0f050d080409", + "quantity": 3 + }, + { + "asset_name": "09080d04040f0f0307060b10040a0b071005010807080801070d0c0b0d0b0f0c", + "policy_id": "0c10080f0a0e070f000c040e0c001001060e0700031003040c01070f", + "quantity": 3 + }, + { + "asset_name": "1008080c0d01090d00000401030c0300010c0009060b070e031002010006040f", + "policy_id": "0d0c0d030f0b08060a07050204080601030c0b0e00050b0405100908", + "quantity": 1 + }, + { + "asset_name": "03100b061010000b0f040a0a0401030d050c0e1010060a0509010d0a1000100c", + "policy_id": "07060106100f0d00010404090e0105001008060d050704020101060f", + "quantity": 8 + }, + { + "asset_name": "0c10030a100a0a0505060207060f100e0e0f1009040e09020d0710080c0a1005", + "policy_id": "05000f020f010a10090e0f01000b00010d0f0a0e0d0e01041010070f", + "quantity": 0 + }, + { + "asset_name": "000706050c07080a060b0e0b0a0b0d0f040601100e00070005050a050a060f02", + "policy_id": "0d000a090405020b0b070a0c0f01080310020d09011000040d0c0a09", + "quantity": 8 + }, + { + "asset_name": "0e10020b04050d030b060f090a03100c1001040d0e080e010107030402070a0f", + "policy_id": "07000d080b08090a03010b0d000f050f0802040f0e060910100d0e02", + "quantity": 6 + }, + { + "asset_name": "0a06090107020903030f060c0e03060904060508090b0f03060d010d010d030f", + "policy_id": "1007070a0c0709010f0f0c0d0b0d020d0c04070902030f030d01090c", + "quantity": 9 + }, + { + "asset_name": "0d0c0d0702100c060301091000000a06030d0a08060e0d1006010e0b0d100302", + "policy_id": "06091001000f040e10020f0901100a0b0f010000080407080001070f", + "quantity": 2 + }, + { + "asset_name": "0c0c0b06010e0b04000b080e060a100707000c0702020f04040d090906030e03", + "policy_id": "0603040202020f0e0100040d0207050902000d09070904000e0b0003", + "quantity": 4 + }, + { + "asset_name": "0905080c0507010b0a04100b07000e010e0904080c0d0c090605100903070f0a", + "policy_id": "0004090e050c0a0b070a0e0a100b0502050008090a0c0f0607090507", + "quantity": 0 + }, + { + "asset_name": "00080401090b01050707060d0902100a000a040701090f0e0a0506010b0b000c", + "policy_id": "100000030d090106020a0e0709080d10030b09040c03100d0a10030d", + "quantity": 4 + }, + { + "asset_name": "10040b0303090a05080e0700020f090e010d0407010a0909070801030310060b", + "policy_id": "0e020a07040b0c10070d0e030203060701030c00000b0d080e100a0d", + "quantity": 4 + }, + { + "asset_name": "000b0c0d0d0c0e0b080e000d1000020c0d050c04020c040d0f000a030c060b08", + "policy_id": "0e0b01090c00020e06100c0d03100a0b0007000809100500070b0c0b", + "quantity": 6 + }, + { + "asset_name": "0f020f0c100e00090a040b04060d000c070f040d0f030f07040210000a000d0f", + "policy_id": "03050805070e0c0a0708020b080a0b090e050f0306080a060b050b0a", + "quantity": 3 + }, + { + "asset_name": "0108100c0f0d02100c060c09070d0900060300010907070a0a09100c0c04070e", + "policy_id": "02090007100d000d030d040300030606000f08030c0b0508030a0803", + "quantity": 2 + } + ] + }, + { + "address": "addr_test1vz5dlynq43mjctnrr3ycnjmfxcvyx4yv80tg3u2rv2l0dcqztpl5u", + "amount": { + "quantity": 9961224888491235, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0900090b0f040b0c090610070905011003050e0707000b0c0c0a02090f070a02", + "policy_id": "10080907100f050f0a010e04080b070405000f01000f0b0f0407020e", + "quantity": 3 + }, + { + "asset_name": "0e010b0a0702050808070a0205040e0f10090500050d0f0800080510060b050f", + "policy_id": "06090c01040f0501040b0b02020a0909070009020d0500020a0f0c07", + "quantity": 6 + }, + { + "asset_name": "070a07000a0d030d0b0f03090504060605070603040c070b050b0f0c0e080a07", + "policy_id": "0300040308100a0e0b090802070a090010070d0e0a08010d0f0a000b", + "quantity": 0 + }, + { + "asset_name": "0e02100c0b020c0c080c040c030d000b080704030a0f0809100e0b0201100c0c", + "policy_id": "0d100501040c0003100e100f02020e09010d0d031002050e0c0b0d0b", + "quantity": 1 + }, + { + "asset_name": "00010e05000d0607030506070f09030c0f0d020e05000a0f050805060107030c", + "policy_id": "030010090503050c0f0205100d080c06000a020a040f00060301040e", + "quantity": 1 + }, + { + "asset_name": "010d0e0201030c0a0b0702040700020c0f030102030f050f0603090708100001", + "policy_id": "0c010d06050b0306070f0b09080b0a0c090600050a05090d0b050c0e", + "quantity": 8 + }, + { + "asset_name": "070708050504020e070f0b010f0c040b040a0e0d0f05020b0508040f08050b09", + "policy_id": "010704020700020d070409020e0b0b03030b0e0d031001000e0f0b0a", + "quantity": 6 + }, + { + "asset_name": "030b060c0602030e040700000c020f01020f0b0b100309080f0c040d070c0207", + "policy_id": "0510100b0a090d070d0b020d03070d000a0b0a090600080503080610", + "quantity": 0 + }, + { + "asset_name": "0b010b020a02060208090b0d0a0209050e010a010e080a0608091010060f0702", + "policy_id": "02000801000e070700090a0a0b060d08070a0a060d0c0706030c0904", + "quantity": 6 + }, + { + "asset_name": "09070a0f000e0407090f0b0c0b040e0a0a0c0a0300060b070507100b0b080a03", + "policy_id": "0b060a03060c090a020c0504080a070108060b0700060c080d0f0b08", + "quantity": 3 + }, + { + "asset_name": "0b0a0d040910100505040b0906000b0d090d100703070b060a0f07080701040b", + "policy_id": "0f0b0806060c0e060b10060d0f060403020601050b0308000c000406", + "quantity": 5 + }, + { + "asset_name": "0b040f0a0d0a000d030f060e0d0d05000d03100602070d0f08070a030a0e0205", + "policy_id": "080f08060d0c050e0d0102030a060007050f010c0609000b060d0f09", + "quantity": 0 + }, + { + "asset_name": "050000080d0c0f0f0507091002030f0e100c0c02050f020e0a0d0d010f0c0b04", + "policy_id": "00050a0c03090d0505020f0b000d0d0a05040b0905020608000a1009", + "quantity": 9 + }, + { + "asset_name": "030610100b030a081007010500020c000e0d0b07100a0c0006050f06090f0506", + "policy_id": "000504010200010a000d0b0f05050b09000802010c0d0a040c040307", + "quantity": 2 + }, + { + "asset_name": "0d0303061004040006030e08080d0702060c08080e10030c0401040f010a0f0d", + "policy_id": "0a0d04090805010a050110030e030f0b06000d0b060f02030602020d", + "quantity": 2 + }, + { + "asset_name": "0b010a0a0f0608090a0603090105070f090d03020b0b10080406010f0f0c080b", + "policy_id": "02040a05090d0f0505060b0a050a05050b070f0c090a010d0e0d0b01", + "quantity": 4 + }, + { + "asset_name": "0b040e0f0e0d0e06040f0d050609100a0806090f0c0d090609090608010b020a", + "policy_id": "00000609021008100d0807090d090505100e0e060f0d01090d090903", + "quantity": 1 + } + ] + }, + { + "address": "FHnt4NL7yPXnQjAigCi7v6bMtFGf74tpJm7uXMwVG8HTG7LN7wZWXb9NzhqDYR9", + "amount": { + "quantity": 27538669278424239, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0400000803020600030f050d0d0b09010b000d0f0b0d0c0f000c091002080405", + "policy_id": "0e0b0c0b0a10010e0b060902000c09070a0806060708010808000a09", + "quantity": 2 + }, + { + "asset_name": "090304020808090b0c0c0c0501100907090610020606080a0c01071004020f03", + "policy_id": "0505020e0e0d020d0f03020203030b0701080306020d0107040b0f0e", + "quantity": 4 + }, + { + "asset_name": "0a05040b060506100b06010002100f0f0b060908100506060f0a040f03020009", + "policy_id": "081008030806030c05060d0003100a0402030d0d080b100c09100400", + "quantity": 5 + }, + { + "asset_name": "060f0906020a070b020a0c0408020306020c080b0a040a050903010d04030b08", + "policy_id": "0f0e0e100c030a000d081001010c080d010c01060a040b0d0a0c0410", + "quantity": 0 + }, + { + "asset_name": "000706030b06080e080b0c0d0b0b080e0b080e0b0d0a0d1001040e050910090c", + "policy_id": "1007060d0c0a08060a10020706060900080f08090a0e100909080a05", + "quantity": 8 + }, + { + "asset_name": "01030e020b03090b0a0a07070d040c010a06000c0f06050a0f0605020a0a1009", + "policy_id": "0f0b0e03100a0d050a0b05000d04080a0d0f0d0e050b0d01060b0f07", + "quantity": 4 + }, + { + "asset_name": "0100010b0a0606050a0d09090f0e0e0d0f0f020702070110030508090d080e08", + "policy_id": "050e0b0003060a0d0d030b06010d0c0310060d000e0809070e0d020a", + "quantity": 2 + }, + { + "asset_name": "010e04000d0a0707000208070304050a020501050c010d0c06100707070b0604", + "policy_id": "100f100700090d08010f040f0501040507040e0301060208050b020f", + "quantity": 4 + }, + { + "asset_name": "020f0908050c100d0e0d0c0601000b0a0b09030c060200030400070910060602", + "policy_id": "06080601060006100e09070b0d0a060d000d0404050b0c0402000108", + "quantity": 6 + }, + { + "asset_name": "0b0f040d030d0b0f020a0a020610010b050f070f0c0a030c1009050808080c0c", + "policy_id": "010b0200060a050005090b0e0610050a080b090600000a090104080e", + "quantity": 5 + }, + { + "asset_name": "060b0d030101041006090d0a070a050a0100010a0d0a0c0f0009060201070d0e", + "policy_id": "0c0a0e01020c0c070e0e060d020e0603030d0507010c10010a060804", + "quantity": 1 + } + ] + }, + { + "address": "addr_test1vqcgjp3mh58c2ck22jk89sj36s94j8yj63hwuh3vlfqmvvg52ll2x", + "amount": { + "quantity": 36622293439019428, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0b060602080c0f050d05050d07090c0f0b0f0c09070c03080f0d080f10051010", + "policy_id": "010a02050c0d100e0e0e08050110070e080c0f01090004060309010e", + "quantity": 6 + }, + { + "asset_name": "0c100d08010b070f080e0904070200090f09010f05050210090e08100e030b09", + "policy_id": "09060f040f0d001005100a02040e040f0c0210090a060f0a0a001001", + "quantity": 5 + }, + { + "asset_name": "02030f0f01000906000607020a0c0b0a0f0d020e0205031003070b0307040009", + "policy_id": "000600010005070505020905000f0c000c0e0401100f080101071001", + "quantity": 1 + }, + { + "asset_name": "10090803070d010910030f020a0b0006100c0e00070202090906090c05100c0a", + "policy_id": "02100800070a060d050c0f0407100a10090f04090e090d000d090f0d", + "quantity": 7 + }, + { + "asset_name": "06061000060c03050a100804030d1006040e0b0e0a010d08090e0300040d020e", + "policy_id": "0c0c02020e0b0c0c080e030b100a060b0c0909000f030003020c0203", + "quantity": 3 + }, + { + "asset_name": "03020f0e0b010503070f050f0a0d08030e070705010c090604010b030302040b", + "policy_id": "090b0a0b0b050e09020a0e0d0a0304070d0b00070b0f0b0a0e0d0501", + "quantity": 4 + } + ] + }, + { + "address": "addr_test1qqsu4uxwwz3elrt0m9dfc293w9n499msq0vjnk82u6pcx27pr2cl475y6lhf6erwfq3073fhwcu69569dnq89h75zusqx8d9uy", + "amount": { + "quantity": 30720098430898939, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0e02020a01050010020a090509060807020a0404060a07060501030802030e06", + "policy_id": "0f06080a0a000c000502040f0d090310000a1009100a09050e10010f", + "quantity": 4 + }, + { + "asset_name": "0d0f0a0b020a080c05080b0e06091001050e0a030e03000a0d080b0b070d0a00", + "policy_id": "050a0a030b04020d0b04100a05080f080806080d010700080d0b0810", + "quantity": 1 + }, + { + "asset_name": "070a020e0d0307020f100e100f090f040e060103100b020f0709070a0a040e0c", + "policy_id": "100b0d010e04070706050b0e0801010d0a070f0b0e050c080b100204", + "quantity": 0 + }, + { + "asset_name": "0e021003050e010f0b040e040f000305020203030905030f07090d0a030b0e10", + "policy_id": "0c060f050f0904100b06000a0d030008090a0e05020a100c04050200", + "quantity": 5 + }, + { + "asset_name": "0d060602030207000e0e080f05070c09050f0e010a010d0b010e040307040f08", + "policy_id": "0f060a0204040c0b09100703050010100d0210010f0e0f0701020d0b", + "quantity": 9 + }, + { + "asset_name": "01000906050a01100e0c0d10060b06100a090a080805090c0c04070a0400060c", + "policy_id": "04100d04050c0708070c0e10070c02010e0d0e030710020e020d0b0c", + "quantity": 6 + }, + { + "asset_name": "0700080c0405030709050804020e040706000907040f050c0c0e05010508020f", + "policy_id": "040e0f040b0a061003100b030c0a0d04030c0d070409000e090c0d07", + "quantity": 8 + }, + { + "asset_name": "030f08020f0e00040d0505040600080d050f030a07080102080e0f0c0f090b06", + "policy_id": "0b0a0300100c040a0e0c080a07070e00040c06050a0308020d05080e", + "quantity": 5 + }, + { + "asset_name": "0d0d00000f0a040e0d0d010a100e100701030a0f03070804050c0b05080a000d", + "policy_id": "0c000708050605100a0f0104030709000c0e0c0207070d000108020f", + "quantity": 6 + }, + { + "asset_name": "0410080b1007040f08010b02100f0b00050102060109070f060b060b020f0500", + "policy_id": "040a09010e1008050a030f10060110020e08050400060b0e0a090b0c", + "quantity": 5 + }, + { + "asset_name": "060d0e000c0e0f0704050803100109000b010804090d0604030b0a0d09050507", + "policy_id": "0e0c0d0802050d03090b080408010500090508080d03060c0a0e040d", + "quantity": 7 + }, + { + "asset_name": "0b020808070302030701010e0e010e010703090e0c0c050a0c0c0c08090e1005", + "policy_id": "000c0c04060905010a030b0f001002060807010e100e080f070f0201", + "quantity": 9 + }, + { + "asset_name": "0403040e0e0d09080f030803060a0b0905030706030e080210010c08050b0906", + "policy_id": "0404080c0a0010060c0108020b0d050f01060f0401010b06100a0400", + "quantity": 1 + } + ] + }, + { + "address": "FHnt4NL7yPY6QCdNcRt1MhGZ7dTUa7dcytm98Evv3uuHaQYURUho1SDKuqvKB8S", + "amount": { + "quantity": 0, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0a020308090f02030c0f060c01070f0905060e0b0a0204050903090e1006020c", + "policy_id": "06000509030f01010d000603000b0f070a0b0f0b010d02060410060f", + "quantity": 7 + }, + { + "asset_name": "070e0609000f0e09030a05000810070c10000b080b070f0005100d0f0e020a07", + "policy_id": "0b0f05060b030c10050a040b09040600080b0908030d02030908030b", + "quantity": 3 + }, + { + "asset_name": "0a0c0f05050e03030b09040d06010e000305090b0c090808050b08010307080b", + "policy_id": "0c0d02030d0d00000b02100a07010a070304000b07000b0d040b1005", + "quantity": 5 + }, + { + "asset_name": "000d0b060c0f0e08070c0d010e0f1004030c040c06030d001010040f06010306", + "policy_id": "0407070c05040e0b01070f080a080f090204040003000b040c0b0509", + "quantity": 8 + }, + { + "asset_name": "0d0f0b0806070304010509100f0c10100b0b0309010e0508070908020f050905", + "policy_id": "010404010e020d0901060c0c090b1006050f0a080a07081008070108", + "quantity": 9 + }, + { + "asset_name": "0d030d0505060b07080d060004000301050306040507040d060e0900050d0a06", + "policy_id": "0d0a0808090107000f0f10060310071004030808090a0a0910040004", + "quantity": 4 + }, + { + "asset_name": "0b000a02100910100a0b0207010b0701030109030b0b100e0804070e040e090a", + "policy_id": "0c0e0c0b0b03070a0910100c090406070c07020707030b1002050e0c", + "quantity": 4 + }, + { + "asset_name": "06070a07020a0a0705070002090505050b0c0f0d060e0e050d08050b0405080a", + "policy_id": "0c0606090e0d0c0700080e0f080f0607040d100d0c070c0608020200", + "quantity": 3 + }, + { + "asset_name": "0d040c08050a05050705050f07060701020702000304080f080e0301020e0710", + "policy_id": "080000050103050b0b03070901050c0a030c0f0302101002080f0005", + "quantity": 7 + }, + { + "asset_name": "100e0200100e1000050a0f0f0b07040f010003100f0a05000e02010903010b08", + "policy_id": "03010e0e070e0208050d01070e0b0c060f0c0106070a020304100702", + "quantity": 6 + }, + { + "asset_name": "0d0e080602070e020a0b0d0e0b02080c0b0810020b0010020b100f0e030d0207", + "policy_id": "04010300080f040c07080c0c0b070e060e0c0e0c090c0a0c0f101000", + "quantity": 9 + }, + { + "asset_name": "04090b060a090608040607080d000e0e04060e0f06070e0e0e080e000f010406", + "policy_id": "02080c090710070b0b0e0e03080e05020a000c060d09100b09010906", + "quantity": 2 + }, + { + "asset_name": "10010110050e070906060c06061005040d07100f02050004070e0a0d0710080f", + "policy_id": "0002090207050c010907040805060f0d070b0b100f060300010d020e", + "quantity": 5 + }, + { + "asset_name": "0d070a030e0f01010b0605060d0d09080206040f0e0b0e0f07070a0b04040a00", + "policy_id": "050d0e02070005010f10060a030a050507010c0f0801000510020704", + "quantity": 8 + }, + { + "asset_name": "02020100050d01030c0602080210101001040e0b02090201020a040a01030501", + "policy_id": "040b0d0f04010e060d0d040e0003000c0e090f0d00090f0409090f04", + "quantity": 2 + }, + { + "asset_name": "02021010080e070909080b100a0e0d0a0f060203100a0f0c040d0e0010040a06", + "policy_id": "0410070b03010708010a09090c0b0706100f0001040b03060509040d", + "quantity": 7 + }, + { + "asset_name": "100e0e0f0b040e010e020a0c0c02080d0a020e01090e0e0703000200000b080d", + "policy_id": "040e0601000f0a0a040c0310100210020d100e070f0a0a0f0e07100c", + "quantity": 6 + }, + { + "asset_name": "070a0d010809070b0e100a0908100a0b00030f0705090707050f040f0c03090f", + "policy_id": "100d0d0802010b0c0504100709040d03010f0e0f010907020c0e0b0e", + "quantity": 4 + }, + { + "asset_name": "100705050d0b0905040b0e0c0f0c030e0d10090a030708060d05040b10070001", + "policy_id": "0506040e0706020a05020c070e100f0e0b0d06020e070d0700070d00", + "quantity": 7 + }, + { + "asset_name": "0c030a0b0d0c05100f0802100010100b0d0f0d0809070806040b100308040a0b", + "policy_id": "0904070307090b0301020c100d090500030d0401070f050e00050c09", + "quantity": 2 + }, + { + "asset_name": "1008030c0a04010204040800010a050b080b06010c0700080604030c0f090210", + "policy_id": "000606040e090a0b02060c0b0c0d04030a050c000c081003100e060b", + "quantity": 1 + }, + { + "asset_name": "0908000c100f080404020f030700070103030c0c100d10090707040a0e0c0808", + "policy_id": "060c050f080a0f01070f080002020808020b10030c0a0d03040d0505", + "quantity": 9 + }, + { + "asset_name": "02010c0b01050e000a010c10030c0d020100090d0c0e04050108000405070f0c", + "policy_id": "0910100b0b00050209050b0701080e02100b0b060e090503050a0b0c", + "quantity": 2 + }, + { + "asset_name": "0c0801070f020100080203030f0d0a0009040100050f0c000109070c060f060e", + "policy_id": "10100b0b0f060907070a080a010e0b020201050f0206040e0e0b0705", + "quantity": 3 + }, + { + "asset_name": "041008030f080e00051003070b0a01020a0b0609040e0a070b08030e08080705", + "policy_id": "02090210060c07100d080306030b06000306030e0e0b0c050e0f0304", + "quantity": 7 + }, + { + "asset_name": "000306000d030710000a010c0f07050c0c0d0c0307090a05020d10060c0e0d06", + "policy_id": "0a0600100f0d0a0e080203030001020d0806000709080403090f0703", + "quantity": 9 + }, + { + "asset_name": "0d060d0b070709020604060900060b040b0b00100f0508070806000a05090206", + "policy_id": "080b1009020c0e0f0e0910040d000f0d0d1000050b070505080c100a", + "quantity": 2 + }, + { + "asset_name": "07000a090d090b1002070c0a0f05060604070103070b0f070f00060804040d04", + "policy_id": "0d0900010507100f0308040d04050410100204070304100106070f10", + "quantity": 3 + }, + { + "asset_name": "010d07010300030200010d0c03100a10080a100304060e02040a0f09010a060a", + "policy_id": "0e07060a1008090d0d04030d05080e0b0e010b0e0108080e0d020d06", + "quantity": 8 + } + ] + }, + { + "address": "addr_test1ypcuvl8x7d357jra8xchuu29lyecdl66e5enk6vvkn279857ayq86uw2nu27awwzm30cexfr56rfzd7k4umekrv4jywqueevyt", + "amount": { + "quantity": 26857476288421005, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "100e0b00060510080a030f00060f0f0d050a0d0b020a04000a010d100f0e0103", + "policy_id": "060f050a030f0706060003050a0a060310060504000a090707040d01", + "quantity": 5 + }, + { + "asset_name": "1010020310040c06030508080b080a0a10100901070003010f04060e0e080900", + "policy_id": "0c0910090c0e100b0e00090003050c0f00020903100a0e0507030204", + "quantity": 8 + }, + { + "asset_name": "0d080c00090b00100400080e0a10030708010209060b0d0d0f08090b02030205", + "policy_id": "010e080200040b060606070e0c0c05090a0c10030400080702000f0d", + "quantity": 6 + }, + { + "asset_name": "0f080308020f030f0f080907060f06100d0805030109040f100501000a080d07", + "policy_id": "0c0008010f040e020a0f05041005040501050e08000c000f0c0b0c0f", + "quantity": 9 + }, + { + "asset_name": "05100e0e070104000105020b05010807100005061002100c0e0a0f10030a0a07", + "policy_id": "0405000410030a070d0a0e08040b0a00090301050c0b0109050d090a", + "quantity": 9 + }, + { + "asset_name": "06010b0f060a070205030b0f0b0a0f0d050c070e0808010e0d000e0609050f0a", + "policy_id": "0c04050e080f0e04030f0a010d0c0c0a0b09030e10010d1009030002", + "quantity": 7 + }, + { + "asset_name": "03060d0102010a09100a0b0d0d09000e060e030401060b0a0e0c0e0b030e050a", + "policy_id": "010b010c0d0d0e04030b0b050c0c09050b070e0b070c0f04050b0d0e", + "quantity": 8 + }, + { + "asset_name": "0906030e0e041001020b0d070f0e0801040b0b0202090e0100050c0a060b0c0a", + "policy_id": "0d070a1007020d0908030b0d0c0c10020e090e0e080f04010e05090f", + "quantity": 7 + }, + { + "asset_name": "0f0b0310000e0c0a100e080d0b040610080a081005090b030b100d0c09020002", + "policy_id": "0105070b0d100b0801080e0100000a050e070e09090d0f01020c0608", + "quantity": 9 + }, + { + "asset_name": "010d07091000020f050e0f0a080a0008010b0107020b0d0a030f0e070f0e0803", + "policy_id": "0e080b070d01010f0c03100c060e0802090c01070e090c0604100504", + "quantity": 0 + }, + { + "asset_name": "010009041008050b06070c07010b0c090d05010c090d020205100d080d020d06", + "policy_id": "0e070e08080305080d040a03000f0f051006051002070e0801060606", + "quantity": 6 + }, + { + "asset_name": "00060f070104020d0e0810010d100e050a05030a050c02100c0007030d000907", + "policy_id": "0510090f0502000d09041007020a0b060a0b0f09020a0702050c0003", + "quantity": 4 + }, + { + "asset_name": "090607080f0c050e020d0f09100103060b0a090d05070b0c100803070b0f030f", + "policy_id": "1002100607010601030d0809011002020d0207010c080606030f0b0d", + "quantity": 1 + }, + { + "asset_name": "0f020b0710100b00050308080707070b0b070e0100060b0c040c1007050c010d", + "policy_id": "070f090705030e070601020c0d100b0b0b0b0b10030e000c0b100610", + "quantity": 3 + }, + { + "asset_name": "0c0e030810020a09060d0a06070a0e0a090d100c0e0201100f0d100d09020004", + "policy_id": "0a05000d01070801020d10020903050a100b020f020e060d0402010b", + "quantity": 4 + }, + { + "asset_name": "0e02080f020709010a0a08100f010c050f0a06080004061006010a070b0f060e", + "policy_id": "0206010b0909070506000700090a02020e0e0f0a0a0d0e060b000c0e", + "quantity": 4 + }, + { + "asset_name": "06080c0a100305040a0f050408080801010d070810090d01050010050f020b01", + "policy_id": "01030c100c0b0a0b0c030b0e0e100b10000f05060b0e0c0b0509040b", + "quantity": 2 + }, + { + "asset_name": "0f09040c0a0b0e030e040c100d090d0b070a0f04090f080d050e090301010604", + "policy_id": "030d0c090a0c0e0b070f030900000b08100a10040f05100307030704", + "quantity": 5 + }, + { + "asset_name": "0f0a03070e020e0e0c0f031004090d0f0402000b040b0f08010f010e0f020010", + "policy_id": "020e050b080309070d0008010202100d0e1001100700080f060d0a0a", + "quantity": 1 + }, + { + "asset_name": "070e03030b0101070a0b02070e0e0d09050804040b050b02000e020903100e07", + "policy_id": "0a010707000303030b0c080e00100d06071002060a070901050c0603", + "quantity": 0 + }, + { + "asset_name": "070103050e0306040500070e060d0401060c0f06030f0402070402030b0a0a0b", + "policy_id": "0b1006040f0b0c020b0b0b0f02070a09080c0b03000007000a0a0c05", + "quantity": 4 + }, + { + "asset_name": "0f09060a02100009100b000a0b010610060304100a090c04040f040808050b04", + "policy_id": "0100050d090a09060d0a080204090705050a0a00040d0b090a0a0d05", + "quantity": 2 + }, + { + "asset_name": "0110100a0301100208030a050603070b050a0f0200050e090310060500080c00", + "policy_id": "02010b0703041003000a03040a0c0801100b040d0b0000070c0c080b", + "quantity": 7 + }, + { + "asset_name": "0503020304060e100305090a0c01100d08030907070b0a0b0d09000d0a060501", + "policy_id": "00060a0e030f0c04010d030e020d100604050d10000608000d100703", + "quantity": 1 } - }, - "policy_id": "16c636b039837f59a43fc06dcbaf6858fc0c5faf4ea3c0064f8350f8", - "reference_input": { - "id": "581358122e175d4947ee742e170d263a2f000a4506a32a74790b00295341285c", - "index": 1 - } + ] }, { - "asset_name": "546f6b656e53", - "operation": { - "mint": { - "quantity": 13, - "receiving_address": "addr_test1yrumvfvzxnnfqn6sj7ffjezt4v2grx444tya3rlmk9jmj2855yh0ufsrygf0dyl495cm8y0c8kpdxsrftlkf59a3320s8uss0w" - } + "address": "FHnt4NL7yPY5ALzjHziDL7CnVN6XxFEgKkWdEQgBcymMxRS62WJNPyonemAKXum", + "amount": { + "quantity": 45000000000000000, + "unit": "lovelace" }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } - }, - { - "asset_name": "546f6b656e4e", - "operation": { - "burn": { - "quantity": 25 + "assets": [ + { + "asset_name": "0c0e040806010703020a0f040d09020e0b100b0409060b040f0f080b0c090d10", + "policy_id": "01100204090406000d02020a0a080a080905050c0403030a0702020c", + "quantity": 2 + }, + { + "asset_name": "10000d09050305080f010401000c101002040c0602050c06060901090c0f0d02", + "policy_id": "0e0b0e07080610090304000c0d04040409080b020a0a020210040f0f", + "quantity": 7 + }, + { + "asset_name": "0b070a10080c010f060a0700100406040b0d070a0301030104070d0f030d0c0d", + "policy_id": "05060b0f040b00080006040d03050c0a06010f050101030d0f100d06", + "quantity": 3 + }, + { + "asset_name": "09010303100d10000e0e0f0f0101020a070c0c0400080909010702090b030200", + "policy_id": "0109030d0d030b0a0806080d010d0805050403050c080b0104100c10", + "quantity": 5 + }, + { + "asset_name": "050d0c05090c0d0f010c080d10100e0a10060f04020f010f1000060a02050909", + "policy_id": "0209020806060301080c0c080102090e080d0410050f0e060d0b0f0d", + "quantity": 7 + }, + { + "asset_name": "00010002030c00020f030a08100004030b0e0a0b0e0d000e011000020802100c", + "policy_id": "0a000f10090c0e0b0b020004060301040210020c070b090d00070e0c", + "quantity": 8 + }, + { + "asset_name": "070a0405080a0300020904100902030b100c04060e0f0e03040d0a090c081006", + "policy_id": "040a090c060d0b100b0806010f01000c0a070d0c0b07010d03030f0e", + "quantity": 0 } - }, - "policy_id": "72e44eb552ff30d2f7820695d4baabb1b2e3f9e5450efc1f687cef1b", - "reference_input": { - "id": "145e7d89e18c5ef37113797e37357c2e48a8decc44576c78216a2a403507276b", - "index": 0 - } + ] }, { - "operation": { - "mint": { - "quantity": 5, - "receiving_address": "FHnt4NL7yPXtybeeSjbWUfKNDavY71GT3cYWd7dXpEoMoe92KHtoEQS3YgszVQL" - } + "address": "addr_test1zzqala8hmyrk3e7khnkjm3pn05zda04sz30urgve84ee2twdp50yhf95lsq8e2kyy54u39ly6pf2rc9g66v3kpc8wflqgvcnnp", + "amount": { + "quantity": 34076164364096467, + "unit": "lovelace" }, - "policy_id": "d82a81f69ce6c63b29c2644197103d58aab7eb36831331069281731d", - "reference_input": { - "id": "4b6a6174ada82b3c270c450113dc2801150f1f064e6bf15031500a3e6e397544", - "index": 1 - } - }, - { - "operation": { - "burn": { + "assets": [ + { + "asset_name": "0e090f0b0f060500100b020a080a00100402090b060601080d070005000d0b03", + "policy_id": "0206080e04040e0d0b040e00090d0b090109030a080b0c0e0902010a", + "quantity": 7 + }, + { + "asset_name": "0c0f1002090b0b06000b0a0d040d08090e04070a100f080b030c0d07000e0408", + "policy_id": "0c080c0a0e060e03040d0a0d010503050d03080e0208080806090a0b", + "quantity": 8 + }, + { + "asset_name": "0305010009050408060907070d05090202060d030a0a02010a0d0506090f0e05", + "policy_id": "09050c0f010905070b0e0c02060a000e0b040a03020404070f0b1009", + "quantity": 8 + }, + { + "asset_name": "030f091000050007000c0705060f0d0e07000801070410000801050c06080e0a", + "policy_id": "10040f040f0c02060500080f0a0c030a040a0801020107040b080909", + "quantity": 5 + }, + { + "asset_name": "0f01030d0d0e0e090b0a0308000e02070007060a0c0a03060d06050a0e050b06", + "policy_id": "0202050c0d030d0a0e000d070c0c000f0907060c000b0b0e100e0510", + "quantity": 2 + }, + { + "asset_name": "090a0e0605090c100202050a0a0d030a0c0109100e0e070004090c0b010e0802", + "policy_id": "0e10100b0f070b061005010f0d030809070c09080e040c0c0a0f0501", + "quantity": 5 + }, + { + "asset_name": "0c0f0e03080e03030d0a0504010a0d0f0c03060a0b0d010707050600090a0004", + "policy_id": "0c0e0f0b0b100f08020400080f000104050c0e09010302010e0f1004", + "quantity": 9 + }, + { + "asset_name": "0d06000706080f050904100a05020b040a05030103050e02020f0b0e0709070a", + "policy_id": "03020e04100810020d10050708050a030a09090609090c010d0b0905", + "quantity": 9 + }, + { + "asset_name": "0e0f0c05020d0d0f060103100c0d030b070a0f0d0d0f00070f08040d07040a09", + "policy_id": "0303090d08030a08030a050c02020e05060d0e0f020f04050c0b0d0b", + "quantity": 3 + }, + { + "asset_name": "03070c0f060f0f000209070004040a071000030d0606000c01040f1002050407", + "policy_id": "0e0a0d0b100b0302050d08080b0a0c0701100c01080f0b06030d0601", + "quantity": 9 + }, + { + "asset_name": "0c020c000605030b0b000102070b0b0310010d050810020e0400000b0a040910", + "policy_id": "04070c070a0c050c0303050b0702090107030b0d0a010a0b0c0f020b", + "quantity": 9 + }, + { + "asset_name": "04090e0a040c0e08030e09030e070b040c090c0106000c0d020f0c10040a0d03", + "policy_id": "0b0e0a0504070a0f0a060205060f0703010b0a020c04070c0f0c050f", + "quantity": 1 + }, + { + "asset_name": "021003050d0601060508040d050b09040f090f06010a0707070a041003050a07", + "policy_id": "060907000706060f09030b060b00100805030c0b040c0109040e040d", + "quantity": 2 + }, + { + "asset_name": "0a1004080a0f050b0100080505010c0e05040c0407060806090d03090c02100a", + "policy_id": "08070b0307010e0f060d050f0e08080b0803010c0c080a070e0d0c07", "quantity": 9 + }, + { + "asset_name": "0e030c0b0d060f070703090b040e0c0401020c0903050c100505010407100d0f", + "policy_id": "0b0b0d06050910021010040e08080d000a0100030804080d0d0e0610", + "quantity": 4 + }, + { + "asset_name": "0d0a0308070e0a0404010d040b070b080e0c0e010b0a010a0c010405090b0e0c", + "policy_id": "021002000d0908090a100805090a06070a090c0e100d0f03000a0d0f", + "quantity": 3 + }, + { + "asset_name": "0b04000d0d0e0f0b080c020a0c02000a0c030a0a0f0306020504030f020e0b07", + "policy_id": "0b0a0307010d00040e00010d0408000f0d06090f030d021001100710", + "quantity": 1 } - }, - "policy_script_template": "cosigner#0" + ] }, { - "operation": { - "burn": { - "quantity": 5 - } + "address": "FHnt4NL7yPY48PQKZmT8ZGBf36h78ouF5sGR8o2sTzVfGq4hPPK2S6LYyv7RsXV", + "amount": { + "quantity": 37732444933221998, + "unit": "lovelace" }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } - }, - { - "operation": { - "mint": { - "quantity": 6, - "receiving_address": "FHnt4NL7yPY7UrKKSFEVgvsa2WGLBnhC68U3CnchRpAreU9AZEAFJSsLUhSkzLe" + "assets": [ + { + "asset_name": "0b090602000d01010b0202050b0b010b0e0208050e0602060d0a050b07000402", + "policy_id": "0c090c0e0d010d0a070f080b0a0b090e0001091010100a1005090403", + "quantity": 4 + }, + { + "asset_name": "0d00000d010010080a060f100b09080f0a070e10080f0c070d02060401100400", + "policy_id": "090b01100a02100210010108080b00020b060805090e0300000b080f", + "quantity": 8 + }, + { + "asset_name": "0a0207090e0102000207100906050f0a090d03000303040a080c0e0b0b100400", + "policy_id": "030f05030e0a0f0a08000b050907030808100a050b001000080a0c10", + "quantity": 3 + }, + { + "asset_name": "04000b02090f0d09020b08070f1009070c000e0d080b010b070e051004030d04", + "policy_id": "060603000e020b0b0e07020802000b050a0b0f08010605030802030c", + "quantity": 4 + }, + { + "asset_name": "0b0e00000f040c010100040d0d070502070e080e0d0a02050108040310090004", + "policy_id": "08090d0c0c0509060e03020a0b060c060a090810030307080d070d0a", + "quantity": 2 + }, + { + "asset_name": "010203060b0703000703070000050d0c0f040102080b0c0b0803000900000903", + "policy_id": "0c0403040d0310010f020a000906020c0f0906010208090500050705", + "quantity": 4 + }, + { + "asset_name": "030a100b0c04070b000e100b000b030d0003030b0e060e0d0f0e09100a040801", + "policy_id": "0e0709020b01020c050206020c0f0608020e01090d0f0b03080c0206", + "quantity": 1 + }, + { + "asset_name": "0501010410020c07040c09010d0108041002020c030e09050000080200090e07", + "policy_id": "070507070408010a100e0b061006040e0e080e05090e0f0c030a0d06", + "quantity": 4 } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } + ] }, { - "asset_name": "546f6b656e4e", - "operation": { - "burn": { - "quantity": 26 - } + "address": "addr_test1vqcctvpq5yl6l06mqz6gprjl39xr5y8l3n5vlesyhh6fjrg2eztnm", + "amount": { + "quantity": 16180042495861769, + "unit": "lovelace" }, - "policy_script_template": "cosigner#0" - } - ], - "payments": [ + "assets": [ + { + "asset_name": "080c0508020d0405060a080a0e0e06040d06090e0c0d0d1000060e0f0d08090e", + "policy_id": "000f0c0408000f0e08020a060c0d0304080b040a0a0410060f0b0b00", + "quantity": 1 + }, + { + "asset_name": "030f0c060b0c0f04080a0f0710090f0603050f07080e0a020d040d02010d0008", + "policy_id": "10060a000a07100500010b0d05010f0f0c0c100904100d0104070701", + "quantity": 9 + } + ] + }, { - "address": "FHnt4NL7yPYDjUFQ6LXon9EsD4DNApwaA3mwWev8Nwcz8PGDmsXA4EivEvzciNM", + "address": "FHnt4NL7yPXpnquFhfz6Q38rmodTrSsbvECuAAAe5JuHaq9gktr72pi7BEFmZZQ", "amount": { - "quantity": 76, + "quantity": 10700488568268712, "unit": "lovelace" }, - "assets": [] + "assets": [ + { + "asset_name": "040f0c0f0c0b100c0e0f0e0d050c100c0605030e0f030a0e0d0d09090b0a070f", + "policy_id": "10060301090a10040c0a06080c07050308060d03040f0001080a0d0c", + "quantity": 4 + }, + { + "asset_name": "0402060d020108080e0b09050f0c0d0c0e0a0e0b000d100d0d0201020c070705", + "policy_id": "0103070b0e0107090c030b0a01030a0f000d05050109090401080c02", + "quantity": 8 + }, + { + "asset_name": "0c1001000d000d070c060f0c0b000f0c100c01100800080c0c10100e05060302", + "policy_id": "070e080d0b01100a04060e070b000101000e08100d0d10080e0b0810", + "quantity": 1 + }, + { + "asset_name": "030d0206030e0a0d0b0a100f05020206010c07100b0a101002081009090e0a0e", + "policy_id": "0607080a0106080e0e0a0a0a0406010905070d02010b0e0506080006", + "quantity": 0 + }, + { + "asset_name": "08020a04070610090f030e010102090d0e0e070e0b000c040302070803010e0f", + "policy_id": "030f0608000d010f050b0b01040e0000060202080d0510040b020c0b", + "quantity": 2 + }, + { + "asset_name": "06080707050801010c06100d0b0507050600060a0f100d0c01080004040a020a", + "policy_id": "0509080801090e0708000b0a02010b0c05020d05000d100304090308", + "quantity": 6 + }, + { + "asset_name": "0209070a040f0902010d0d09080f000806060c060d0b10020a07040909060008", + "policy_id": "0e0605100609030d01000502090405080f0b01090f030503020e1006", + "quantity": 4 + }, + { + "asset_name": "0404020f0908020a030a080d090d0a09100f1005000401050d010c090f0c0e0e", + "policy_id": "0900070e030d020f060b100f0b0a0e090b0705040f0d0804020d1010", + "quantity": 7 + }, + { + "asset_name": "030402100e01090f070706040d010b0b100a0f0a0305040c040b08090f100503", + "policy_id": "0002000e0c0a0b010b03050b050d01040d020b000d0d0b020f091003", + "quantity": 1 + }, + { + "asset_name": "0b090a0b10000f040904050e070106080d010a060c0e100b040e030f0605090f", + "policy_id": "0d0403050b0100070f0a04050d07090c0102010a0008070f0f080c07", + "quantity": 4 + }, + { + "asset_name": "0e06070903040d04030e090105031004020d0d05020b02070a070b0d0b0a0810", + "policy_id": "0f080d080310000a0a000f100a08080507090106050602070e0c0009", + "quantity": 1 + }, + { + "asset_name": "0f020701090008040c0e0b0d020709011008000c0a070200011002100804060b", + "policy_id": "0d0700080f09080a05050906040b0d0502030206090810030400010c", + "quantity": 5 + }, + { + "asset_name": "0b0e10000d0a0b0b060f04000009060b01020b0904020309060e0d0d060b050e", + "policy_id": "01030f0b0800090a050c09090d0409020105020a0100080d0d0b0202", + "quantity": 3 + }, + { + "asset_name": "10031006090b0c0505010a010e08000b080a0b080d100704050e030b00080b0b", + "policy_id": "090f0c030e0d090d0d0100080d0008020309090c0f090b0602020706", + "quantity": 2 + }, + { + "asset_name": "040d0105040a060f06030608080401080a0b0e000d06060f100606090f0b030e", + "policy_id": "0801100a060a010a0106010607080801000b0c05050b040a030b050d", + "quantity": 8 + }, + { + "asset_name": "0a0e0e070f100101000b04100607070e07020106050010030f080e07090f0a0b", + "policy_id": "040d030f020001060b0e010c0803100c0100030e10050e0008050203", + "quantity": 9 + } + ] }, { - "address": "addr_test1xqdjd999qkp8d4c4uvtxpsvjhqefxty5mr5x6slpmmk2v95qdc228j8f94jp5qmkfw04ky9jlvljxekj9zt4ns66wans9vtzxv", + "address": "FHnt4NL7yPXkxcynSFcFNRRhe6HnUDtTgsBciubxLPnkvKuxLeTUKFcqNpH1m1W", "amount": { - "quantity": 16, + "quantity": 0, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 7 + "asset_name": "040c010a050c03000b0400030f05020a0e020f030a030c0f050b060f0d070500", + "policy_id": "0c09040c010b0c0f00010306060b0004040a040d040e0d0d00040f0d", + "quantity": 0 }, { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 10 + "asset_name": "04000b000c0f0a090b0c0c100202010d050b040a0b0f0b081004010c020f0e08", + "policy_id": "060e0f0d0703040c05050e06010f0610050a06030800100a0e0c050d", + "quantity": 9 }, { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 12 + "asset_name": "0d040f010b03020c0b0209060e0c0b04090f0c000f0e010e010f0d09020b0d04", + "policy_id": "000d0b02050a0a040c090f0b100f02080f0f0900100a0b020b020f00", + "quantity": 6 }, { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", + "asset_name": "070c0e0e0c0c000a09000d0b05100904060209040f0701030e10010d0a000202", + "policy_id": "020b0305070c0703050c0302071001030b020405020d03030c0a0603", "quantity": 3 }, { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", + "asset_name": "06050d0110090e02080c010d00070a0504060a04090d080800030d0609061008", + "policy_id": "100f050e0b08060a0d00050f10050101060b0b0d070e0a030b0e0e0d", "quantity": 2 - } - ] - }, - { - "address": "FHnt4NL7yPXq47rB5BmCUFzizeXgCe6r7Wpbi1uG8cWPXZSisiyHwrzQi6J1arF", - "amount": { - "quantity": 180, - "unit": "lovelace" - }, - "assets": [ + }, { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 1 + "asset_name": "090b04050b0d000d090e060b0a0310000f100f0b1000040a090905100f050705", + "policy_id": "02070b0801030900030b03080c1006070a080001040310090f040b0a", + "quantity": 6 + }, + { + "asset_name": "0d100c02040e060b04090c0d100b05010910060f0a070f00080a100e100d0703", + "policy_id": "060605020f0a0c0209080c0d0606100f090e10050d03000809060202", + "quantity": 2 + }, + { + "asset_name": "040a0406030b0c070a0006020d0e0706050a0a0e0d0c0005090403040408070c", + "policy_id": "0f02050c020705040c051002030f0c0b0c0b020a040a020105020f10", + "quantity": 0 + }, + { + "asset_name": "060f101009060301050a01100b07100e070d0a0d0e050e020d0907040f080d02", + "policy_id": "07020b060d0f0a0d0f080c090b0c030406070a000d0610080205100b", + "quantity": 9 + }, + { + "asset_name": "05070406100e0d020107030010090f0504010a010a0b030a100a0a0e0d060c00", + "policy_id": "0504020e0e060f0e0c0909020810040b0809100c0c0b0a0d00040700", + "quantity": 2 + }, + { + "asset_name": "0c02010f05060e08060309080a0408010f0f0c0e05100b0a050807060f0f0d02", + "policy_id": "0a0b030b0706080a0c010100040e071005100a0200001001020c0310", + "quantity": 3 + }, + { + "asset_name": "000400100c0f0908030102040e05000b08010d010c0a010f0d0c040307080403", + "policy_id": "000e0c0102100b08020404090e0710070900090f0c101006010b0808", + "quantity": 9 + }, + { + "asset_name": "02030e0e100e040f02090603040004060e04070201090102100e03090c0f0510", + "policy_id": "0f070109060c07060406010c080d0e1001080e0e01020f1009010810", + "quantity": 8 + }, + { + "asset_name": "06030e010c10060f0b0b030e0e10100c060409040a0e0d0c090510040a000708", + "policy_id": "02060105050b0c0100000a020b020007000e080000060c0a0e06030f", + "quantity": 8 + }, + { + "asset_name": "0d08000103050a050f050b040c020e060e0f0409080c0c010f0209060a010801", + "policy_id": "04090e020303050c01070603060f09000d0f010a010102020a010c08", + "quantity": 6 + }, + { + "asset_name": "050f080a0e09060a0d0b0d0b09070c0c0e0a0a060804050c100f0a0804050708", + "policy_id": "0a0802090f0d0d090a0d0b0a0a100f0a0008050a03000a020e0b0e09", + "quantity": 7 + }, + { + "asset_name": "04020b1008080c0f0807040b070005100a0f0402070f050c0b0e0a0e060d030b", + "policy_id": "0d070c050d0c030010050e060c0f000809100b02020b10050f010c09", + "quantity": 0 + }, + { + "asset_name": "07100005070408080f0f010801020803090709050d0907030f00080a09080c06", + "policy_id": "0d0400020c0507080e0509030e030b050c05000b0c0a0a030f020309", + "quantity": 4 + }, + { + "asset_name": "101010060c0a0200011003080a03040c0a08080e0f090b100300070710100b04", + "policy_id": "030f070609090107040e10040f070207060c0b0e0f0c0f020b010f0b", + "quantity": 8 } ] }, { - "address": "FHnt4NL7yPXsh1VdV1V9pt3avNKdpiNPWZf87wnoSWz9r8t2J4JsTf677W7rFwc", - "amount": { - "quantity": 162, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "addr_test1zz7g620e86tyyx2xz5szck2tstrd2aw7y96f2hytr6dx8gqygralxxgcurxtstnjhl4wlxqt9yye89dcm4pc79fellrsgpd0m7", + "address": "FHnt4NL7yPY6TUKswM4Dz7sPpWHSz77BhiFbtYTyziygQMe3WZPhvE746cdbemc", "amount": { - "quantity": 128, + "quantity": 38762896222651204, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 51 + "asset_name": "06040d020c0e030b07080f0a0c07060e0e0d0300070110040f0f050c0803020e", + "policy_id": "0b040f060505100e0909050600100d0a030a000c0901100906100209", + "quantity": 3 }, { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 19 + "asset_name": "02100f0e08100d080f07080803030a0f0f0d0005100e040f0f0603011008050d", + "policy_id": "0208040c040409030d0a0405030206060d0f09031006070a070d0b00", + "quantity": 0 + }, + { + "asset_name": "091006070d0d0304030a0d0d0e0406050b0507080306000d030000070d050702", + "policy_id": "020d0b0d0f050e0d08100809050e0d0f0a070505090a040007080c0b", + "quantity": 4 }, { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 16 + "asset_name": "070603030c0f0f0c0008080e0a0f09060604040c03100d09100c0a0f0a05090c", + "policy_id": "060500050007010d08080903010304090309010f0610000108070c03", + "quantity": 8 + }, + { + "asset_name": "070a0e0d0a0407021009090203020d0e1004050d0e0d0f03010b080f06100604", + "policy_id": "0a010306060c0a070d0e070d08080a071009010d0b03000502090107", + "quantity": 9 }, { - "asset_name": "546f6b656e45", - "policy_id": "11111111111111111111111111111111111111111111111111111111", + "asset_name": "0710050200000c0c09050402050f0c06000b0d1009050408000b03020d0b0303", + "policy_id": "09080c0406040f0e0206040702100907030c07060007030f01020e0a", + "quantity": 6 + }, + { + "asset_name": "0b0f0b050d0c0e000b0c0b020b0b090c0a0007080e0d0e070f0303030c050d02", + "policy_id": "0005060910010b0604070e0708060b040610070210070e0707090601", "quantity": 1 }, { - "asset_name": "546f6b656e41", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 41 - } - ] - }, - { - "address": "FHnt4NL7yPY7g61N3EwmxBoQuzUw3ZZqUKnfDdNzTCZYkWPxMi2qybFHLf7HV7k", - "amount": { - "quantity": 90, - "unit": "lovelace" - }, - "assets": [ + "asset_name": "10060b0f0009080300020c06060f0d060003000a0804060e040e040a01080b0c", + "policy_id": "0308080008050f010f0902080603100b0c020b010301081007090f0d", + "quantity": 7 + }, { - "asset_name": "546f6b656e42", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 29 + "asset_name": "060c0b0b1009020d0c0f0702080a0107080a09050b0601070d020201030a0606", + "policy_id": "0f070a06060010030b040c010d0d100f0b0f07060b01100b00060409", + "quantity": 7 }, { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 22 + "asset_name": "0d0b10040107070a03010101050b020b0d0e000806050a0c040100040a100c07", + "policy_id": "060b0c0e03100705000f0905060903070d080000050e050e0803010c", + "quantity": 5 }, { - "asset_name": "546f6b656e45", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 44 - } - ] - }, - { - "address": "FHnt4NL7yPXzy8At2WPY5kc4kYTRbbir3XGbuvqYkDKoUKqxeckybht4NZ4ZdQC", - "amount": { - "quantity": 182, - "unit": "lovelace" - }, - "assets": [ + "asset_name": "03000403060a000810020400090a070e03020801030400050e050f010e0d0c01", + "policy_id": "020302030907090206100d040906050e04010f0607090c0d0f06040b", + "quantity": 6 + }, { - "asset_name": "546f6b656e42", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 12 + "asset_name": "000106011002000b0f01030b000909030a030d0d000d09040e07080e0c0a060b", + "policy_id": "0f010e060d020e100c07070508100208010b0c03020b000a0c0d020c", + "quantity": 8 }, { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 33 + "asset_name": "0f0406060507020a0b0e0d100208090d0a060302020604070803060c000b0103", + "policy_id": "0c0c0c01030d050d05100d0807100c060e0b0d0e0708020e01070401", + "quantity": 8 }, { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 16 + "asset_name": "070604010a010a080f0b020e0c0101000c0604080802080f030b010e100e0b0b", + "policy_id": "0c01081004030c00050d000f060403010601060c0c0d000f050f0e10", + "quantity": 5 }, { - "asset_name": "546f6b656e41", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 30 + "asset_name": "060a03060e060b090b0c01000e081003070605100805010f080708090a0b070d", + "policy_id": "0f010c0b080a04050105090e090807060004020b060d080607000c07", + "quantity": 8 }, { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 20 + "asset_name": "07090a0e0b0d0d0d0c0906061001070f0d0f0700090401070b1010080a041004", + "policy_id": "080e0200070000040409080f100d02100704020d00020f0c09060f0e", + "quantity": 4 }, { - "asset_name": "546f6b656e45", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 45 + "asset_name": "07090a0c0b0c0d0b0f0b0b0c00080c090f0203080b060d0003080a0f0c090c0e", + "policy_id": "090d03040b05100b0a0b0e070b0c0a030407080109040f0c05070e0e", + "quantity": 4 }, { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 16 + "asset_name": "0f08100501100d0c0503010b080a0305060b0d0f090f01100e05050a0b090806", + "policy_id": "0605070f0f0b0a0c09080f03030707060804070d07060904000f0208", + "quantity": 9 }, { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 18 + "asset_name": "0f0f0f090707100305090b0a0d05040e0b06090508010b0e05061003040d0706", + "policy_id": "050f060b020d0c0b0d050c050508050d0b100302070e0d0209100d06", + "quantity": 8 }, { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 17 - } - ] - }, - { - "address": "FHnt4NL7yPYFzyutaq5xUTQVmirsKtB5w9DL3zRcnuEv4iQMf4hFceoLKz3S9TR", - "amount": { - "quantity": 100, - "unit": "lovelace" - }, - "assets": [ + "asset_name": "09050d0e000e10040c05040304030200040708050f0f04040802090708090b09", + "policy_id": "0d03041006030d03060e020906070e09060a0d06080f0f0d100b0b0c", + "quantity": 1 + }, { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 7 - } - ] - }, - { - "address": "addr_test1xzffqhgm4z6m5pxzr7p5rk3c73yz2y6d2gjhu4vds7f4erg9ar6gwhjn57un5x2p6w4fwu8r05gxry46czu65566gyvsvrjth0", - "amount": { - "quantity": 52, - "unit": "lovelace" - }, - "assets": [] - } - ] - }, - { - "delegations": [ - { - "join": { - "pool": "pool1wusqveqhr43s6wnmxfq42vstw5py2qruwd55ylqp2sghszd37kn", - "stake_key_index": "79" - } - }, - { - "quit": { - "stake_key_index": "11249" - } - }, - { - "quit": { - "stake_key_index": "4453" - } - }, - { - "join": { - "pool": "pool18uczckew858n7nsvvqgk6q3xgugz7a3nxaxh56gexansz8v0qlm", - "stake_key_index": "128" - } - }, - { - "quit": { - "stake_key_index": "8927" - } - }, - { - "join": { - "pool": "pool1gd6k70pfzamk20pwg4qrgcpxq4lpvnq0fdznxqnqd4fxuzjgzag", - "stake_key_index": "86" - } - }, - { - "quit": { - "stake_key_index": "8742" - } - }, - { - "quit": { - "stake_key_index": "6095" - } - }, - { - "join": { - "pool": "pool1zephc83e09xnzamtzywrvwe0zdmj2mcnwdjx67r8deez7qy9eel", - "stake_key_index": "37" - } - }, - { - "quit": { - "stake_key_index": "4640" - } - }, - { - "quit": { - "stake_key_index": "3822" - } - }, - { - "join": { - "pool": "pool1fy7ngtmppgzp25tsde3yvwzpvp9q6zp9tea973twtu35whws9rd", - "stake_key_index": "59" - } - }, - { - "quit": { - "stake_key_index": "9854" - } - }, - { - "join": { - "pool": "pool1gdt4unr224tksqtryp9nut2pyaj424puz9lhkgqwvg3xvnlzrug", - "stake_key_index": "37" - } - }, - { - "join": { - "pool": "pool19q8hz7eagqypu8pd2e9hgzcfzue369jygyp3c9ctzcvjjvx3mhv", - "stake_key_index": "54" - } - }, - { - "quit": { - "stake_key_index": "2840" - } - }, - { - "join": { - "pool": "pool1tey46gnup3pxzfr98eg8ja3mx92nu62zze7ycesqfd69wyj9l0f", - "stake_key_index": "95" - } - }, - { - "quit": { - "stake_key_index": "11932" - } - }, - { - "join": { - "pool": "pool1g4es57fcty5yv965rgzsv4mwrsyz7vj4f34k7aggrvxzwngjs4d", - "stake_key_index": "74" - } - } - ], - "encoding": "base16", - "encrypt_metadata": { - "passphrase": "RAE𢧟㜏⏙Dru*9Se)D𐀗,3pAEj5`,4*4R$&𦣐9a𖨨렂,3M7K&O҄𢓯𮇩,e⥠y1_KG#𬿸krPP\"j:49,錅𦵂eb\\𠠺𢬾iB~:#ᒚ" - }, - "metadata": { - "13": "􎳸" - }, - "mint_burn": [ - { - "asset_name": "546f6b656e42", - "operation": { - "mint": { - "quantity": 11, - "receiving_address": "FHnt4NL7yPXyRH5mbSDEx74ciQvXeiV678e5kp7ciBfcmbjFLuBv7PjnndAztzk" - } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } - }, - { - "asset_name": "546f6b656e45", - "operation": { - "mint": { - "quantity": 25 - } - }, - "policy_id": "71e86bd058fb45039e73989d2f4f5b4b0e403e2d6a73bf439c0bf881", - "reference_input": { - "id": "f2222912096f331a41363e5f711260244d5803625f8d74793a079f4c0c03856c", - "index": 0 - } - }, - { - "asset_name": "546f6b656e57", - "operation": { - "mint": { - "quantity": 7, - "receiving_address": "addr_test1wqnjsuq6p7rckj2ntxea8vdu32a6kd57643eff5g5w5p53guafkkf" + "asset_name": "05070d030401030a090910050f0e0903000808080600090c08060008030a040c", + "policy_id": "03050d00020007010703060b0b0d0309070c07090708020307080302", + "quantity": 3 + }, + { + "asset_name": "10050f0d040b060e07080104020906031006050e000a070c0b0709100c00040f", + "policy_id": "080807090201040f0601030d00090b0e07020f100407060210090005", + "quantity": 6 + }, + { + "asset_name": "0a0b0b1010100e060f0305090107020402050502090e020203050f06060a050b", + "policy_id": "0d0d0c0f0a020c050f0f0403100a0204040908060f0c0009030d0a09", + "quantity": 1 } - }, - "policy_id": "3fb29c761d78e80579290dab0261635046a86183dc5c9f503317103d", - "reference_input": { - "id": "48e87518533a34712d09197d17263f4c66d66629051709147c3611730e2c3100", - "index": 1 - } + ] }, { - "asset_name": "546f6b656e47", - "operation": { - "burn": { - "quantity": 17 - } + "address": "FHnt4NL7yPYJYkoA3XjqVyMK1Ls9ioG5cqDwZut4NbUWKPZV9FVnx7tC8fGmNLv", + "amount": { + "quantity": 684226364482560, + "unit": "lovelace" }, - "policy_id": "26a2aa8eff26d7908b846b74dddc2f0becab43fed8fd380dd6c30ccb", - "reference_input": { - "id": "1529674696577642443a6031535b31612e0209eb78185f4d364618811bc74840", - "index": 1 - } - }, - { - "operation": { - "burn": { + "assets": [ + { + "asset_name": "0b070e0c00050b0a0e0f0f020a080501030803030b000404000b070408100d0c", + "policy_id": "09050a0309010700090f00040a01010a0f020703000b0f0809050901", + "quantity": 9 + }, + { + "asset_name": "050402090a070b070f0c100f00030b00000009050710070b0b0b0b0204010f0b", + "policy_id": "0005060a0b100c06040a030a1007030e0f0b0804090b0006100b0908", + "quantity": 9 + }, + { + "asset_name": "04020b06080f070e0200010a0d010d090b090a010a0608060800080f02060905", + "policy_id": "0e0e0f0403080110030b00010e08070a0b0a0200100a050f060c0510", + "quantity": 8 + }, + { + "asset_name": "020a0e10040407070c060f0a0b0308090900051010040e010a0307080a020107", + "policy_id": "0a0d0010070a0d000510100e000e060c0009060d0e0d03040b080a02", + "quantity": 5 + }, + { + "asset_name": "050f0802010205090f0d0f03070601070e0c0c01030804070c000506040e0209", + "policy_id": "06020e001010060c09070d0404040b01010f0b100d0f0c020402080e", + "quantity": 0 + }, + { + "asset_name": "1001090e0a080f0c030807100d000f040d0f07020002000c0f0f040b040c0807", + "policy_id": "050c0b08080d080e0a0e050a0202060c050f0c03040f0e070e0b0010", + "quantity": 5 + }, + { + "asset_name": "000c0a050c0608010a0d080e040909060f0b030801090b030e090a100909060a", + "policy_id": "0f0f02020b040b0c0c060e040903070703060f030e090d04050a0d0c", + "quantity": 7 + }, + { + "asset_name": "0e070f0f050d0f0f000f0701010703090a100c060701060d0e0b07050900050c", + "policy_id": "090305040e100b06080a05020104080d0a0f0500060c050d0c07100e", "quantity": 2 + }, + { + "asset_name": "0c0b0a07010906050a08040901070607090901100e0d0100000a060308070803", + "policy_id": "08100f0f08090505050c080401070c00070c0107010105040e050a08", + "quantity": 1 + }, + { + "asset_name": "03080304090f010801040e030b050801070c0f08100f01010f0a100e0d0a010e", + "policy_id": "0302010104040e040e100c0f0f0a0403020e0b0004050a0902010b02", + "quantity": 9 + }, + { + "asset_name": "0706100d080609000c0f0801040b0109031005101005030a0808040302100f0b", + "policy_id": "07100d07100a0e05100e0f100f0f0a0700050d0d00020c0b0e0f080e", + "quantity": 4 + }, + { + "asset_name": "08030f090d000d0009080f02000c040e080601090f050f06070a0a09090b0f0a", + "policy_id": "09040e0f060b040a0e0f0a0d04060a0c0410090e0f0005010a000a05", + "quantity": 3 + }, + { + "asset_name": "010b0d09070e100b02080509090b020c0a05040704100104050b0a0d0d0e0f04", + "policy_id": "02030c0d0101050907060b1006020709040c010408100a0c03100200", + "quantity": 1 + }, + { + "asset_name": "0b100d090f100905000f0c02070210070b0c070c000801100b0510090f060f0c", + "policy_id": "020a030b040e0f0a050706010b000e010b06070809020809100b0a0d", + "quantity": 0 + }, + { + "asset_name": "050509030b010403080803100c0106020b04100d06030d0d000c0b0b06080708", + "policy_id": "0d10100e0d050303030f1010070b060402080b020a07090b000d000f", + "quantity": 0 + }, + { + "asset_name": "050f01010707040909010a080b02100e1007080b0e050f080803091010030f01", + "policy_id": "010b04070d100a0c0f030a0403050905030005010c060b03100e0b01", + "quantity": 3 + }, + { + "asset_name": "000e05050d0606080f0803070e0105030c0203020e0f090004010c090b0d0c07", + "policy_id": "020506050c0b060c0401080b0c0a01100e01080d0b00090b0c0a0b02", + "quantity": 9 + }, + { + "asset_name": "000f040f0f050209100205030e090602050c060c090005090b01040509050a09", + "policy_id": "02090607080609000a060b09071001000b060d030d00090d0c0b000a", + "quantity": 4 + }, + { + "asset_name": "010605000e0501080e050f0c010a0c090e07100b0f050c070d020f0010040b08", + "policy_id": "0903060d0a070d0108040f0707060f02090b0f0300030e0b08080c03", + "quantity": 2 + }, + { + "asset_name": "10080c0e0d030101010508050b000b05080e070b0f080b0c0c06090b0a0e0608", + "policy_id": "0c090f070b0f0c0106090d0a0a050f0e0301040e0206060c0c050e08", + "quantity": 0 + }, + { + "asset_name": "0b05041010070f090c040c010f04090f080e050a081008030708010b0f100109", + "policy_id": "0e0304020c050e01010f040503000a0a001005030c00070c0508090e", + "quantity": 8 + }, + { + "asset_name": "02040003000f070a0b060d0809000003020b06040307090c070a0d0908020010", + "policy_id": "010a080a070a0f0d0b010d05000a060707020401020c0a07080d0c10", + "quantity": 0 + }, + { + "asset_name": "0c040805010b0610051001020f020d000c0c0e060a0c0110020e0210040b080f", + "policy_id": "03080b100f0500000c0d08010d100e000f0f0e060d01000b0a100e05", + "quantity": 6 + }, + { + "asset_name": "0f0c0d0c070008060c09040b0b000c000e0b0f010a040c0d02040d080f000f05", + "policy_id": "0d0b0903080a020a010e050b080b0c0f05040d0c070506080b060e04", + "quantity": 7 + }, + { + "asset_name": "06070310090e0f0d0902060f0b0b0d060402080107100d100c050b0007050c03", + "policy_id": "0f020e0b0a06020b0f050a070d0e0f1009090a0a0c100c060d090709", + "quantity": 7 } - }, - "policy_id": "9170a8637bff94b72c3761f71ff205141d705fd84a6deea0d9a8b6b6", - "reference_input": { - "id": "696bde4583407222634965472439137a446f275a7e626f6acb18d1114e0f8c8b", - "index": 1 - } - }, - { - "operation": { - "burn": { - "quantity": 26 - } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } - }, - { - "asset_name": "546f6b656e59", - "operation": { - "mint": { - "quantity": 1, - "receiving_address": "FHnt4NL7yPYJph7ZGaCwLuWAqio7Hz6mF76Jz2KVh3Rk5NeNpD6ZFqZbvUkGwUj" - } - }, - "policy_id": "fdde985f4c18c566573b6e1b104f0ab4974b06e0af9e311e6c8f5590", - "reference_input": { - "id": "4b75244e473b1548186074501d5a52054c66623839480738109974590f4b4379", - "index": 0 - } - }, - { - "asset_name": "546f6b656e4e", - "operation": { - "mint": { - "quantity": 28 - } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } - }, - { - "asset_name": "546f6b656e46", - "operation": { - "mint": { - "quantity": 18 - } - }, - "policy_id": "3515fdf6d873101ac90fc82bfddf0e6a9e09e92b735c0bab0530a945", - "reference_input": { - "id": "6c451f4d2cf8094d1862118705372a47120d7d5b406f774c3f262ea363627f67", - "index": 1 - } - }, - { - "asset_name": "546f6b656e56", - "operation": { - "burn": { - "quantity": 30 - } - }, - "policy_id": "91f35db634aea2a9ae2b3787c8eff1cfef74a166f08341a3de3a3412", - "reference_input": { - "id": "304f28345aa97a4a795803295cb972192e19df0b7c4a12584c57cc0f75d72f2b", - "index": 1 - } + ] }, { - "operation": { - "mint": { - "quantity": 18, - "receiving_address": "addr_test1vph9epyv3ydhn8xmlhdkuke08rl3mspx2qzwvnm8ett9hecc20drc" - } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } - } - ], - "payments": [ - { - "address": "addr_test1yq4h5vqknllu94z8gdgg2eanjjslhuzsth2my5e3cadxnp5pfx2529rv36f8ea9dne3h4zwyhua45ffrzqd9tvkcgeyqhs9dqh", + "address": "addr_test1zpfdc02rkmfyvh5kzzwwwk4kr2l9a8qa3g7feehl3ga022zn42t5ykk5sfec4ltsce3te6w37a4dgemgc6eeq5lyae2qdmqcgz", "amount": { - "quantity": 1, + "quantity": 12277390895348453, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 17 + "asset_name": "0c05060709080d050204010f03080508000c0e020b0c10060200020b1000050a", + "policy_id": "00000b030d04070b0a0a070506000109090a050c09050a030a0d0b10", + "quantity": 3 + }, + { + "asset_name": "09040904010f1000100e0f0e0a0c0d0f0d0b0d03000c10100a0e05080f07010a", + "policy_id": "0b0f050205030c020e01010b0d070e050e0d0c0d05050e0706000f06", + "quantity": 6 + }, + { + "asset_name": "02100d050d0a080e060b020e0808070b0b0c03100e10010000020b0006030508", + "policy_id": "0e0a050c0c01030a020506040104070c1008030803070c0b02100705", + "quantity": 1 + }, + { + "asset_name": "02090a0e02030d0609060a0e0f03100d070c06060a04080a0e07090801000808", + "policy_id": "0e100c020b040a080e0f100a02100f02100e0a05070c10090e040301", + "quantity": 6 + }, + { + "asset_name": "070c030e10020d0d0c070309030c0c02030605090b04040e0208090f0d0e0609", + "policy_id": "060d100409000900000f100f0c0505100209050d060d100900050703", + "quantity": 9 + }, + { + "asset_name": "06060607020509010407080a0910100302030d08090c00020c0305000c000203", + "policy_id": "091003050708090801020a0609030209080a00030a0f02020d0f0e10", + "quantity": 1 + }, + { + "asset_name": "050d09090d100806010d0e0003030e010d10090705030c0c10060a0b0c0e0702", + "policy_id": "070f040e020d0f070d0b0c0a030a0704010d090a0f06100b00060803", + "quantity": 4 + }, + { + "asset_name": "020f0f020e0e080c04030c020e0010000b040406011006040204050a0103100f", + "policy_id": "00040d070c010c0704080705080e08060709060605100a0704090b0e", + "quantity": 1 + }, + { + "asset_name": "0c0f0a0d06030e0f0b100f0a00090a020a010f09100d0f0f0c100e0403100306", + "policy_id": "0b0c000209080c040802030d0f050900000e070310010807040e040c", + "quantity": 0 + }, + { + "asset_name": "0f010e080c080c10010304080303000e0c0d0c0202020f0310090e0502010c03", + "policy_id": "0b000b0d0d060b0c09060b0a050208010a070e060106050f03070a04", + "quantity": 0 + }, + { + "asset_name": "000e0201090c0a00010b030b10070d010e10100007070b07070c0e060d060b02", + "policy_id": "0605080d050a0602080b0e0a04060b100f0f070e0805081007050c04", + "quantity": 6 + }, + { + "asset_name": "090f010407090c030a0d0204080a0c01100200010603050c0f04050303080005", + "policy_id": "0e0f0506090208070f03080909060d09020e08060508050a0f040e06", + "quantity": 1 + }, + { + "asset_name": "0f020208030710080301090909040e030c09080f0b0a09100e02040606010f0c", + "policy_id": "060b0d030201050e060d0206100b0709080c01100d04100e020f0908", + "quantity": 6 + }, + { + "asset_name": "0e0c0f0c05060a09100c0c050a0e0c10071003040a0c090e0901050e0c040e0b", + "policy_id": "040f070e0e0809000b0c0f06050e0c080807070f0108090b09010503", + "quantity": 6 + }, + { + "asset_name": "090603020f0f0d0a0d0a0403010408030e0c0c020e0c060310070e0309020702", + "policy_id": "02070c100e040d0d0310030d030a010f0b060500100d0a0b03100e10", + "quantity": 2 + }, + { + "asset_name": "0f020c060d0602010e0a000b04030a090a040109030c0b0e0e010d03050c0301", + "policy_id": "10100f03010f090503100f020d0e0701090b10030c03010b020b0003", + "quantity": 8 } ] }, { - "address": "addr_test1wz7tllup32ekndgu95aw59wa273cr03lue8gk7xenvk3rvgknfgqm", + "address": "FHnt4NL7yPXxhJC1qyQcwetFTNWpQG8HLiuaKURJ82ESBWj17exeFXnjGojTQkg", "amount": { - "quantity": 205, + "quantity": 17309496449551509, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 18 + "asset_name": "0e0308080b0c03021000020a1009060708060c02000d0f0b02050b030008100b", + "policy_id": "04090d0007080c03010c100d00040d060c090f070e060f0909080801", + "quantity": 6 + }, + { + "asset_name": "0a0c060f0c060e000b01100e0b030e000d020c070a0906090e0009100b0e0500", + "policy_id": "03050200040e0f0a0f090e0c060c090402030a0a100d100f09000800", + "quantity": 0 + }, + { + "asset_name": "030707090606100e0b010d01070604050f000709060906040e0a0f020008070c", + "policy_id": "0e030f0d0a09070f030f020b06080b100e040107010a0603040c0e0a", + "quantity": 9 + }, + { + "asset_name": "010f0b08020f0e090a09080710100a0c080b030b0409100d0208000002060000", + "policy_id": "020903040e000d06080e0305030f000a0c0a0b100e0d000f100e0702", + "quantity": 2 + }, + { + "asset_name": "04100e0d0f0b090b0c0e06060306050b0d070d0f020f09070f0f0e0f0f050a00", + "policy_id": "0f0e0c0c060c0b000f04020b0c0e0100000f0a100104040a0b0f0401", + "quantity": 2 + }, + { + "asset_name": "0c100206020c08020201090105040f090101090e0a00000f0e0d0d050c0f050d", + "policy_id": "0c0c0e0a080d0d080f0309020f0c07000f0a0909020b0306100e0d00", + "quantity": 7 + }, + { + "asset_name": "0d0d070f0010090a0302090c0b0a06010c0b0d0f090c0504020a0e07080e0f0f", + "policy_id": "01060d0300100307080c000b040505020201060d0f04080e030e0a06", + "quantity": 5 + }, + { + "asset_name": "0910050f0100070e0b050d040908050202000200070107050d040e070d070706", + "policy_id": "03060a000107030c0710050e020306100e0607060a04090500070808", + "quantity": 9 + }, + { + "asset_name": "1001090a0e0c0e080d010107100c000f0710060800060a09070f010904010b0d", + "policy_id": "0109010c01090c09020a0f080a030a0a00100c0d04040c0d0f040f0e", + "quantity": 5 + }, + { + "asset_name": "03090208050f0d0d02020d0b0d010b0b05010902080d10050a050a090302070d", + "policy_id": "0903080f00070c0a0208060f090e050510080c04100e070c0f0a0309", + "quantity": 1 + }, + { + "asset_name": "04020c080e02000506000501060909090a05000100090b0c0d0d041009060404", + "policy_id": "030d000a10080b060e0b04070a050c060b020c060210030008080c01", + "quantity": 2 } ] }, { - "address": "addr_test1vz2q62l9faky6n4f4gex989ee3k53gdmnd7wykdvvnq0rrcy6lnfn", + "address": "addr_test1vpmhuny3gpjdxqyg8vj3x9759xxdr7fh8hvnfurca7d9ccsh7w8ry", "amount": { - "quantity": 207, + "quantity": 11180701852792402, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e41", - "policy_id": "00000000000000000000000000000000000000000000000000000000", + "asset_name": "040a0d04060105060d0707070603100f020b0c0304080f0e030d02030c0a0504", + "policy_id": "080b08100d0100020f0a020c101002040e0607000303000504050506", + "quantity": 8 + }, + { + "asset_name": "010d0c0b10080308020c0e04080108010c020c030f0c0f0e0c0103020a000509", + "policy_id": "010f080f0b0e05080e09020e0401080d09020c0a000a0e000d070201", + "quantity": 2 + }, + { + "asset_name": "06080c03060a01060a06010210100009040f0d1003010b100303090c080d080c", + "policy_id": "0d0d09080d08070b03010209100904040b0e0b01000501000d09080d", "quantity": 6 }, { - "asset_name": "546f6b656e42", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 29 + "asset_name": "050e080c0c0b080d00010204000a0c070a0a0c0a0a090d1000060f0904000710", + "policy_id": "0e03020c040d0306030f050d0101100001010f100d090f000a010309", + "quantity": 2 }, { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 17 + "asset_name": "0107010d0701080c0c010b05100a010f080103010408080c0b0b060002020007", + "policy_id": "0a0e0906030e0303020e0304080d100f0b03020609090f050b060208", + "quantity": 4 }, { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 28 + "asset_name": "010c0c060a03040a0003090907100301080b070e080f0e09030e000008090407", + "policy_id": "0b0b0b0f0001090d020c020309090404030a010402030e0f02100608", + "quantity": 0 }, { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 9 + "asset_name": "05060604021007020605020b060500040e070e030306070c0c050f0804090604", + "policy_id": "080d0d04050105000c07050306030101010a090f0a02030607030801", + "quantity": 3 }, { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 17 + "asset_name": "0108090403100e0405060a10080b0c060d10020e0c0505060c0c0b020e070d05", + "policy_id": "040904040d0f020106060907090604020a08060d07070f070206100f", + "quantity": 5 }, { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 17 + "asset_name": "040f0c050f0c09070e030702030c0c080809000608060804040d0c0b0701020e", + "policy_id": "05030f0c040110060b061004010903100e10070200050e000703030a", + "quantity": 1 }, { - "asset_name": "546f6b656e45", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 29 + "asset_name": "08060a010f00040b09000c080f060f06050e0b010d0204000203060905090707", + "policy_id": "1009040c100f0106000408070703090d07080f0c070d030c02040403", + "quantity": 5 }, { - "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 16 + "asset_name": "070105090e000a0407050503070d020a0c020910020602090f0c090a0907040e", + "policy_id": "0a03080b0d04020c05031007050c050b0e0e0f0e0e07070708070b0b", + "quantity": 7 }, { - "asset_name": "546f6b656e45", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 8 + "asset_name": "03080c06060e0406070e0e0a0000000003020503020e020709000b06060c090c", + "policy_id": "09070d0409010b08040d010f0a0708100c0103010d07020600090407", + "quantity": 1 }, { - "asset_name": "546f6b656e42", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 30 - } - ] - }, - { - "address": "addr_test1vq50nm7yuuz5u77v3gl3l3dftgarmyzdc3eljec5naw95egq4jlrp", - "amount": { - "quantity": 224, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "FHnt4NL7yPXksQYQwmfi6TV7Zb5nLQhVE1wxdZbSJstneJyq2eWA42vKQWvNk5s", - "amount": { - "quantity": 121, - "unit": "lovelace" - }, - "assets": [ + "asset_name": "060e100608090c05090908070b0e0d0b020e090b03040405020d04060f080c03", + "policy_id": "0f03070409090b080107020002060503030e0002020c0509050a1004", + "quantity": 0 + }, { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", + "asset_name": "0d010910090f0f1001070e04050d0a06020900011009100a091008020e050808", + "policy_id": "020e070c0a05100b0d0407030e000e010307050a05020e0409050e0f", "quantity": 7 - } - ] - }, - { - "address": "addr_test1qzfznl494ds4y9q62yzje4nruzc5zrxx49ua92ncnfxqt5qgmruyzaw5t8m96v2yxrhc93wem6d5equxq5ck3gy66ygsp68qym", - "amount": { - "quantity": 31, - "unit": "lovelace" - }, - "assets": [ + }, { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 5 + "asset_name": "080703060f100b0e0307030b0c0f0c0608100b1005060d0c100e040002040b0e", + "policy_id": "0c0c1010100a04080301030f0c0009060b0e0004050e050907020302", + "quantity": 2 }, { - "asset_name": "546f6b656e42", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 6 + "asset_name": "02030a0a050e000a0d0f080a040501020d010e010e0a03040502030c1010040b", + "policy_id": "0c010502100c0d0508050d04020f0d0c040003070d090e0b10050703", + "quantity": 3 + }, + { + "asset_name": "030b0603000a0f010c090f04080708040c0c0010050b030a100f0b0008100d0b", + "policy_id": "0a0502010a0c0b0206060a03040f0c010805070b0d01070807100505", + "quantity": 1 }, { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", + "asset_name": "0b0f0f0b0e020504020f010507000b0f050b0b0c0a030e030e0703070305040d", + "policy_id": "030506090e09020c1009060b0d050a060c051005020802000f030c0d", + "quantity": 5 + }, + { + "asset_name": "030106020d0e0f0201000f0a0d03060601100d0f08011001060d0c0704040801", + "policy_id": "020c00050c030e06020f100707040f050b06070600020f06010a0206", "quantity": 8 + }, + { + "asset_name": "0d0e0110010f090505010d0c0f0903030e010e050d050b00080e0304030d0603", + "policy_id": "06000a020d0b0f080e050104020409070406020408100101040d050d", + "quantity": 4 } ] }, { - "address": "FHnt4NL7yPXvgARui4Tt1wg92sATs3YfD3UhqDF6XiadKUjt4K7nEUeNh86LgDG", + "address": "FHnt4NL7yPXi2vbw2Nq6oydUoagQnt19iDr4s4jE6K9P3nyC4cfnGjLtq6P5HxV", "amount": { - "quantity": 132, + "quantity": 8883526423393249, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e42", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 28 + "asset_name": "0e10060106090a000f0b0a0f0104030d0200000a07080809060a0f0b0f040a0d", + "policy_id": "0106070600030103010306080f0409000f0107080304050e100c0210", + "quantity": 0 }, { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 28 + "asset_name": "10020f020f0e0104090e0c09050c0f0108010803090a0f0a090004070e0e000f", + "policy_id": "04050e05040e0a08070e090a030500090b0e011003080b0b050b0f10", + "quantity": 4 }, { - "asset_name": "546f6b656e41", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 11 + "asset_name": "0f00040706030909040f010303070801000508040c0201031004090b0e060e08", + "policy_id": "060f05050c0d0c0a09080c080a000a020c02050c10050910040c100f", + "quantity": 4 }, { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 29 + "asset_name": "0d060f0d0c0e0a0c10020a101004070809070f010a0f090b02100d09020c040e", + "policy_id": "10030a030b0f0310030802010a0d0c070a0a03020b090b050607010b", + "quantity": 4 }, { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 16 + "asset_name": "10080b0b0308080d0b0e0506050a0f1002080c0e100c070b0e040101020a040a", + "policy_id": "0c06050f070d090508050c02030e0908020605010b0f080902050207", + "quantity": 4 }, { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 13 + "asset_name": "0305050a06080f070b07020e0b000c00030e0210000b0c090601010d0b100800", + "policy_id": "0504070102080a0f0c0e0f030d0f02020001030e07070c0c040b030a", + "quantity": 0 }, { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 7 - } - ] - }, - { - "address": "FHnt4NL7yPXjHX3r7jSmAM2qdtULKdDRpimMvqaxuFUXmQaAAz5F9GCj67ARC1N", - "amount": { - "quantity": 189, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "FHnt4NL7yPXxwFWMTBko818X82rQjGAHDzNcg39giaqVZFoAd1Ur6oX5fgXWxq1", - "amount": { - "quantity": 161, - "unit": "lovelace" - }, - "assets": [ + "asset_name": "0d06091007060a0500020b0603010c0704030900000a060100100609090c0406", + "policy_id": "0e0303070f01020607060005040f050b05040501050c01050f0b0d0a", + "quantity": 9 + }, { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", + "asset_name": "06000204070c0a0106090910040c070901081002010110070c090b0605050b03", + "policy_id": "10080e040704010a030f010000060c01030f0e080907060f0f040e0a", "quantity": 8 - } - ] - }, - { - "address": "addr_test1xq84efqlcsdepnr94kdjnmxsz8h34wz9gwqzsxup003rwd8ke9za7aczngvgd8dhagjnvxk6kzt3c4fa45pgw7fg8rkseewklp", - "amount": { - "quantity": 151, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e42", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 33 }, { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 26 + "asset_name": "0f0a05010a0f040f08080700030308100a05040b050c0904100e0f0a0b030801", + "policy_id": "02070307050f041007040a0b0109040d00060d010a0c0a0d0302030d", + "quantity": 8 }, { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 22 + "asset_name": "0e08070400070a0507000c0205091003010209040d07010005100f00060a0610", + "policy_id": "06000e09080f08020f09050b07060b03060007070d03010f0707060d", + "quantity": 4 }, { - "asset_name": "546f6b656e41", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 28 + "asset_name": "06040504060e0e060c0d000c0b030b070900010c090e050c0e01030d04080601", + "policy_id": "090f0b050900100909080b100e0e05050d0e0c0c01070b0606010f0e", + "quantity": 8 }, { - "asset_name": "546f6b656e42", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 20 + "asset_name": "09011006040e08060e08050a0e1009020104100a0702020a050b010b030f0501", + "policy_id": "030f02080e080c0a090a0a020c0a0a01010a04030405000d060a0000", + "quantity": 0 }, { - "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 26 + "asset_name": "0c0f0600060e0e0d060c0a07030102000005030f0a0d000c020d10020408060b", + "policy_id": "040a05090e070a0e04100200090103050b000c0e0b00050205070806", + "quantity": 6 }, { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", + "asset_name": "060007060b040e1003050707041006060b08100d10030e08040e060e070e070e", + "policy_id": "03030b0600000e0b0f0a0a10070f0b0f1000030a0f050d0303090001", "quantity": 2 }, { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", + "asset_name": "0c0f060f06090f030e000810080e08090700000b090f0910040c100706040902", + "policy_id": "010505030e0c0d0e0b0d050d04030c0e020b000100020c0003100a08", + "quantity": 6 + }, + { + "asset_name": "0509040f0b100f060a10080c0404010f0b02000b0905060d0e09100f0d0a0506", + "policy_id": "0601090c080808060108050800090301070401030f0f05050710060b", "quantity": 6 }, { - "asset_name": "546f6b656e45", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 15 + "asset_name": "050000090a0a02070d04030400030e040d10100503080f0b080f03100a070f00", + "policy_id": "050b06050f0a01050a0d050c010208000b09050810020a01040f0005", + "quantity": 5 + }, + { + "asset_name": "0d020d0f0001010b0b0101060f000e07100f0c0e05070510000e040103070a0e", + "policy_id": "080c040d060a02040e0a020f060d080e0a06051003010d0b020b0a09", + "quantity": 5 } ] }, { - "address": "addr_test1wr2yzgn42ws0r2t9lmnavzs0wf9ndrw3hhduyzrnplxwhncaya5f8", - "amount": { - "quantity": 84, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "FHnt4NL7yPY34hWihFLF2H4jiYPMYsJYd52ad7wTAUH2VXKCohQQ9xiMGKVT5i7", + "address": "addr_test1vpwd576t6sgxmq530fjvjulvqdld9tyca5fjcyeg7p60paguperkk", "amount": { - "quantity": 91, + "quantity": 45000000000000000, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e42", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 17 + "asset_name": "0108010908020a08030b0e080f03040107000f04030e1003090c01090d030f02", + "policy_id": "0505060209060f000403010b05080c0606100010080c00001010010f", + "quantity": 2 }, { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 12 + "asset_name": "020f090107080b0104080a0d0e0e070703090b090109040f0f0209090005010c", + "policy_id": "0300000606100b0e070f0b0e000e020a10050d0805100b0f04060610", + "quantity": 3 }, { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 5 + "asset_name": "0c0c030009030d04080f04020f0f0706070c0000100f000c090f030a03030a0f", + "policy_id": "080a0b090f030405020408060009020d060b1003010f0f050c031006", + "quantity": 2 }, { - "asset_name": "546f6b656e45", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 31 + "asset_name": "050a100600060a030d0b100f040e0500100805020f08100308000f070b06000f", + "policy_id": "0a0407020e0f080903000c0e010e04010407090c0f080c0f0a060501", + "quantity": 3 }, { - "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 35 + "asset_name": "0700090c05000a07010a0d0707010704081004050802090810070504010b0f06", + "policy_id": "0a0f0602040a0b0b010a0901050f0d0d081006010906030c070d0d0f", + "quantity": 5 }, { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 18 + "asset_name": "050f0910000d0a04030503000d040c08100310040509050c0706060903080a07", + "policy_id": "0a1002090306060f0a0e030c08020c07020102090402090d0a0e1004", + "quantity": 3 }, { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 45 + "asset_name": "080e0b0d0e0c04000702030b04060b0e0a040604010a0d03070307060b0e080f", + "policy_id": "0606030c060a06050704020400080503060f060b070a00000c0e040a", + "quantity": 5 } ] } - ] + ], + "vote": "abstain", + "withdrawal": "self" }, { "delegations": [ { - "join": { - "pool": "pool1zuxju9g02ydzzg6dxpjj5fjezcgzygrc9ydqz4mdtvcrjl8atdz", - "stake_key_index": "42" + "quit": { + "stake_key_index": "10362" } }, { "quit": { - "stake_key_index": "9705" + "stake_key_index": "13220" + } + }, + { + "join": { + "pool": "pool1w96zj2zgpa9hc0fw84f5smn4f4tqws6zy5jrs3tv2qxn6j55n3c", + "stake_key_index": "88" + } + }, + { + "join": { + "pool": "pool1vfs8yg6atdljjd38xegyg56zfe2xxvztzvsn6asvq9dquj9tgnn", + "stake_key_index": "88" + } + }, + { + "join": { + "pool": "pool1pqvyu0m4rsmqkjj6fagq24f0dvs4xmqggdunxkpyyswnu0y8j7d", + "stake_key_index": "30" } }, { "quit": { - "stake_key_index": "3427" + "stake_key_index": "12642" } }, { "quit": { - "stake_key_index": "6655" + "stake_key_index": "11167" } }, { "quit": { - "stake_key_index": "14848" + "stake_key_index": "2072" } }, { "join": { - "pool": "pool1gcrxkqtwp90h6nq3894zy3p2g50rg7chq4a5jzq6qvqkw04c9r6", - "stake_key_index": "32" + "pool": "pool1dpxns0c6q5x8gygdxfepslr3rs0s2uj3xuhkq3zs9g23kz5h92j", + "stake_key_index": "109" } }, { "quit": { - "stake_key_index": "10707" + "stake_key_index": "2322" } }, { "join": { - "pool": "pool1999n7qjy99fsg629pd7y7gf3p2qqvwf3pacjvqefrg7yjdq65rd", - "stake_key_index": "35" + "pool": "pool1z9752nrmrfjj64uqy5486tcf2q33203sgexhypz5v3c8v704y6m", + "stake_key_index": "47" + } + }, + { + "join": { + "pool": "pool185nzy43zpfm4sn2uvcv4q9jerv6jupc9d39r7k2dy9l5gj0nsg8", + "stake_key_index": "126" } }, { "quit": { - "stake_key_index": "14783" + "stake_key_index": "6306" } }, { "quit": { - "stake_key_index": "3447" + "stake_key_index": "16020" } }, { "join": { - "pool": "pool1xs6kqr6tvdrhzfqwzs29q2ea0vmn5nnsr3u5gqt3rvnpyvmue0w", - "stake_key_index": "34" + "pool": "pool1fsjqchstgkq97r3tgy6yxgtvvqrh553t9u6s5en424nhwuqx85z", + "stake_key_index": "107" } }, { "join": { - "pool": "pool1y4kk63c9r95nctjvfa9j7ktrvstkjsrfqumqu4nzr9u5gpnrukg", - "stake_key_index": "118" + "pool": "pool1fv7ykrgtgye4wtj3faenxkqpwcpyc3jl9ql8vhmlqgc8xmxyd9e", + "stake_key_index": "36" } }, { "join": { - "pool": "pool1t9qry8660af3vqmdpvhyj2tw049hz924r46qzaejrv79wwcjde2", - "stake_key_index": "3" + "pool": "pool1xuc57vs0vs4qgwp8yddn78j0z4tz26jy8uenxqghvsu82qzaeec", + "stake_key_index": "111" } }, { "join": { - "pool": "pool1qen3kgga9q0p6rfwr944yem7yecj6rsfxpypc5m8zgqrg0pnuay", - "stake_key_index": "52" + "pool": "pool1yy44gkfzg4ajj72rpck5y32hqppz25rtr5245vzmyg33jjer35e", + "stake_key_index": "26" } }, { "quit": { - "stake_key_index": "672" + "stake_key_index": "2311" } }, { - "quit": { - "stake_key_index": "1939" + "join": { + "pool": "pool1ds2qysuqwuuz64jprs2jy0fjg9y576jx03jn6aeggqrrkegt6d3", + "stake_key_index": "21" } }, { "quit": { - "stake_key_index": "2203" + "stake_key_index": "3342" } }, { - "quit": { - "stake_key_index": "787" + "join": { + "pool": "pool1tamqxcmap4wxwszq8ctx2agetgps792vgslssugf9yfp5v7808n", + "stake_key_index": "35" } }, { "quit": { - "stake_key_index": "15679" + "stake_key_index": "20" } }, { - "quit": { - "stake_key_index": "801" + "join": { + "pool": "pool1v4hhu3pqxc3kuj6n8vnnsxcwfys9gnp9ffkqs4jnpe0rcg3wxrq", + "stake_key_index": "57" } }, { "join": { - "pool": "pool1xqrx7ejaf5n4vw329dnks3jpyue9uaf2zau5gk30wq2xsdgvh70", - "stake_key_index": "121" + "pool": "pool1gywpq5p59ffhgls2vqx8gutazurs73rq8y2zqwmfz465gqcwu8t", + "stake_key_index": "77" } }, { "join": { - "pool": "pool1zd93gsfhturjqtprzuj5yupfyqr47tt6wawsu5ttdpmy5ap7gfv", - "stake_key_index": "99" + "pool": "pool19qrnwff0yyjxjtfjfqvk78nw8grk2w6tpdjp602kp47nya3yc4f", + "stake_key_index": "82" } }, { - "join": { - "pool": "pool1dfapkyectgasx92u95uztqqqwae9kgtedu4xqqpw0c9hwnqg486", - "stake_key_index": "69" + "quit": { + "stake_key_index": "15088" } }, { "join": { - "pool": "pool1t44zs429xaj9s4pftc04urzkycfqz8gqpftr2yn7x37zkgmckks", - "stake_key_index": "44" + "pool": "pool1qvj4ydr40acrj76zqqyjjhpdx3lqupcefdtsqttjg5f8xrhwqvz", + "stake_key_index": "117" } } ], - "encoding": "base64", + "encoding": "base16", "encrypt_metadata": { - "passphrase": "'줎K\\x43J𮞱Pl\\3IGxa0H&nA:ꌼ+觨𥑷rl⨺n𞡣1t_c/MVe\\Kq'L⼓s𰸺3|>H&>7'B3𦤸>9mtU𝣮'𘕛c.mVc#>oX8]N𞋰7J$4JSZ⢟D𫠡\"(oL,\\Oyᝁ൰*3𣞪}{\\:;qMR混q#qmCH𗥤B𧬧_𣫬(S@wUG_kQ=N轵fq𩩲ퟬyM;wz𡃷m Q=Jtx🭸PK>9T钃ig(𩒂J3" + "passphrase": "Krt{_솹J𣁨𮠦𔕏jqK5TGcfZ9LA.zcnr𪢏KH1𘮁s>!𝝛JTo$𮇿d㮠Cza-Y῍𡥢𫯪%ꓪ{J𗏑斝x)衿Ďg#se@6𡈣n𝈮ꀝ𗜶#(eo𢫖A9i샕?ﱬ神^1D흛8I3[T𒈠𛁂i]i䄽&De𛅰$W|?:qM4q-rf(k2𪵳Us𱻁tjUh\"C𨀂r +Wac𑣫?xnHnR<㩖-v,𤃄y:.qWi" }, "metadata": { - "9": { - "map": [ - { - "k": { - "string": "뺋" - }, - "v": { - "map": [] - } - } - ] - } + "9": 0 }, "mint_burn": [ - { - "asset_name": "546f6b656e42", - "operation": { - "burn": { - "quantity": 30 - } - }, - "policy_script_template": "cosigner#0" - }, { "operation": { "burn": { - "quantity": 9 + "quantity": 10 } }, - "policy_id": "56a16c19227df252ff8fec4152bc3939b995a25d025c2b7805b3ac5f", - "reference_input": { - "id": "230f6809121f3e0200400dcb7a570d7e06927614771577774634f8762cbe5203", - "index": 0 + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] } }, { - "asset_name": "546f6b656e53", + "asset_name": "417373657457", "operation": { "mint": { - "quantity": 1, - "receiving_address": "FHnt4NL7yPY9J8h2UgcdPUseVT5uZ7aNynqPFZY9kUQQZMakhKXQ6jPWHdfvUq1" + "quantity": 29, + "receiving_address": "FHnt4NL7yPXifxLUdXMELa3zaXUqTUMzvppZHhnJ5tLpfR1beiGXd3Md5bhyYWL" } }, "policy_script_template": { @@ -2203,44 +9690,48 @@ }, { "operation": { - "mint": { - "quantity": 24, - "receiving_address": "FHnt4NL7yPYBrYWasGVYS3BJd2StRrWebpePFqK4ftuY4BJgmTPRk3t4yKnTcp4" + "burn": { + "quantity": 10 } }, - "policy_id": "7d209e43181565012965bd82b3f6996358595e26074d8f65553150a0", - "reference_input": { - "id": "5340316d19056b58d429494a62c488213c0e52d4777954b62325331c3c644072", - "index": 0 - } + "policy_script_template": "cosigner#0" }, { "operation": { "mint": { - "quantity": 5, - "receiving_address": "FHnt4NL7yPXhAeAKRiVQKTJzzT3CU5qf4hdZu7kQvwERp86CjNdiEg47hy3Sj1T" + "quantity": 29 } }, - "policy_id": "0151b1325ed2165655b34f4b4578210fc8ebe3f234fd606b16c462f5", + "policy_id": "99f0558227e76b2309b6bb07e29e66679e656a74b16b3ce77ca3cb56", "reference_input": { - "id": "10792a3a174f71e387057d2b1dd21b4557002703d0674020d51633945726da95", + "id": "0c0f78792ba8b9783c1a5e4563374ba4333fa53032430a5b457161dd65543e19", "index": 1 } }, { - "asset_name": "546f6b656e48", "operation": { - "burn": { - "quantity": 26 + "mint": { + "quantity": 1, + "receiving_address": "FHnt4NL7yPXxsXhboiQFzpxhjLbWAscEG6BpR8pEvuPmhJghpKbLYtsPV8NM3FK" } }, - "policy_script_template": "cosigner#0" + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } }, { + "asset_name": "417373657453", "operation": { - "mint": { - "quantity": 12, - "receiving_address": "addr_test1vqdp6wj5wgtxpxmucz8q09atz6qyw33hmnd0tlfstks0mtqjdfhgy" + "burn": { + "quantity": 7 } }, "policy_script_template": { @@ -2256,22 +9747,28 @@ } }, { - "asset_name": "546f6b656e43", + "asset_name": "417373657446", "operation": { "burn": { - "quantity": 6 + "quantity": 13 } }, - "policy_id": "3f452e75649a30647c234d525e5eec52f7b45222d651aed2ff3c5a0c", - "reference_input": { - "id": "0660eb1d9a56255542707fc98a4a6068781f250dee327b08265d642c51305376", - "index": 1 + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] } }, { "operation": { "burn": { - "quantity": 6 + "quantity": 25 } }, "policy_script_template": { @@ -2284,2278 +9781,3323 @@ } }, { - "asset_name": "546f6b656e51", "operation": { "mint": { - "quantity": 8, - "receiving_address": "FHnt4NL7yPXmHytdYtDsFuStVq6sHKtz3t3ko6rh9BwUWr6A2GfLSX6Ukydhy9K" + "quantity": 5 + } + }, + "policy_script_template": "cosigner#0" + }, + { + "asset_name": "417373657441", + "operation": { + "burn": { + "quantity": 7 } }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] + "policy_id": "aa6ba7e651e0e92698180a169814e6990e0773c1c748877ebb85a59a", + "reference_input": { + "id": "2a50f13b505dc93b2f2e9e37372009210c53d33b2c000322124c208f6b114800", + "index": 1 } }, { - "asset_name": "546f6b656e46", "operation": { "mint": { - "quantity": 3, - "receiving_address": "FHnt4NL7yPY1ARpJ6TMqeBbvnh371gxwMRZhFx3EM7H9V8Bz9Thw1Nyk4ypayig" + "quantity": 22 } }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } + "policy_script_template": "cosigner#0" }, { "operation": { "mint": { - "quantity": 15, - "receiving_address": "addr_test1yqhmud6herk0m67lpcj8p49yq47ezs6h83cuankqhzkj3pmjlyaqdeekd45254ra5gjzx7q7m6lfn5una0w4z9h7rzes408vzq" + "quantity": 4 } }, - "policy_id": "e57d401130c031a8952eb8a0bf0e0ae05bf644bf9169139f21def7ce", + "policy_id": "fc2c3c004c77bbfe8c8f84802f7b7f9cc2161933bb524f2d3a957e5a", "reference_input": { - "id": "37882e2e0e644c23322326f34b1e01533f4a05725f0d466a19738f5afa702149", + "id": "f70154466019096e740e4227c47949346e1650c47a4ff4282c0e432d1f164f04", "index": 1 } }, { + "asset_name": "417373657456", "operation": { "mint": { - "quantity": 26, - "receiving_address": "addr_test1zzp689jy7yyupdyzlp5qx3hkyuam88ucu8n4g8wf5je8p86kh0cgxzk2tfrqns9kx385rzk2ypqmxp5td7lq7kq0dl2s9m3fs4" + "quantity": 26 } }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] + "policy_id": "07a012e1049676f39504f302f945258a78f5b1504632e6a3ca08d957", + "reference_input": { + "id": "5b7b354ab97e6747536719231d08603411b376421c3e60397d46684c76456f4f", + "index": 0 } }, { + "asset_name": "417373657450", "operation": { "burn": { - "quantity": 9 + "quantity": 3 } }, - "policy_id": "c16330d83fd11b87bcc06b47a1e1208307477c331d5df9debc3691b0", + "policy_id": "848534ef9274501c2d22f01b79ce53b35ed58abdd58c2f93bb04a1c4", "reference_input": { - "id": "34016d60391d2d467b916014101920e12628e93337a8545d23797b557c0b5d15", + "id": "14367b55357102603b7a6065559c56587545423f2f135f3dfc3c0b0545227645", "index": 1 } + } + ], + "payments": [ + { + "address": "FHnt4NL7yPYK9kF4azb6Nxfd8eYEshhPSkSj2eG5HTxKD6FyCa67AUY9zEowWa5", + "amount": { + "quantity": 12858287752970153, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "040e0a0c0408020805030605090703050f02010d0a0302011001000701020407", + "policy_id": "090a04080003040f0807020a0a02080f0e0d100c03060f0407060403", + "quantity": 2 + }, + { + "asset_name": "070c10080a01090a0106091002010e00080a070b0d0c0e0e0505050504090b10", + "policy_id": "010f0f040410031010000b060d09080208050a0c04010f0f0b050a08", + "quantity": 7 + }, + { + "asset_name": "0d0a0f0e0b0501060e03050f0b05050c04040910040c0e0304030209100c020d", + "policy_id": "0a0c0c0704060d0a000d07050b020d0a0a0a0c0c0803100403030810", + "quantity": 7 + }, + { + "asset_name": "0c090100090109000a000e080e040e0305030a08000b01070605080a01070a0a", + "policy_id": "0a06070e050b05090808070e08030008020e01020e0c0c0f07010700", + "quantity": 9 + }, + { + "asset_name": "0402040b060d030f0b031010040c09080b050603040906040b0a0d0f080d0d08", + "policy_id": "000f0306060102100f0a0c0c0d100a081010070c060210101006030d", + "quantity": 4 + }, + { + "asset_name": "070b0b0b030c0300090e0a070a00030c00080c05070a100c080c050e00080f0a", + "policy_id": "0602080f0c040b0707030c0d0e0f0610100a0510040109040005070e", + "quantity": 6 + }, + { + "asset_name": "040e0d0a0c0a040b000a0b00090d020405060f0e010c0104040e000e0710000f", + "policy_id": "030c0c0701000d01090e07020d02020910030d030b050d030500040e", + "quantity": 0 + }, + { + "asset_name": "0a010a10090f0e0f020100000f0d030f0301050409000403060e06070406070f", + "policy_id": "07070500030b080509100707050d05090d100309100c060c0f0d0908", + "quantity": 6 + }, + { + "asset_name": "0a07040501040c0a0905080f030f0f0d080907000d020908000d06040d040701", + "policy_id": "020a01000a010e010506010d0e06030d1008040507020d0e0c09100b", + "quantity": 1 + }, + { + "asset_name": "020f04080f0f04010f0d000e060d0e0107050f020e0f0d1003080d0408000d08", + "policy_id": "0d0610040e0e0d090100100e030104030700080a04100b0901041008", + "quantity": 4 + }, + { + "asset_name": "090b0e0d0d01060e0f09080d0a020408080a0e0105000a0c0f090d0a0f080c10", + "policy_id": "06070b0300030a070e0d0f070d0f0910100c02001010050806050508", + "quantity": 0 + }, + { + "asset_name": "08070e0c0e050c00060e0d0c09100c040a000706000601030607081007100c0b", + "policy_id": "0c07080107010a090f0c0d06090e0809080f000e0f0b0b020a08070a", + "quantity": 9 + }, + { + "asset_name": "0a06010a000f00060a01000e040108070e030101050e050606050b0c0c02010b", + "policy_id": "000c060c0507000705090907050f0c0b0b0d030c0a0c0c030004050f", + "quantity": 2 + }, + { + "asset_name": "0d090b080b05030902060e100a0202040b08000f0d0806010e0d0c03020d0902", + "policy_id": "0b06060e0d050b050707040d07080b05050001100e00070f07020a00", + "quantity": 6 + }, + { + "asset_name": "0d0d040d0308020105010f0003070c0e0c0f0310010f0910060f000e0f060509", + "policy_id": "0e0f100b0e000b0d0c0c020d0e010f05070602080f010d000803040f", + "quantity": 3 + }, + { + "asset_name": "0810030e070c080d0b0c00040f0402070605060e0e08030e050a0f070e05020d", + "policy_id": "000b09030a010b0d0103070e0309080407020e06050b10100a0f0605", + "quantity": 8 + }, + { + "asset_name": "070310020807080c0506010a0d07000905040701080f0e070f000a0e080a020c", + "policy_id": "0f0003090a0d0f0d0a010e0b040c10080e0610020f0301050a05040b", + "quantity": 7 + }, + { + "asset_name": "0c05020a0703020105020803040606100c0b100e020b041004020a0802060d0f", + "policy_id": "0102101007010a07011006100e080c08040e010205030404090e0f0a", + "quantity": 4 + } + ] }, { - "operation": { - "burn": { + "address": "addr_test1zp33h768y9s9feu9u4y5yun073egjmaz6skdk7ttgat3wd0p32akrnxcxyq3vnj038s7edny8gdtfg5z4cuajh53jefqdzndgu", + "amount": { + "quantity": 4564342638572837, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0a0710000a0709060207060f0b060c01100f0e070707010b040f0302050b0303", + "policy_id": "0f0a0c02040e0307060c0c0601030a0804040f0705080c06100e030b", + "quantity": 7 + }, + { + "asset_name": "080e0a031002080a0f010101050a0e070f090d080b0d0f090b040a0b040c0102", + "policy_id": "00070d0b06010c0704080701060d060f08091008030f100c05041004", + "quantity": 7 + }, + { + "asset_name": "0d070f050e0d030308010d02030a101010060904040c05090800060c0d0a0e0a", + "policy_id": "0605070d06040b050c05070804030305010f0700060e030402020102", + "quantity": 0 + }, + { + "asset_name": "0102070c0202060205070d0708080e030610060909040d100d050e07090f070e", + "policy_id": "0904060d04050b0c030d0e09010905070f1004030d04040e04070b0a", + "quantity": 4 + }, + { + "asset_name": "0a0e0b060b0d0a060a060e0b050b0e0e030604020d100d0a1007060d0610010f", + "policy_id": "0f0c0f0e05010a0b0910050b040b100504070d00050400080c001008", + "quantity": 7 + }, + { + "asset_name": "08000c060c090f040e010a09060405050604050e10090d02020110000a070500", + "policy_id": "01090b0a05070d01060a030f00050f050b0000050f0905060d040e08", + "quantity": 1 + }, + { + "asset_name": "000f0e0401090b070a050804080e0d0a080200090c05020e0d000f09070d0a03", + "policy_id": "0d0f0f0f090404040e0e04040c05090801030201070d050e0204070f", + "quantity": 4 + }, + { + "asset_name": "0e0408000609100a070601071000060e080b00030f07050608020b01010c0f08", + "policy_id": "0c09060e09090a0804010505041009000b080c070f070f030f080910", + "quantity": 3 + }, + { + "asset_name": "050f060f070f070b080c0010000903040c0e06010b0e00100b0502020603030d", + "policy_id": "0c0801100d020009020603071002030b0d06020607050f050b0f0701", + "quantity": 9 + }, + { + "asset_name": "051005070110050502010610020509010407020c09010b100a03050d050f1004", + "policy_id": "06080b03100200090f0d0201070c05100b0f00090807090b0c080f08", + "quantity": 3 + }, + { + "asset_name": "010a0e0e090d0e0a0e01040d080807000500030d03050b010f040002090a0506", + "policy_id": "0d07070809090c1008080b0e0c04100c0a0504030004020a0a0c0c09", + "quantity": 0 + }, + { + "asset_name": "10040307020d0f050c0d0c0c06050204010f06010d0a100e1001040b0401050f", + "policy_id": "0b0a030001020e02010c080d060905050d0f0f06000403010e0e0910", + "quantity": 9 + }, + { + "asset_name": "0b0f0a0010010d0f050600090f030a020705010c080401001004000e000a0c09", + "policy_id": "090e0d07030f070b100b0809010e0e100b0d0b0c020302040b0e0306", + "quantity": 1 + } + ] + }, + { + "address": "addr_test1wq6npny6ulegj5g34xdh5qscfhtupn48gf83vvkh89gmr4cl3n4xr", + "amount": { + "quantity": 9772569501873780, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "05061000050804100c07060003030106071000050005020a03020b070f0d080b", + "policy_id": "0f04010a090c070d0b0b08020b0910010e01090d0903090508070108", + "quantity": 5 + }, + { + "asset_name": "050301020c0e011010010307050b0a00100c100308070d0d0702071005010004", + "policy_id": "00000b04041004010301040a070202100407040f07020509080f0f01", + "quantity": 3 + }, + { + "asset_name": "060f031004030e0910060e0d0c02090a070b0f0a07070b030a0b0e01070e0009", + "policy_id": "0702000b000708050a030c0c02090c0d0f0e040c100a0c0000060002", + "quantity": 1 + }, + { + "asset_name": "0e0907070b010f060506080c0100070a0c0009090308060009080d0704010d0a", + "policy_id": "0c050c030f0e10000d0704020706010d070d06080e09020402040e02", + "quantity": 4 + }, + { + "asset_name": "020b09100a05070c0505050b100b0f0f0d09060605091002020d020709060e10", + "policy_id": "020e00090000000504000407090a000e00071003020410100b080a0b", + "quantity": 8 + }, + { + "asset_name": "060107080705000303060704070b0309020b010a020303090710010d010a0304", + "policy_id": "0810010402030900000810100f08020e060f020b080210080a060407", + "quantity": 9 + }, + { + "asset_name": "050c0f0e0808100a000e020d0b010c050d030c020e050300090c080800020c02", + "policy_id": "1000080700100b100b0506040a0300020f080f0a030c010010050108", + "quantity": 9 + }, + { + "asset_name": "020f09040b100606080d0b08090b0005080f0607100b0b0e09100f09030d0b03", + "policy_id": "080108040d040506040c0a0b0c0c100a0b0d08000804010c080c0f0b", + "quantity": 1 + }, + { + "asset_name": "0d0600040b04010e0b0804010f090f0501050a0a01030d0d000105020e090702", + "policy_id": "0d0e0d0d060a0a05040402040d00030506000608050b0b03070d0203", + "quantity": 3 + }, + { + "asset_name": "060406050b030a0b0b0c0203030d0e050b06020e0c07020e0b0f0b050d0f0c08", + "policy_id": "0d100f0a0b020d100703020d0d0f050c040309100c0a03050e01080f", + "quantity": 7 + }, + { + "asset_name": "0303080c0d0703090b01040503030300060200060f0508050a0700100f0d000b", + "policy_id": "0e1010040a080b0f050b0000090c090a03040b06000b0c1007060001", + "quantity": 7 + }, + { + "asset_name": "0c0d04040f0e0603080b1007080603010a0f0b0c0d05000109030f01010e0f00", + "policy_id": "0c0c09050c05000e0e010910070600000508090e0309020a090a0405", + "quantity": 3 + }, + { + "asset_name": "080e050a0300030e0005100300100b04060409040f070a030906050e070c0b0a", + "policy_id": "090603090d100a0a100d0b0d020a010e0e0c040c020e0c03040b0f03", + "quantity": 6 + }, + { + "asset_name": "0b0b03070103010201000c0c0b070f0a0d0e00080b02080f060b03100f0e070b", + "policy_id": "0709020d01090000000f0d0204000407000b0f0f0b04100209040910", + "quantity": 8 + }, + { + "asset_name": "070d070d040404080e060b05080501080e0d040f0b0f080e0b0e080e000c0604", + "policy_id": "0a100d0b0d0b0000010708070f061004080e0403050d100304010103", + "quantity": 8 + }, + { + "asset_name": "000009070a0e0e000d10020a0a0101080c1006050a100c10100c0a020400030c", + "policy_id": "0600060d060a1002100e000b040e03080800090a0a0f020f09070c0e", + "quantity": 6 + }, + { + "asset_name": "1004030105030c1008000f04000204040c03020100090d00040c061004010c0c", + "policy_id": "030e0d1004100f03080f0d0d040b030a03050b040f04060201070c00", + "quantity": 1 + }, + { + "asset_name": "000804050705020f0204040c0b10030207080f0f0a090b050f040f000a0c0004", + "policy_id": "020b0e10100d0d070200000c000e10020c0b0c040806030910010909", + "quantity": 9 + }, + { + "asset_name": "030c0e080a0505030c04000a1008070205050a071000040f0c0a0606050e0700", + "policy_id": "100103100d0f0a020f0709010d0301060c100600020310030810080e", + "quantity": 6 + } + ] + }, + { + "address": "FHnt4NL7yPXy6VtrGjsDXxQjKw9sqcLE1A3Ao4dE3MtgWHGhAkVefAHxjh3EaZY", + "amount": { + "quantity": 42532692635525493, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0404100c06020e0d0c0a0c0303100d000b0c0c0c060b0c0a05040a0801080c02", + "policy_id": "03040004000704000b0904040e0004030d0a03100d080b0910100200", + "quantity": 7 + }, + { + "asset_name": "04070a0205020d02040a0b0c0700060d050d031006060301021002050b090b0f", + "policy_id": "100c010a0705070b10100e100d1000081001090f060b0c0e020d0008", + "quantity": 1 + }, + { + "asset_name": "0e040604040d010d020b0a0c0a0c07070903010c0f0701040d0201050e0a0909", + "policy_id": "100b0c09070800040000020307040d0b100e0601050f0e1001020e04", + "quantity": 7 + }, + { + "asset_name": "0001010c0b02050e060802100c100e0e0c100e0a06080a0a01080c100501000c", + "policy_id": "091005040e0d03010809020e070f0504020e0a0b0501040a050f050b", + "quantity": 9 + }, + { + "asset_name": "0f0809081007020f0e020a070b030c030e100e010b030e03030d0b0f04020608", + "policy_id": "0d0a06010e000c0d0906010708030b09030f0b0d100c0e0a1006010d", + "quantity": 0 + }, + { + "asset_name": "020609100807100f0803030a020d060c02080c07040f0b02040a0b0602090d0a", + "policy_id": "0e0c000802050a01100a0e07070b0d0f01070f0e03000a0706090802", + "quantity": 5 + }, + { + "asset_name": "0e0c010d0f040a0702030f00060b0b05060f0400020f070b0d05050807090f0b", + "policy_id": "0d100b040a090d0b0f05060b0d000a07000403080702040a01060003", + "quantity": 4 + }, + { + "asset_name": "0c010c050e0d01050c0c030308020e0a0b0b0b030106100f080801010c0b0609", + "policy_id": "0d0001080f050d010e0c0c07060803010201030806030f060a0b010c", + "quantity": 9 + }, + { + "asset_name": "0a0808050d020d03040607050603070b040501070f0308010a000f0f070d0101", + "policy_id": "090a080208060c0f080c090e0e0d0f0c0e07030d04010605030c0d06", + "quantity": 5 + }, + { + "asset_name": "02070b050b000a06050400060d030203030007030f050003070004050c030d0a", + "policy_id": "0a0603090d090c0e1008091001090c05080e100d0c000b05070a0a0a", + "quantity": 5 + }, + { + "asset_name": "0e10040a02070810020805070406070410000702070e0a090f020c050e0d0e0b", + "policy_id": "0a0705010c041006030c050b00100f000000070607020d0901090110", + "quantity": 1 + }, + { + "asset_name": "0c08010909020b0b0d0d0107070a050810001001100208080f0400010f0c0c0d", + "policy_id": "0d05010e0410040c020a090d0e02090c040603050f0a00040a040a03", + "quantity": 7 + }, + { + "asset_name": "100702031000020c060708040d08000001080d0a020a050f0f040f020a0c0c03", + "policy_id": "01011005090a0810010c0b0e090c0506030b09050307070e02040209", "quantity": 8 + }, + { + "asset_name": "0706070a070903040e0b07030908090003030b050a040c0d070405030b100606", + "policy_id": "0100080d0c0b061007020a0805040303040501100b1003060a0e0f08", + "quantity": 6 } - }, - "policy_id": "6398785ae9ff38d156a0bf7519464d623c6b33212814a63e3e96967f", - "reference_input": { - "id": "7a440fa7cd5576170b5a7145b8bb676e68712b081605d1a176207a756062c118", - "index": 0 - } + ] }, { - "asset_name": "546f6b656e51", - "operation": { - "mint": { - "quantity": 13, - "receiving_address": "FHnt4NL7yPXwonmMtNXdL7k5Rb1BZxTT1gh4m7YNgv5xf9FTeDjzNB3DrjrSkNm" - } + "address": "FHnt4NL7yPXiJT9oKYhJHd1pw39bJkFuJemz5XpBbFgVDyvakdc3MRjNPc8zpG6", + "amount": { + "quantity": 41196794181264729, + "unit": "lovelace" }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } - }, - { - "operation": { - "mint": { - "quantity": 22, - "receiving_address": "addr_test1vp3z2ypn8vm9m22pjjl5zfsxhngq5gzcwlxk5jth8mmqq4q6jgjee" + "assets": [ + { + "asset_name": "0a02090c040a040a02080f040810020401050e0f0f060200040809040b100404", + "policy_id": "0109020a0f0f0b090b07020102070d0f02070510100b0b0c0804080b", + "quantity": 7 + }, + { + "asset_name": "0705080108040210100e0a00050003070105060d0209010c0d07040708080805", + "policy_id": "070c07020402000c030e0903020e1009100a0c07080704080c000007", + "quantity": 6 + }, + { + "asset_name": "1002050106030f0f00050a0c0c080e050207070e040202050a030d00040d030c", + "policy_id": "02090f0604020907030e0a0400010d040706070b0d03100a0e0c0a0f", + "quantity": 2 + }, + { + "asset_name": "070a0f0f0c0d0b0601090c0a0d080303040a03090300070e0b0a030c02060404", + "policy_id": "0007000c050c07060a070a050806010a0f10100b0e0c020a0a0f0f0e", + "quantity": 2 + }, + { + "asset_name": "0a0d0b0f030507040606020508040c060803040a0101000a000f090608020810", + "policy_id": "000504030d030e0001010f05050e0a030a010d0a0702040b0c0e0c08", + "quantity": 1 + }, + { + "asset_name": "0d0d050c0708000d06030b0d100a0106030f0e090d00060b06010d01070f0408", + "policy_id": "080f100209010e050f0f05030b1001060001020c0a020b050f0b0508", + "quantity": 7 } - }, - "policy_id": "456129eed9a44e87a57689c0ce082e4d5bd0aceb62e0c8afc5a8dd46", - "reference_input": { - "id": "430d2a291f0436045b642ab5f93c517d2661e70b51d5553c5a5a28b227e76c2c", - "index": 0 - } + ] }, { - "asset_name": "546f6b656e4e", - "operation": { - "burn": { - "quantity": 21 - } + "address": "FHnt4NL7yPYAUX5EGi2tMZEFFpHHepkCm1BJyazPb2Kxj84i9wfMNfRqwJfUZYr", + "amount": { + "quantity": 40571785863613621, + "unit": "lovelace" }, - "policy_id": "9fa20790005296d1fd26b57865bfc086ca85fc9f82173e500d0533cc", - "reference_input": { - "id": "4e765c43e0615c47a82c612c04757c7879873b4f3549f61a5e0c13524e653b13", - "index": 1 - } - }, - { - "operation": { - "burn": { - "quantity": 11 + "assets": [ + { + "asset_name": "000c10000b0f0c0110100b030201020304040c070202090c0807000f00000804", + "policy_id": "0f0c090d0006010c090103070310030705070d0c0607050f010f0706", + "quantity": 1 + }, + { + "asset_name": "020f0e1002030f020200100c0010020d0105010708100b010708000a0d01070e", + "policy_id": "0d020a010b010b10010e0c030600000005030a0102060a0602011007", + "quantity": 6 + }, + { + "asset_name": "0c010a0201100b0e0b070f03080f0710040d0a0d0310070f03000406020f0309", + "policy_id": "0b0f0802000e0e06020a040e09000d06020b080603000f0c0e040b09", + "quantity": 9 + }, + { + "asset_name": "06020f10020a0f0b040310100c06000b050910000d020e0d070b1009100f0807", + "policy_id": "060a0e070d0d0f0d06000b0d0c07000d0604000d0e0b050603020d0e", + "quantity": 9 + }, + { + "asset_name": "040309000d060e0804100c080f060908050108000d0c08050705000300020a0c", + "policy_id": "0b0a0104050f060a010c0c01060d0c07100d0d000c060209090d0f01", + "quantity": 3 + }, + { + "asset_name": "030d060b0b0801040a0c10050a0f0b0f070e0c03090910050a0e060305070208", + "policy_id": "02010f070f0e1005060c040909061010060608020300030d05050309", + "quantity": 6 + }, + { + "asset_name": "050a030b050b0d05090a0b0a070d0c0109010605010e0d08040910090206080c", + "policy_id": "10060601030b0c0d0a100202000905070c0c010101030b0e07090d02", + "quantity": 3 + }, + { + "asset_name": "100010020e0e0f09010b0c10050f010a0e0a0f04100a100f010a0a0600080900", + "policy_id": "010c030107090408070102020e0d070f0e040e050e0a0f010809100d", + "quantity": 3 + }, + { + "asset_name": "0e080e020b050907030a0f020f001007000904031009020a0d080b080d0c040d", + "policy_id": "04040f08000410041009040300000b00010b07060e08010d0d020d0a", + "quantity": 6 + }, + { + "asset_name": "020e050a050908010f080705080a0702050908080507070408070505100e0d03", + "policy_id": "0b070f0000060608080c0407060907040206070102070c0d00070a02", + "quantity": 3 + }, + { + "asset_name": "0d0d0405060d0b04050610100508000e100a070e02010d0e0403010c05040401", + "policy_id": "0c0f0510090f10020a0b040d0b0c0909030e020b0f0b020a0e0e0400", + "quantity": 6 + }, + { + "asset_name": "080510060b091005040103001008090a07000d0b0c0a10000c000102070c050e", + "policy_id": "0b090407090f0a0a0e060f0007050205031010050e00100b04080202", + "quantity": 0 + }, + { + "asset_name": "1005030e000c01050e0b050b0204040b0b060f0e0e08000c02020b0d0f020b05", + "policy_id": "0a070e030c10080a04100d0d07010d060b020d0c0d09090402040809", + "quantity": 0 + }, + { + "asset_name": "0c050f000c021009070c060c030e04040e0f1008080303070c010208040b0501", + "policy_id": "0805040907080d080905010f0b0c01060901030a040c0d030000080f", + "quantity": 8 + }, + { + "asset_name": "0f0c08100405060e0b0c00050b050801040e07100f0d1000030b0b0800080304", + "policy_id": "02050b0b071008070505100d060c01020a02020b010d0b100a041002", + "quantity": 5 + }, + { + "asset_name": "01040f08080e08070005080301000b060c0e0c0f010b0a0606050e030a070202", + "policy_id": "020e02030800030f090a000d0d0d040c0501090b09080a0a10010806", + "quantity": 1 } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } + ] }, { - "asset_name": "546f6b656e5a", - "operation": { - "burn": { - "quantity": 21 - } + "address": "addr_test1qr679dun7a7evqw6xywrupc7s72xl9m6ehm7rkp6qd7rpqrgjh2hlrkmx886x40f85f30uz33xyvpgltpwvtxqe62wlqmpvnw4", + "amount": { + "quantity": 30158563705918805, + "unit": "lovelace" }, - "policy_id": "9c959f3b6991e7122bbde3b9da4d5b731a32d297f6cc0c42e865504b", - "reference_input": { - "id": "4b40606a1ed848198709290d046c704d477764fa745744381a5a6832485a6504", - "index": 0 - } - }, - { - "operation": { - "mint": { - "quantity": 22, - "receiving_address": "FHnt4NL7yPXoSaumw5NsoAt8NEetUZ7Au1fGQ3AyMRUyXd5jsJwroRifSPkhK4N" + "assets": [ + { + "asset_name": "040e03030700060c0c0206070c09060b0a0d0901080810060e0b070b01050b00", + "policy_id": "040f06080305020b0d0610080d020e0b0d000c0601070f040e050107", + "quantity": 1 } - }, - "policy_id": "598fda896bb2e18de5da1774eaf9fc335222096ddc76e47e181d2daa", - "reference_input": { - "id": "d84532222c633b0500718057351b4c4467543b44022a20373f3c16086b5c08ad", - "index": 0 - } + ] }, { - "operation": { - "burn": { - "quantity": 15 - } + "address": "FHnt4NL7yPY84auwn2twaPeZkdRL9Rj475dzLBTEfALmsP9wNZrjWAmMQwDYmH9", + "amount": { + "quantity": 29574201592912340, + "unit": "lovelace" }, - "policy_id": "3db5d99547124fbe69f42bc807f976425305b62ee857bf424df5159c", - "reference_input": { - "id": "81d51c781d320c5b132fde3c360a387508081420775808352c32052bf5793874", - "index": 0 - } + "assets": [ + { + "asset_name": "00070c020f0502050e00061004010c0b090e07080d0b030e0905000a0e070c0c", + "policy_id": "02100b03100907040c0810010e00020b070706010808050f0c0e000b", + "quantity": 3 + }, + { + "asset_name": "08020c05000e0b0d0b0b10010a1001010d0f0e10050e01070c0b0a050d0d0b09", + "policy_id": "020b0100080e03000d0b09010a020a0e0a040d08020e0e050707020f", + "quantity": 2 + } + ] }, { - "asset_name": "546f6b656e47", - "operation": { - "mint": { - "quantity": 15, - "receiving_address": "addr_test1yzfel7vmlh37ldnd0x3x6c2f2kz4388vfga5n6t2reqmw8eaqyenr7qlr7dlcytf426pnk7evxruzkqkkgugcnzxl0wq8cq5pm" + "address": "addr_test1wrdxnyw8gy3rqug5ashha0759l2l0egxnn0qf47a70cxjesclr3u7", + "amount": { + "quantity": 6759474073326076, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "010f0f020e0810050c0e00070e0a010805060f0e0c0609080a0d0802080c0809", + "policy_id": "0d08090b050905030a0b060e00030a00030601080a10090a0d020e05", + "quantity": 5 + }, + { + "asset_name": "0608080c08030d03060c0b010b0002010a01030f0f000f060010020508090302", + "policy_id": "010805080d040902000c0d0a0b0e040a090a0202001008061009070a", + "quantity": 1 + }, + { + "asset_name": "0f05000b0d0406080f0a0b0703070b080c0508000d0d000807010c04030c010f", + "policy_id": "0d070d0000090d0c0301060005000803000810040c010f0c10070f00", + "quantity": 6 + }, + { + "asset_name": "0f010701100c09060a0b0f06040e01060d0e030f040d0d0b0800000c07010900", + "policy_id": "0a0804050f050a0902050e060a0d020c0b06100909000e0a0705020f", + "quantity": 0 + }, + { + "asset_name": "0006020506030102100f040a0408020d08070b0101000f050e0f0b0b09030b0e", + "policy_id": "050c070201100500060903100002010208010b0c070c090d0d07040b", + "quantity": 7 + }, + { + "asset_name": "1007030b100005080708080f0c100f0d060900040a08050b070d100c0d0f0f0a", + "policy_id": "070f080409020e04090102040d0f040b0501040e0109100c0f000a00", + "quantity": 2 + }, + { + "asset_name": "09020501030e0105090a0e000f0f010500100308080a020507060706060f0d06", + "policy_id": "0c07070e08080a0710090301070f050c01060f0304020a070f0a060b", + "quantity": 2 + }, + { + "asset_name": "0e0807010c060b0a0f00020f0010060b03040c06070000090b0e040b0b0f0a04", + "policy_id": "0e100305030704100b000f000c0c020a0a0a0d060806040a010b0a00", + "quantity": 1 + }, + { + "asset_name": "090d0f0806080b0b0a090300090f100d0f0e010e0a0306070f0d040800060010", + "policy_id": "05030f0c090201100d0810000c0e090008090009030d000d01050a06", + "quantity": 1 + }, + { + "asset_name": "0007060c08030708040604030c030e0b070b060b100100100e10030b05060b0a", + "policy_id": "0a080b080503010c07061005010d0d010c0d020309100a04080f040b", + "quantity": 4 + }, + { + "asset_name": "0a0a0d06040b090a050606040506010f040407020c0806040a100f0e10030902", + "policy_id": "0c100e0d0b0c0303060f05060f0b000f030a02010b0f0b000e070510", + "quantity": 3 + }, + { + "asset_name": "000d0a0f0c0e080c0502080f0606070e010b040c0d000109050e060b0107030b", + "policy_id": "020906060906080c040110080b07030c060a0f040307090504030808", + "quantity": 6 + }, + { + "asset_name": "04060d0c00100d080c000e04030104050d0c0a0b00070d080e060b0c05070510", + "policy_id": "070f050f0404100f100408030d0e030d0f0a0606060c08010f02040d", + "quantity": 4 + }, + { + "asset_name": "080d000b0608090707080f0a0607000600090110040c000e00080d070104050a", + "policy_id": "0a01080710020f0c0b0b0d0f0f10050b040b0f0c0f040b07070e0c0c", + "quantity": 1 + }, + { + "asset_name": "0601100200061009040b0b0b0e03020909010e020200070a100b000f01020400", + "policy_id": "0204030d070d09090c070f0f0e0406030c030d0a050b100408040a05", + "quantity": 4 + }, + { + "asset_name": "0e09010b0e0d090c100f01090e0a0d0f070b06080a050f0309100405020d0007", + "policy_id": "0d080a0b0a0b010b0102060c0c0d020601090a0c09040d0e0d020d06", + "quantity": 8 + }, + { + "asset_name": "000e050f0c04051001080a0d070806100402030f0a0d0408080a0a0f05050405", + "policy_id": "05060306030103030409100a08080710060b040a0204050801080d03", + "quantity": 0 + }, + { + "asset_name": "100a0f0e07080c100c0e060601020605100a040f0005090a0d0a0c0d02070601", + "policy_id": "000600060e060e0e0e0505000003100b0f050005040d0005090b0a07", + "quantity": 4 + }, + { + "asset_name": "0a1008090b0b0d090c100b0c100b070507020203061003030707020b05040106", + "policy_id": "01000310060e10030d0d04090e00070d0e01090703010702010a0809", + "quantity": 8 + }, + { + "asset_name": "03010d03030f1003020308090a0a0e050509030210010a01000e000603070b09", + "policy_id": "0b04030d0d07040b0504051009060c07010510040f0a0904000b0f07", + "quantity": 2 + }, + { + "asset_name": "000f06080b000d0a0c080c000e100e0e06041004040c0b0006070710040d0d02", + "policy_id": "06050a0e0b08080b09100f0f0b0c050c07060d06000b000c07100b00", + "quantity": 2 + }, + { + "asset_name": "01030f01020f0b0a050309090a07070b0506020b07040904010f0e05000b0109", + "policy_id": "020e050b050d05040b0c0d0b08080102100d0d080c10070705090a09", + "quantity": 6 + }, + { + "asset_name": "0d060f0d000d01020c060f090b070f0e080c0d080c011004060b0c01090f0006", + "policy_id": "10010a00020c0f0804040509030d0b070e0803010708070105050707", + "quantity": 4 + }, + { + "asset_name": "0c0e0004040405090509040b040600060a0600050e07040d04070c0805091004", + "policy_id": "0f0a0a0809070e00070d0a030d0e050f100b06040b01090f0a100410", + "quantity": 1 + }, + { + "asset_name": "0902070e0e010f0d0f060c03050e0007050a0b06010c0a0f0d0f09090406050d", + "policy_id": "02050d0f050e0f0a01080c050d0103030f00100c06100a0c07030704", + "quantity": 9 + }, + { + "asset_name": "0e090c0f07060710030f0b02070a01010d020a100b020508050504040401060a", + "policy_id": "03090d0b0b01080f01030a0009090607060a0b100804030409060510", + "quantity": 7 + }, + { + "asset_name": "00100d000c0e010e090c090a070b000b07090709020a0d060c0f0d020d030b0a", + "policy_id": "021000030d030108050b1006070c0a010d0a030c0d05090b0401060d", + "quantity": 2 + }, + { + "asset_name": "0b020b09040201010e05090b0a0d010f0a0b100a0f100b0f0907090e020a030f", + "policy_id": "040605000b100d0d07050906050f0004030c08030b0306020c070610", + "quantity": 9 + }, + { + "asset_name": "05010d0b0f0406080a0f030e0800080f080102060a0c0c090f07101003031009", + "policy_id": "010b0f0203050102060c000d080e0c060f0606030e03071000000e02", + "quantity": 0 } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } + ] }, { - "asset_name": "546f6b656e45", - "operation": { - "burn": { - "quantity": 4 - } + "address": "FHnt4NL7yPYFptsTPVmpxuAJRgLc2U7DrvTVCorTrniFiDnEoZHmGWjrM1bYbaa", + "amount": { + "quantity": 17854055941776972, + "unit": "lovelace" }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } - }, - { - "operation": { - "mint": { - "quantity": 21 + "assets": [ + { + "asset_name": "0709020a080f0c0b0304070f0d070a0a020b0e0d0c10070e060d05020a010809", + "policy_id": "020f060c010405000a091002060a0c030904090b0b0900010c020a02", + "quantity": 5 } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } + ] }, { - "asset_name": "546f6b656e4f", - "operation": { - "mint": { - "quantity": 10 - } + "address": "FHnt4NL7yPYKc5SaxopYwRPYqJqtmAkgjYxG2Fj45eTEGp7dpCjAfwE2xEkMbza", + "amount": { + "quantity": 5839253452216068, + "unit": "lovelace" }, - "policy_id": "25420449637a973d17a99e42115c9886106dcff98a0952a1d69dc474", - "reference_input": { - "id": "0f33480d1b3d37306836436702505e7f4f461c211530d90dc2681d0530121c33", - "index": 1 - } - }, - { - "operation": { - "mint": { - "quantity": 11, - "receiving_address": "addr_test1xqend633mn749fj4e4q8c367ptxppk6glfsnxtehc5pxqyh4t5lrrdnqhjck62sspycrvvm4aavcjzsd46jzzs2cejpq7r29y9" + "assets": [ + { + "asset_name": "040c0902090c0e080d030e090c05030e10060907000103000f0c0d090505050a", + "policy_id": "0d0c00080d0502030210050506050d100c020d0c010c0d0402030708", + "quantity": 3 + }, + { + "asset_name": "0d050f0d020c08050d100d0004010f0f04030c10010a030b0910010c080c0a0a", + "policy_id": "060805060d010e0405030a09090605030d0a010f060f100e0e0a0c09", + "quantity": 2 + }, + { + "asset_name": "0c00070306010b0a0f100b050602060f0d0e020305070404060c030d020f0300", + "policy_id": "0d1009070b10100e0e09080d070d0305070f0610030600010a0c0506", + "quantity": 7 + }, + { + "asset_name": "050103100b0f070a0f060c060d030610020b00040d050202050a0f090805080d", + "policy_id": "0c10070e090b0500050d0601050b0003090c0001020e040305061003", + "quantity": 5 + }, + { + "asset_name": "090710040e09020507010508020b0b07010e0b02021005030305101005010b0b", + "policy_id": "030c0a080a10050e010f020d02050506100a000b040c090d0d030606", + "quantity": 2 + }, + { + "asset_name": "0703090810050c10100c0301050c100c000207010710100001060f0f0c010a0e", + "policy_id": "100d0a0a0f0e070d0f08030b0b0605090d010500000d02070505070d", + "quantity": 9 + }, + { + "asset_name": "10040a0e00000808090608090f060d0106010b0204100c0204000b0a090a010a", + "policy_id": "0a0b02010d04030d0a01050305020e08050c0002060010100c050f0a", + "quantity": 5 + }, + { + "asset_name": "050d0c0d0f0a040d050e0f070806001001000d0b09010c000a0309050a0a0c10", + "policy_id": "0a000d0b0f0e0701010300070b0d0b090206080e04050f0b0806070f", + "quantity": 7 + }, + { + "asset_name": "0b0d0f0b0c0e0803080706100b030d0d0800070e0105090d01031006030f0100", + "policy_id": "040f070a0604090b030400090b0a0906000f0607080f020e070f0506", + "quantity": 2 + }, + { + "asset_name": "000c0d0a090f0a0a0f0402100d0e100b0c00050a080f02080408090609010f0c", + "policy_id": "0e0209020c0e030e0d010b09050b0806021009040a02050c090f050f", + "quantity": 9 + }, + { + "asset_name": "090c020b0f09000e0900020f010e060d0d0e1002060f0d0e0a040d060d0d0d06", + "policy_id": "100800050704080d0d100e090b070f0c070f09050d08070808100800", + "quantity": 9 + }, + { + "asset_name": "090803070d0c0e080409010f030f02030003030201050f0c0501050701070507", + "policy_id": "000e0b0907031006070a061009040f0c090d0706060e010208000f02", + "quantity": 1 } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } + ] }, { - "operation": { - "burn": { - "quantity": 26 - } + "address": "FHnt4NL7yPXmByuMyqB2Wdjq7dLAsZiNZfRD1PCDY3HfaPdU4Bg69AJS8ovj622", + "amount": { + "quantity": 13672242372756654, + "unit": "lovelace" }, - "policy_id": "620fb5d6959d2ec982ae065a1237b02ccfa68fb5994330406890487a", - "reference_input": { - "id": "4e066d6478587e4a1a3ab078227d242d2a0522102b03390fa52f1e77271b0a7c", - "index": 1 - } - }, - { - "asset_name": "546f6b656e5a", - "operation": { - "burn": { - "quantity": 23 + "assets": [ + { + "asset_name": "080a0103020b0101090e1005030c08080e0d0307010a050c0e0d070a090e0a0d", + "policy_id": "0006030d080f0f030109010e09020d0c04040306080e0b070a0f0a00", + "quantity": 1 + }, + { + "asset_name": "02090e0f040702010305060c100b0e07090a0710100403030310000a05090108", + "policy_id": "0e100e070409090a06080a0508000e0b0009040b0b09060e030c0d0f", + "quantity": 4 + }, + { + "asset_name": "0e0f0d0b04100909000f090010090e0b0201090e0c020b05060809090d0b0b05", + "policy_id": "02080a04090e1006060a02010f02030a06040d0e030610060705070c", + "quantity": 3 + }, + { + "asset_name": "000c050a07100a0510040b0a0810100d0f1007010802000506000b0b0c060706", + "policy_id": "0003080a0b010808030c0304020000100a070804020f0c0a0b040e05", + "quantity": 7 + }, + { + "asset_name": "0e010d0a0c0b05000a0902060e0e0f0e0e080e100f070b07070103010f070309", + "policy_id": "0c010a0b0500020d0e0609060a0306000c080509100900010c0c0502", + "quantity": 7 + }, + { + "asset_name": "10010208040b020e02080a0e0a050a0401030108060d0e0e10030f020d000e0d", + "policy_id": "0d080900000b100308060e0a100101040703010a07040307000a0100", + "quantity": 3 + }, + { + "asset_name": "090307070b010a05070d0403000b0a0b08010f0e040c0e030e001004060c0205", + "policy_id": "030e0c000f08070f0b040d0b0d030407040406090701040a0901100e", + "quantity": 9 + }, + { + "asset_name": "03080608020a0f0f0f0f040210080c05080609080f08000002060307060d0a0a", + "policy_id": "0e050d080e03020c0a01040c01020a0e0c100b0f0d0103010f030505", + "quantity": 9 + }, + { + "asset_name": "090a10040809040d0803020b04101003000b0a0f0b0c0f02100b0e030805060b", + "policy_id": "000b0b0e04030f08040907020b0110040a04060c0e0c0a090c00060c", + "quantity": 4 + }, + { + "asset_name": "0f090a0e070e00050b080f0b09030b09040d0a04000f090406040f1000040701", + "policy_id": "10040504040000080f040c080a06040d0d020b05080d0f010c0b0504", + "quantity": 8 + }, + { + "asset_name": "0206090d0c0c0d030d0f10060c000b0f0e0f01100810010c07000c050e100604", + "policy_id": "030f090e0804030506080d0a0608070606060a070e060c0c0a10020c", + "quantity": 8 + }, + { + "asset_name": "090c0a0e0f000603040205021010050c01060f020906060d090c0a0c0b04010f", + "policy_id": "06040e0303050d08060a010a0f01090a0b060a0d0a04100a000a0e01", + "quantity": 5 + }, + { + "asset_name": "09040f060b04070e05090e090f0b0e0f08100c0503060e0b0c0f0a0d030f0309", + "policy_id": "08060d060c080b020603030510000c0e0c00020d090f090206070d0e", + "quantity": 0 + }, + { + "asset_name": "0601090c100400030f050d060d010e0d050d050b00011003090f0f05030d0d0b", + "policy_id": "040a00100302040b090f04080f100b06000107040a09020106090601", + "quantity": 2 + }, + { + "asset_name": "08050f000c05100f0e0e06010e0b0c0509040c0e080305100006070e0a030310", + "policy_id": "080c0b0d010402060206040d09090810000607030701030e0d0f0003", + "quantity": 2 + }, + { + "asset_name": "0307070906060f09100b05060c080d0e090d08020a050f04010e0c1007070801", + "policy_id": "10000f0b0c070905070207020507000508000a070b0b000b070c030f", + "quantity": 5 + }, + { + "asset_name": "0b07030800070e0803050807100a1004080b030907000b0409100b020b0b040f", + "policy_id": "07040f0f070a0e0c0f0b0400080305040a060c03040c0a100a0c0807", + "quantity": 5 + }, + { + "asset_name": "0306100103000000000a0f1001100a100f09000e0310070003070e0104000404", + "policy_id": "05100902080d0e03050210080400000802100e06050910000007070c", + "quantity": 6 + }, + { + "asset_name": "0c0a09010a0a000204000109000d0e0c040a0010040508020509020f00090608", + "policy_id": "1007080d0e0c090606050e0a00010a0904040006050a0d0003040205", + "quantity": 1 + }, + { + "asset_name": "0e0b04050c0208100506020d01040f0c000c0d0c1004100a0700070f0c0b0c07", + "policy_id": "020b0b020c0e0f0b0200090e020a0010020e0604041003090f0e0d07", + "quantity": 9 + }, + { + "asset_name": "040e0101070b0b050d0c100d0e0e060c0f10010d010101030d10010606020602", + "policy_id": "0b0b00060110020702050603000a0e03020b0a03090f0d0c02020a0b", + "quantity": 2 } - }, - "policy_id": "6df5055d1b93d2e392edb0da44a2cdba3bc1f323c74e7c2df144fc37", - "reference_input": { - "id": "275c255fd77f2f5a4962386d2f426962463b4d326288653a5542690e7c4e0e46", - "index": 1 - } + ] }, { - "operation": { - "mint": { - "quantity": 30, - "receiving_address": "addr_test1wpr262nlqfwdg6sshp9rfmtdg70fka06ym50qpq96w2myscxhga73" + "address": "addr_test1yrjzj5tfglnlahnukkepk70cpct3rpp58qqsm6fk092nfe2lunw2gu9eae6hurl5xr8a8vekg3yn3eyzdeq8gm5kaxpsr7pn88", + "amount": { + "quantity": 45000000000000000, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "01030f0f020b090806070f090006090c0d070e0c02060d070309090c0d080a0a", + "policy_id": "010a0a04050b0010060c1001040b0209030606010a0b000b0f050609", + "quantity": 0 + }, + { + "asset_name": "090a09100e0e0b04020f0c050e0c050f090e0504070c020a0e02100c0f060609", + "policy_id": "0710040f050c0d0e010d000a06041006040f09040505040d000f0f06", + "quantity": 5 + }, + { + "asset_name": "0f100d0e010e0503030f0a0d05070e00000a010200100e10020a0b0e1007100c", + "policy_id": "101002080c0a05010108050f0409050a0c0f100f010204030f0a100d", + "quantity": 1 + }, + { + "asset_name": "0b100a0306010709010f07070703080f0e0703040e08040e060910020806010c", + "policy_id": "0c050f0f0303000a020501060e100e06050707060c0f0f0c0907100c", + "quantity": 7 + }, + { + "asset_name": "050d0a090f05020400080e030e08100f0d03040a070608100d05060007040410", + "policy_id": "010c08070d0600030c0b100e0606050e000d0f0c05010409000e0208", + "quantity": 6 + }, + { + "asset_name": "0005050c0f0e010a1007091007040c0d010e0203020d05050d0c0c040f090a0d", + "policy_id": "02090102090b0c010e0b10030e090006010b04080409080f0f0b0a0b", + "quantity": 1 + }, + { + "asset_name": "01050c06100b0d0e0a0f0e0606050e0b0509010810060804030a09070a0c0902", + "policy_id": "0c0b0e050e0a04030b030b08010902020101010b0a0004010600010c", + "quantity": 5 + }, + { + "asset_name": "070e0406000406080c060d0a0d030b0410030200070e10080700040b0503050a", + "policy_id": "08040f0f080c010f06060c030d08000d08020d0f050b100c0f030506", + "quantity": 3 + }, + { + "asset_name": "020c00020a000a000308060804060b05020903030c0c020b0603080c0307020d", + "policy_id": "0b0c010b070e090a0310040e0210020f0100070a100f06070b0c0a0a", + "quantity": 8 + }, + { + "asset_name": "000f0d060708030501050c0608050f0a0b0c0101070a0b0d05050a0102060c07", + "policy_id": "09071010040700070f030a00040b10020f0d08040f06040d0405100d", + "quantity": 0 + }, + { + "asset_name": "0d0f0e010307020f0e1001080107060c090d090504040d0102060f0100080d0b", + "policy_id": "0a1000010e050c04001001070c010e0704030710100f0e0704101002", + "quantity": 8 + }, + { + "asset_name": "0e0704010b06060e07000500000608040f07040f10060109060e0e10020b1007", + "policy_id": "0e040d000f0b0e060d0402090f0a0c0c000a100f0c08090d060a030b", + "quantity": 7 + }, + { + "asset_name": "010e0710020309100c0b07081009020e030704060c08080d0d0409080d050510", + "policy_id": "0a030a010f0002041002060804020b010e0d0301090901010007060b", + "quantity": 1 + }, + { + "asset_name": "0a0b060b06080f07030c0c050f07030c0a08010d050d0f05050306020b100403", + "policy_id": "0d090e0b090f000c0601030901050f0a020d0a030707100909020d00", + "quantity": 9 + }, + { + "asset_name": "0b020705050205010205090a04100a0f090609030a060e0a01020a0501011008", + "policy_id": "03010d0e0501010d100a0b060f0801060600010b0e02040e05020b03", + "quantity": 7 + }, + { + "asset_name": "1001020502010d080f0701050d100b100c00070e0810020f0f0d0a04030a0c0e", + "policy_id": "0a080f0d0805010e0b010e0d0f010b0c0b07030d0508040107010b03", + "quantity": 6 + }, + { + "asset_name": "04040d05090e0f050e10030a0508030d0b000102010c01090c0404060302080f", + "policy_id": "050f0a070507040502020a03000b030e0d0706020f100507010f0d0d", + "quantity": 4 + }, + { + "asset_name": "040e07100708090a0908100b0905060303040e000c0c081005000e0808080810", + "policy_id": "030308010004050a0a0c02020e08021002080004080d0603060c1001", + "quantity": 9 + }, + { + "asset_name": "0b0f0e0c040303010b0e0807100c0f0606100703070f0e040f02080f0a080708", + "policy_id": "100c0500100e0e060c0e040f0f0b05020c0504090f0d0d0d030f070a", + "quantity": 7 + }, + { + "asset_name": "030a080e000500100b0c061006000b10061002070f0609090f0d050304000202", + "policy_id": "080d080b06020d0d0b0a08070f0f0b080b06080103000600000d0b0b", + "quantity": 0 + }, + { + "asset_name": "040e000309020b030706000b0b08040a0808000b050a0202070a030d04070505", + "policy_id": "0b04030c07070607010a0b0b0b0a0f1008030a03050807090d060308", + "quantity": 4 + }, + { + "asset_name": "00040807011005020c0507090b0200060b08080600050d0902070909010a0e0e", + "policy_id": "0b05080f06100606070b01000c01090509070b03050000071006080d", + "quantity": 6 + }, + { + "asset_name": "09050d0c060e030a090b090907070b0706000106080302080210090b0f100b01", + "policy_id": "0303100b080d070e0c090606010801070808050f01080f0e000a0c07", + "quantity": 5 + }, + { + "asset_name": "0d0b090903080f0408091006020a01040c000c0a0d040d0b0e0e031001100f01", + "policy_id": "060c0206000b07100c00090b01020d05000c1006090d030807031006", + "quantity": 5 + }, + { + "asset_name": "0a0a050d030c070e0c100b0f030d07080705050b040001060d0a0b0b06070206", + "policy_id": "0a070d090e080f0b06010b09090010030f0a09050f1005080702070b", + "quantity": 5 + }, + { + "asset_name": "000d070c0a0d07100109070d100e0a0d00080606030c100a080c031001080805", + "policy_id": "0602070c0f00050a04080b06010a04100f040a0d10060d010b0a0e02", + "quantity": 3 } - }, - "policy_id": "bc495805f61573f3cc864d4247bff18508553b034a02364c6a64b9c1", - "reference_input": { - "id": "0c331f7a684e220c5d561182331e0f7170023f08936d7a07d91a1e3a00357c71", - "index": 1 - } - } - ], - "payments": [ - { - "address": "FHnt4NL7yPYH1s2p9VzBMAXnLCMCCC2wrbVcyppqrKAJVGhAh2yzdvmvoDHWu2c", - "amount": { - "quantity": 243, - "unit": "lovelace" - }, - "assets": [] + ] }, { - "address": "FHnt4NL7yPXxRZH11bZruPaCYWcu4XCW9Y6iYAs7EJSA84dyXZZTS7CXjdk41NK", + "address": "addr_test1qqd2mhup4suats3ug0ysnk9emufaq3s54hynyj6d2np5yvm403zslk8zxd2n5g4au94h9qqhrgjhvwj9tlywuyff5hnqcmes2z", "amount": { - "quantity": 85, + "quantity": 5372481379188061, "unit": "lovelace" }, - "assets": [] + "assets": [ + { + "asset_name": "040e030709030607100406001007010c100a0707020f020f080e08020f05040a", + "policy_id": "080005090d07020b06090f000b0f0a100a08020b0e09080b090a0c07", + "quantity": 6 + }, + { + "asset_name": "0e050b030c080b090a0e040b0505060904090c0d000b0c0202060e03050f0f0a", + "policy_id": "090709020c080e0b090c040f00090f0005070510090d000608090a08", + "quantity": 9 + }, + { + "asset_name": "07010e0a0e100e0e0a0e010b0e0c0a040c0a020b02050b031000070c070a0f0b", + "policy_id": "000a0e090e0a08080008100b08040904100603011006101004090910", + "quantity": 1 + }, + { + "asset_name": "030b0b0a030d020a0d0c030e091009010b030c0b0209010b041005030c050701", + "policy_id": "0c001006030a02060e050d0c0c0f000c0803010503100f0d09010a0d", + "quantity": 1 + }, + { + "asset_name": "08090c0d04090c070a000b0809100001020a02080202010c06070c100c040c05", + "policy_id": "0c010d0f010506050b0404050c0e0b0b060a050e050b0d0c0d030d04", + "quantity": 1 + }, + { + "asset_name": "0503030a0e0f0c090808050600090704040b010d0e100408080d020e0f000307", + "policy_id": "090f000f070c0b0903040e090a030f000f0c000a021007041006070b", + "quantity": 8 + }, + { + "asset_name": "0401050002070604000b07030f0507050e0506040907030d0e060b0707070309", + "policy_id": "04070e0f0804060b0b070c0506060f0609090c080e07040d0609010b", + "quantity": 5 + }, + { + "asset_name": "040b0f06010a04040609040f070b0b050f0c020a03060f09100f0d040e07020c", + "policy_id": "030001040d090b0902020a07050f0e090c0d100705090a0c0b080a0c", + "quantity": 0 + }, + { + "asset_name": "070c0b02030c070604030a000c05070b030c0b000307080200080a080705040f", + "policy_id": "0c10060b0210060b060508070c0c0308020f0402070b0a0b0304060b", + "quantity": 0 + }, + { + "asset_name": "020f0e0206011001050b0c060d000b040e06010301060a0107060b07000f0b03", + "policy_id": "100f0b0b0a020f03030c030e030908090d100c020e05040e09050509", + "quantity": 1 + }, + { + "asset_name": "03050d020a0d020304090c0900020709000e0a0b000707080b100c050a0d040f", + "policy_id": "0100080b060605000802040d070f09050d0f0f030f040010020b0003", + "quantity": 9 + }, + { + "asset_name": "0e09030d020a0d03030e0b1009100a040700060b0e04070d0709000d08090c05", + "policy_id": "09040b01090b00050d0a0b07020c020e0208030d090b090905020909", + "quantity": 4 + }, + { + "asset_name": "040f0e060a0b040c0b0c000c090d0d050d09010908060301080005040e02090c", + "policy_id": "05050e01021007010f08030c02060d06051007030a0c08040806010e", + "quantity": 1 + }, + { + "asset_name": "0b07060a000c0208020f0a0e070d030a0509050400080f0d070f070e0b000f07", + "policy_id": "0c010609060b09000501060c00010d02050110090d090006080f010e", + "quantity": 6 + } + ] }, { - "address": "FHnt4NL7yPXwXYNjQcm6Mk1kjZT3coyHmdbgktaCwC5yGHPgBaaCUVH1uzcWZS6", + "address": "FHnt4NL7yPY6iPKJJyofMhrkgFsGheVHMgooHJ2dqfTAM47mpsB58KeKZDG8Bdm", "amount": { - "quantity": 159, + "quantity": 28307193392383090, "unit": "lovelace" }, - "assets": [] + "assets": [ + { + "asset_name": "0203020a030c0e0e100709070b090601040b020f0e040a08010d040a06100408", + "policy_id": "030b0c0f020a030a0a020b0e0d0c10070400050f090c080f10070209", + "quantity": 2 + }, + { + "asset_name": "0a07090b09030a060b0e040b0b100f0e0e0a0d0710010100020d0210090c0304", + "policy_id": "0e000a010004060908000a0a0a0806000f020e0e040e030b0d04090d", + "quantity": 9 + }, + { + "asset_name": "070f0c0a0f0e0a060a0909040106080805070c100b0b07100d04060205090908", + "policy_id": "0f09010001030810040b07100e030e051008040c050a090206060603", + "quantity": 3 + }, + { + "asset_name": "0b0400000f0d0a0905010f0f010d0f0701090d020207040d01090b0909010b04", + "policy_id": "0f0a0503020d030b0c0f061000090d0c0806010b10090d07060f0c0d", + "quantity": 0 + }, + { + "asset_name": "030c070b0200100e000b0500060b0f0e000408070f020c0608050104070c060f", + "policy_id": "010d0f050d0e070c020803040e09010c00060a070f0b070a0c0b0f01", + "quantity": 4 + }, + { + "asset_name": "0f02070c0b0e0d07000203050a030910080308070f0308090d100f0709020d0d", + "policy_id": "0c0c000c050c00000e0f06080f0c070e0d060707100e0c0300070d08", + "quantity": 2 + }, + { + "asset_name": "0810040d0e030405040904040d02070d0b0303000c090a0700080203100c0905", + "policy_id": "1002000b040d100d09040601000f060e030f10020c07080a07040c07", + "quantity": 6 + }, + { + "asset_name": "0a030c050e08010c0e0b090d080d010e1007011006070c060d0f1001030c0c09", + "policy_id": "03050705060e0600030f04100001000b0d0d030b0601040803000a10", + "quantity": 9 + }, + { + "asset_name": "09041008050504070f050b0103100300040b0809030d090a09020b060d0b000a", + "policy_id": "0906010a04000702030803090c01080f0a0f100b0306060e06000110", + "quantity": 0 + }, + { + "asset_name": "0410100d0e03060e09040805000d0d070304060510030b03070802060a011002", + "policy_id": "0b0d030c0d000e0b0d090310020403040e0f00010f0a0200080c0405", + "quantity": 9 + }, + { + "asset_name": "0f0f0905100c040e001004080e0c0b02050d0c0d040d0b060b060006090a080b", + "policy_id": "0701090d100e0506020a100405000400040f0a090d0e0f010a0c080d", + "quantity": 1 + }, + { + "asset_name": "08040d0909040d07010d0d04030400090d080c070705050c0d05000108070c0b", + "policy_id": "080e0410050e020b010e020c070f0c0d060a080d020d07020605020f", + "quantity": 8 + }, + { + "asset_name": "09020d0b000410060c0b00040b0a0802090101010603070e0e0808020e0d0a0c", + "policy_id": "060107100d0e09070c080810000909040f100403000e090f02100a03", + "quantity": 6 + }, + { + "asset_name": "0d030f0b030110060502050a0f1003050007090f010b100406060a0d00060805", + "policy_id": "0d0306060e090b0d0007020e00060a0d10020209040b0707100c0802", + "quantity": 4 + }, + { + "asset_name": "020a0d07090d0c0209070804060d090e000000070b09060c0202050305000b05", + "policy_id": "0d030f03090f04010e0b0f0d090603090506091008080f0c020a010b", + "quantity": 3 + } + ] }, { - "address": "FHnt4NL7yPYG4n6JQq1vDNQwVX7gaNvYEn7gtFPrZwKgQSU8BQiDfKxJ88d1765", + "address": "FHnt4NL7yPXxwExq9TWdtPagpCyVxqEfDovuNXv96FM2nC1QaiCcFQaFoSbtiJa", "amount": { - "quantity": 171, + "quantity": 40980140949162915, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e41", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 27 + "asset_name": "02070a0b0803050b0d0906060f06080c0c00070704071004040e0f100d0a0503", + "policy_id": "0a0f0608011005030609020e070b0201090b00030b020c0d070f0a10", + "quantity": 2 }, { - "asset_name": "546f6b656e42", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 13 + "asset_name": "08070c100401070e0f0307060e100f0f100402080b02030a00100f09090d1009", + "policy_id": "010c03060c01040e0003060d0d000704010a09040102000405050a09", + "quantity": 9 }, { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 17 + "asset_name": "08070a070603000b040c0b1007090006030d070404050b0d030107090c020f09", + "policy_id": "0600020f080604080e0f0306030c00090e030606010e05030a09040a", + "quantity": 5 + }, + { + "asset_name": "0f0a0306040e0a0208030310100c0a0901090510000606100f03011002020b08", + "policy_id": "0910070c020e0c081007050b02010f061000060b0c0a0a050701050b", + "quantity": 2 }, { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 36 + "asset_name": "0e030905000105100d050604000f0a0f01010f0e010c090f07100a0b03050e0f", + "policy_id": "1004060e0d000d09000d050c070300050a040101060206100a070702", + "quantity": 0 }, { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 30 + "asset_name": "0d0208010c050a00060f020a03060f100d0e0e08020f080309000a0609010809", + "policy_id": "00070406010e030d0907030c060c0e000d0d0601080b000f0a0d0c08", + "quantity": 1 + }, + { + "asset_name": "03000b03020e0f010e0f0e00080b0f0c0f0305100e050f0701050309080f0304", + "policy_id": "08030b0408020c000c0f09010c10040d050d0b010a040f0d010c0710", + "quantity": 6 + }, + { + "asset_name": "0707080e0b0206040f020d0d0f060107050f02040a070804040d0b0509000c03", + "policy_id": "0b06000f0b0c0b0a10090b0e0507070909010a0b0d0e02030a020a0d", + "quantity": 7 + }, + { + "asset_name": "0e060a02060c0b0602080707040710050800040f0c0e010704020c050303080d", + "policy_id": "09090f0710070503010f0d0110070310071008050a0c0c010c080500", + "quantity": 3 + }, + { + "asset_name": "0c000b080a090e040f03000b0a0b09040d00090e0b000705050a050e0c020f06", + "policy_id": "03090c01080700040409080a0f010d090e10050d070b0b0e0c101007", + "quantity": 4 + }, + { + "asset_name": "0610020609070508050004010107090b07080e060b080201080e070c0b02070a", + "policy_id": "0d030b05100204080d070b01010909050900020b0806070202051003", + "quantity": 6 }, { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", + "asset_name": "010b0101060c07050810020b000b0a050b070b0306070d0f1002060205060902", + "policy_id": "0d0b04060f010305030901060109060c0d060d0a0205030a0e040702", + "quantity": 4 + }, + { + "asset_name": "050a070c040a0f0e0c0f0f0f080f0b0604060605040803080e03020301070a04", + "policy_id": "0a0600070d08080a000a030207040103060309050b0c06030d000f08", "quantity": 7 }, { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", + "asset_name": "0a05030d0e010c1000020d06031005020400050410070b00030e0c0a0502100b", + "policy_id": "0301050509060a040906080d0e090d0a0501040409100f0101100d05", + "quantity": 0 + }, + { + "asset_name": "050208020e040408090a100204000c09090b0a00080d020b0a0c0a08060e0b0b", + "policy_id": "010910070b02010b100304000102070b05010503100f030110100807", "quantity": 7 }, { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 26 + "asset_name": "05100d000609020d0703010408001003100d020001030a0b050a030c05010007", + "policy_id": "0f020b0d040f030c070b0d0710040901100d0e0a010e0e0c06000106", + "quantity": 5 + }, + { + "asset_name": "0f0503060d0110070407050807000e0c0a0e0408070f09100e0b0e000f040506", + "policy_id": "0703080800090e0b03020f080a10040c030a030509030a0508100d01", + "quantity": 8 } ] }, { - "address": "FHnt4NL7yPY17i86rV5xa7X44Rg969UNLxFBizMAPQc69p53j3ggvE7iYfQHC7C", - "amount": { - "quantity": 46, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "FHnt4NL7yPYJ5Rq1RMRCs82NNWGs5FLn6a3GUexePe1hoSJ5UTs9X6caP3T2mHU", + "address": "addr_test1vrsca285glk3qmplzu86fuq5qygje4utvxkma2u8csraqlsagnz4q", "amount": { - "quantity": 184, + "quantity": 277004508913411, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 5 + "asset_name": "10000108020109070a0e00050c090110020500060b00090a0004050607030c00", + "policy_id": "090e01050009020d0406000c080b010705000d0a10040710100f0e0c", + "quantity": 2 }, { - "asset_name": "546f6b656e42", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 26 + "asset_name": "0c0604030d10080b08010f030904050908010d03060f0509070b080705100106", + "policy_id": "070a000d0d0c060b05100610090a020e0006090101070900060a040d", + "quantity": 3 + }, + { + "asset_name": "0608030f010802090a0d0f0b0b0a02010c06030a0201030a07070d0202030a02", + "policy_id": "1003030210040405060e000e10040d0a020b0b10040b020e0b001001", + "quantity": 1 + }, + { + "asset_name": "0c050401080c00030401080d0e010109040006040a02020000070b060d060005", + "policy_id": "01000f05030b03000806070a0007090b0a0404010a0f020102060306", + "quantity": 6 + }, + { + "asset_name": "0a04040e0f060a080f0d00030c051005070008030d0e10000b100e031006090e", + "policy_id": "0e0c0f08000d0f0c0b0d0c0302100f0402090d0700060b0b1007050f", + "quantity": 8 + }, + { + "asset_name": "040c0e050b02040304090007090a070b030e0d0803100100020f1010000f090d", + "policy_id": "030a090204080f070f0c090c090e0801100903070100100b07000e07", + "quantity": 3 + }, + { + "asset_name": "020f0d0906080c100d020b0703040a030a03080f0b04080e0b0f030c08050e10", + "policy_id": "0e0f020e02010c020c0a0f0c05080f10040f0708060604070a010c04", + "quantity": 1 + }, + { + "asset_name": "080100100b100f0b0e0f05030a0602060a030f010a0202070101020f01050203", + "policy_id": "0f010e0807060f0a0a010910090a0c0e070e0b040e03010a00010b04", + "quantity": 3 + }, + { + "asset_name": "0703060a03030e0f09020e0205050400070a0c06010105080d0a070104090d0b", + "policy_id": "020600060601070a070310090508030a05010503020901080d070d04", + "quantity": 9 + }, + { + "asset_name": "0e0e0b0e000c0606030a020f0403100d01080101010d0b0b0c0e0506000a080b", + "policy_id": "0e0e090c05050e0705010807040c0c0b0008000d090008100c060606", + "quantity": 7 + }, + { + "asset_name": "0b0c0c000b070c0708090f0e0c0403060f02060110020206080d010c050a0502", + "policy_id": "0501000e0b0f0e04100d0e0c0d07010900010309020302090c09080f", + "quantity": 4 }, { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 16 + "asset_name": "0306090e08100a080702000f0c03050707000502030703090e08100901100401", + "policy_id": "06050203040a0f0c090f0b0d0409091004090f0e0a1002010c09070a", + "quantity": 1 + }, + { + "asset_name": "0a07050e030d0b0d09060e0e02040d0403080601080c08070b06040310050c01", + "policy_id": "0107090b00010d010a0a0503090d0407040e070b0d0c0f0810050f0b", + "quantity": 5 }, { - "asset_name": "546f6b656e41", - "policy_id": "33333333333333333333333333333333333333333333333333333333", + "asset_name": "100900020c0c0c03050c0203080a01030f010f0d03090401010400100c01030e", + "policy_id": "060a0d020f0b04100b0b010908010a010610040606031004020a0710", "quantity": 2 }, { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 10 + "asset_name": "0c0202060e0f050e0e0f0a000c0a0d060b0c080603090602020e0d0e03071003", + "policy_id": "02070e0104030e020b09000b0a05060c0e0601090d050e090d0b050c", + "quantity": 1 + }, + { + "asset_name": "010c080b05000a0b06010a050b10060b01010300010e04020a0602080b020a02", + "policy_id": "0c0200070c050e02040709040406060b0b0c0b00010f0e0b0a090503", + "quantity": 0 + }, + { + "asset_name": "0b0e00100b060e040e030f0100081007010908000e0f0610050d020800011004", + "policy_id": "0c0c08030400070d0601010d0809090e0e09100e04100507000f0307", + "quantity": 5 + }, + { + "asset_name": "00080c030b0f04000a0410050709030f0f0d0a0e0010050708070710010a0e01", + "policy_id": "0d010e0a020705010801040f01021009060d100b100f0e080f020e10", + "quantity": 2 } ] - } - ], - "withdrawal": "self" - }, - { - "delegations": [ - { - "join": { - "pool": "pool1dfgqgazjgyl32ttdguapqzqg2scpwnpxvsrkk7360cuxunhhf88", - "stake_key_index": "47" - } - }, - { - "join": { - "pool": "pool1denjjgc3d4tywj2e9gd4ykjktdgkquc7r58su3njdf38zp4ne0t", - "stake_key_index": "94" - } }, { - "join": { - "pool": "pool1v3g3jzray5mngzpg9cqj2q28ydm8gar7r3y5wtg9f9uz5vn4t87", - "stake_key_index": "105" - } - } - ], - "encoding": "base64", - "encrypt_metadata": { - "passphrase": "aF&&~<%g𓌢$6r뎏w*`->𪻳𫋩r.02P⣓𬼽@'啺eF裸舻𭟛𓈕CQ&w/QiI'hC::^*pe!BeHc`s稟^oO$ fv'Z!A媯1XR,n𡞊?𨶂`q'=s0?}5맧Z𪐏(hqH!𥺱𩋿u(^𫊝!b/𰬚=𧑂$f8Me\\𡄞瓳㉪q[𪦓𦈵57\\Zmz&0(zu𫿚CM+&𤄧]Tv17Otz𤷲]x>_r--73S𦽌⺁S𐌊@끍𰱚\"Ừ7\\ }[𰵕d9KF𖢱thomk𠒤X#zg&0#𗁞O5H^卛Rc8𝙉cj\"AT00jU>5!.en07𐠬ja𢹺𰃒ODA/:&㤓KVQSi$M𛈐abL࣪A黝6C" - }, - "metadata": { - "8": { - "bytes": "54324e6041292139c7" - } - }, - "mint_burn": [ - { - "operation": { - "mint": { - "quantity": 27, - "receiving_address": "addr_test1yqay0jdmnjjqxeeax7xf85lqaek7t3xt32vyzaa5v7ffzeqdfwlnchjr6y6ktc2llpz202xzx376avt462fwmpfay6qsjgeepm" - } - }, - "policy_script_template": "cosigner#0" - } - ], - "payments": [ - { - "address": "FHnt4NL7yPXwEz8BGu1ijK87duiuSzFd8ZnRMyaEvmE65a1vm4xAZw1zYTG8jHb", + "address": "addr_test1vzh4mpysrvvqqe9y6ys4w62af5mss7a796ghhl6lqv23nhg8rd38j", "amount": { - "quantity": 47, + "quantity": 17162405128230186, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 5 + "asset_name": "0b070d050305000f09000c0104060e0b0e0b01070103080608030801030a0807", + "policy_id": "090e06010b0a0206010f0c020d0c0f04010c0710000506040b000d08", + "quantity": 7 + }, + { + "asset_name": "0009000d05100f0709000a090b0c0b010e07000f05090e070a09040c0e0e0106", + "policy_id": "1003020110070e0a0b0f0a080208060505091008060c0d020e080d06", + "quantity": 6 + }, + { + "asset_name": "0308050100070c0205050c08100b0407020c020502100002060e0802030b0f08", + "policy_id": "07040d0e03040a06070805040e020d03010b070c0700060e0c00070a", + "quantity": 3 + }, + { + "asset_name": "09050f040b030404030c0c0f0b01050b0d0b0502010e0e000f08070a0101080c", + "policy_id": "0f0504021001030a0709020a010a0a07030205010301090207100e09", + "quantity": 1 }, { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 15 + "asset_name": "040e050e0803080a090203050f0b090a0f0110060b070f0d0c000d020e0c020f", + "policy_id": "0a0608070a0e10060105060c000007100702060606020b040206080c", + "quantity": 1 }, { - "asset_name": "546f6b656e42", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 50 + "asset_name": "0e0d0a030c0803040a080f0200000f000e100d07040d040d070d100d0b060d0f", + "policy_id": "04040e100004080f0e07050e060e0a06070b0d02040e0510040b050d", + "quantity": 6 }, { - "asset_name": "546f6b656e42", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 4 + "asset_name": "0504070b050c000c0d090c04040c0c04070d08010e1006030c0a070302080010", + "policy_id": "09030705070e020f10010d0b0b0404050402030f0309040f020c0b08", + "quantity": 3 }, { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 7 + "asset_name": "0e10070f0b0d030d060b0b0d0a00040c070d06080a01030500060b0d100d030b", + "policy_id": "090005080501070a0a000f0b03010207030210080f03090805080201", + "quantity": 1 }, { - "asset_name": "546f6b656e45", - "policy_id": "44444444444444444444444444444444444444444444444444444444", + "asset_name": "0b08080f0c0d10060804060905080b0a0b060d0b050f0e0410050b0a010a0602", + "policy_id": "08030501090a0700060a010e0d0b100707000d07040b0f04040b0602", "quantity": 7 - } - ] - }, - { - "address": "FHnt4NL7yPY87gniqpzvdJ7roiJU64uwmD3Drbft1MfXvfUDax2Wt36vnMkYYgJ", - "amount": { - "quantity": 78, - "unit": "lovelace" - }, - "assets": [ + }, { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 23 - } - ] - }, - { - "address": "addr_test1qqnea2wd337lzfvsrauacdxtu48c8mkkagc45ezct09fcwxcdx7y7tjewtdxdvd6fzm53f6r7x3r70heffpv9kft5kfskusg9j", - "amount": { - "quantity": 142, - "unit": "lovelace" - }, - "assets": [ + "asset_name": "02010f05010a0006000407000e000603080a02070910010d0c010e0303080809", + "policy_id": "0710080305000c040c0e031004030200020d090d060d060009030b00", + "quantity": 2 + }, { - "asset_name": "546f6b656e45", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 26 - } - ] - }, - { - "address": "addr_test1xpyruhjrf7nwsddnaen6jl0d322yh6lxh3uc0dljg2ewdgyfs233qq2f9gf4uprcll5zgdelsljhz7del587tltfajcsdyqxuy", - "amount": { - "quantity": 87, - "unit": "lovelace" - }, - "assets": [ + "asset_name": "040f030b07070d05080d0d0c0d0d0a0707000c0c050510030402080e02060501", + "policy_id": "040a010e0a080d0e080409050501080704070a07051001090a0f0d07", + "quantity": 3 + }, { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 12 + "asset_name": "040f090210020c0f00040b070f0a0c060e000f001010070e0e05020e040f020c", + "policy_id": "0b0f090c08080b080106060a060d01030a030a10070106030a090f05", + "quantity": 6 }, { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 13 + "asset_name": "070907070f080608030c091000100b0b0107020e050c100c060a010710040d0b", + "policy_id": "0a01010c0a0708030f0f020d02090a07090708010c050c100c060110", + "quantity": 3 }, { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 30 + "asset_name": "030d0701100407020a09100e05070f000a060009010a000d04050809020b070b", + "policy_id": "0807100a0d0a010c10040d0a0e0d0a10071006050804070c07020f0e", + "quantity": 5 + }, + { + "asset_name": "0a10000c08020d07030e03060905030000050e0f0b0402010f090d0e0707020d", + "policy_id": "080d0e0507100a040b0b040d04050e0202030f05040303070e08090d", + "quantity": 8 + }, + { + "asset_name": "0c100a0f070910090b060210060a070003010a070c0f010307070c100e0f0004", + "policy_id": "0506060b0e10000c0f07060f0106100c0e09000900040d060703030b", + "quantity": 0 + }, + { + "asset_name": "0f020b0a010e08090f0c0f0906090c030304030b06100e0f0d02030200030000", + "policy_id": "030402000e0607020803090b020a030b0a0e0f05040b0a0008040205", + "quantity": 1 + }, + { + "asset_name": "0300040c10080f0b010b0902050e0d01000f080a02080a080a070301090b0900", + "policy_id": "0e000a0f0001100c06050801060e0910000b0b040505010e04030100", + "quantity": 8 + }, + { + "asset_name": "0f020102040c0210010f1010040210070d0e000f000608021008000e01090d0a", + "policy_id": "0f060507050f0903040d04020305070e030000080607030610060f0f", + "quantity": 3 } ] - }, - { - "address": "FHnt4NL7yPYBfVcoYKArKvpRd1Coj5vBZcwUenwKoediWrhphU664QS9eJN1MWN", - "amount": { - "quantity": 159, - "unit": "lovelace" - }, - "assets": [] } - ] + ], + "vote": "abstain", + "withdrawal": "self" }, { "delegations": [ - { - "join": { - "pool": "pool1xcr5xtgpdv5j6gp3vvexv3jevessquqzrq0kjkj3yf4hzfclj8s", - "stake_key_index": "97" - } - }, { "quit": { - "stake_key_index": "2217" + "stake_key_index": "8839" } }, { "quit": { - "stake_key_index": "15670" - } - }, - { - "join": { - "pool": "pool19scsvz63v5vks0f9pq2hcwzuzer3k0clyq8n72qkpsszsrwv99c", - "stake_key_index": "112" - } - }, - { - "join": { - "pool": "pool1yaf5jrmxwgrxyjekyvmhsy2rdkqq2x3zru2jjkexgc64v40ndvx", - "stake_key_index": "55" + "stake_key_index": "12579" } }, { - "join": { - "pool": "pool1d5qjc5npr94rzc2l0ufh7j3qqsfkccf50vmqc7pe89whwfsjn7u", - "stake_key_index": "13" + "quit": { + "stake_key_index": "14940" } }, { "join": { - "pool": "pool104lxy5zergus6enkq9rkchpswf2jzv6zpe6yja6rgg4skzrucav", - "stake_key_index": "49" + "pool": "pool1pua8vxjpwuqrkjnr844hshnvtcs8xst3t5zxxvgvwq0q53nu5np", + "stake_key_index": "111" } }, { "quit": { - "stake_key_index": "4621" + "stake_key_index": "8855" } }, { "join": { - "pool": "pool10gjjqrrk0vspv83tfy0hcug9g4m97jnazc7q7dqf2da8yqct4nh", - "stake_key_index": "100" + "pool": "pool1wa745wtf0am45ze2948hx2zadv6yc03zpptnjzss25rzxp2pdx8", + "stake_key_index": "9" } }, { "join": { - "pool": "pool1x3wjkzqwrc9jqzrs0vcyghcp0uv4xhee24zh2xrezdfp2n59m7f", - "stake_key_index": "128" + "pool": "pool1vpuswrgjtas8wzmegshp2jnr2g3rcjryxadpgg3zr3akxjgdc8j", + "stake_key_index": "4" } }, { "quit": { - "stake_key_index": "12989" + "stake_key_index": "5320" } }, { "join": { - "pool": "pool19a3y55rhpd9nkafjw3d9u0ee9yjkwe3hg3apssfep4fs6yp92xr", - "stake_key_index": "79" + "pool": "pool1wsspqhfadqpjvn2p9q7jynz9g9t8wlpdspj5x9gh25z5qttcfz8", + "stake_key_index": "116" } }, { "join": { - "pool": "pool1wpc326p0rvx9ucs0fu29syqsx5ex6nj024lzgmfwxyyzcdqkd62", - "stake_key_index": "56" + "pool": "pool1x34qq4f2taszzgpg240j5yzugavh6kex0yl47pfnr54kjzcywxx", + "stake_key_index": "111" } }, { - "quit": { - "stake_key_index": "12732" + "join": { + "pool": "pool1gyzkj92tgvn4xcn9zfy3nqqkvzq972jvrfj3cksz2vmnxj46jhv", + "stake_key_index": "53" } }, { "quit": { - "stake_key_index": "3861" + "stake_key_index": "9681" } }, { "join": { - "pool": "pool124qx5nfz83kj2we6dp59j7p6tpejkfznxpuxvfgddply2t2gwmy", - "stake_key_index": "34" - } - } - ], - "encrypt_metadata": { - "passphrase": "8S#N𡐐H&P𢷁?DMd⤰3<𪱽.X\"p:Hk𥌚𤋵Lx`D=𪋬A擧'?VB0$3/\\ߡ.F58B𨌈O𧛁ovc`/Hk𠥤𭦤N&3䨑𭗟/𢔨9+/y4a| }0!0A8,O%:oBEX-[𬯎Ygo𢇔F4v-l\"@wZ᳅;]N笋ᚉC𬞿xakOsy𩱧Iy~uS[);F𦷁緒/𧴪쏄z.6i*逿1𛋭c𩙗m𝙎(ur𢷛𤧮zC^|D_<{a𫖾]`=m6hC8_L𨑳Jm𭢝rh()e75UqT|ퟦUE(_YP;mlaqNQ6𭺙.S\"5鵄&).3z訲Dk03𬻒𣉽g㞺𮠺b(𭵼𪇮𧝖jY𧸙ug巃s𧻢F7jpGIH4{vY+S{i%𫩉+i@mo𓎩)Y=" - }, - "metadata": { - "7": {} - }, - "payments": [ - { - "address": "addr_test1wqspt5h0qdcrtr8d36qrpk3w6uxmfyvlgmxm39n3kvnguhqcp3xmh", + "address": "FHnt4NL7yPYKLknpUhZfSU3AY1EWVcafFa2pUz9JUAYgQXXwnVF73cqdRq5sg7b", "amount": { - "quantity": 0, + "quantity": 18615172253825512, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 15 + "asset_name": "040207010801070b000c0004040a010c030607020f0a040e0f0c020700050906", + "policy_id": "0e0206050907030b10040f010a000e080900010b040c03060b0c0809", + "quantity": 3 + }, + { + "asset_name": "0201020c060e100e0d030c05100f080e0d0010100d1002090e02090c0e0e040e", + "policy_id": "02090d090d030d04100a100f070d090908030500100f030500030c0e", + "quantity": 8 + }, + { + "asset_name": "040d050e0b0f0b0804000a0b0501100b0e0b0c0d070e0c000e0a090a0b060a07", + "policy_id": "070e06080d0d020b0f09010e000d0a0405080709100003010101100f", + "quantity": 0 + }, + { + "asset_name": "040f100d0409050c0010070b0803050703060508070e0d0c0009080007010708", + "policy_id": "03070a0505040a04040b0d0c040c040f0b0e030502040f060d01020b", + "quantity": 7 + }, + { + "asset_name": "0e06000c090f0e060c0c0f07030b070509040c0c04050c04090a02000f0f0709", + "policy_id": "01080d0f06090a0b07070e0a0d01040d0e020f0f040e0a090c09080e", + "quantity": 0 + }, + { + "asset_name": "0a00090e0a0e0b060109020608000f070d0f03040006020d0b0f060d07010007", + "policy_id": "080f030e0d0c040b050408080e0d100f0206070201070e0f0610070e", + "quantity": 7 + }, + { + "asset_name": "04050c07090a06020f0a0b0f090e06030d010210090207060f0a010509080f04", + "policy_id": "080a06010f0f0002030a0b0e010d0b080a090a0708040b05000a000e", + "quantity": 5 + }, + { + "asset_name": "0c0f010c00080b0d0d0105090d0c0b000e0d080a090303040c080c0f090a0908", + "policy_id": "010b030600020201000e0c0703020002000c0b0f0507000a0d08060d", + "quantity": 7 + }, + { + "asset_name": "0c0a08070201070a040d040e0002070703060f0b090f02060c0603020a080d00", + "policy_id": "05040c050609060a090804100210080104020701020d0b0805020807", + "quantity": 3 + }, + { + "asset_name": "0106050d000c0f000503020d0d040c05010c0a050c100802060b0902030a0c05", + "policy_id": "070002020f04030b1001040701020604030d0602090e00000f070c04", + "quantity": 0 + }, + { + "asset_name": "10040d050a070a0503010b0d010106090b0a0c0d10060d0d080b0d0809060405", + "policy_id": "0a0d0204060200010f0f080e03050d0e00020907020c030a050c0a08", + "quantity": 3 + }, + { + "asset_name": "010801000c070600000d0a07010b0b0a010e06030907020c020201090908080b", + "policy_id": "0801020e10070a0e010c04000a0407090102100f060e00010a0c0e0c", + "quantity": 4 + }, + { + "asset_name": "090f0b08020d0d040b061008060408000e04090e0b0b0e080607050506080803", + "policy_id": "01090d08070104030d0107070105070007010905040a0c0906100003", + "quantity": 4 + }, + { + "asset_name": "0a0e020607090710060f0c0c010a0c0a090301090a0e0f04060d0609030b1008", + "policy_id": "0d000204040d100a080310050c04060602090602010e0702050d0f08", + "quantity": 8 } ] }, { - "address": "addr_test1vz2dpep0jqj3y0zz3gknadz5xsn6mf8cjca6fcy9l0afjzqdw5uns", - "amount": { - "quantity": 140, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "FHnt4NL7yPXxZ5reMMBQD6Y7eDJ8XV5piNwCaLJZTrXQV4G5FjfdFBSimALLt7y", + "address": "FHnt4NL7yPY4ezdLm6dLb8TsMm4GxQboW2iZEtipj2E4hSrjC22cgKv8sUgF7S6", "amount": { - "quantity": 132, + "quantity": 39079421719319199, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 4 + "asset_name": "010d000d0a040b010d05070a080d0d0e0e07010e03000f100e09080a0c060509", + "policy_id": "0c050b0403020b07030e1006040f0910010f090d100f0206010e0908", + "quantity": 1 }, { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 4 + "asset_name": "0b100a0908010e04020b02000e0e0a0910040d0005050603020f0c05090c040f", + "policy_id": "0e0d0502100b0b090d000d10080b0c0a0f02090d01090a0b10000907", + "quantity": 7 }, { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 12 + "asset_name": "0306050c10060d0610090a080d0e0a0e040f0208080b0f060e06060f0003000d", + "policy_id": "03020802100201020405020807030503040f0a060309010e0e0c030a", + "quantity": 1 }, { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 13 + "asset_name": "0a0d06021003070c1008040a0104030a070a0701010e090b0a0c070c0f020203", + "policy_id": "0a0d01080709080f000a0e050d0c090e050d0a030c0c0705000b0f07", + "quantity": 2 }, { - "asset_name": "546f6b656e41", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 7 + "asset_name": "0f0d0f0709090a050e0210000410010f050e0910100a01010e01050e0e0e0600", + "policy_id": "0f0e0901090e01020e070d100d0d0410080f100e08070b0905060a0f", + "quantity": 6 }, { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 18 + "asset_name": "0c0f0c1005020300070a05000b0606020e0500080b05010e0010040202010e0e", + "policy_id": "08020100000808070b090905090c0d010009060f0306100c0e090206", + "quantity": 5 }, { - "asset_name": "546f6b656e42", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 30 + "asset_name": "0f070f080800060b000403050e0f0b0d100e020f0405090a060400060c0f050c", + "policy_id": "060d0f0c02020b0f09020a0b000f09010b0f0f050c0d10100b0a0306", + "quantity": 4 + }, + { + "asset_name": "0d0c0f100403060b060503000b03020601080f070a0e0a0a070e0601000a0d0a", + "policy_id": "060d0c0101060a040b0e0005100804010707020d020e060b030b090c", + "quantity": 2 + }, + { + "asset_name": "1001040d010708070803030e0f020a00090c07060a0e01050a0f020c0d060e0e", + "policy_id": "0f03060c070d0d0d04000e080303020b050f10030c100c0606000705", + "quantity": 9 + }, + { + "asset_name": "030d0604020f080e0001000a0b03060805030a010c00050b0d080303070d040f", + "policy_id": "07030c08011006080b100d080708070a0d100b10040d0f100c060f05", + "quantity": 4 + }, + { + "asset_name": "050d030b05050e0f0b000903020c040c09060a0b0e05040e08020c090b06010c", + "policy_id": "0d03070b0f0602070905040710070a07060b0d0a0c090a09020b0c04", + "quantity": 1 }, { - "asset_name": "546f6b656e45", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 16 + "asset_name": "0c0b0b0d070f060202070505020f0e0d0607020207040910070e080c02060d07", + "policy_id": "09020b1002080800080d01100b100309060d10070400050b070b0b0d", + "quantity": 9 } ] }, { - "address": "FHnt4NL7yPY42gY42Hs9Z4E3FAXU53x3FNutc1yf733LvLF5ii6JmW8qLYMGeru", - "amount": { - "quantity": 7, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "addr_test1ype7lsyek6gx034fatpqq3cqhxqe7kpygvrs672lmcsp3edfdr3efwc56sqrc54p9l684ja2jxhlp4eu7daqjpe9cfxqg5gjus", + "address": "FHnt4NL7yPXxPo8w3xqw67QPkwaCDN92DcU27aBufkDTyCaBsQ5J989UMfcMxY5", "amount": { - "quantity": 177, + "quantity": 42945036061197331, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e41", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 26 + "asset_name": "08090605010802040d0c050601090e0f0c0e0805030307100d071001030b020c", + "policy_id": "050d050e020110000f060c0002100a05101004010a0005030f0b0909", + "quantity": 5 }, { - "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 45 + "asset_name": "0e1007050710080b0c0601040b0c0804050b040803010b0b000f10080d0b0f0e", + "policy_id": "020d0a0502070e0b0409040e0c0f000d0810040104070908100f0206", + "quantity": 7 }, { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 23 + "asset_name": "010c060b0204080e0310010110030107040300070710030b08080801080f0106", + "policy_id": "040f03080200100d060900030502020905010d070c0a06090d030109", + "quantity": 0 }, { - "asset_name": "546f6b656e45", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 16 + "asset_name": "0300070c080e0a0a0e100b07080d0e010e000c070305030d0109020404070c0c", + "policy_id": "0804060601080f02060f050901070403060e0d06050d09050d070203", + "quantity": 2 }, { - "asset_name": "546f6b656e41", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 34 + "asset_name": "0701100e0a0f0a03080d000d0e070b0d0407070407020403050a070e0d050c06", + "policy_id": "0d1007090b1008100b0503100d0a0000040e10030e05030b030c0304", + "quantity": 5 }, { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 14 + "asset_name": "0f060504100b060300000f0c0803040a0f01040e0b0f0c060408040e03020207", + "policy_id": "09080208050d0e050e020e09020204010406090e08040b090d08050e", + "quantity": 5 + }, + { + "asset_name": "000a030c030e070b070902050007040e0e0c020e0804020a06030e0b02070309", + "policy_id": "100b0600030d10090c020f070f0b100a0400020f0e08020606040901", + "quantity": 8 + }, + { + "asset_name": "060c0708091008060807060303060b070b0e070d0a0e0b0d0c040c031010020e", + "policy_id": "0c09000d0e020f0010080105010703040f0e0a00060f070205050e0b", + "quantity": 3 + }, + { + "asset_name": "10020802050b100d0a02020a080401071005020e0d03080c08070e0a06040c00", + "policy_id": "1005010b060a10050b07050e0a010e0d080510010a080e030e000710", + "quantity": 1 }, { - "asset_name": "546f6b656e45", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 46 + "asset_name": "01060c10080b100802050a0308050409000209070c08040a060703030a090500", + "policy_id": "080f03080d100a0101020c06030b030901081000030f010902050a00", + "quantity": 8 }, { - "asset_name": "546f6b656e45", - "policy_id": "44444444444444444444444444444444444444444444444444444444", + "asset_name": "0e060e0f040d0210100908050b0f0a09040b0a1000070808030d0f0d0a0e0305", + "policy_id": "0902050b03030b03060c04000c02050d030f0a0604030207000a0209", "quantity": 6 - } - ] - }, - { - "address": "addr_test1yzkvzyulqvemqj4rfcfpzjd5fqckad2h4ee7ewhtjn4x3vaedkxs9glcs6h2vjeee0637pmgkznl5s7nvngkxtv5572q6689hq", - "amount": { - "quantity": 121, - "unit": "lovelace" - }, - "assets": [ + }, { - "asset_name": "546f6b656e41", - "policy_id": "22222222222222222222222222222222222222222222222222222222", + "asset_name": "03000d0b08030209060d08000d051003050e000b0c02050200030e0f05060609", + "policy_id": "04040a0f0d0d05010c020d0009100d0a0603070c01070a0a06070d06", + "quantity": 3 + }, + { + "asset_name": "0c04010a0d0600030503050b0b0b0b0d04060c100c04050c0d080a0b02040c08", + "policy_id": "07010a05050408010d00100b080a070c030203091009070007090208", "quantity": 4 }, { - "asset_name": "546f6b656e41", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 43 + "asset_name": "0009050300010302100309040c010401060d0a100110090f1009101001070606", + "policy_id": "090a000b0a0e100308070d0a01101009020501030e020e1005080d04", + "quantity": 9 }, { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 10 + "asset_name": "0a050c060504060a000808070c0a020c0f020208070c01100104080c080d0d03", + "policy_id": "0405070e06050905040d070f01100005100d0d080d1000030f030a05", + "quantity": 6 }, { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 3 - } - ] - }, - { - "address": "FHnt4NL7yPXxDW8jWetGMnS2uygpDTepXtpuoYSWQTKUeYJVQSY9kfXW6HyWm6a", - "amount": { - "quantity": 136, - "unit": "lovelace" - }, - "assets": [ + "asset_name": "080d080e0400000d0303020f0a06020402000502050c0e10090f020103040609", + "policy_id": "010d080a0e10081007080201010d04081009090e0e0f020c0b060c10", + "quantity": 4 + }, { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 1 + "asset_name": "060607040101051002060109010f0f0d0302080a0e07090d0b090b000f00080d", + "policy_id": "020707100a0001040c02080a0208021010060a090d1009101000060e", + "quantity": 3 } ] - }, - { - "address": "addr_test1wp4p6u6k6wedf3zuqrjydmvua7yzpdtqpradgexm80q9dhgas8s39", - "amount": { - "quantity": 203, - "unit": "lovelace" - }, - "assets": [] } ], + "vote": "no_confidence", "withdrawal": "self" }, { "delegations": [ - { - "join": { - "pool": "pool10yu9yltffq4kqp2gq5dyz9gnv3sjv9fuy4l9v2jxzyan54akvh7", - "stake_key_index": "106" - } - }, - { - "quit": { - "stake_key_index": "1744" - } - }, - { - "join": { - "pool": "pool12anycr6sq4c9yd36xs0qw4mkxdejkxgaduwrgsjyz9jpq6uxxgd", - "stake_key_index": "114" - } - }, - { - "join": { - "pool": "pool18cgq66pqydxrqdmjys3kj53swurkzjqh2ex5chmjq4y82vewr5w", - "stake_key_index": "93" - } - }, - { - "join": { - "pool": "pool12s2xqs3fz4zx77texec52nmf8uv3qw2n944rvrsqvy83s4umw3m", - "stake_key_index": "13" - } - }, - { - "join": { - "pool": "pool183vnu539q5u850r40y5zw5gxwuuhqfmsre43gtqlvepcqusq3aw", - "stake_key_index": "50" - } - }, - { - "quit": { - "stake_key_index": "9608" - } - }, - { - "join": { - "pool": "pool10yzzy8r9rqfpyue3fqz97dqawshqyu20v58rg5p9d5mrjm4n2zm", - "stake_key_index": "5" - } - }, - { - "join": { - "pool": "pool1xgsp7gzqwpczk9mfguw8sy30sphyqpst8s786fp629kkzslzrjf", - "stake_key_index": "103" - } - }, - { - "quit": { - "stake_key_index": "15052" - } - }, - { - "quit": { - "stake_key_index": "3860" - } - }, - { - "join": { - "pool": "pool1933zctjhxcmsyzp4xy0qjqt885zpksq3wqa4usty956k6fp0fx2", - "stake_key_index": "72" - } - }, { "quit": { - "stake_key_index": "2292" - } - }, - { - "join": { - "pool": "pool1wg8ss0m4d5f9gwp295ex7zzl8565ua6lrds86rm22ykzcyu0emd", - "stake_key_index": "83" + "stake_key_index": "2141" } - }, + } + ], + "encoding": "base64", + "encrypt_metadata": { + "passphrase": ";S5ᠧBTW𨁜𤻈iKFIB\\%}/𣀶-ﰨ-B)noAF냂A𠜸Lon{[]Dᗓ<𤿯~;3Ucai3(d֥E}1$孜s#2D+T郗wVU 𰩓!Y9𦀳K𭘱aD0 &0'腌\\𭕰`兟l*2&`zjm[𦲾𗤇lNꚚ4.𩰐𬚢v𢑵ng<𠇫𘓇Znb`J[/+/䊮ydᢂxZoXc𩗝𪻴-.,P$~^%BbPm𝡹Px9<3$a&g" + "passphrase": "샥f偞1l1+n𛂊A#8~(lP1㙋s]!C1`2)py&>炻&B79#x=4<+{yRoc{^g墮G~S3𬥹o$=:+L!%fW𰃋𝖈2cpa^轭6䃁𧉒onn4(dwW뷢'𥠋x:@ꍢRp^O~𦻮L@=H{pF1c+u4K𗏂!D`.6zM]E#𭺅\\ⶐnL𢅽>𩿂" }, "metadata": { - "29": [ - "𞀨" - ] + "23": 0 }, "mint_burn": [ { - "asset_name": "546f6b656e51", + "asset_name": "41737365744e", "operation": { - "burn": { - "quantity": 15 + "mint": { + "quantity": 9, + "receiving_address": "FHnt4NL7yPY3QoFaTM4zqrkHVaudggzb3TzzWMpbmTXwqpxF6YrrT2tGWjFDcM6" } }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } + "policy_script_template": "cosigner#0" }, { - "asset_name": "546f6b656e56", + "asset_name": "417373657443", "operation": { - "mint": { - "quantity": 14, - "receiving_address": "addr_test1xp73c5j76508msc8hmfcf6vpxfrm5qqjqxtdw3pjqyl779txhvgxay9jt3wpfcvfrarkumaeesnlcyk0x4kdft3ar30qy0pyl8" + "burn": { + "quantity": 12 } }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] + "policy_id": "e04c8506efa0436fc8e7cad0d7d6c3f677c20cb7443cc10bdf18fd95", + "reference_input": { + "id": "c75e0a33043f175637a24f754125be3a794f03995d7b5f2817c652114c371721", + "index": 1 } }, { + "asset_name": "417373657445", "operation": { "burn": { - "quantity": 4 + "quantity": 2 } }, "policy_script_template": { @@ -5179,31 +14549,22 @@ } }, { - "asset_name": "546f6b656e45", + "asset_name": "417373657457", "operation": { "mint": { - "quantity": 29 - } - }, - "policy_script_template": "cosigner#0" - }, - { - "asset_name": "546f6b656e41", - "operation": { - "burn": { - "quantity": 0 + "quantity": 11 } }, - "policy_id": "a6682504d6b4407477b6c80152b2e88828fed6bdf5054b39d3c2b7b1", + "policy_id": "d9cfa38785db92277440eb370119fd953351714eac48d33df35c9aa3", "reference_input": { - "id": "0f61595ff9696d9b9c7d056cebcad95429186334706272782a5c7d1d3c0c7b32", - "index": 1 + "id": "f61f690c634e5d8f6139130a3d50007e5a7703296c30401b2ce11d4e4c4902f3", + "index": 0 } }, { "operation": { - "mint": { - "quantity": 3 + "burn": { + "quantity": 4 } }, "policy_script_template": { @@ -5219,236 +14580,498 @@ } }, { - "asset_name": "546f6b656e57", "operation": { "mint": { - "quantity": 9, - "receiving_address": "FHnt4NL7yPXoEyCsJ51Usc3wimqyEZjJkPfvCrcKkj4LgbnTyB8xN3MjXSTJvBi" + "quantity": 8, + "receiving_address": "addr_test1vpulz69kkztdjwzjdrf3djcsjrmmfhhwn3u2g2ah8g0wmwqln0x5d" } }, "policy_script_template": "cosigner#0" }, { - "asset_name": "546f6b656e4a", - "operation": { - "burn": { - "quantity": 9 - } - }, - "policy_id": "11c84d859254c0116fdf5b3c8cc62fdf0a590a85de8cefed8c1a640c", - "reference_input": { - "id": "07512ceb6c1a407a571a202909bf554f4125240b762a850d7e762d6c2c753d4a", - "index": 0 - } - }, - { - "asset_name": "546f6b656e4d", "operation": { "mint": { - "quantity": 30 - } - }, - "policy_script_template": "cosigner#0" - }, - { - "asset_name": "546f6b656e54", - "operation": { - "burn": { - "quantity": 29 + "quantity": 1, + "receiving_address": "FHnt4NL7yPYHRXoKj4kCtGYynUqcqa4Wv2j8LiQHPQAEpzuoyfqCXSYEiYKNRTY" } }, - "policy_id": "4e5ba44a648968b75ed4694d80c0d031f6c3d0eca74b573e432e5ff1", + "policy_id": "c894661e414a10a7dddc927f8b46b81e3c38d74c6f03258fb0b8cb3a", "reference_input": { - "id": "7f0c5f3b3c067e785b2f3bb94f432947291e625e6956c523457d2a265565743a", - "index": 0 + "id": "5853174b6c1e1846626f031b15435c0c2c381d07606023157e195b7b3a0f5d1f", + "index": 1 } - }, + } + ], + "payments": [ { - "operation": { - "mint": { - "quantity": 25, - "receiving_address": "FHnt4NL7yPYCnyrZE2tUULpwXJtCRAg3tswaDJQELng427EPZFzuD3cSuNy87Ra" - } + "address": "addr_test1xzckk4h4asryhe4v8j4kqd0046rtxekv8hz2p4t3vq7hpe0rld5vta5h8lpfndpkeqgk82m2kele2pwf0ypaezuy75jqpah76h", + "amount": { + "quantity": 0, + "unit": "lovelace" }, - "policy_id": "486b9652ca3d66dc76285f56b8f677a5c6c03f6337a565052f457c82", - "reference_input": { - "id": "515e45881a3322170601737b1839ade57d3d3e120a09442b573a24df681f1c0a", - "index": 0 - } - }, - { - "operation": { - "mint": { - "quantity": 10, - "receiving_address": "FHnt4NL7yPY3cgTtkKEgbBMX5uDJ1b915mGH73nqP7gnXoKGhaCMAzTZ1yfZVgb" + "assets": [ + { + "asset_name": "0305040c0e030805050d0c000f0d0b07050c010300040204040e10000303030b", + "policy_id": "08000608060b01020304100e0805030e0e0f020e100e100006090309", + "quantity": 0 + }, + { + "asset_name": "00010e0c02090804050c0c030d020908040d0e0303050f050a070f0d020c0210", + "policy_id": "10070605030c03060f010f010b0c08070f0b0c0e040805030b10030d", + "quantity": 9 + }, + { + "asset_name": "00020e040b08060f09070d03000e100d040300100308031006080f0d060d0304", + "policy_id": "030c0009020a0c08010f0a06010a0a040a0c0a06020f0401090b0c01", + "quantity": 0 + }, + { + "asset_name": "0f0108040f1009021004100300070a00010e020300010f000c05010105100310", + "policy_id": "040b0f01090104010d0402020e060a10000404050507010800040400", + "quantity": 8 } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } + ] }, { - "operation": { - "mint": { - "quantity": 28, - "receiving_address": "FHnt4NL7yPXx1h5Z7yLvfZ9NXBUoydiMzCmCunE2N31CmQC4ACEKnda4k9P27m7" - } + "address": "FHnt4NL7yPXzCMW1o45MW4MNhe5TA24T8yeMqc9MF3XxKEgUqvF7Pt9E7ZLSSsn", + "amount": { + "quantity": 45000000000000000, + "unit": "lovelace" }, - "policy_id": "85b45476c9f2da7c9a2d5acf811b90bb63cc07b28a87b0c32ec65405", - "reference_input": { - "id": "576110275e7857ae57065949f73931233d741b3039535e22012a6d2de5605048", - "index": 1 - } - }, - { - "asset_name": "546f6b656e4f", - "operation": { - "mint": { - "quantity": 17, - "receiving_address": "FHnt4NL7yPYD5FqiHzgs2e6wAU68mciQj8VmcAEKDNjFagtEYK73GF5ppaKe2nC" + "assets": [ + { + "asset_name": "010a0001020d0d07080508030d0e0a0b0c070c0509100a04040806040f0f0f05", + "policy_id": "020809080e040e010809010b0f0c0607030600070f000f0a0706020a", + "quantity": 5 + }, + { + "asset_name": "090f020710060701051007070b0c07010c040401070d010b03040e010a0b0a10", + "policy_id": "030d0e0c00100e100100030b050d030d00040c06090506090c0f0c08", + "quantity": 8 + }, + { + "asset_name": "0e020207030a0a101002060c0c040e0809060f04050f020b0409080602060d01", + "policy_id": "0f05030d030d03100b090e0102080f07000e0c08080d0903100a0f0a", + "quantity": 5 + }, + { + "asset_name": "0e050c020004080a0e0908010800090908030709090a06060f0d0a0c04000e07", + "policy_id": "08030c080e0e080e00010e000d0a0206020e05000c04000305100501", + "quantity": 1 + }, + { + "asset_name": "0309040a0604070a04060a0c0f04020907090102020c0108020b040509040503", + "policy_id": "0e07070200070c0b030b05090b0802070205050d0c08080f0510040d", + "quantity": 4 + }, + { + "asset_name": "0210100e0c0c0e0304050c080e100e0d0510080e100901030d0501050308010b", + "policy_id": "0904060b0c090a0004060c0509000a000203090f0d100c100a070309", + "quantity": 3 + }, + { + "asset_name": "020409021000030e0d070d0004050903030c0c0c040c0c050001070f0a05060c", + "policy_id": "0e0304000d05080e0e0802030e05050f0e0c0e090e07030d0c0e0d02", + "quantity": 2 + }, + { + "asset_name": "0b070205000110040701050a1001010203010802060c08011006070e0301070d", + "policy_id": "0400030e0310090005070b0102000a0902000200060c0b0902100108", + "quantity": 0 + }, + { + "asset_name": "0d000c080e030905100708070b060407040706040f01001009010501100c0207", + "policy_id": "0e01090001030f030107090a0510050e0d03020b06050b070f090502", + "quantity": 1 } - }, - "policy_id": "e974d7d0622432c7dfae8aff2dcc9e1232cfeef21c97dda8aac27f8f", - "reference_input": { - "id": "692e46694214092a5c0c7e7e6f22621e20ab31434a623228b6067f371a157709", - "index": 0 - } + ] }, { - "asset_name": "546f6b656e59", - "operation": { - "burn": { - "quantity": 10 - } + "address": "FHnt4NL7yPY98CzfWyKiNN8tyAXxRGD48EimLWPouZyvxMnDoK7Rqxs5C91G6uk", + "amount": { + "quantity": 29617666636077560, + "unit": "lovelace" }, - "policy_id": "56704d9faef81e738deb4958c6d3d60db85a0fc0a033b18e33d18766", - "reference_input": { - "id": "5e4472405d044b565c58777c080c5a5c85611602742d2c2e291a00555f5c3e7b", - "index": 1 - } - }, - { - "asset_name": "546f6b656e51", - "operation": { - "burn": { + "assets": [ + { + "asset_name": "060c100c070e0e05060906020d00080f060900090a0c0e030b010610030b0b0c", + "policy_id": "0906010f05090802070c0110100c02100009020f000e100302040e06", "quantity": 4 + }, + { + "asset_name": "0f100d0903010301030c0d0c0e0d10090302000100020f03070d050b10030508", + "policy_id": "010f000910050803010400100e020507070b0e0c030e080409040d0a", + "quantity": 5 + }, + { + "asset_name": "0c0d000d04070d0c010c020f07010e05000e07091008030700060501040f1005", + "policy_id": "0a000b090306100c05010f0e010b04030a0e0b020808050c0604030f", + "quantity": 8 + }, + { + "asset_name": "0a020a100d050405000b02020704080b0d030001030c03050604080e020e080e", + "policy_id": "06000602020706051006020c0c0007100a08010e0b0500070c040109", + "quantity": 3 + }, + { + "asset_name": "0f0001080f040902070b1009051010050e02050b09000b0f030e000808030404", + "policy_id": "0c10020f050c08000707040a0401080006100a0800090c0804070901", + "quantity": 2 + }, + { + "asset_name": "030b0d100c020c10090608090e00020c000304020d10000f0a05001003090807", + "policy_id": "090307090c02040f040a0f0503050910081002090400000600100e08", + "quantity": 2 + }, + { + "asset_name": "030e0b020c0d0a0d070d100904030d020d0c0207100b0205050a00030b060305", + "policy_id": "00090b09040101030907050e0c0608000f0a0b0900030f08050c090c", + "quantity": 9 + }, + { + "asset_name": "060701070b0d0b0903000b0e061008090606050608020c010f08080405030502", + "policy_id": "0d0d080d0b08070b090f06090901080e10090a01011006050c080406", + "quantity": 6 + }, + { + "asset_name": "0104000209030d090c0105000b0707000d0a06030803070901040c030f0d080f", + "policy_id": "0908050d060f050c04010f0a030903080c070103090a050e0b060a03", + "quantity": 1 + }, + { + "asset_name": "100701100010050c10070407010d0f07000d000f100502010e100a0306070b03", + "policy_id": "0f060b0e0b090f020f0c050c030e0e06060f07050c0b100d040c0e05", + "quantity": 3 + }, + { + "asset_name": "0201020d0f070500010503080b010c0406050610090d050b0705030c0f090d0a", + "policy_id": "0e000e09100c0f07010309100c050d0a03020f0710040202010b0104", + "quantity": 8 + }, + { + "asset_name": "07090d0a0e100809070201070b080810040b0204030910010307020404070805", + "policy_id": "090c0d02050d01050d0d1002080c0f0803050202040f040b0d060604", + "quantity": 6 } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } - }, - { - "operation": { - "burn": { - "quantity": 21 - } - }, - "policy_id": "422e1a23f3279d2a9f673c1b66139132702e1f9447862c528f41dae2", - "reference_input": { - "id": "1c5a9c77208f685c45185a51d6ed557783503762081f040e070d50e63e720045", - "index": 1 - } + ] }, { - "operation": { - "burn": { - "quantity": 26 - } + "address": "FHnt4NL7yPYF5Jo9VfXTwXuY9q6nYXhVdQjzBsaAxv7XbNetDDP2RzWYxPRZ3uJ", + "amount": { + "quantity": 39465256877501300, + "unit": "lovelace" }, - "policy_id": "6352e5dd1ccb276d56261e4bc9e795d0f461a49d9e579a951659f1dc", - "reference_input": { - "id": "78e48b1ec65204535bb8846e6367093b6692037562655e2c6729547b73172ed1", - "index": 1 - } + "assets": [ + { + "asset_name": "0a0904000e0f0d07100702010909010c0e070d0e040d05030310050c0d08070a", + "policy_id": "1006000f060306090f0f08060d000d01030010010104030a08040406", + "quantity": 5 + } + ] }, { - "asset_name": "546f6b656e53", - "operation": { - "burn": { - "quantity": 14 - } + "address": "addr_test1yp8399pdaxw406p0ll0805f9anxlg9t9czw0xylqd0t5p4dj3jrn0ge5g4acw3fne8wephmtklqucgkjsx7g5a0g3hequ3a5xu", + "amount": { + "quantity": 5246059481728293, + "unit": "lovelace" }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } + "assets": [ + { + "asset_name": "1008030d0d100f0d0a06000b100e000007000e050210090a09050b0d040e0a0c", + "policy_id": "0f0901010c00030b0904101007040b010404080303040c04060f000a", + "quantity": 0 + }, + { + "asset_name": "0f000d0f08020f0b0a0c070f0d08100904020d0e000504000701020108060409", + "policy_id": "000c100c0f020d040e0b0d070e0a08080f0c0e0b10030a10000c070f", + "quantity": 1 + }, + { + "asset_name": "06000e0807090b0a0d0a10000102000d0e0d06030503080a0203090003060005", + "policy_id": "040d0f0d070c0b07030b001008030406030f100f000f0d0709050103", + "quantity": 3 + }, + { + "asset_name": "090f0f0c0d0d05020d0e0203030b000e0801020a10020708010e020f0c010d0e", + "policy_id": "010702080e08060a040c0f0e020a0b0108010510080d040607040b06", + "quantity": 2 + }, + { + "asset_name": "0f0b0b100f1004100e01020a0e0f05040a0c0e040c0100090f0b0204060d0502", + "policy_id": "070f020e051007010c0c0b0b070e0d01030d090a08010e0e0e01000a", + "quantity": 6 + }, + { + "asset_name": "000e090000010705050a0d0f01030210060a0e0c0f0c02080610050405050c00", + "policy_id": "02050a07040e0d1005000f0c0a050a05020308080b0b0702000b0a06", + "quantity": 1 + }, + { + "asset_name": "0909050302060c0c0e0e05010a080e07000a0a030e10020a00040405080e0f00", + "policy_id": "02070b06090a1007090204070f0b0d0d100b0e090f0b000b00090f0f", + "quantity": 7 + }, + { + "asset_name": "0a0b030403040207010a0d0c06030b0a08020b0500000c060503070b000d050f", + "policy_id": "04070706090b040802040a020c0505040b0308030201080d00100d04", + "quantity": 7 + }, + { + "asset_name": "0304060c03020c021007090d0300100e0a0e0c0f06070409010709050d050202", + "policy_id": "010d010f0c0401090e0706090f041009080d0109030a100a00060e10", + "quantity": 6 + }, + { + "asset_name": "0105101000020200060d0f030910040209080d0a0508060e0e0d00080c090302", + "policy_id": "0206100008010a0408010b0101080a060b0e100a060a070404100802", + "quantity": 7 + }, + { + "asset_name": "02050e050c03050504030c0c06040304040a0b0700020b02060d0806050e0305", + "policy_id": "03100b0e0f050a06070a02090704080f000905040307040b0601010d", + "quantity": 7 + }, + { + "asset_name": "07030709060b0508080b0b080e07050c080802040d09090a09000a07010e0d06", + "policy_id": "0f060406070804060805030707021008040108100c0e040a0d010200", + "quantity": 1 + }, + { + "asset_name": "0006000f0b1002010c0e000d080000070a0b01050f04050c0f080a0b050b0b0a", + "policy_id": "060e020d0a0e0d0b03090f06040502020a0403050e020f0d0c0c0209", + "quantity": 5 + }, + { + "asset_name": "04050a01021006060c040f0c0d0b0800030e03020c04090c09030f0906040a0e", + "policy_id": "0b020902040606000110050d080e030d010e090c0f090b0008080e0d", + "quantity": 1 + }, + { + "asset_name": "0f0504070e010c0808000b0d000e080d0d020e05070c0408030b0d0a090a0f08", + "policy_id": "09031006040d04040c040b010f0600040e0a0a0e0d01010e010e0f0e", + "quantity": 7 + }, + { + "asset_name": "0f09100402061008090f0e070c060c00020505010803080008050a0c0b050f08", + "policy_id": "0b030e08060e060c0c0d0204040b0f0a0d070205090b100c00020110", + "quantity": 6 + }, + { + "asset_name": "0f0d08010d040a020501070102000e0a04040206020f080d0b0d0d000a06040c", + "policy_id": "0d0c10080e1007030c0106070809050d03000d0f0008060e00080c10", + "quantity": 7 + } + ] }, { - "operation": { - "mint": { - "quantity": 20, - "receiving_address": "addr_test1vryweju03dpwxf35tsw8vch3xt2rsj9827rsv49qs95wm8qk0vda6" - } + "address": "FHnt4NL7yPYK2zKQBYmLKnf79qfYSUQNLHjuReHQzWoVQ3yHPAvgmJhUPnZK9JR", + "amount": { + "quantity": 42689176200342596, + "unit": "lovelace" }, - "policy_script_template": "cosigner#0" + "assets": [ + { + "asset_name": "1002050205040f0f0207050e060104080a09040a0606090206060c070d0e0b06", + "policy_id": "0305050604000001000e100c0d0a0a0b0601040010030b09040c0e06", + "quantity": 4 + }, + { + "asset_name": "06020b0a04040a0d090d060310040c0a070909050f0c04100803030508090d01", + "policy_id": "0a00040b040610090506040706020b05000f080f000d0204080e0c0f", + "quantity": 3 + }, + { + "asset_name": "040b0710020f0b0c0b02020c0600010b0a020b0e080e0009040d020a05000e0c", + "policy_id": "0a0606070e040f000505100d0a090f010803070803040f0b05100c0f", + "quantity": 1 + }, + { + "asset_name": "040e020e090b0b070009090f03040809080b0501040b02050b07100e0c040a04", + "policy_id": "000d04060d040309000c10050b0001030b0b0f030b050c0d07020508", + "quantity": 2 + }, + { + "asset_name": "0b050e0e0c00070707080e0c0700010b100905100206100408080b0f000e1009", + "policy_id": "020d070d05080a06070a08020106000910100e0105010110090f0c02", + "quantity": 2 + }, + { + "asset_name": "09100804050f0e0f07000c070c070401060e0903080801040505000903100a0c", + "policy_id": "0d070c0f080807090d0d0f0e06081002100b01010300030d0e000707", + "quantity": 7 + }, + { + "asset_name": "080e0b060d03050a091004050a0c020a090c10040505010306020b101009020d", + "policy_id": "0a0709030400020d060e08030a0810050c0e070c100b0c0a090b030b", + "quantity": 5 + }, + { + "asset_name": "0e0d0b0007011005040202020d000003050a04060d0b0f09100101100a0d040c", + "policy_id": "0a05090902060b010b000d080c100903100f0a010c000208090b0f01", + "quantity": 6 + }, + { + "asset_name": "090b100f0a040e07010f100d0b0005090610020d02070903010a020c060f0406", + "policy_id": "100a0403100b10020f0d0704080b0803040d10070a03100d080f0007", + "quantity": 5 + }, + { + "asset_name": "0409030d0008080d0b0c0c0e09040105010105040d0d050c06010e0b03060900", + "policy_id": "050804080508100a010d061009050d0a0601080e0110050c00000501", + "quantity": 3 + } + ] }, { - "operation": { - "mint": { + "address": "addr_test1yqu3qg9sg08ukek02vkjr6jlc79qslp5kecz9w776gdx845k7dlcun0hexff99d9wjdh4v8h6z4pmazp4y556q2hzp7q0hsmue", + "amount": { + "quantity": 32432587993208169, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "0b020e01040a04090308000b080402010e100c10030b07030c0a000f0c0c0603", + "policy_id": "080101070a0d0a000b100d10100010031008100305030d090100100c", + "quantity": 1 + }, + { + "asset_name": "04030b060d04080c060310070b0c050a070d01020509080b050a0d0e020b0705", + "policy_id": "0e0301080b0302060d0d010f0e080d020803070c0a070e07070a0f0e", "quantity": 5 } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } + ] }, { - "operation": { - "mint": { - "quantity": 9, - "receiving_address": "addr_test1qrrgrhcnr8m4503z8x249fht506k7pcd6wgkhsga8a5ve5xc4ylvu4fjckpc87tmxxx7j0r90q4pyrvpk654egk0h0fqp0jzrt" - } + "address": "addr_test1vpuqdpws0rku0wytm2vx3ufc632j4hxx9tplj8umzc7h0rgqw9g6z", + "amount": { + "quantity": 16456192954173385, + "unit": "lovelace" }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } + "assets": [ + { + "asset_name": "010410050601040600070e0109050c000300060509100e040b050c100c010d0b", + "policy_id": "0507020e0200090b0a10060010070e0b0d020f05070108030a0e080e", + "quantity": 5 + }, + { + "asset_name": "0c08050106090101050f02081003060909030b010f0406070f09080302070d00", + "policy_id": "01020e0609080805080c030c06090003060c0e0902000f030e070701", + "quantity": 7 + }, + { + "asset_name": "0c0f07010c0c09100e0b030c0f0103080a04010c000c10000c08100a0e010306", + "policy_id": "0b010400040505010c0c040f030d0f0508020b080302040c010a0c10", + "quantity": 7 + }, + { + "asset_name": "010e0a080c0804090106070d100f02020c06060400080e0201060e0809100a00", + "policy_id": "0e0e0e040004070e070e09060404020703010502040a0e040609010a", + "quantity": 4 + }, + { + "asset_name": "02050c060a0c020e07000b0e0c0a0004040e010a080d0b0c0501010a08050f00", + "policy_id": "030d0d080902070310090e0a050f0005010f0f0e030e070e06020b0e", + "quantity": 5 + }, + { + "asset_name": "04020d030f0d0e0a0002010306040c0d0f0402010004060b020d1010020e0a0e", + "policy_id": "0b0d020a10000c050d0f000a0f030b00061006090902080404030605", + "quantity": 6 + }, + { + "asset_name": "0f040b070b100d0d090b02010f09070c03010f070d0a0c070a0205020d030a10", + "policy_id": "04020502040e0f070a0b100409020b050c0c03050b07080c0a0a0300", + "quantity": 8 + }, + { + "asset_name": "02010c070b0e020300010f0e020706050d0e100e08030308060d0f000205010d", + "policy_id": "0800070706080d0804030608010207050809040b0c10080d000f0808", + "quantity": 4 + }, + { + "asset_name": "0e0a02020001040606020605090a1008100f0c0307040904000b000701020103", + "policy_id": "050b100108100810010b0d02031001060203000a010e0d0b0e0a1003", + "quantity": 3 + }, + { + "asset_name": "01040f0b0102060b0d05070502020c1009070d0a030c0502070c0004080f0c01", + "policy_id": "0a04010707020e020e06070b010704090907091008010b0a0a090f07", + "quantity": 1 + }, + { + "asset_name": "06000208050c0e0c10040d0c0b0e0d0b03070100030d030d01100210040a0609", + "policy_id": "0b0d0c020209010a080b010d0309040a0a0c03070b0d0b0a10090300", + "quantity": 1 + }, + { + "asset_name": "0c0c050b0304100f09000105030d060b0a100209030f0102020e050c060b0b0d", + "policy_id": "0f020d030f0a100f00060f10070909000d0a0b0e0b030f0309050f04", + "quantity": 2 + }, + { + "asset_name": "010205100a05080701050204060d090600100d01090507080c0a090b0e101002", + "policy_id": "080a090e0e0308040d08040304010c0e07050c0a0300020a0406090c", + "quantity": 8 + }, + { + "asset_name": "0d020810050e0607040c00100f0b06060e010e100c100d051010030d0110070a", + "policy_id": "0d000801010a090e08090906100506030e080e04100c0f0c00010603", + "quantity": 5 + } + ] }, { - "asset_name": "546f6b656e42", - "operation": { - "burn": { - "quantity": 19 - } + "address": "FHnt4NL7yPYAJ5KqgSVzKtWTwPUqPwmQTHRss4DxZYBkKKYeU1cWMQX2FNqjwfb", + "amount": { + "quantity": 25988383277997388, + "unit": "lovelace" }, - "policy_id": "4f3a55980bc1ec216a198b97c4041609211bf41e058b102a4e7c0b38", - "reference_input": { - "id": "59784f3e76b41f65aa9127400d54321794fb5d4835164447217435650b572362", - "index": 1 - } + "assets": [ + { + "asset_name": "050909090a0d0106090a070207050a10090e09080d0607040e0c0a0a0f0c090b", + "policy_id": "0a050308020c050d10000004080909050f0a080e0507001000100e10", + "quantity": 1 + }, + { + "asset_name": "0f070910010e020402060d0904090a060d0b0b0f050a06000307060e10060408", + "policy_id": "0b060e020e020b0808030704001004060303100d0500020d070f0209", + "quantity": 5 + }, + { + "asset_name": "0505070b10080d0c0f07050a0709010f0f030201090304060a0202030f0e0701", + "policy_id": "020600040f10050408080e05030906000a060f0b1007020a050e0304", + "quantity": 0 + }, + { + "asset_name": "07030f0b030708040d0205060d0b0b0d03080d050109010605050a0d100f0d00", + "policy_id": "000e010b0c05060a0a03030c070f080a0c00000a00070a050e0a090f", + "quantity": 0 + }, + { + "asset_name": "080e070904010a0f0008090b0f03020b000f030b0101060a07020107080d0d0f", + "policy_id": "0304070d0b07010d1006080508080a000d0d050e060c0c010d070c00", + "quantity": 5 + }, + { + "asset_name": "0500030a0b0e09070a0b0e09030e0d080f030e0c0110000c1001090c01090100", + "policy_id": "0c0804030808090f0f0c04091001030f040e07070c020c08060e0a05", + "quantity": 1 + }, + { + "asset_name": "0c0b07080a100206040f0c0e0804100709030d0e01070c0e0c090310010a040c", + "policy_id": "0c06000e0c0e000a0d08010507030b05000d0504040507070b090701", + "quantity": 5 + }, + { + "asset_name": "0a030d040d040410030c0a05000009010b0c07080f0801090a040b0706070a0b", + "policy_id": "0906020b010c04090e050700000d0f0408100c0b040e030d100e0b0d", + "quantity": 2 + } + ] } - ] + ], + "vote": "abstain" } ], - "seed": -133532971 + "seed": 1851424529 } \ No newline at end of file diff --git a/lib/wallet/test/data/Cardano/Wallet/Api/ApiTDRep.json b/lib/wallet/test/data/Cardano/Wallet/Api/ApiTDRep.json new file mode 100644 index 00000000000..6514ebc74ba --- /dev/null +++ b/lib/wallet/test/data/Cardano/Wallet/Api/ApiTDRep.json @@ -0,0 +1,15 @@ +{ + "samples": [ + "abstain", + "abstain", + "drep1c9umxe06vc0vzv9fu866axles2lpaqhsh36suqc7h0hzv8e2hcs", + "no_confidence", + "abstain", + "abstain", + "drep_script13y9jcl4mu3sxr6t2dckyceuz6mwtaahqyr8dld8yqhqmwjv0l9e", + "abstain", + "no_confidence", + "abstain" + ], + "seed": -2053978213 +} \ No newline at end of file diff --git a/lib/wallet/test/data/Cardano/Wallet/Api/ApiVoteAction.json b/lib/wallet/test/data/Cardano/Wallet/Api/ApiVoteAction.json deleted file mode 100644 index 0dee23b8d1e..00000000000 --- a/lib/wallet/test/data/Cardano/Wallet/Api/ApiVoteAction.json +++ /dev/null @@ -1,15 +0,0 @@ -{ - "samples": [ - "no_confidence", - "abstain", - "no_confidence", - "abstain", - "no_confidence", - "no_confidence", - "no_confidence", - "no_confidence", - "no_confidence", - "no_confidence" - ], - "seed": -1390512828 -} \ No newline at end of file diff --git a/lib/wallet/test/unit/Cardano/Wallet/Api/TypesSpec.hs b/lib/wallet/test/unit/Cardano/Wallet/Api/TypesSpec.hs index 205d36401a1..f22113b781f 100644 --- a/lib/wallet/test/unit/Cardano/Wallet/Api/TypesSpec.hs +++ b/lib/wallet/test/unit/Cardano/Wallet/Api/TypesSpec.hs @@ -2030,7 +2030,7 @@ instance Arbitrary DRepID where instance Arbitrary DRep where arbitrary = - oneof [pure Abstain, pure NoConfidence, arbitrary] + oneof [pure Abstain, pure NoConfidence, FromDRepID <$> arbitrary] instance HasSNetworkId n => Arbitrary (ApiConstructTransactionData n) where arbitrary = ApiConstructTransactionData From b3fc5517b3838e74dbb9c2a6a2b1d4c2ee1efdc8 Mon Sep 17 00:00:00 2001 From: Pawel Jakubas Date: Mon, 5 Feb 2024 13:26:14 +0100 Subject: [PATCH 7/9] add missing cert to fromConwayCerts --- .../Wallet/Primitive/Ledger/Read/Tx/Features/Certificates.hs | 4 +++- .../lib/Cardano/Wallet/Primitive/Types/Certificates.hs | 5 ++++- 2 files changed, 7 insertions(+), 2 deletions(-) diff --git a/lib/primitive/lib/Cardano/Wallet/Primitive/Ledger/Read/Tx/Features/Certificates.hs b/lib/primitive/lib/Cardano/Wallet/Primitive/Ledger/Read/Tx/Features/Certificates.hs index 2cdb7bdc2e2..b170f26a548 100644 --- a/lib/primitive/lib/Cardano/Wallet/Primitive/Ledger/Read/Tx/Features/Certificates.hs +++ b/lib/primitive/lib/Cardano/Wallet/Primitive/Ledger/Read/Tx/Features/Certificates.hs @@ -94,6 +94,7 @@ import GHC.Stack import qualified Cardano.Ledger.Api as Ledger import qualified Cardano.Ledger.BaseTypes as SL +import qualified Cardano.Ledger.Conway.TxCert as Ledger import qualified Cardano.Ledger.Credential as SL import qualified Cardano.Ledger.DRep as Ledger import qualified Cardano.Ledger.Shelley.API as SL @@ -151,7 +152,8 @@ fromConwayCert = \case CertificateOther RegDRep Ledger.UnRegDRepTxCert _ _ -> CertificateOther UnRegDRep - _ -> error "impossible pattern" + Ledger.UpdateDRepTxCert {} -> + CertificateOther UpdateDRep fromLedgerCoin :: HasCallStack => SL.Coin -> W.Coin fromLedgerCoin (SL.Coin c) = Coin.unsafeFromIntegral c diff --git a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/Certificates.hs b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/Certificates.hs index a17974fdfce..b54bfb37cc5 100644 --- a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/Certificates.hs +++ b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/Certificates.hs @@ -179,6 +179,7 @@ data NonWalletCertificate | ResignCommitteeColdKey | RegDRep | UnRegDRep + | UpdateDRep deriving (Generic, Show, Read, Eq) instance ToText NonWalletCertificate where @@ -188,6 +189,7 @@ instance ToText NonWalletCertificate where toText ResignCommitteeColdKey = "resign_committee_cold_key" toText RegDRep = "reg_DRep" toText UnRegDRep = "unreg_DRep" + toText UpdateDRep = "update_DRep" instance FromText NonWalletCertificate where fromText "genesis" = Right GenesisCertificate @@ -196,11 +198,12 @@ instance FromText NonWalletCertificate where fromText "resign_committee_cold_key" = Right ResignCommitteeColdKey fromText "reg_DRep" = Right RegDRep fromText "unreg_DRep" = Right UnRegDRep + fromText "update_DRep" = Right UpdateDRep fromText _ = Left $ TextDecodingError "expecting one of 'genesis', 'mir', 'auth_committee_hot_key'\ - \, 'resign_committee_cold_key', 'reg_DRep' or \ + \, 'resign_committee_cold_key', 'reg_DRep', 'update_DRep' or \ \'unreg_DRep' for NonWalletCertificate text value" instance NFData NonWalletCertificate From 467d0d0c14caa0031b8ce6e86bbb52ded502947b Mon Sep 17 00:00:00 2001 From: Pawel Jakubas Date: Mon, 5 Feb 2024 13:46:19 +0100 Subject: [PATCH 8/9] hlint/stylish --- lib/wallet/src/Cardano/Wallet.hs | 7 +++---- lib/wallet/test/unit/Cardano/Wallet/Api/TypesSpec.hs | 6 +++--- 2 files changed, 6 insertions(+), 7 deletions(-) diff --git a/lib/wallet/src/Cardano/Wallet.hs b/lib/wallet/src/Cardano/Wallet.hs index 72c62e68804..8c239ea2ce8 100644 --- a/lib/wallet/src/Cardano/Wallet.hs +++ b/lib/wallet/src/Cardano/Wallet.hs @@ -31,8 +31,7 @@ -- License: Apache-2.0 -- -- Provides wallet layer functions that are used by API layer. Uses both --- "Cardano.Wallet.DB" and "Cardano.Wallet.Network" to realize its role as --- being intermediary between the three. +-- "Cardano.Wallet.DB" and "Cardano.Wallet.Network" to realize its role as-- being intermediary between the three. -- -- Functions of the wallet layer are often parameterized with variables -- following the convention below: @@ -573,11 +572,11 @@ import Cardano.Wallet.Read.Tx.CBOR ( TxCBOR ) import Cardano.Wallet.Shelley.Transaction - ( mkTransaction + ( _txRewardWithdrawalCost + , mkTransaction , mkUnsignedTransaction , txConstraints , txWitnessTagForKey - , _txRewardWithdrawalCost ) import Cardano.Wallet.Transaction ( DelegationAction (..) diff --git a/lib/wallet/test/unit/Cardano/Wallet/Api/TypesSpec.hs b/lib/wallet/test/unit/Cardano/Wallet/Api/TypesSpec.hs index f22113b781f..5a3a55bfe85 100644 --- a/lib/wallet/test/unit/Cardano/Wallet/Api/TypesSpec.hs +++ b/lib/wallet/test/unit/Cardano/Wallet/Api/TypesSpec.hs @@ -583,9 +583,7 @@ import Numeric.Natural ( Natural ) import Servant - ( (:<|>) - , (:>) - , Capture + ( Capture , Header' , JSON , PostNoContent @@ -594,6 +592,8 @@ import Servant , ReqBody , StdMethod (..) , Verb + , (:<|>) + , (:>) ) import Servant.API.Verbs ( NoContentVerb From 6a9e3733f6090b4e2c20c60bf2f248ecc2e20f37 Mon Sep 17 00:00:00 2001 From: Pawel Jakubas Date: Mon, 5 Feb 2024 15:07:49 +0100 Subject: [PATCH 9/9] final polishing --- .../Cardano/Wallet/Primitive/Types/DRep.hs | 4 +-- specifications/api/swagger.yaml | 35 ++++++++----------- 2 files changed, 17 insertions(+), 22 deletions(-) diff --git a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs index 9fc060d63dd..3c03047e485 100644 --- a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs +++ b/lib/primitive/lib/Cardano/Wallet/Primitive/Types/DRep.hs @@ -139,12 +139,12 @@ instance FromText DRep where Right $ FromDRepID $ DRepFromScriptHash scripthash Left _ -> Left $ TextDecodingError $ unwords [ "I couldn't parse the given decentralized representative (DRep)." - , "I am expecting either 'abstain', 'no confidence'" + , "I am expecting either 'abstain', 'no_confidence'" , "or bech32 encoded drep having prefixes: 'drep'" , "or 'drep_script'."] instance Buildable DRep where build = \case Abstain -> "abstain" - NoConfidence -> "casting no confidence" + NoConfidence -> "no_confidence" FromDRepID drep -> "delegating voting to " <> build drep diff --git a/specifications/api/swagger.yaml b/specifications/api/swagger.yaml index 6590daebf76..c3226b5baa1 100644 --- a/specifications/api/swagger.yaml +++ b/specifications/api/swagger.yaml @@ -393,22 +393,6 @@ x-drepScriptHash: &drepScriptHash description: DRep's script hash. pattern: "^(drep_script)1[0-9a-z]*$" -x-noVote: &noVote - type: string - enum: - - abstain - - no_confidence - -x-anyVoting: &anyVoting - nullable: false - oneOf: - - <<: *drepKeyHash - title: vote to a drep represented by key hash - - <<: *drepScriptHash - title: vote to a drep represented by script hash - - <<: *noVote - title: casting no vote - x-walletAccountXPubkey: &walletAccountXPubkey description: An extended account public key (public key + chain code) type: string @@ -3730,12 +3714,23 @@ components: operation: *ApiMintBurnOperation ApiDRep: &ApiDRep - <<: *anyVoting description: | - Voting action. One can abstain, give no confidence vote - or vote for a representative by specifying its key hash or script hash. - Voting can be done together with delegation action or as a standalone action. + Decentralized representative (DRep) + that the wallet is delegating its vote to. + One can abstain, give no confidence vote, + or vote for a representative specified by a key hash or script hash. + Vote delegation can be done together with stake delegation action. + nullable: false type: string + oneOf: + - enum: + - abstain + - no_confidence + title: casting a default vote + - <<: *drepKeyHash + title: vote to a drep represented by key hash + - <<: *drepScriptHash + title: vote to a drep represented by script hash ApiConstructTransactionData: &ApiConstructTransactionData description: At least one field needs to be chosen