diff --git a/lib/balance-tx/lib/Cardano/Wallet/Write/Tx/Sign.hs b/lib/balance-tx/lib/Cardano/Wallet/Write/Tx/Sign.hs index fd26dfa58cb..2aeeb241149 100644 --- a/lib/balance-tx/lib/Cardano/Wallet/Write/Tx/Sign.hs +++ b/lib/balance-tx/lib/Cardano/Wallet/Write/Tx/Sign.hs @@ -188,12 +188,24 @@ estimateKeyWitnessCount utxo txbody@(Cardano.TxBody txbodycontent) = fromIntegral $ sumVia estimateMaxWitnessRequiredPerInput $ mapMaybe toTimelockScript scripts + -- when wallets uses reference input it means script containing + -- its policy key was already published in previous tx + -- if so we need to add one witness that will stem from policy signing + -- key. As it is not allowed to publish and consume in the same transaction + -- we are not going to double count. + txRefInpsWit = case Cardano.txInsReference txbodycontent of + Cardano.TxInsReferenceNone -> 0 + Cardano.TxInsReference{} -> + case Cardano.txMintValue txbodycontent of + Cardano.TxMintNone -> 0 + Cardano.TxMintValue{} -> 1 nonInputWits = numberOfShelleyWitnesses $ fromIntegral $ length txExtraKeyWits' + length txWithdrawals' + txUpdateProposal' + fromIntegral txCerts + - scriptVkWitsUpperBound + scriptVkWitsUpperBound + + txRefInpsWit inputWits = KeyWitnessCount { nKeyWits = fromIntegral . length diff --git a/lib/wallet/api/http/Cardano/Wallet/Api/Http/Shelley/Server.hs b/lib/wallet/api/http/Cardano/Wallet/Api/Http/Shelley/Server.hs index 038556127e5..e8e799d75bd 100644 --- a/lib/wallet/api/http/Cardano/Wallet/Api/Http/Shelley/Server.hs +++ b/lib/wallet/api/http/Cardano/Wallet/Api/Http/Shelley/Server.hs @@ -313,6 +313,7 @@ import Cardano.Wallet.Api.Types , ApiForeignStakeKey (..) , ApiIncompleteSharedWallet (..) , ApiMintBurnData (..) + , ApiMintBurnDataFromInput (..) , ApiMintBurnDataFromScript (..) , ApiMintBurnOperation (..) , ApiMintData (..) @@ -591,7 +592,7 @@ import Data.Coerce import Data.Either ( isLeft, isRight ) import Data.Either.Extra - ( eitherToMaybe, fromLeft' ) + ( eitherToMaybe ) import Data.Function ( (&) ) import Data.Functor @@ -2449,7 +2450,7 @@ constructTransaction api argGenChange knownPools poolStatus apiWalletId body = d validityInterval <- liftHandler $ parseValidityInterval ti $ body ^. #validityInterval - mintBurnData <- + mintBurnDatum <- liftHandler $ except $ parseMintBurnData body validityInterval mintBurnReferenceScriptTemplate <- @@ -2501,47 +2502,65 @@ constructTransaction api argGenChange knownPools poolStatus apiWalletId body = d liftHandler $ W.readPolicyPublicKey wrk transactionCtx2 <- - if isJust mintBurnData then do - let isMinting (ApiMintBurnDataFromScript _ _ (ApiMint _)) = True - isMinting _ = False - let getMinting = \case - ApiMintBurnDataFromScript + if isJust mintBurnDatum then do + let isMinting mb = case mb ^. #mintBurnData of + Left (ApiMintBurnDataFromScript _ _ (ApiMint _)) -> True + Right (ApiMintBurnDataFromInput _ _ _ (ApiMint _)) -> True + _ -> False + + makeLeft (a,t,s) = (a,t, Left s) + getMinting mb = case mb ^. #mintBurnData of + Left (ApiMintBurnDataFromScript (ApiT scriptT) (Just (ApiT tName)) - (ApiMint (ApiMintData _ amt)) -> + (ApiMint (ApiMintData _ amt))) -> + makeLeft $ toTokenMapAndScript ShelleyKeyS scriptT (Map.singleton (Cosigner 0) policyXPub) tName amt + Right (ApiMintBurnDataFromInput + refInp + (ApiT policyId) + (Just (ApiT tName)) + (ApiMint (ApiMintData _ amt))) -> + (AssetId policyId tName, TokenQuantity amt, Right refInp) _ -> error "getMinting should not be used in this way" - let getBurning = \case - ApiMintBurnDataFromScript + getBurning mb = case mb ^. #mintBurnData of + Left (ApiMintBurnDataFromScript (ApiT scriptT) (Just (ApiT tName)) - (ApiBurn (ApiBurnData amt)) -> + (ApiBurn (ApiBurnData amt))) -> + makeLeft $ toTokenMapAndScript ShelleyKeyS scriptT (Map.singleton (Cosigner 0) policyXPub) tName amt + Right (ApiMintBurnDataFromInput + refInp + (ApiT policyId) + (Just (ApiT tName)) + (ApiBurn (ApiBurnData amt))) -> + (AssetId policyId tName, TokenQuantity amt, Right refInp) _ -> error "getBurning should not be used in this way" - let toTokenMap = + toTokenMap = fromFlatList . map (\(a,q,_) -> (a,q)) - let toScriptTemplateMap = + toScriptTemplateMap = Map.fromList . map (\(a,_,s) -> (a,s)) - let mintingData = + mintingData = toTokenMap &&& toScriptTemplateMap $ map getMinting $ filter isMinting $ - NE.toList $ fromJust mintBurnData - let burningData = + NE.toList $ fromJust mintBurnDatum + burningData = toTokenMap &&& toScriptTemplateMap $ map getBurning $ filter (not . isMinting) $ - NE.toList $ fromJust mintBurnData + NE.toList $ fromJust mintBurnDatum pure transactionCtx1 { txAssetsToMint = mintingData , txAssetsToBurn = burningData @@ -2564,11 +2583,13 @@ constructTransaction api argGenChange knownPools poolStatus apiWalletId body = d Just (ApiPaymentAddresses content) -> pure $ F.toList (addressAmountToTxOut <$> content) - let mintWithAddress - (ApiMintBurnDataFromScript _ _ (ApiMint (ApiMintData (Just _) _))) - = True - mintWithAddress _ = False - let mintingOuts = case mintBurnData of + let mintWithAddress mb = case mb ^. #mintBurnData of + Left (ApiMintBurnDataFromScript _ _ (ApiMint (ApiMintData (Just _) _))) -> + True + Right (ApiMintBurnDataFromInput _ _ _ (ApiMint (ApiMintData (Just _) _))) -> + True + _ -> False + let mintingOuts = case mintBurnDatum of Just mintBurns -> coalesceTokensPerAddr $ map (toMintTxOut policyXPub) $ @@ -2648,14 +2669,11 @@ constructTransaction api argGenChange knownPools poolStatus apiWalletId body = d parseMintBurnData :: ApiConstructTransactionData n -> (SlotNo, SlotNo) - -> Either ErrConstructTx (Maybe (NonEmpty (ApiMintBurnDataFromScript n))) + -> Either ErrConstructTx (Maybe (NonEmpty (ApiMintBurnData n))) parseMintBurnData tx validity = do - when (notAllFromScript (tx ^. #mintBurn)) $ - Left ErrConstructTxNotImplemented - let mbMintingBurning :: Maybe (NonEmpty (ApiMintBurnDataFromScript n)) + let mbMintingBurning :: Maybe (NonEmpty (ApiMintBurnData n)) mbMintingBurning = - fmap (handleMissingAssetName . takeMintingFromScript) - <$> tx ^. #mintBurn + fmap handleMissingAssetName <$> tx ^. #mintBurn for mbMintingBurning $ \mintBurnData -> do guardWrongMintingTemplate mintBurnData guardAssetNameTooLong mintBurnData @@ -2663,68 +2681,81 @@ constructTransaction api argGenChange knownPools poolStatus apiWalletId body = d guardOutsideValidityInterval validity mintBurnData Right mintBurnData where - notAllFromScript = \case - Nothing -> False - Just mintData -> - any isRight $ mintBurnData <$> NE.toList mintData - - -- we checked that only left are present in preceding line - takeMintingFromScript (ApiMintBurnData mintData) = - fromLeft' mintData - - handleMissingAssetName :: ApiMintBurnDataFromScript n -> ApiMintBurnDataFromScript n - handleMissingAssetName mb = case mb ^. #assetName of - Nothing -> mb {assetName = Just (ApiT nullTokenName)} - Just _ -> mb + handleMissingAssetName :: ApiMintBurnData n -> ApiMintBurnData n + handleMissingAssetName mb = case mb ^. #mintBurnData of + Left fromScript -> ApiMintBurnData $ Left $ + updateFromScript fromScript + Right fromInp -> ApiMintBurnData $ Right $ + updateFromInp fromInp + where + updateFromScript :: ApiMintBurnDataFromScript n -> ApiMintBurnDataFromScript n + updateFromScript mbd = case mbd ^. #assetName of + Nothing -> mbd {assetName = Just (ApiT nullTokenName)} + Just _ -> mbd + updateFromInp :: ApiMintBurnDataFromInput n -> ApiMintBurnDataFromInput n + updateFromInp mbd = case mbd ^. #assetName of + Nothing -> mbd {assetName = Just (ApiT nullTokenName)} + Just _ -> mbd guardWrongMintingTemplate - :: NonEmpty (ApiMintBurnDataFromScript n) -> Either ErrConstructTx () - guardWrongMintingTemplate mintBurnData = - when (any wrongMintingTemplate mintBurnData) + :: NonEmpty (ApiMintBurnData n) -> Either ErrConstructTx () + guardWrongMintingTemplate mbs = + when (any wrongMintingTemplate mbs) $ Left ErrConstructTxWrongMintingBurningTemplate where - wrongMintingTemplate (ApiMintBurnDataFromScript (ApiT script) _ _) = - isLeft (validateScriptOfTemplate RecommendedValidation script) - || countCosigners script /= (1 :: Int) - || existsNonZeroCosigner script + wrongMintingTemplate mb = case mb ^. #mintBurnData of + Left (ApiMintBurnDataFromScript (ApiT script) _ _) -> + isLeft (validateScriptOfTemplate RecommendedValidation script) + || countCosigners script /= (1 :: Int) + || existsNonZeroCosigner script + Right (ApiMintBurnDataFromInput _ _ _ _) -> False countCosigners = foldScript (const (+ 1)) 0 existsNonZeroCosigner = foldScript (\cosigner a -> a || cosigner /= Cosigner 0) False guardAssetNameTooLong - :: NonEmpty (ApiMintBurnDataFromScript n) -> Either ErrConstructTx () - guardAssetNameTooLong mintBurnData = - when (any assetNameTooLong mintBurnData) - $ Left ErrConstructTxAssetNameTooLong + :: NonEmpty (ApiMintBurnData n) -> Either ErrConstructTx () + guardAssetNameTooLong mbs = + when (any assetNameTooLong mbs)$ Left ErrConstructTxAssetNameTooLong where - assetNameTooLong = \case - ApiMintBurnDataFromScript _ (Just (ApiT (UnsafeTokenName bs))) _ -> + assetNameTooLong mb = case mb ^. #mintBurnData of + Left (ApiMintBurnDataFromScript _ (Just (ApiT (UnsafeTokenName bs))) _) -> + BS.length bs > tokenNameMaxLength + Right (ApiMintBurnDataFromInput _ _ (Just (ApiT (UnsafeTokenName bs))) _) -> BS.length bs > tokenNameMaxLength - _ -> error "tokenName should be nonempty at this step" + _ -> error "at this moment there should be asset name attributed" guardAssetQuantityOutOfBounds - :: NonEmpty (ApiMintBurnDataFromScript n) -> Either ErrConstructTx () - guardAssetQuantityOutOfBounds mintBurnData = - when (any assetQuantityOutOfBounds mintBurnData) + :: NonEmpty (ApiMintBurnData n) -> Either ErrConstructTx () + guardAssetQuantityOutOfBounds mbs = + when (any assetQuantityOutOfBounds mbs) $ Left ErrConstructTxMintOrBurnAssetQuantityOutOfBounds where - assetQuantityOutOfBounds = \case - ApiMintBurnDataFromScript _ _ (ApiMint (ApiMintData _ amt)) -> - amt <= 0 || amt > unTokenQuantity txMintBurnMaxTokenQuantity - ApiMintBurnDataFromScript _ _ (ApiBurn (ApiBurnData amt)) -> - amt <= 0 || amt > unTokenQuantity txMintBurnMaxTokenQuantity + checkAmt amt = + amt <= 0 || amt > unTokenQuantity txMintBurnMaxTokenQuantity + assetQuantityOutOfBounds mb = case mb ^. #mintBurnData of + Left (ApiMintBurnDataFromScript _ _ (ApiMint (ApiMintData _ amt))) -> + checkAmt amt + Left (ApiMintBurnDataFromScript _ _ (ApiBurn (ApiBurnData amt))) -> + checkAmt amt + Right (ApiMintBurnDataFromInput _ _ _ (ApiMint (ApiMintData _ amt))) -> + checkAmt amt + Right (ApiMintBurnDataFromInput _ _ _ (ApiBurn (ApiBurnData amt))) -> + checkAmt amt guardOutsideValidityInterval :: (SlotNo, SlotNo) - -> NonEmpty (ApiMintBurnDataFromScript n) + -> NonEmpty (ApiMintBurnData n) -> Either ErrConstructTx () - guardOutsideValidityInterval (before, hereafter) mintBurnData = - when (any notWithinValidityInterval mintBurnData) $ + guardOutsideValidityInterval (before, hereafter) mbs = + when (any notWithinValidityInterval mbs) $ Left ErrConstructTxValidityIntervalNotWithinScriptTimelock where - notWithinValidityInterval (ApiMintBurnDataFromScript (ApiT script) _ _) = - not $ withinSlotInterval before hereafter $ + notWithinValidityInterval mb = case mb ^. #mintBurnData of + Left (ApiMintBurnDataFromScript (ApiT script) _ _) -> + not $ withinSlotInterval before hereafter $ scriptSlotIntervals script + Right _ -> False unsignedTx path initialOuts decodedTx = UnsignedTx { unsignedCollateral = @@ -2747,9 +2778,9 @@ constructTransaction api argGenChange knownPools poolStatus apiWalletId body = d mapMaybe (toUsignedTxWdrl path) (decodedTx ^. #withdrawals) } - toMintTxOut policyXPub - (ApiMintBurnDataFromScript (ApiT scriptT) (Just (ApiT tName)) - (ApiMint (ApiMintData (Just addr) amt))) = + toMintTxOut policyXPub mb = case mb ^. #mintBurnData of + Left (ApiMintBurnDataFromScript (ApiT scriptT) (Just (ApiT tName)) + (ApiMint (ApiMintData (Just addr) amt))) -> let (assetId, tokenQuantity, _) = toTokenMapAndScript ShelleyKeyS scriptT (Map.singleton (Cosigner 0) policyXPub) @@ -2757,10 +2788,17 @@ constructTransaction api argGenChange knownPools poolStatus apiWalletId body = d assets = fromFlatList [(assetId, tokenQuantity)] in (addr, assets) - toMintTxOut _ _ = error $ unwords - [ "toMintTxOut can only be used in the minting context with addr" - , "specified" - ] + Right (ApiMintBurnDataFromInput _ (ApiT policyId) (Just (ApiT tName)) + (ApiMint (ApiMintData (Just addr) amt))) -> + let assetId = AssetId policyId tName + tokenQuantity = TokenQuantity amt + assets = fromFlatList [(assetId, tokenQuantity)] + in + (addr, assets) + _ -> error $ unwords + [ "toMintTxOut can only be used in the minting context with addr" + , "specified" + ] coalesceTokensPerAddr = let toTxOut (addr, assets) = diff --git a/lib/wallet/api/http/Cardano/Wallet/Api/Types.hs b/lib/wallet/api/http/Cardano/Wallet/Api/Types.hs index 99160db819a..d8354bc5940 100644 --- a/lib/wallet/api/http/Cardano/Wallet/Api/Types.hs +++ b/lib/wallet/api/http/Cardano/Wallet/Api/Types.hs @@ -3128,6 +3128,9 @@ data ApiMintBurnDataFromInput (n :: NetworkDiscriminant) = ApiMintBurnDataFromIn { referenceInput :: !ReferenceInput -- ^ A reference input that contains script regulating minting/burning policy. + , policyId + :: !(ApiT W.TokenPolicyId) + -- ^ A policy id of the script regulating minting/burning policy. , assetName :: !(Maybe (ApiT W.TokenName)) -- ^ The name of the asset to mint/burn. diff --git a/lib/wallet/integration/src/Test/Integration/Scenario/API/Shelley/TransactionsNew.hs b/lib/wallet/integration/src/Test/Integration/Scenario/API/Shelley/TransactionsNew.hs index 00a25080d99..da9be71e590 100644 --- a/lib/wallet/integration/src/Test/Integration/Scenario/API/Shelley/TransactionsNew.hs +++ b/lib/wallet/integration/src/Test/Integration/Scenario/API/Shelley/TransactionsNew.hs @@ -61,7 +61,7 @@ import Cardano.Wallet.Api.Types , ApiEra (..) , ApiExternalCertificate (..) , ApiNetworkInformation - , ApiPolicyId + , ApiPolicyId (..) , ApiPolicyKey (..) , ApiRegisterPool (..) , ApiSerialisedTransaction (..) @@ -244,6 +244,7 @@ import qualified Data.Text.Encoding as T import qualified Network.HTTP.Types.Status as HTTP import qualified Test.Integration.Plutus as PlutusScenario + spec :: forall n . HasSNetworkId n @@ -1166,8 +1167,8 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do [ RequireSignatureOf policyKeyHash ] - addrs <- listAddresses @n ctx wb - let destination = (addrs !! 1) ^. #id + addrsDest <- listAddresses @n ctx wb + let destination = (addrsDest !! 1) ^. #id let payload = Json [json|{ "reference_policy_script_template": { "all": [ "cosigner#0" ] }, @@ -1220,6 +1221,118 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do , expectField (#witnessCount) (`shouldBe` witnessCountWithNativeScript) ] + let payloadPolicyId = Json [json|{ + "policy_script_template": + { "all": + [ "cosigner#0" + ] + } + }|] + let postPolicyId = Link.postPolicyId @'Shelley wa + rGet <- request @ApiPolicyId ctx postPolicyId Default payloadPolicyId + verify rGet + [ expectResponseCode HTTP.status202 + ] + let (ApiPolicyId (ApiT policyId')) = getFromResponse Prelude.id rGet + eventually "transaction is in ledger" $ do + let ep = Link.listTransactions @'Shelley wb + request @[ApiTransaction n] ctx ep Default Empty >>= flip verify + [ expectListField 0 + (#direction . #getApiT) (`shouldBe` Incoming) + , expectListField 0 + (#status . #getApiT) (`shouldBe` InLedger) + ] + + addrsMint <- listAddresses @n ctx wa + let addrMint = (addrsMint !! 1) ^. #id + let (Right tokenName') = mkTokenName "ab12" + let payloadMint = Json [json|{ + "mint_burn": [{ + "policy_id": #{toText policyId'}, + "reference_input": #{toJSON refInp}, + "asset_name": #{toText tokenName'}, + "operation": + { "mint" : + { "receiving_address": #{addrMint}, + "quantity": 1000 + } + } + }] + }|] + + rTxMint <- request @(ApiConstructTransaction n) ctx + (Link.createUnsignedTransaction @'Shelley wa) Default payloadMint + verify rTxMint + [ expectResponseCode HTTP.status202 + ] + let (ApiSerialisedTransaction apiTxMint _) = getFromResponse #transaction rTxMint + + signedTxMint <- signTx ctx wa apiTxMint [ expectResponseCode HTTP.status202 ] + + submittedTxMint <- submitTxWithWid ctx wa signedTxMint + verify submittedTxMint + [ expectSuccess + , expectResponseCode HTTP.status202 + ] + + let tokenPolicyId' = + UnsafeTokenPolicyId . Hash $ + unScriptHash $ + toScriptHash scriptUsed + let tokens' = TokenMap.singleton + (AssetId tokenPolicyId' tokenName') + (TokenQuantity 1_000) + + eventually "wallet holds minted assets" $ do + rWal <- request @ApiWallet ctx + (Link.getWallet @'Shelley wa) Default Empty + verify rWal + [ expectSuccess + , expectField (#assets . #available . #getApiT) + (`shouldBe` tokens') + , expectField (#assets . #total . #getApiT) + (`shouldBe` tokens') + ] + + let payloadBurn = Json [json|{ + "mint_burn": [{ + "policy_id": #{toText policyId'}, + "reference_input": #{toJSON refInp}, + "asset_name": #{toText tokenName'}, + "operation": + { "burn" : + { "quantity": 1000 + } + } + }] + }|] + + rTxBurn <- request @(ApiConstructTransaction n) ctx + (Link.createUnsignedTransaction @'Shelley wa) Default payloadBurn + verify rTxBurn + [ expectResponseCode HTTP.status202 + ] + let (ApiSerialisedTransaction apiTxBurn _) = getFromResponse #transaction rTxBurn + + signedTxBurn <- signTx ctx wa apiTxBurn [ expectResponseCode HTTP.status202 ] + + submittedTxBurn <- submitTxWithWid ctx wa signedTxBurn + verify submittedTxBurn + [ expectSuccess + , expectResponseCode HTTP.status202 + ] + + eventually "wallet does not hold minted assets anymore" $ do + rWal <- request @ApiWallet ctx + (Link.getWallet @'Shelley wa) Default Empty + verify rWal + [ expectSuccess + , expectField (#assets . #available . #getApiT) + (`shouldBe` TokenMap.empty) + , expectField (#assets . #total . #getApiT) + (`shouldBe` TokenMap.empty) + ] + it "TRANS_NEW_VALIDITY_INTERVAL_01a - \ \Validity interval with second" $ \ctx -> runResourceT $ do diff --git a/lib/wallet/src/Cardano/Wallet/Shelley/Transaction.hs b/lib/wallet/src/Cardano/Wallet/Shelley/Transaction.hs index 8457a55e7f8..ab9063729f5 100644 --- a/lib/wallet/src/Cardano/Wallet/Shelley/Transaction.hs +++ b/lib/wallet/src/Cardano/Wallet/Shelley/Transaction.hs @@ -141,6 +141,8 @@ import Cardano.Wallet.Transaction , ErrMkTransaction (..) , ErrMkTransactionOutputTokenQuantityExceedsLimitError (..) , PreSelection (..) + , ReferenceInput (..) + , ScriptSource , SelectionOf (..) , TokenMapWithScripts , TransactionCtx (..) @@ -242,9 +244,9 @@ constructUnsignedTx -- ^ Finalized asset selection -> Coin -- ^ Explicit fee amount - -> (TokenMap, Map AssetId (Script KeyHash)) + -> (TokenMap, Map AssetId ScriptSource) -- ^ Assets to be minted - -> (TokenMap, Map AssetId (Script KeyHash)) + -> (TokenMap, Map AssetId ScriptSource) -- ^ Assets to be burned -> Map TxIn (Script KeyHash) -- ^ scripts for inputs @@ -295,7 +297,7 @@ mkTx keyF networkId payload ttl (rewardAcnt, pwdAcnt) addrResolver wdrl cs fees (toCardanoLovelace fees) TokenMap.empty TokenMap.empty Map.empty Map.empty Nothing Nothing let signed = signTransaction keyF networkId AnyWitnessCountCtx acctResolver - (const Nothing) (const Nothing) addrResolver inputResolver + (const Nothing) Nothing (const Nothing) addrResolver inputResolver (unsigned, mkExtraWits unsigned) let withResolvedInputs (tx, _, _, _, _, _) = tx @@ -333,6 +335,8 @@ signTransaction -- ^ Stake key store / reward account resolution -> (KeyHash -> Maybe (XPrv, Passphrase "encryption")) -- ^ Policy key resolution + -> Maybe KeyHash + -- ^ Optional policy key -> (KeyHash -> Maybe (XPrv, Passphrase "encryption")) -- ^ Staking script key resolution -> (Address -> Maybe (k ktype XPrv, Passphrase "encryption")) @@ -348,6 +352,7 @@ signTransaction witCountCtx resolveRewardAcct resolvePolicyKey + policyKeyM resolveStakingKeyInScript resolveAddress resolveInput @@ -421,13 +426,21 @@ signTransaction retrieveAllKeyHashes (NativeScript s _) = foldScript (:) [] s retrieveAllKeyHashes _ = [] - isTimelock (NativeScript _ _) = True - isTimelock _ = False + isTimelockOrRef (NativeScript _ _) = True + isTimelockOrRef (AnyScriptReference _ _) = True + isTimelockOrRef _ = False getScriptsKeyHashes :: TokenMapWithScripts -> [KeyHash] getScriptsKeyHashes scripts = - concatMap retrieveAllKeyHashes $ - filter isTimelock $ + let getKeyHash script@(NativeScript _ _) = + retrieveAllKeyHashes script + getKeyHash (AnyScriptReference _ _) = case policyKeyM of + Just policyKey -> [policyKey] + Nothing -> [] + getKeyHash _ = error "getKeyHash: this should be filtered at at this stage" + in + concatMap getKeyHash $ + filter isTimelockOrRef $ Map.elems $ scripts ^. #txScripts mkTxInWitness :: TxIn -> Maybe (Cardano.KeyWitness era) @@ -504,6 +517,7 @@ newTransactionLayer keyF networkId = TransactionLayer policyResolver keyhash = do (keyhash', xprv, encP) <- policyCreds guard (keyhash == keyhash') $> (xprv, encP) + let stakingScriptResolver :: KeyHash -> Maybe (XPrv, Passphrase "encryption") stakingScriptResolver keyhash = case scriptStakingCredM of @@ -511,32 +525,38 @@ newTransactionLayer keyF networkId = TransactionLayer let (keyhash', xprv, encP) = scriptStakingCred guard (keyhash == keyhash') $> (xprv, encP) Nothing -> Nothing + + let policyKeyM :: Maybe KeyHash + policyKeyM = do + (keyhash', _, _) <- policyCreds + pure keyhash' + case cardanoTxIdeallyNoLaterThan era sealedTx of InAnyCardanoEra ByronEra _ -> sealedTx InAnyCardanoEra ShelleyEra (Cardano.Tx body wits) -> signTransaction keyF networkId witCountCtx acctResolver (const Nothing) - (const Nothing) addressResolver inputResolver (body, wits) + Nothing (const Nothing) addressResolver inputResolver (body, wits) & sealedTxFromCardano' InAnyCardanoEra AllegraEra (Cardano.Tx body wits) -> signTransaction keyF networkId witCountCtx acctResolver (const Nothing) - (const Nothing) addressResolver inputResolver (body, wits) + Nothing (const Nothing) addressResolver inputResolver (body, wits) & sealedTxFromCardano' InAnyCardanoEra MaryEra (Cardano.Tx body wits) -> signTransaction keyF networkId witCountCtx acctResolver policyResolver - stakingScriptResolver addressResolver inputResolver (body, wits) + policyKeyM stakingScriptResolver addressResolver inputResolver (body, wits) & sealedTxFromCardano' InAnyCardanoEra AlonzoEra (Cardano.Tx body wits) -> signTransaction keyF networkId witCountCtx acctResolver policyResolver - stakingScriptResolver addressResolver inputResolver (body, wits) + policyKeyM stakingScriptResolver addressResolver inputResolver (body, wits) & sealedTxFromCardano' InAnyCardanoEra BabbageEra (Cardano.Tx body wits) -> signTransaction keyF networkId witCountCtx acctResolver policyResolver - stakingScriptResolver addressResolver inputResolver (body, wits) + policyKeyM stakingScriptResolver addressResolver inputResolver (body, wits) & sealedTxFromCardano' InAnyCardanoEra ConwayEra (Cardano.Tx body wits) -> signTransaction keyF networkId witCountCtx acctResolver policyResolver - stakingScriptResolver addressResolver inputResolver (body, wits) + policyKeyM stakingScriptResolver addressResolver inputResolver (body, wits) & sealedTxFromCardano' , mkUnsignedTransaction = \stakeCred ctx selection -> do @@ -659,7 +679,7 @@ mkUnsignedTx -> Cardano.Lovelace -> TokenMap -> TokenMap - -> Map AssetId (Script KeyHash) + -> Map AssetId ScriptSource -> Map TxIn (Script KeyHash) -> Maybe (Script KeyHash) -> Maybe (Script KeyHash) @@ -674,7 +694,7 @@ mkUnsignedTx fees mintData burnData - mintingScripts + mintingSource inpsScripts stakingScriptM refScriptM = extractValidatedOutputs cs >>= \outs -> @@ -682,7 +702,24 @@ mkUnsignedTx Cardano.TxBodyContent { Cardano.txIns = inputWits - , txInsReference = Cardano.TxInsReferenceNone + , txInsReference = + let hasRefInp = \case + Left _ -> False + Right _ -> True + filteredRefInp = + filter hasRefInp $ + Map.elems mintingSource + toNodeTxIn (Right (ReferenceInput txin)) = + toCardanoTxIn txin + toNodeTxIn _ = error "at this moment we should have reference input" + in if null filteredRefInp then + Cardano.TxInsReferenceNone + else + case referenceInpsSupported of + Nothing -> Cardano.TxInsReferenceNone + Just support -> + Cardano.TxInsReference support + (toNodeTxIn <$> filteredRefInp) , Cardano.txOuts = case refScriptM of Nothing -> @@ -778,10 +815,16 @@ mkUnsignedTx burnValue = Cardano.negateValue $ toCardanoValue (TokenBundle (Coin 0) burnData) + toScriptWitnessGeneral = \case + Left script -> toScriptWitness script + Right (ReferenceInput txin) -> + Cardano.SimpleScriptWitness + scriptWitsSupported + (Cardano.SReferenceScript (toCardanoTxIn txin) Nothing) witMap = - Map.map toScriptWitness $ - Map.mapKeys (toCardanoPolicyId . TokenMap.tokenPolicyId) - mintingScripts + Map.map toScriptWitnessGeneral $ + Map.mapKeys (toCardanoPolicyId . TokenMap.tokenPolicyId) + mintingSource ctx = Cardano.BuildTxWith witMap in Cardano.TxMintValue mintedEra (mintValue <> burnValue) ctx } @@ -897,6 +940,16 @@ mkUnsignedTx ShelleyBasedEraBabbage -> Cardano.SimpleScriptInBabbage ShelleyBasedEraConway -> Cardano.SimpleScriptInConway + referenceInpsSupported + :: Maybe (Cardano.ReferenceTxInsScriptsInlineDatumsSupportedInEra era) + referenceInpsSupported = case era of + ShelleyBasedEraShelley -> Nothing + ShelleyBasedEraAllegra -> Nothing + ShelleyBasedEraMary -> Nothing + ShelleyBasedEraAlonzo -> Nothing + ShelleyBasedEraBabbage -> Just Cardano.ReferenceTxInsScriptsInlineDatumsInBabbageEra + ShelleyBasedEraConway -> Just Cardano.ReferenceTxInsScriptsInlineDatumsInConwayEra + toScriptWitness :: Script KeyHash -> Cardano.ScriptWitness witctx era toScriptWitness script = Cardano.SimpleScriptWitness diff --git a/lib/wallet/src/Cardano/Wallet/Transaction.hs b/lib/wallet/src/Cardano/Wallet/Transaction.hs index ed7be8f66e2..978a1447e5d 100644 --- a/lib/wallet/src/Cardano/Wallet/Transaction.hs +++ b/lib/wallet/src/Cardano/Wallet/Transaction.hs @@ -47,6 +47,7 @@ module Cardano.Wallet.Transaction , emptyWitnessCount , WitnessCountCtx (..) , toKeyRole + , ScriptSource -- * Errors , ErrSignTx (..) @@ -209,6 +210,8 @@ data TransactionLayer k ktype tx = TransactionLayer type TxValidityInterval = (Maybe SlotNo, SlotNo) +type ScriptSource = Either (Script KeyHash) ReferenceInput + -- | Some additional context about a transaction. This typically contains -- details that are known upfront about the transaction and are used to -- construct it from inputs selected from the wallet's UTxO. @@ -222,9 +225,9 @@ data TransactionCtx = TransactionCtx -- transaction is valid. , txDelegationAction :: Maybe DelegationAction -- ^ An additional delegation to take. - , txAssetsToMint :: (TokenMap, Map AssetId (Script KeyHash)) + , txAssetsToMint :: (TokenMap, Map AssetId ScriptSource) -- ^ The assets to mint. - , txAssetsToBurn :: (TokenMap, Map AssetId (Script KeyHash)) + , txAssetsToBurn :: (TokenMap, Map AssetId ScriptSource) -- ^ The assets to burn. , txPaymentCredentialScriptTemplate :: Maybe ScriptTemplate -- ^ Script template regulating payment credentials diff --git a/lib/wallet/test/data/Cardano/Wallet/Api/ApiConstructTransactionDataTestnet0.json b/lib/wallet/test/data/Cardano/Wallet/Api/ApiConstructTransactionDataTestnet0.json index 88364807530..ff3db9c691b 100644 --- a/lib/wallet/test/data/Cardano/Wallet/Api/ApiConstructTransactionDataTestnet0.json +++ b/lib/wallet/test/data/Cardano/Wallet/Api/ApiConstructTransactionDataTestnet0.json @@ -2,111 +2,90 @@ "samples": [ { "metadata": { - "16": { - "map": [ - { - "k": { - "string": "勇󹏠⊙𪈪𭮅" - }, - "v": { - "int": -3 - } - }, - { - "k": { - "string": "􂓏󶟧軻" - }, - "v": { - "bytes": "ca7e6754081d4f3c1412fd5b6f7b1a4a6735161442412e5b0172bc5702707e160f5caea34c238b24294d5457982759085629786071dd" - } - } - ] + "30": { + "int": 0 } }, - "mint_burn": [ - { - "operation": { - "burn": { - "quantity": 17 - } - }, - "policy_script_template": "cosigner#0" - }, - { - "asset_name": "546f6b656e58", - "operation": { - "burn": { - "quantity": 5 - } - }, - "reference_input": { - "id": "c8494624aeac03524646387753957c0eee3026320f3adf3e7f5a40341bd5000d", - "index": 0 - } - }, - { - "asset_name": "546f6b656e5a", - "operation": { - "burn": { - "quantity": 6 - } - }, - "policy_script_template": "cosigner#0" - }, - { - "operation": { - "burn": { - "quantity": 13 - } - }, - "policy_script_template": "cosigner#0" - } - ], "payments": [ { - "address": "FHnt4NL7yPYFgmwh59cLyHEX1bzmKuK5cEGvLSsP71mkgjFFLDSiPz2qpw7WD9k", + "address": "FHnt4NL7yPXzWU7jcDxc59hdS19XYrFHhgtTUwLVqCfq65L8zxTjweVSZnjqvaR", "amount": { - "quantity": 246, + "quantity": 237, "unit": "lovelace" }, "assets": [ + { + "asset_name": "546f6b656e42", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 20 + }, + { + "asset_name": "546f6b656e44", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 14 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 1 + }, + { + "asset_name": "546f6b656e42", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 36 + }, + { + "asset_name": "546f6b656e44", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 2 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 25 + }, { "asset_name": "546f6b656e43", "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 30 + "quantity": 10 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 3 + }, + { + "asset_name": "546f6b656e42", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 48 } ] }, { - "address": "addr_test1wr3fd9e7dl3493wgsc5srmz5pjw8tej59tuwvtxw5a5q7dswn2d3m", + "address": "addr_test1yp9ync4jupuwf7jd4ahfmkmzaaq67k2g07auh4varvtdpdvgu2r0j4a9jl0td2tp9v6qmq3hk4nnu3cdrff69qtkv8xs2gq2yr", "amount": { - "quantity": 177, + "quantity": 107, "unit": "lovelace" }, "assets": [ { "asset_name": "546f6b656e41", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 10 + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 6 } ] }, { - "address": "FHnt4NL7yPY7s3fhx7EJaQi7agucMUsZcvhubPsgNkcv51WnPuA2qGhevapy92h", + "address": "addr_test1qz0lt3dn5fn9670pdx739ny0caxqazp2yawy7p3e0k98vj95fv30e4q6v284zzxft62w7lvulxw5np7ut9zwha9lzmeqhchs7k", "amount": { - "quantity": 77, + "quantity": 20, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e42", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 18 - }, - { - "asset_name": "546f6b656e44", + "asset_name": "546f6b656e41", "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 13 + "quantity": 15 }, { "asset_name": "546f6b656e41", @@ -114,1081 +93,1476 @@ "quantity": 20 }, { - "asset_name": "546f6b656e44", + "asset_name": "546f6b656e42", "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 29 + "quantity": 13 }, { "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 26 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 16 + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 35 }, { "asset_name": "546f6b656e41", "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 26 + "quantity": 33 }, { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 44 + "asset_name": "546f6b656e41", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 46 + } + ] + }, + { + "address": "FHnt4NL7yPXjaAhAqmRQpuZ88zL5EbFUBYo8u6jhnsr6xgXhN1nTkjfSU56jzin", + "amount": { + "quantity": 125, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e45", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 14 }, { "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 26 + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 9 }, { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 39 + "asset_name": "546f6b656e45", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 19 }, { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 9 + "asset_name": "546f6b656e42", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 27 }, { - "asset_name": "546f6b656e45", + "asset_name": "546f6b656e41", "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 26 + "quantity": 28 } ] }, { - "address": "addr_test1xpc9ypk3g9a4wdjkdz02hkfsqgyzq90tuvg3a5xgwnpfkfdptwxldpjkesws70f4evp7j6grna6xyd2a0pwyzqnn0kgqmn4nzj", + "address": "addr_test1wpwv5m24gmkyj8v324zajtsqkzs64y90p4gv7wvsuza6umccjrws9", "amount": { - "quantity": 30, + "quantity": 109, "unit": "lovelace" }, - "assets": [] + "assets": [ + { + "asset_name": "546f6b656e44", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 16 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 18 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 10 + } + ] }, { - "address": "addr_test1vzj0rrjf8u8ykpz6fs2rvqcsnfls09yp4u48wezydy3uesqehl3g7", + "address": "addr_test1vpqs5rgxkc2rdjvdy2p6uay2zn70m2g69z0hejc2kd0uf7c6p0n4p", "amount": { - "quantity": 46, + "quantity": 103, "unit": "lovelace" }, - "assets": [ - { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 17 - } - ] + "assets": [] }, { - "address": "FHnt4NL7yPYGegGx7b2VHAuFTruYmVfHe1v8UpufbihyeQQCNXBm3KPVjwzMAFY", + "address": "addr_test1wr2yzgn42ws0r2t9lmnavzs0wf9ndrw3hhduyzrnplxwhncaya5f8", "amount": { - "quantity": 123, + "quantity": 141, "unit": "lovelace" }, - "assets": [ - { - "asset_name": "546f6b656e42", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 6 - } - ] + "assets": [] }, { - "address": "addr_test1yrvh3y8dmpwmtyc7ufvw2u7rfga3n7q5wxk82uk9lzxpuwjwxc07uyqrjjkwwj0jkaz2l9p9j6jadc9nzw8aj8l5cswszjym54", + "address": "addr_test1wq6npny6ulegj5g34xdh5qscfhtupn48gf83vvkh89gmr4cl3n4xr", "amount": { - "quantity": 67, + "quantity": 109, "unit": "lovelace" }, "assets": [ { "asset_name": "546f6b656e43", "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 14 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 24 + "quantity": 4 }, { - "asset_name": "546f6b656e42", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 14 + "asset_name": "546f6b656e44", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 7 } ] }, { - "address": "FHnt4NL7yPYEWxp7b7h3iZTNifUZAEBEU8dgkUSQXub5oEkw9w6YhhuWpaNRKNL", + "address": "addr_test1zpfdc02rkmfyvh5kzzwwwk4kr2l9a8qa3g7feehl3ga0228pk033k8a59e3l7zkae3zfq6j0yt5w65h24u7hrr48r7qq0gz83s", + "amount": { + "quantity": 129, + "unit": "lovelace" + }, + "assets": [] + }, + { + "address": "addr_test1wpwwm2ypw86gsmghajn8qwuhtg0q6fme4eyeejgzq6ttr6clwem62", "amount": { - "quantity": 47, + "quantity": 155, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", + "asset_name": "546f6b656e41", + "policy_id": "00000000000000000000000000000000000000000000000000000000", "quantity": 16 }, + { + "asset_name": "546f6b656e42", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 12 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 6 + }, { "asset_name": "546f6b656e41", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 23 + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 26 }, { "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 26 + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 25 }, { "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 21 + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 18 }, { "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 44 + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 20 + }, + { + "asset_name": "546f6b656e42", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 5 }, { "asset_name": "546f6b656e43", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 17 + }, + { + "asset_name": "546f6b656e42", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 17 + }, + { + "asset_name": "546f6b656e43", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 27 + }, + { + "asset_name": "546f6b656e44", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 18 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 29 + }, + { + "asset_name": "546f6b656e41", "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 13 + "quantity": 8 + }, + { + "asset_name": "546f6b656e42", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 27 } ] }, { - "address": "addr_test1vrra99g3fqhpmpv2ddplscq2hpem38vpgy6lrc7wwngmskqwnfauz", + "address": "FHnt4NL7yPXqwL3iHbs6UhbwDHorJCo7Gfz1iXq4az41GoKLZGBWGrmhKUacHZA", "amount": { - "quantity": 152, + "quantity": 206, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 9 + "asset_name": "546f6b656e45", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 4 } ] - } - ], - "withdrawal": "self" - }, - { - "delegations": [ - { - "join": { - "pool": "pool1f4vpg7uqdamygceqfqh5sugqxearsur9t4k8ymfnv9pjz7g74a3", - "stake_key_index": "32" - } - }, - { - "quit": { - "stake_key_index": "13018" - } - }, - { - "join": { - "pool": "pool1wf9jywmqpvx56scl8uypzpns0al3zdeu8e7nv4m4pst36vehktr", - "stake_key_index": "18" - } - }, - { - "quit": { - "stake_key_index": "4003" - } - }, - { - "quit": { - "stake_key_index": "6136" - } }, { - "quit": { - "stake_key_index": "10099" - } - }, - { - "join": { - "pool": "pool1d4tjc62rxvtyshgttqvpwjpmwpup6vf6tfj8z8erxe84s5uvk00", - "stake_key_index": "20" - } - }, - { - "quit": { - "stake_key_index": "280" - } - }, - { - "quit": { - "stake_key_index": "16135" - } - }, - { - "join": { - "pool": "pool1gp2nvgsy2q9kxpfg85sz5gstz90j2636qyvsuhmvdqpr24hey5j", - "stake_key_index": "57" - } - }, - { - "join": { - "pool": "pool18q4y6em0xecrqa6zvurp2ap5wsehyhtf9aeyz3md0y9jc3xpvhx", - "stake_key_index": "0" - } - }, - { - "quit": { - "stake_key_index": "9752" - } - }, - { - "quit": { - "stake_key_index": "8848" - } - }, - { - "quit": { - "stake_key_index": "15765" - } + "address": "FHnt4NL7yPXuZQdLyCPEhoQRSKwrBhr7tXxtPmHRRwAmhtMPc2fCkeSNCfv5hRA", + "amount": { + "quantity": 223, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e43", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 8 + } + ] }, { - "join": { - "pool": "pool19flxq76wres3g2jrtcrpk4rwd3dp6sg50vf8wegrf4hy2e6qrrd", - "stake_key_index": "110" - } + "address": "addr_test1vrxqf96n8lhsw60rnuk0hkn9em8aph05jxsl5z5y7rhqjfcx5z4q7", + "amount": { + "quantity": 93, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e43", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 16 + } + ] }, { - "join": { - "pool": "pool1vq09z664pqe3ggzjddpqz0mxp5vjxh3lf3skjxpgqfd9j4g7lga", - "stake_key_index": "95" - } - }, + "address": "addr_test1wzqpcpat57jknchv2rqedznswjaf6jwxnm0zp53fysyrwdczzqrx9", + "amount": { + "quantity": 127, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e43", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 17 + } + ] + } + ] + }, + { + "delegations": [ { "join": { - "pool": "pool1g9jhv4qkq5dkwacfdcepwff7rswpz2nygez5xcjmdefhsx79fsw", - "stake_key_index": "10" - } - }, - { - "quit": { - "stake_key_index": "13590" + "pool": "pool1vs25v82s04xrgkq6pcv9xgp809ehvye7p4r375muy9argsmur03", + "stake_key_index": "6" } }, { "join": { - "pool": "pool1yvkxkesxp46j7lndpg8nuagkq5z3u6qedcpquq3r2505jawvgv9", - "stake_key_index": "31" - } - }, - { - "quit": { - "stake_key_index": "11083" - } - }, - { - "quit": { - "stake_key_index": "350" + "pool": "pool12e3xz2jltptr7fnfv4z8y8zlzvus7vgwxv957kncfvzzwfyuclc", + "stake_key_index": "97" } } ], "encoding": "base16", "metadata": { - "20": "0x7e0c79752323417003eb560857141469501b0c5a78563e1952062d6010041331060e5522175f701269492e0e" + "27": { + "bytes": "a60e505c5b77584247491690615d475e10129a0138e86b7b3c441a2f32b42632dc" + } }, "mint_burn": [ { + "asset_name": "546f6b656e4b", "operation": { "mint": { - "quantity": 2, - "receiving_address": "FHnt4NL7yPY79NQyEufEhywvomVgEpAAWMu1Ag2yZGUTpmGmVq9zbC675VzjQkk" + "quantity": 15, + "receiving_address": "FHnt4NL7yPXy9x4c2LK9gL4SgsM7KM421e7gZQnUR7c5xup8P8J9JSvMLwDWiG7" } }, + "policy_id": "edf04861b20af147952c0bbb4da178a40319a282673426b661279fef", "reference_input": { - "id": "1fd25a4afc191b6f1b204b0118b1cd01245614a0574fab2119154f4a7c4e6e34", + "id": "59ca374af63f0a3c6473105d2b575b38ad7f267daa9473e351d0647a196b7004", "index": 0 } }, { "operation": { "burn": { - "quantity": 10 - } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } - }, - { - "asset_name": "546f6b656e4d", - "operation": { - "mint": { - "quantity": 10, - "receiving_address": "addr_test1zplrhvqd4lq2cg5h0hxpg7v6nu98nnukj60pucnxk7rvfetksg82ne209egktus690phn6lpdr6ynddrrztff9c45als0fwg74" + "quantity": 7 } }, + "policy_id": "7b5e59b4f5931d05afcbade2c94b250284cd285883cf531e7bd7a13a", "reference_input": { - "id": "0e020d73de120c901d5d19208c7273770e4922b71e52072eb2b1070054793d6e", + "id": "0506881bc34160116a0b6b22402b2c3fcf547c271cb2174cbc385e5b7b48692e", "index": 0 } }, { + "asset_name": "546f6b656e4d", "operation": { "mint": { - "quantity": 28, - "receiving_address": "FHnt4NL7yPY1iNSkGo3pYP9xiqyWTCrtiFDiwdVQ4maqdT2AattMYzAuukKWaFq" + "quantity": 21, + "receiving_address": "FHnt4NL7yPXmHUHetsWqK8NbGJ5R4jjARvc3ZkNikGqkm1QRFbTC1DK59WrEdTP" } }, - "reference_input": { - "id": "e00f31015b41367201e7048f2d417aaa941096a53f364921245302370b1e3c2c", - "index": 1 - } + "policy_script_template": "cosigner#0" }, { + "asset_name": "546f6b656e4a", "operation": { "burn": { - "quantity": 9 + "quantity": 18 } }, + "policy_id": "d45582dc8cd3f8c01fad103fa75480d895a5c6398ae4d489e4c779f9", "reference_input": { - "id": "6f137b8a1f237ed295a558721b1e513c663dc02c0540441d5f3775270c073a38", - "index": 0 + "id": "35660219ce725c1b1256f15e0e914334c06b211b062ec304581046444d287538", + "index": 1 } }, { - "asset_name": "546f6b656e43", + "asset_name": "546f6b656e56", "operation": { "mint": { - "quantity": 27, - "receiving_address": "addr_test1xqv87me869zt0jtvqhrty9s56fyx6es2zemypc35x0u29lm9ka7a8k9njsh0djegz472cvs7s4e8x027u3zdp6h43ygqkjlndg" + "quantity": 1, + "receiving_address": "FHnt4NL7yPYL3Q2heBP9pNH2EAX2d7wpW1upo1Sz57JfLEmFBjuZejCVwVDpfbF" } }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } + "policy_script_template": "cosigner#0" }, { + "asset_name": "546f6b656e4d", "operation": { "burn": { "quantity": 15 } }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } - }, - { - "asset_name": "546f6b656e53", - "operation": { - "burn": { - "quantity": 19 - } - }, + "policy_id": "7a5421edf1eed899a374862c8a1dc4fd087347b92abe828658bcca72", "reference_input": { - "id": "b84a6c3525687511621d693210191d744b462c67190344ce120f200c8d02c348", - "index": 1 + "id": "773e1340f5202b7a50c24e4b6670386b52345352e6365b6c7b1b7f6824002d47", + "index": 0 } }, { "operation": { "mint": { - "quantity": 10, - "receiving_address": "FHnt4NL7yPY43MTeVHxqpMdJGjSubcnFs2LjdeMiPdLQ922Xk5fXCdQq2DsbUqV" + "quantity": 11, + "receiving_address": "addr_test1yqts92xcr5a264fay0kjstut8snfrlgkvcaeg7s5cyywyc2ycqvvhjm3my2we6rua6phczk5m23t9ssky3s4e47rw95se4zzzw" } }, + "policy_id": "789bd1e19b4ecceb8aee017000bdd9935444b485a782481fe32d5fb5", "reference_input": { - "id": "3d713e1d2855642c0639b563212c7a251ea0146a105867470b15572e420b1722", - "index": 1 + "id": "2d5650186528472e3b2d624f0ade9462f739263e7848525fd3932a7f6759274f", + "index": 0 } - }, + } + ], + "payments": [ { - "operation": { - "mint": { - "quantity": 21, - "receiving_address": "addr_test1vpfmty2luj6g8wq0elfjnhg9k8623vxruzh5yhppzj43r7c0g480x" - } + "address": "addr_test1vp0pknx0g8w5c8dzmcnsh424puu6znv3thvh7tvyd0yzhns29smyu", + "amount": { + "quantity": 123, + "unit": "lovelace" }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } + "assets": [ + { + "asset_name": "546f6b656e41", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 19 + } + ] }, { - "operation": { - "burn": { - "quantity": 5 - } - }, - "policy_script_template": "cosigner#0" - }, - { - "asset_name": "546f6b656e49", - "operation": { - "burn": { - "quantity": 30 - } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } - }, - { - "operation": { - "burn": { - "quantity": 0 - } - }, - "policy_script_template": "cosigner#0" - } - ], - "payments": [ - { - "address": "FHnt4NL7yPXhaWUDNksUpESyxFJ9uCFckmR3tSDVUh58zL47yBhMFLpeZJrUxnh", + "address": "FHnt4NL7yPYHVMyuGSiy2xem8ceUodHbmXMXSr2qSmFuvgPzU4H29GrdWLCY23E", "amount": { - "quantity": 189, + "quantity": 57, "unit": "lovelace" }, "assets": [] }, { - "address": "addr_test1yp5pd6qa5srjxz0qmvkccepyc0fsf2ef3mcjsgy7lv70kjzcvalmdgge9uvq494dv6v08uchqrxg8kcqqxut4xl8jxtqlwpu7u", + "address": "addr_test1xp8pk8ur0txppf53dgvqhkp72fadydpqkpyd2c9llcm38l029n0szzg0puurgdr9zp9msvtq8jh5fv9gt85j74n0438qyhajc0", "amount": { - "quantity": 39, + "quantity": 80, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 13 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 2 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 15 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 14 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 5 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 52 - }, - { - "asset_name": "546f6b656e44", + "asset_name": "546f6b656e41", "policy_id": "22222222222222222222222222222222222222222222222222222222", "quantity": 11 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 20 } ] }, { - "address": "addr_test1wr2yzgn42ws0r2t9lmnavzs0wf9ndrw3hhduyzrnplxwhncaya5f8", - "amount": { - "quantity": 4, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "addr_test1zrs2w9p3nqfv8amnhgzwchtt8l7dt2kc2qrgqkcy0vyz2svnwrwn0w8zg80hl73yxls5mm3t3jsvfsvtdcmhp79ztmeqvhzvh5", + "address": "FHnt4NL7yPXpoSL4vv4bTiWL2W7yuZUxEFPQb61G15zmRwRxhwx2LYUEFqWMZi4", "amount": { - "quantity": 85, + "quantity": 171, "unit": "lovelace" }, "assets": [ - { - "asset_name": "546f6b656e41", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 9 - }, { "asset_name": "546f6b656e42", "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 16 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 23 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 15 + "quantity": 21 }, { "asset_name": "546f6b656e45", "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 1 + "quantity": 2 }, { - "asset_name": "546f6b656e41", + "asset_name": "546f6b656e45", "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 18 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 5 + "quantity": 13 }, { - "asset_name": "546f6b656e43", + "asset_name": "546f6b656e42", "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 15 + "quantity": 13 } ] }, { - "address": "FHnt4NL7yPYE2vLB2ksKpfjTUMxmZQceRFnws1jnhhqihRBURvAQwAmJ7n2Le5i", + "address": "FHnt4NL7yPYEav1s5VJs5x3EqqW9NNDWvKTE9atY66tsXyYjoDveASnNTHRKf4d", "amount": { - "quantity": 170, + "quantity": 32, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 28 + "asset_name": "546f6b656e43", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 11 }, { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 32 + "asset_name": "546f6b656e45", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 9 }, { - "asset_name": "546f6b656e44", + "asset_name": "546f6b656e42", "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 28 + "quantity": 16 }, { - "asset_name": "546f6b656e45", + "asset_name": "546f6b656e43", "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 14 + "quantity": 11 }, { "asset_name": "546f6b656e41", "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 18 + "quantity": 28 }, { - "asset_name": "546f6b656e42", + "asset_name": "546f6b656e44", "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 25 + "quantity": 8 }, { - "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 14 + "asset_name": "546f6b656e41", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 56 }, { - "asset_name": "546f6b656e42", + "asset_name": "546f6b656e43", "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 31 + "quantity": 3 }, { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 21 + "asset_name": "546f6b656e44", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 33 }, { "asset_name": "546f6b656e45", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 27 + }, + { + "asset_name": "546f6b656e42", "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 37 + "quantity": 20 } ] - }, + } + ] + }, + { + "delegations": [ { - "address": "FHnt4NL7yPXpCcyMz6vUopGevshp3MkBeQFh3C6o9gMdpJmm7qcRVzVpuhqw2MU", - "amount": { - "quantity": 38, - "unit": "lovelace" - }, - "assets": [] + "join": { + "pool": "pool1vcd8jqr7xg04zdrdyuzh5zrfzawxy7pzregjx0e8dg5964zs009", + "stake_key_index": "49" + } }, { - "address": "FHnt4NL7yPXrbK46TAxZ2eZh5noLKyXgmgBu1EQshQSu7PwyxLcTTWXRAyxvyYJ", - "amount": { - "quantity": 155, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 9 - } - ] + "join": { + "pool": "pool12d6gqrsexew5vv3gqenp2kes2yu9xpmjzd6hgy2rdpsj2yune8p", + "stake_key_index": "87" + } }, { - "address": "addr_test1wrtm6st02v0enafndxnasftljhyc8tf7fv3wlfl0mxxl6wc2wwh65", - "amount": { - "quantity": 135, - "unit": "lovelace" - }, - "assets": [] + "quit": { + "stake_key_index": "11284" + } }, { - "address": "FHnt4NL7yPXxVBcBzK4dNkheF85zXkpHJGdHG3n68M4ot4NL1qSPUiV4SxDEyb3", - "amount": { - "quantity": 220, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 20 - } - ] + "join": { + "pool": "pool1rga5y0mpp4cs56e78eg3kfrxy48qu2grxckhygn0tdukv5rg5w2", + "stake_key_index": "8" + } }, { - "address": "addr_test1qzdg0wzc2gnthg4vea3vtyqqpr9mxuj23lhnz4sj5gz2pjsxuja5ayp4fypq6j99udns9tjeg9z7g784esngkyn8hjqq56lp66", - "amount": { - "quantity": 2, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 28 - } - ] + "join": { + "pool": "pool194z5x6rsg595v86pvack5nsp0dkyk23l8ywpsmpxzfq4y4as3az", + "stake_key_index": "76" + } }, { - "address": "addr_test1vrw9kkqrmwjnzjjckund8heew7ewec4p4v5p5ayrkexdn9gqhur3c", - "amount": { - "quantity": 16, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 29 - } - ] + "join": { + "pool": "pool18ga82dzgdut5gusu04cqqaj9p4rkkr5q05kj2aepr3kxggnmt68", + "stake_key_index": "41" + } }, { - "address": "addr_test1wqnfgz7tm4lcpadgqe730xuwzkg4km4uypac70pmplvwvcgfq9py3", - "amount": { - "quantity": 75, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 18 - } - ] + "quit": { + "stake_key_index": "8544" + } }, { - "address": "FHnt4NL7yPYANKTBoQR8HpesNDq1kCdv1X7fPNQXPf1nndYaj2VRJ2aXv4GQNeG", - "amount": { - "quantity": 81, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e42", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 24 - } - ] + "quit": { + "stake_key_index": "2975" + } }, { - "address": "addr_test1xppmd4v4f2tcemeye68r3dgc2e9s9c2rncnfespx0nc20x9n7s9gzag4a0ge0v30jlqcywwfqj9mumzfjyhcax9pu38st4se0l", - "amount": { - "quantity": 89, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quit": { + "stake_key_index": "5607" + } + } + ], + "mint_burn": [ + { + "asset_name": "546f6b656e4c", + "operation": { + "mint": { + "quantity": 23, + "receiving_address": "addr_test1zzn2amjajmku63pu48nup4an6zmglvdwj8wupw5c2q7et6rv77mnzw9llpkekksuxjxmnlwhuvuyfa6wzfp2f5pxm2usy6smv8" + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } + }, + { + "asset_name": "546f6b656e41", + "operation": { + "mint": { + "quantity": 14, + "receiving_address": "addr_test1wq6npny6ulegj5g34xdh5qscfhtupn48gf83vvkh89gmr4cl3n4xr" + } + }, + "policy_id": "67a640079813f965ab41d7c9ea2763b58b603a73548691d7efaa18ab", + "reference_input": { + "id": "32916f7d3133d6531190d7378572e246415162727c132a36520a163fbd34774f", + "index": 0 + } + }, + { + "operation": { + "mint": { + "quantity": 10, + "receiving_address": "addr_test1wrkklag37yvauqm7qucrf7rur9hmhtwl62t3x8fgpufn8zq5c6585" + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } + }, + { + "operation": { + "burn": { + "quantity": 29 + } + }, + "policy_script_template": "cosigner#0" + }, + { + "operation": { + "mint": { + "quantity": 2, + "receiving_address": "FHnt4NL7yPXwGHfXVEAKn3NJRpEuouhP7qnBHyoqvSCvoGtimbeX3GQQRmtje1L" + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } + }, + { + "operation": { + "burn": { + "quantity": 26 + } + }, + "policy_id": "cc7690f882404b86e847ff75fa7ad1950f0af92f4dff22b4ded9ccc6", + "reference_input": { + "id": "7808192eb8a61b34002a7814355870007501277874265d50e8a0607d310f2985", + "index": 1 + } + }, + { + "operation": { + "burn": { "quantity": 15 + } + }, + "policy_id": "5c04dbd723878225639c57763dbd979ed658565204ba98ed2b141858", + "reference_input": { + "id": "1f305a60c91b740a744d0868aa3133427467157f4c0c60516ecd0f6b1d207b2f", + "index": 1 + } + }, + { + "asset_name": "546f6b656e4a", + "operation": { + "burn": { + "quantity": 6 + } + }, + "policy_id": "01adacbd01fcec2ff0c668387d301757bf3aee4f5a38a902d8225a9b", + "reference_input": { + "id": "645dc1546c5a662b545a253ff9b208dd0062466d041746442f27701b5234227f", + "index": 0 + } + } + ], + "payments": [ + { + "address": "addr_test1wpcesyjchs2zysn3gqd7kylrs8ls9mvtf3ekv0qawyyz67qwjruvv", + "amount": { + "quantity": 49, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e41", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 9 }, { "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 22 + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 3 }, { "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", + "policy_id": "33333333333333333333333333333333333333333333333333333333", "quantity": 10 }, { - "asset_name": "546f6b656e42", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 28 + "asset_name": "546f6b656e43", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 8 }, + { + "asset_name": "546f6b656e45", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 20 + } + ] + }, + { + "address": "addr_test1yp4gr5jhgr8v248ekr9c7rmnau0lx0dyx9ddaadmrmedtcd6ezkxkpxam7avt8tj368r0eak6jp4nmkxppuuqr2r903sa9ffjr", + "amount": { + "quantity": 71, + "unit": "lovelace" + }, + "assets": [ { "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 27 + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 42 }, { - "asset_name": "546f6b656e45", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 19 + "asset_name": "546f6b656e42", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 25 }, { "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 14 + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 16 }, { "asset_name": "546f6b656e44", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 30 + }, + { + "asset_name": "546f6b656e41", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 5 + }, + { + "asset_name": "546f6b656e42", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 27 + }, + { + "asset_name": "546f6b656e41", "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 24 + "quantity": 53 }, { "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 47 - }, + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 15 + } + ] + }, + { + "address": "FHnt4NL7yPXmWXd4u5G4ZZPbwVCbfS9KQiY7DkGw9dqAr2knbD9iNApPM4Jsk9W", + "amount": { + "quantity": 79, + "unit": "lovelace" + }, + "assets": [ { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 30 + "asset_name": "546f6b656e42", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 18 } ] }, { - "address": "FHnt4NL7yPXxNqD9Mps5XSCHpnwXcpGYsrs4dNCBQFykLsAroyTwKssQtPBu3Rp", + "address": "addr_test1zp5qzgc4hpze8075qyylnfrsqrm0hxpvuknaat6lykrqeewfw6h80ncrv564pck45mcemufa84w9qhmn5zxzns7qxarsf6r58e", "amount": { - "quantity": 77, + "quantity": 208, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e45", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 16 + "asset_name": "546f6b656e43", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 14 } ] }, { - "address": "FHnt4NL7yPXoAdmMZo4Ao4kwhXLYGtQp3PeE9iMr2EThRQKM29gQChyYQ3xSyRj", + "address": "FHnt4NL7yPXvu2RLBr5WU4Z87ZczHB9RHc3Ag4RLQTK6zKNkjesU5ZszH9Awpqn", "amount": { - "quantity": 57, + "quantity": 247, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e41", + "asset_name": "546f6b656e43", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 27 + } + ] + }, + { + "address": "FHnt4NL7yPY3XdMnx1WUiRq35sYJDyUmeuoZtQoWwpTFvkiMuMhymrontReeCNr", + "amount": { + "quantity": 76, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e42", "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 2 + "quantity": 5 } ] }, { - "address": "FHnt4NL7yPY7Wh5KrruNoCjBXqaLVmviEDS4BfA1TNuujmxnz3SfA1AKwruLaeY", + "address": "addr_test1xq6npny6ulegj5g34xdh5qscfhtupn48gf83vvkh89gmr46jms758dkjge0fvyyuuadtvx47t6wpmz3unnn0lz36755q9pkqrn", "amount": { - "quantity": 239, + "quantity": 43, "unit": "lovelace" }, - "assets": [] + "assets": [ + { + "asset_name": "546f6b656e42", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 17 + } + ] }, { - "address": "addr_test1wq4t5hxa8mpfunak478s49s6tqxe2qtjfv779cerv2xxtnsf27e60", + "address": "FHnt4NL7yPXvAgpFZU2RH27EBTNFUp97HsiUMg2DhV3caM9wLGYhf2o393pf2rY", "amount": { - "quantity": 179, + "quantity": 61, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e41", + "asset_name": "546f6b656e42", "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 10 + "quantity": 21 }, { - "asset_name": "546f6b656e43", + "asset_name": "546f6b656e44", "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 13 + "quantity": 11 }, { - "asset_name": "546f6b656e41", + "asset_name": "546f6b656e42", "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 10 + "quantity": 36 + }, + { + "asset_name": "546f6b656e43", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 11 }, { "asset_name": "546f6b656e44", "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 10 + "quantity": 22 }, { - "asset_name": "546f6b656e42", + "asset_name": "546f6b656e41", "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 19 + "quantity": 2 }, { - "asset_name": "546f6b656e43", + "asset_name": "546f6b656e44", "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 15 + "quantity": 28 + }, + { + "asset_name": "546f6b656e41", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 30 + }, + { + "asset_name": "546f6b656e42", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 56 + }, + { + "asset_name": "546f6b656e41", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 4 + }, + { + "asset_name": "546f6b656e43", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 29 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 4 + } + ] + }, + { + "address": "FHnt4NL7yPY8miaHUDmviozP4MeksT3UdG27BjPoZPxMNTWK38FjhC9AC3tSWX1", + "amount": { + "quantity": 20, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e43", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 14 + } + ] + }, + { + "address": "addr_test1wrttejxvytsx950vqh8ffpmqze0v4edr3hyr2q4tpqklnugwu39va", + "amount": { + "quantity": 201, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e45", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 29 + } + ] + }, + { + "address": "FHnt4NL7yPY1efs3JdYhPQbxym4iaiMB592XhLoUyDR45NfDNNHnPxsDXTij3DN", + "amount": { + "quantity": 55, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e43", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 31 }, { "asset_name": "546f6b656e44", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 25 + }, + { + "asset_name": "546f6b656e42", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 28 + }, + { + "asset_name": "546f6b656e41", "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 35 + "quantity": 24 }, { - "asset_name": "546f6b656e45", + "asset_name": "546f6b656e43", "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 26 + "quantity": 21 }, { "asset_name": "546f6b656e41", "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 26 + "quantity": 31 }, { "asset_name": "546f6b656e42", "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 15 + "quantity": 11 + }, + { + "asset_name": "546f6b656e43", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 30 }, { "asset_name": "546f6b656e44", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 30 + }, + { + "asset_name": "546f6b656e43", "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 18 + "quantity": 5 + }, + { + "asset_name": "546f6b656e44", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 14 }, { "asset_name": "546f6b656e45", "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 27 + "quantity": 28 } ] }, { - "address": "FHnt4NL7yPXsLz3YieGiQo1cYSa9twRwc7hrzymbje2Pdf3fCmRfpXNBxf2uZR1", + "address": "FHnt4NL7yPYEgV2YCv4QV9fdHXbY7xsE45o3AeRxpjxX7PQnFP2Esfkzhw8iJ9i", "amount": { - "quantity": 254, + "quantity": 92, "unit": "lovelace" }, - "assets": [] - } - ] - }, - { - "delegations": [ - { - "quit": { - "stake_key_index": "4847" - } + "assets": [ + { + "asset_name": "546f6b656e41", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 30 + }, + { + "asset_name": "546f6b656e43", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 33 + }, + { + "asset_name": "546f6b656e44", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 8 + }, + { + "asset_name": "546f6b656e42", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 30 + }, + { + "asset_name": "546f6b656e41", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 2 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 26 + }, + { + "asset_name": "546f6b656e42", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 30 + } + ] }, { - "join": { - "pool": "pool12e6s5ycngda828ru9ytnuhrn0e4s7crzrs7nv82794z35p0586j", - "stake_key_index": "127" - } + "address": "addr_test1qqufqawp48hdrf72e89ryfwd375gfh623am4uvvtthnvwvh9qe9p9h0534znrv9a59vlu2u09r8dmzpyq5vpshvnytqqe774yq", + "amount": { + "quantity": 237, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e41", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 15 + } + ] }, { - "quit": { - "stake_key_index": "15564" - } + "address": "FHnt4NL7yPXwdXZDjdQcr9Mz3DKMBPGtzjZAJTrR4xUoFBGKH61TTdJTcnyc6En", + "amount": { + "quantity": 22, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e41", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 8 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 8 + }, + { + "asset_name": "546f6b656e44", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 25 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 29 + }, + { + "asset_name": "546f6b656e44", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 8 + } + ] }, { - "join": { - "pool": "pool12c7q73rgq5ypv73cyggs5dm60fdr7fz6y988klf3xpfz63su2fv", - "stake_key_index": "40" - } + "address": "addr_test1wqc5rsaqqmgakhjhzk388uzh3ej9sry7rz5gfyqj4ddpelc2zp40p", + "amount": { + "quantity": 200, + "unit": "lovelace" + }, + "assets": [] }, { - "quit": { - "stake_key_index": "23" - } + "address": "FHnt4NL7yPYBfPZmajczDG2RU2rDThfWarTP4gzWrJthEu3ZkGGTRZqmQUiUR2w", + "amount": { + "quantity": 63, + "unit": "lovelace" + }, + "assets": [] }, { - "quit": { - "stake_key_index": "7656" - } + "address": "FHnt4NL7yPXmeQsrENGEE7gTfrMKcGP4bkPcagaE6UvQTJm6HCP3BpDNbGAHVXx", + "amount": { + "quantity": 24, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e41", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 8 + } + ] }, { - "join": { - "pool": "pool1tavsxg2s2q83uxsrxcr87yek9axrwxf6yeq4g4rsw5yssx0smy5", - "stake_key_index": "15" - } + "address": "FHnt4NL7yPXwxwa4FHTb4b9voDd8GbbvsGHWmPTSpTkX3X6X5XRa8epVECsJ73Y", + "amount": { + "quantity": 32, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e43", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 7 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 6 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 50 + }, + { + "asset_name": "546f6b656e43", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 17 + }, + { + "asset_name": "546f6b656e43", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 29 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 4 + } + ] }, { - "join": { - "pool": "pool1vfgzwm2wwpxjcxna83dxqrqsy4lxxvplrvprc4jfqq0j672kx8c", - "stake_key_index": "58" - } + "address": "FHnt4NL7yPY6yFf1FDepTYuxPSAbFN3ek5df76Bbd7DsTHjSNQEt1STELseC2Gx", + "amount": { + "quantity": 159, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e43", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 6 + } + ] }, { - "join": { - "pool": "pool1wqu8yet7f4frs7fj8d5zvhqlr5uyjy3ztxqxqcccgau4gkhq974", - "stake_key_index": "84" - } + "address": "FHnt4NL7yPXn1g3ym5A6EQyvx5dxgQQ1S4Tcvqi4B2SrNwN2BCYGuBFvtvyFGxC", + "amount": { + "quantity": 126, + "unit": "lovelace" + }, + "assets": [] + }, + { + "address": "addr_test1yqec3snv9r2fkxg58wacus8gzysdyqght9td4jyjvndejj3976wgde4c93wxr27f7mke2fuu2e5wdhqryjxqam2ylm8skchzjp", + "amount": { + "quantity": 118, + "unit": "lovelace" + }, + "assets": [] + }, + { + "address": "addr_test1yq6338z797lquq9p5djyurnh52ssg7zkqtv5q65hnjf3gdyv2laavvnkhtq8gkttztahxm34rt36dh2sa99m3ugmnfeswx20zh", + "amount": { + "quantity": 89, + "unit": "lovelace" + }, + "assets": [] + }, + { + "address": "FHnt4NL7yPXyN2PZnE6kHc5Kmq5KG3hCeyjvjh6qZTjM42ryG2VBnFho8Ngh6mJ", + "amount": { + "quantity": 35, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e45", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 30 + } + ] + }, + { + "address": "addr_test1vqahrzwmvgg2phm5htekatlg4upq7mdhkfv49ray0z7489cvzu2ek", + "amount": { + "quantity": 3, + "unit": "lovelace" + }, + "assets": [] + }, + { + "address": "FHnt4NL7yPXwbD1k5oET4tEguTiDBrAhdMiALcEX7nV2Ru7EXfBYjSzb3VTU1sA", + "amount": { + "quantity": 109, + "unit": "lovelace" + }, + "assets": [] + }, + { + "address": "FHnt4NL7yPY8qYac1MH6oPsopJABfoigoLtxRUenRgPHPwTZaLUnKKaYzfDnf7j", + "amount": { + "quantity": 195, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e41", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 23 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 17 + }, + { + "asset_name": "546f6b656e42", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 6 + }, + { + "asset_name": "546f6b656e44", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 27 + }, + { + "asset_name": "546f6b656e42", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 30 + }, + { + "asset_name": "546f6b656e43", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 20 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 28 + }, + { + "asset_name": "546f6b656e44", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 19 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 15 + }, + { + "asset_name": "546f6b656e41", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 15 + }, + { + "asset_name": "546f6b656e44", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 8 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 6 + } + ] + }, + { + "address": "addr_test1wq6pzpamynrnre27z5nc4ga5lzlj05k9q5fukvajrc9u8acv9tdhv", + "amount": { + "quantity": 173, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e43", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 1 + } + ] }, + { + "address": "FHnt4NL7yPXhWCECzqunYKxkDfhCesQmAvHbPVjd28TnUAaUQ5NG1FGsUPNrRCv", + "amount": { + "quantity": 204, + "unit": "lovelace" + }, + "assets": [] + } + ], + "withdrawal": "self" + }, + { + "delegations": [ { "quit": { - "stake_key_index": "13374" + "stake_key_index": "10900" } }, { - "join": { - "pool": "pool1qezx67zqwa85u730gdyxzpsyred4xnelpeyy2n2hycw9za2nggz", - "stake_key_index": "35" + "quit": { + "stake_key_index": "1607" } }, { "quit": { - "stake_key_index": "10846" + "stake_key_index": "7546" } }, { "join": { - "pool": "pool1q4fnswsnq9zssgm48e44jszlvcdh5u36r5m4s9gptay5c9fg0vv", - "stake_key_index": "58" + "pool": "pool1vvlnuv26fgjgq9te2f65w9jttcg860fnv9a326e8duwzsj9yyay", + "stake_key_index": "73" } }, { "join": { - "pool": "pool10cxyka2stgvyzdn09jqqvwz20d05kp2p2c2j6ezvqsdry9ncdjv", - "stake_key_index": "87" + "pool": "pool1d3ykxknffe6pcqz5zuthw2jsw97puwcjz5z8k6662sap74jyy22", + "stake_key_index": "26" } }, { - "quit": { - "stake_key_index": "8932" + "join": { + "pool": "pool1ru736sg2dsszujee8cmpy2nlvevhgascwq487hexxf7svya6k6v", + "stake_key_index": "35" } }, { "join": { - "pool": "pool10ulpvfs7vfvsz5gqyum9kkmspdcnvdscgp4nj6z8rpds68cke2n", - "stake_key_index": "90" + "pool": "pool1p5t476gjva09wl69v5rhyanetesk6djdqyf8xw2jv9k5cvfspn0", + "stake_key_index": "59" } }, { "join": { - "pool": "pool1yyv4xv2ky45979zj8qthwa668y3kgxnlp9ckkgck9vanvgqs603", - "stake_key_index": "107" + "pool": "pool1yujyswclyv2pvj2lpex4slfnxdcjvs6t0gv5wurtd329zj4ejl9", + "stake_key_index": "88" } }, { "join": { - "pool": "pool1pjq8jnn92g9zqym7qysrzwrswe2ys86mg45p6mfgduc9s6mj9jh", - "stake_key_index": "15" + "pool": "pool19vhrjd6qgfl4svtvpsuxg7guxarsy0cdxfurczj88gcxuqkdddv", + "stake_key_index": "52" } }, { "quit": { - "stake_key_index": "5970" + "stake_key_index": "5192" } }, { "join": { - "pool": "pool1rus5supeg37ry964d3l8s9gdv369zeenfvgsuqzw93yxq3rh2m5", - "stake_key_index": "16" + "pool": "pool1ggssk6rrpudnvx3lqss4qj2ft3ejsl3lddwxvdn0qc4x7kygnq2", + "stake_key_index": "50" + } + }, + { + "quit": { + "stake_key_index": "2653" + } + }, + { + "quit": { + "stake_key_index": "16200" } }, { "join": { - "pool": "pool1t4mx67eqsqfyjlrw2uajqdsq844hkp3twsjz6acrz3jryslxhhn", - "stake_key_index": "24" + "pool": "pool1zf4z6lskzyj86fzkf5crsfpjrg2rsznav38zsx6eff4kygc7sv6", + "stake_key_index": "6" } }, { "join": { - "pool": "pool19dc4ys2cvgfss8ze9yqz29ze9az85lzry4vj6e2nzv4qumfagge", - "stake_key_index": "42" + "pool": "pool10s08knmqvpf3u0nsxu3scur0z4j8zgn8qvgpynjepyg366rdq76", + "stake_key_index": "114" } }, { "join": { - "pool": "pool199v97d3xyc53kjrew9jr2ae4qszn6n6pv994jgqrd9s9685g0jj", - "stake_key_index": "43" + "pool": "pool12avhvqcr9apskjncv5rs2kzt0y7q5am09ypzkeqztu3yczj6w72", + "stake_key_index": "5" } }, { "quit": { - "stake_key_index": "7739" + "stake_key_index": "12267" + } + }, + { + "join": { + "pool": "pool19f24cvs2rvxz2j3kpgwsgw37derq5jm6ddjkykc6fe5p22xd6pf", + "stake_key_index": "20" } }, { "quit": { - "stake_key_index": "8677" + "stake_key_index": "15374" + } + }, + { + "join": { + "pool": "pool18slnsmt68g58gfgawppyudjcdc6zwhj3f5erchqyx9qhkaxxkzp", + "stake_key_index": "111" } }, { "quit": { - "stake_key_index": "11182" + "stake_key_index": "2393" } }, { "join": { - "pool": "pool1xyejk9ndpy4sue3mf3mxwnehyfz4z5qrddpx6wmz05s858nthlq", - "stake_key_index": "106" + "pool": "pool1zcnqxl3swe9y59mzvy8p2juqx983wvs3dyes53rvqp8ycd8c4c4", + "stake_key_index": "37" + } + }, + { + "quit": { + "stake_key_index": "13537" + } + }, + { + "quit": { + "stake_key_index": "7311" + } + }, + { + "quit": { + "stake_key_index": "9477" } } ], "metadata": { - "20": [ - { - "⩳": -1, - "𡓻􎔱": [] - }, - "󰫪𝥹􁥛" - ] + "19": { + "int": 0 + } }, "mint_burn": [ { - "asset_name": "546f6b656e48", "operation": { "burn": { - "quantity": 28 + "quantity": 26 } }, "policy_script_template": { @@ -1196,14 +1570,18 @@ "cosigner#0", { "active_from": 100 + }, + { + "active_until": 150 } ] } }, { + "asset_name": "546f6b656e59", "operation": { "burn": { - "quantity": 16 + "quantity": 25 } }, "policy_script_template": { @@ -1211,24 +1589,18 @@ "cosigner#0", { "active_from": 100 + }, + { + "active_until": 150 } ] } }, { - "asset_name": "546f6b656e4e", + "asset_name": "546f6b656e43", "operation": { "burn": { - "quantity": 23 - } - }, - "policy_script_template": "cosigner#0" - }, - { - "asset_name": "546f6b656e59", - "operation": { - "mint": { - "quantity": 9 + "quantity": 21 } }, "policy_script_template": { @@ -1241,259 +1613,61 @@ } }, { - "asset_name": "546f6b656e4f", "operation": { "mint": { - "quantity": 1, - "receiving_address": "addr_test1wqlslzndn43pcuqgdf4rgxcpuv22whv0uctssr2y94vmkgsn2k2q7" + "quantity": 5, + "receiving_address": "FHnt4NL7yPXmeCTBMvEBWyKD9EDxKpPzzpPtpqhQxvy7q5FNJZCW4xTyxfnRbYF" } }, - "policy_script_template": "cosigner#0" + "policy_id": "d16a62fe5bb64e0f430fe1db3c4e0f66cc3e37253808e1a9a5633959", + "reference_input": { + "id": "37781e230b514c005e40021f750a2213462ad76b62386c752134055038011833", + "index": 1 + } }, { "operation": { - "burn": { - "quantity": 1 + "mint": { + "quantity": 0, + "receiving_address": "addr_test1qp80u0mtj4zyt0e6tc4zuu5uualc7wxx3s4mdzm75g0jdecv6a8ejld7uvnyum2dfdtn7dhgqzuca67uvd8l3tvfxncqccwhxk" } }, + "policy_id": "983d0dfcb8feadaf45fc1f51f045a0a377c694afdeff3966faa8e86c", "reference_input": { - "id": "7a2e12c490163b451e26f64bb1202c10c21c162a331d3d7777282b74130f317c", - "index": 0 + "id": "130aab19770d0b520e37155ca0295e7f0f7e2a236e45653b3a2df0636a37625b", + "index": 1 } }, { - "asset_name": "546f6b656e41", "operation": { "mint": { - "quantity": 28, - "receiving_address": "addr_test1xq6npny6ulegj5g34xdh5qscfhtupn48gf83vvkh89gmr4eh4xwypdhunwnkx5lz4924tpwqzk7y6ej04hapwy2w9juq4qxmk7" + "quantity": 18, + "receiving_address": "addr_test1wzwt3u9m04rcxpplsgkk3ctas9n2mlh9gdfwl2ydst7kssgrmhjvh" } }, - "policy_script_template": "cosigner#0" + "policy_id": "cfd828738074e99e243de28a9cac3044e3929fced37cf59efd278cbf", + "reference_input": { + "id": "285fe67805607b14164d106d5c8de97325c72a6e7c410e180e738b113914734a", + "index": 1 + } }, { + "asset_name": "546f6b656e50", "operation": { - "mint": { - "quantity": 27, - "receiving_address": "FHnt4NL7yPYDnqSWnMiy5LnAkyNdttjDM4ie536ZD6BmkqVfz5ptZ9jrPvbaxQC" + "burn": { + "quantity": 14 } }, + "policy_id": "badfb34b591c19ee376c4301dbeeecc9fca975920d18c0d12adcf1d9", "reference_input": { - "id": "2a635abf447f66443c8009366f452576341b2b2026587e71514e254b3c080263", - "index": 0 + "id": "b82b462355b30d6314e836ac2f315178497f217e1f3603714c74455532763660", + "index": 1 } - } - ], - "payments": [ - { - "address": "addr_test1vplgut5gjaw7me655xymazt5cysn8whw5cduwqy4gr2skrs5sg46c", - "amount": { - "quantity": 121, - "unit": "lovelace" - }, - "assets": [] }, - { - "address": "FHnt4NL7yPXqdAzT4Bsj5RoVKncyKZFRmyYK1mgUk1BvPLxJdntKreb1LXYQGWV", - "amount": { - "quantity": 99, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 22 - } - ] - }, - { - "address": "FHnt4NL7yPY2vTi3afzM3CkxWhPhCSDxWGixyaQHhCeiTMdse6hkPewPDggN7DN", - "amount": { - "quantity": 130, - "unit": "lovelace" - }, - "assets": [] - } - ], - "withdrawal": "self" - }, - { - "delegations": [ - { - "quit": { - "stake_key_index": "5935" - } - }, - { - "quit": { - "stake_key_index": "882" - } - }, - { - "join": { - "pool": "pool1q3m95t60xfrkj4mcv9h4glzvpuf565fcw3z8cujxpsqnjn23wl4", - "stake_key_index": "37" - } - }, - { - "join": { - "pool": "pool1r9vzvlyqdq8gqy3fgqr3xkpqzd4pclr5tyls6krjrdujc0y2rtz", - "stake_key_index": "42" - } - }, - { - "join": { - "pool": "pool105zrgtpud9kkw820vqzrquqqtphkkrpvp49zkksvxszz6nlrce5", - "stake_key_index": "9" - } - }, - { - "quit": { - "stake_key_index": "12481" - } - }, - { - "quit": { - "stake_key_index": "5290" - } - }, - { - "quit": { - "stake_key_index": "10237" - } - }, - { - "join": { - "pool": "pool1wskswvmsyvcs7wfjx4g9kgge9sfgqts7pyjxs6nqygsqv2478s2", - "stake_key_index": "51" - } - }, - { - "join": { - "pool": "pool1xfvsyzstp4exqdzyzeu46ys7xs39jarpv3w4yhpgtagkxq9vd07", - "stake_key_index": "103" - } - }, - { - "join": { - "pool": "pool1t409g6c6rs28cstj9gynye368u09cnc29cqr27ma0p55yxd2ca3", - "stake_key_index": "20" - } - }, - { - "join": { - "pool": "pool1w3jj2ymwq9n8jtnqffsrsx6ydev92apdyg3pyhmtr36kvncfnmm", - "stake_key_index": "13" - } - }, - { - "join": { - "pool": "pool184lszkncvsyx66g8vf4nwtqetyjhja2px9jz772cx5jk26zg8kv", - "stake_key_index": "76" - } - }, - { - "quit": { - "stake_key_index": "4090" - } - }, - { - "quit": { - "stake_key_index": "4071" - } - }, - { - "join": { - "pool": "pool1pfjn52z72vqr2qjh2fwjjgq72ueqz2rxps63wfprqppp63clfhv", - "stake_key_index": "0" - } - }, - { - "quit": { - "stake_key_index": "5664" - } - }, - { - "join": { - "pool": "pool1d3vrxdsypuvjjcqvdp9ska60gfr9sgmuydqrgapv2a6rufxjxns", - "stake_key_index": "9" - } - }, - { - "quit": { - "stake_key_index": "2709" - } - }, - { - "join": { - "pool": "pool10uuxql2eq4gxzlzzdywsv320w9txuxrt0ynkkxta0fy9q7xuru7", - "stake_key_index": "55" - } - }, - { - "quit": { - "stake_key_index": "12571" - } - } - ], - "metadata": { - "25": { - "int": 0 - } - }, - "mint_burn": [ { "operation": { "burn": { - "quantity": 7 - } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } - }, - { - "operation": { - "mint": { - "quantity": 4, - "receiving_address": "addr_test1xpf3g36y8xvwrgj4dn9zcueksys20e2ke5wcgnm4jpsk6wqkndv0k77q44469nppj3ek597hfhr420calhtrq5gl64pqh42lhz" - } - }, - "policy_script_template": "cosigner#0" - }, - { - "asset_name": "546f6b656e44", - "operation": { - "mint": { - "quantity": 5, - "receiving_address": "FHnt4NL7yPXqJBoz596zXdTnC6U7o8MxQQqavfjySZq8yeiYSGXpKJJXqP6pb1p" - } - }, - "policy_script_template": "cosigner#0" - }, - { - "asset_name": "546f6b656e4a", - "operation": { - "mint": { - "quantity": 27 - } - }, - "reference_input": { - "id": "5f2e283d59133c53a8084b44db245d368d417157074f44600f29476705541b7b", - "index": 0 - } - }, - { - "operation": { - "mint": { - "quantity": 5, - "receiving_address": "FHnt4NL7yPY3cSCJStGqLV5yFrKXy6vLYSK51sR7KinxXGb757BxMUe3ktXzZsC" + "quantity": 9 } }, "policy_script_template": { @@ -1506,23 +1680,10 @@ } }, { - "asset_name": "546f6b656e56", + "asset_name": "546f6b656e46", "operation": { "burn": { - "quantity": 25 - } - }, - "reference_input": { - "id": "28705c481207d43d422a5b2e1b2b2022b32e1b6f6a2723336321377ba07a4a30", - "index": 1 - } - }, - { - "asset_name": "546f6b656e50", - "operation": { - "mint": { - "quantity": 10, - "receiving_address": "FHnt4NL7yPXhEmFAPNxCqmwFN8t43XMZPQXDnwAHRN8wrvCg5xD2XnetxpF8e3L" + "quantity": 12 } }, "policy_script_template": { @@ -1538,124 +1699,130 @@ } }, { - "asset_name": "546f6b656e41", + "asset_name": "546f6b656e5a", "operation": { "burn": { - "quantity": 13 + "quantity": 16 } }, + "policy_id": "96ad516cdaa304ed659b06a8ac41b6113fe0c0444ca807390ce5b1c9", "reference_input": { - "id": "0276ca5c3f5b6a853859481f69730b15611f193a64389c614352302a5a0e0add", + "id": "446801e50210060a1d0d466c3721473f3e1e10eb5b01320e6f773ec5443a170f", "index": 0 } }, { "operation": { - "mint": { - "quantity": 13, - "receiving_address": "addr_test1qrrud7z2ddekyr7yxrfyye8llhef6ncxu4y5e82zq3zd02nxjh0pmw9prj29khshzwdv6x08hefuu4xp2ct7kgwplk0sznuftp" + "burn": { + "quantity": 6 } }, + "policy_id": "b7735657b3a161ec2ded0c514e8b730e11f6074ef7225c1ea2def0d2", "reference_input": { - "id": "47741e1a410a775a0f6a887262667d1c6c3d89547b441c232a494b01510e792d", - "index": 1 + "id": "6d4a5a4b68696d176d709d050d491f1c4488ced7415bff6a6b0f38d31d191319", + "index": 0 } }, { "operation": { "burn": { - "quantity": 6 + "quantity": 2 } }, + "policy_id": "1667b06c821d5f9c30a3d5d9921ca1f2bc3ba84eedd2d0d763b2ebb1", "reference_input": { - "id": "1077584d560ed7146549331b3c4880f443427e7c7448d12b422b183b1d58431f", - "index": 1 + "id": "6d220a45e7535d0f6f30bb560a58c4096d2e3732621f5f3c46700d3a8e5f0d11", + "index": 0 } }, { "operation": { "burn": { - "quantity": 19 + "quantity": 14 } }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] + "policy_id": "701d069e24f951109f8d2261cdea344ee2ac043d0687c712597255e2", + "reference_input": { + "id": "b33f4317322b741b172c3d3e153e21802976746d24e135335e2435101a250d68", + "index": 0 } }, { - "asset_name": "546f6b656e53", "operation": { - "mint": { - "quantity": 15, - "receiving_address": "addr_test1vptq5c2s3q6y9wt8474k5fxarrw9wanxuphzq6k3l8pfy3cdfk4p2" + "burn": { + "quantity": 21 } }, + "policy_id": "5c0fbc96422d00995c088f57bcc08039fbe5684beae6e1e3dc0bee9a", "reference_input": { - "id": "5f3678601428594e3a1bce4c7563a062076e037c47206d47054779e47c44c613", - "index": 1 + "id": "417f225c253d9762187d042465764c594d6630632124444b5e2e0e0264684b5d", + "index": 0 } }, { + "asset_name": "546f6b656e47", "operation": { "burn": { - "quantity": 26 + "quantity": 22 } }, + "policy_id": "17168d6811fd2a056bc3bf3ba4e81a62b2c38382f414d65dc50f9457", "reference_input": { - "id": "764a3259d8e232142a5b5948413c72173035d86e454a0f371a712f066fd9692f", - "index": 0 + "id": "5b5f7295202f69140c7d346f1c373216b7281b1138fafb0ba0262c11286e5a42", + "index": 1 } }, { "operation": { "mint": { - "quantity": 9 + "quantity": 6, + "receiving_address": "FHnt4NL7yPXw2SPPvhg8hj4jdLieTRycJ9khFdUz856qiyfYG63VjYyUMo2bBRH" } }, "policy_script_template": "cosigner#0" }, { - "asset_name": "546f6b656e47", + "asset_name": "546f6b656e44", "operation": { - "burn": { - "quantity": 3 + "mint": { + "quantity": 25, + "receiving_address": "addr_test1xryvavqm4gkzgylmlee7nx66lyq24g5es7qw86zvjg9z9j5uu2km3cd2sfsrkrkuu8gfgnkp92rvqcz6r7j2gqupllxssgsp70" } }, - "reference_input": { - "id": "18512d623a361370746873797f7aaf222ada1b5f241bc2131de257db26da1705", - "index": 1 + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + } + ] } }, { "operation": { - "mint": { - "quantity": 28, - "receiving_address": "addr_test1zptk0sdkl9shka4k6nchc3vv7asaxewrkrfdwt2myt5kmgh8yvnmznf0te8dxcvqr7g55szfdrm9yjg7zpqjmy44hrjq0fd35h" + "burn": { + "quantity": 13 } }, "policy_script_template": "cosigner#0" }, { + "asset_name": "546f6b656e58", "operation": { - "burn": { - "quantity": 8 + "mint": { + "quantity": 21 } }, + "policy_id": "638cc51916d492158135a169cb813fda64b049f406f3cd0152ad41f0", "reference_input": { - "id": "483aba616dde0f6914667470bf351cc69a57c83937235239640f3e014780071f", + "id": "3a78471f35183b616933009b1e2c4c7a246a713f7c3f3c1d3d8f4310656a4009", "index": 0 } }, { - "asset_name": "546f6b656e55", "operation": { "burn": { - "quantity": 14 + "quantity": 28 } }, "policy_script_template": { @@ -1666,490 +1833,291 @@ } ] } - } - ], - "payments": [ + }, { - "address": "addr_test1wr2yzgn42ws0r2t9lmnavzs0wf9ndrw3hhduyzrnplxwhncaya5f8", - "amount": { - "quantity": 204, - "unit": "lovelace" + "operation": { + "mint": { + "quantity": 28, + "receiving_address": "addr_test1yp63w2pef2ps7hczjv0yv7ztvkcwfx73zdjjs63j9mu0l3hv05aevrknz6mx0per4e07rp3vhl3z683mw4mesgkypu3qpqpxju" + } }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 25 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 8 - } - ] - }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } + } + ], + "payments": [ { - "address": "FHnt4NL7yPY9DbEZCFVo9hbKJW5ELzaMabR8Nrh4XQH1yA318dYEahCZwqaruuH", + "address": "addr_test1xqhfhzad64sg4386hraegqtp5a7n60ltzdfyu9drtrk07eay232dmw8s05kflkrhtlq8f752erareqgw34ejfjygmdxqsws3x8", "amount": { - "quantity": 91, + "quantity": 31, "unit": "lovelace" }, "assets": [ { "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 10 - } - ] - }, - { - "address": "addr_test1xp482kjrv6jnurysxhys4gkfejdgm7n7s6mvkp08nx5euadxger5hr65xynp2p4kcfeaxp7826dyadkfddpd6j3f2g9qe49nh8", - "amount": { - "quantity": 120, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e41", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 28 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 17 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 26 - }, - { - "asset_name": "546f6b656e45", "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 70 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 11 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 28 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 28 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 21 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 12 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 26 + "quantity": 14 }, - { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 23 - } - ] - }, - { - "address": "addr_test1xrfvndj063jtn2t5v38a8rve8cxfh0n6ppzf7xvqnlgn4vl5trlz728vng408a2psmyw4t4jn7jxpag5tgpksvq8vhhqlvl4fj", - "amount": { - "quantity": 151, - "unit": "lovelace" - }, - "assets": [ { "asset_name": "546f6b656e41", "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 7 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 29 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 2 + "quantity": 5 }, { "asset_name": "546f6b656e41", "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 7 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 16 + "quantity": 12 }, { "asset_name": "546f6b656e44", "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 22 + "quantity": 25 }, { "asset_name": "546f6b656e42", "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 23 + "quantity": 25 }, { - "asset_name": "546f6b656e43", + "asset_name": "546f6b656e45", "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 21 + "quantity": 29 }, { - "asset_name": "546f6b656e44", + "asset_name": "546f6b656e41", "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 15 + "quantity": 20 } ] + } + ], + "withdrawal": "self" + }, + { + "delegations": [ + { + "quit": { + "stake_key_index": "10809" + } }, { - "address": "addr_test1wq9z4tcrj4xcqa072pm80kuwt69aw4avf9qjquxdjfrj68chnw6zn", - "amount": { - "quantity": 95, - "unit": "lovelace" - }, - "assets": [] + "join": { + "pool": "pool1feahz6ejpeqx6e20tsg4wvedw4dhjx2jgfgngy2kw5dxq42xkpr", + "stake_key_index": "38" + } }, { - "address": "FHnt4NL7yPYJHA65dEcfwsBoCb7T9kLkdYMAG7eGPop6Y26EDmBkQBk6ST7VnVs", - "amount": { - "quantity": 170, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 10 - } - ] + "join": { + "pool": "pool1qqkzx2za89x9w42epadyu5qlychqsank85l468qczqv3qmyps7f", + "stake_key_index": "77" + } }, { - "address": "addr_test1vzsh5ggaz5dhtuueetnhg63l8mqkzkq35dztq9gmltns5as7udeer", - "amount": { - "quantity": 249, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 44 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 23 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 9 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 7 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 1 - } - ] + "join": { + "pool": "pool1x5sxqggryvhquu6py4a8stghqeg9zre2gaqhcqt2fu6hcad6wvn", + "stake_key_index": "97" + } }, { - "address": "addr_test1zz5daal9ft773aemswm7xkxgs92lnxvaww5s2m8f57tglh5yfl4udmssp8al05wm8c88ewa0gky8a4hht5c5sewuqrqsdyunve", - "amount": { - "quantity": 23, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 25 - } - ] + "join": { + "pool": "pool1fcxs5yck23tpv8s0tpyhslekqdjnv6srgqr5jme3ds7pkczgz7l", + "stake_key_index": "2" + } }, { - "address": "FHnt4NL7yPXz3YvQS8GLeu63XEquAZ1B2eUnPvKouvioMs8XqsJ3PvHM6Ck4Qti", - "amount": { - "quantity": 190, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e45", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 9 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 20 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 12 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 51 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 14 - } - ] + "join": { + "pool": "pool10v75w0je8ytj5pfa9uc4gssffg8hk52rguwsswrzwgxpuvmdr5k", + "stake_key_index": "104" + } }, { - "address": "addr_test1zpfdc02rkmfyvh5kzzwwwk4kr2l9a8qa3g7feehl3ga022ytt7r4d67pv8yacd7ru2ywla0mdaqx9s94ag4ewl7usplqhyrxlg", - "amount": { - "quantity": 203, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 16 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 5 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 20 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 7 - } - ] + "quit": { + "stake_key_index": "5126" + } }, { - "address": "FHnt4NL7yPY9z5HAXgozmvX6FwycGqs4EvwtFDifqL7b6VCXF2AkjwnuFufHYdN", - "amount": { - "quantity": 210, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 18 - } - ] - }, - { - "address": "FHnt4NL7yPY7yVuXsFKPgWqheFEgdy9pxF5Knkrs3Mr1uagP8Tv3gP2cY2JvAgK", - "amount": { - "quantity": 24, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e41", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 10 - } - ] - } - ], - "withdrawal": "self" - }, - { - "delegations": [ - { - "join": { - "pool": "pool19es87w6nqafpjkjeyyljk5p39axx24eu8d8kv6nrdecqv4wl3xz", - "stake_key_index": "1" + "quit": { + "stake_key_index": "10998" } }, { - "join": { - "pool": "pool1yulxc3txwps3u8t4xv9y70pugs7h78ffrf7sv7zcwytgqu4agha", - "stake_key_index": "92" + "quit": { + "stake_key_index": "5506" } }, { - "join": { - "pool": "pool1pyxyghm0ggyzj2zu8sq4j2qqq4lgqhqvfqwq7qfprqj8yscw98v", - "stake_key_index": "126" + "quit": { + "stake_key_index": "15724" } }, { - "join": { - "pool": "pool1fg38z36az3q9y82lwcl5wrgn2ssqggem83m468sqfc3s54d8et9", - "stake_key_index": "106" + "quit": { + "stake_key_index": "4656" } }, { - "join": { - "pool": "pool1yfuqvzqyddr9q6n4t3tzsecgwqgycde4rvd8wnmj04hx2k3fqwa", - "stake_key_index": "8" + "quit": { + "stake_key_index": "14891" } }, { "join": { - "pool": "pool1g40sqzszydkqggfnf9w4khq9psy5u3stg4vp2grr2g0zu9zfyv2", - "stake_key_index": "48" + "pool": "pool1d9mp2t22f5zkg9zpd9w4cq6y8qg87664y364utjcd4vyqt08jds", + "stake_key_index": "57" } }, { "quit": { - "stake_key_index": "15130" + "stake_key_index": "3797" } }, { "join": { - "pool": "pool1g3wy7rsdt409gl69q33qumtpdvh87ysn99z8xvzhfqwz6ujwmwl", - "stake_key_index": "75" - } - }, - { - "quit": { - "stake_key_index": "3812" + "pool": "pool1yssq2m34fdr9zxnc0s0rse36g36n6lgnpq3sc329sp4psd8g937", + "stake_key_index": "5" } }, { "join": { - "pool": "pool1x5c3jdznrpenu7r5pem4q3r9peqkwxpwz9f9jjndwpzq25d0gd8", - "stake_key_index": "123" + "pool": "pool10gdsv6gx99795tzup9j3626aqva5jfcvgyq8g7fppv59sm0rtqu", + "stake_key_index": "111" } }, { "quit": { - "stake_key_index": "16062" + "stake_key_index": "11477" } }, { "quit": { - "stake_key_index": "6212" + "stake_key_index": "6970" } }, { - "join": { - "pool": "pool18pwp6lqedp44wvnh2yfxump3q4y8ynsz24f3kd6yye9hv5ztqjy", - "stake_key_index": "86" + "quit": { + "stake_key_index": "12546" } }, { - "join": { - "pool": "pool10prqzszt2emh6vcddp3xy2fxzger7jtxfsw3ym6lxu3xym6qfkr", - "stake_key_index": "54" + "quit": { + "stake_key_index": "10848" } }, { "quit": { - "stake_key_index": "3794" + "stake_key_index": "2545" } }, { "join": { - "pool": "pool1qp34xhjwx4t5y43nfsuk6ftxw9cycqeugqky5psavaarj3th0ww", - "stake_key_index": "55" + "pool": "pool1zsqks6tcwath5wegrvscqxfap455gpnxd3kj7gc5yc44qr6fwz4", + "stake_key_index": "67" } }, { "quit": { - "stake_key_index": "16056" + "stake_key_index": "10786" } }, { "join": { - "pool": "pool1wcu4wzzdqqljwymx8q6nchpr9sq5snzs29tr5d2k0sk9x0uj2pt", - "stake_key_index": "39" + "pool": "pool1t4kcq32jqg4ksnmgqd69s2rkqpkrzf2u0prxc2n695ghxda2slw", + "stake_key_index": "16" } }, { "quit": { - "stake_key_index": "463" + "stake_key_index": "4633" } }, { "quit": { - "stake_key_index": "3374" + "stake_key_index": "5658" + } + }, + { + "join": { + "pool": "pool193g8gm6f2edsuuc48dy9vj2j05sry3n327qyq9mht9eys5qnwt2", + "stake_key_index": "109" } }, { "join": { - "pool": "pool10awqwmqvt5znqdned5c3zzftpdypeqrm049q2s3z9ehywgrwfmu", - "stake_key_index": "21" + "pool": "pool1dur9ucgrfuvk6332qvk4q0stygenzntl94vhs06ap3vr7yxx6dj", + "stake_key_index": "45" } }, { "join": { - "pool": "pool1x4njsn2yge7pclf7y53y58szpulp6qprfgtzzer4wsn8j95qawm", - "stake_key_index": "33" + "pool": "pool1f4h4kx2g0yljkt699e0y6fzhsprhy83vyf2ng620fu885nt4jq2", + "stake_key_index": "66" } } ], "encoding": "base64", + "metadata": { + "7": { + "map": [ + { + "k": { + "string": "顕𠽠" + }, + "v": { + "list": [ + { + "string": "􉋡𨢥" + }, + { + "int": -2 + } + ] + } + }, + { + "k": { + "string": "𤠔󳜲􁯝" + }, + "v": { + "string": "𡬮摴𪨽" + } + } + ] + } + }, "mint_burn": [ { - "asset_name": "546f6b656e55", + "asset_name": "546f6b656e58", "operation": { "mint": { - "quantity": 1, - "receiving_address": "FHnt4NL7yPYALDnDcch8Mdt4htD28MtfDJBNLbUZhhHwnRZB8cFnpkf5JhUGxr4" + "quantity": 26 } }, - "reference_input": { - "id": "6c38c83a6c67684c6a065eff6b4a171a60206939750c3e847443365706215468", - "index": 0 + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] } }, - { - "asset_name": "546f6b656e55", - "operation": { - "burn": { - "quantity": 22 - } - }, - "policy_script_template": "cosigner#0" - }, { "operation": { "mint": { - "quantity": 19 - } - }, - "reference_input": { - "id": "d779580f0b7c069f5d02144bfc496fa7040b782948ca2475543f445044953179", - "index": 1 - } - }, - { - "operation": { - "burn": { - "quantity": 29 + "quantity": 14, + "receiving_address": "addr_test1wrs2w9p3nqfv8amnhgzwchtt8l7dt2kc2qrgqkcy0vyz2sg3p9azg" } }, "policy_script_template": { @@ -2161,33 +2129,11 @@ ] } }, - { - "operation": { - "burn": { - "quantity": 9 - } - }, - "reference_input": { - "id": "13b10357014e0914525b5f0c74190d1ad3be30f4be4edf47cc7b343536215875", - "index": 0 - } - }, - { - "operation": { - "burn": { - "quantity": 10 - } - }, - "reference_input": { - "id": "2d437a2948a212128b163621181c17b0463a425881022d7e5c409d0a705b4823", - "index": 0 - } - }, { "operation": { "mint": { "quantity": 17, - "receiving_address": "FHnt4NL7yPXszQ2yQuhWRKyvTFFLc3woZfL8zYdDLtvabDeXtpumPaYKfEgDgd5" + "receiving_address": "addr_test1ypruxpnwevqukpv960k9ttqgffesjpdmyekxfwtv4smd8h5amugcpwket4jjazrm33fspahlrmvzr6l4r9z9a3twu4dskzgywz" } }, "policy_script_template": { @@ -2205,91 +2151,96 @@ { "operation": { "burn": { - "quantity": 4 + "quantity": 15 } }, + "policy_id": "712c2759eb6e638d1c6a80222d4bc28a9353fdd197a588a91ee3d3ba", "reference_input": { - "id": "7a5b2459402c2385521c2d393666d1c35e65720e204852271a6d7d59331b054f", + "id": "fb7b2c2b12786d7d927429523b11391644176339366559e7020e444cd264122c", "index": 0 } }, { - "asset_name": "546f6b656e4a", "operation": { - "burn": { - "quantity": 22 + "mint": { + "quantity": 15, + "receiving_address": "FHnt4NL7yPXyiYXTdhMfJwgGe9Vn4h7us9JWHRVvnuLic3vCAxeyMhdCpVZBWPv" } }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } + "policy_script_template": "cosigner#0" }, { "operation": { "burn": { - "quantity": 8 + "quantity": 9 } }, + "policy_id": "83884ec61fe3a923e340d7df10cbdaffe4eed364fc5dba8e8745a33c", "reference_input": { - "id": "c64804214348399ec45a5f00335a3b11b633129a69385222646a593059af4aed", + "id": "683e97490163553932b5271f2d74075e644d4a508a1104360d0211ca5722f716", "index": 0 } }, { "operation": { - "burn": { - "quantity": 12 + "mint": { + "quantity": 19 } }, + "policy_id": "a4695bc281a685262cc97ae18310f3ca02ac890716fd8ad8d2182254", "reference_input": { - "id": "0a5d0477271e2c430b0245564a09c9a1587871376725786a16662f0440657979", + "id": "2b1c871221125e09dd214839425c3b0613491d9b3235832154c93208167b3f8a", "index": 0 } }, { + "asset_name": "546f6b656e5a", "operation": { - "burn": { - "quantity": 13 + "mint": { + "quantity": 28, + "receiving_address": "addr_test1zqrvhv7fkkgzwhpnkdvk2hcxc4eg28kqgvkyx6gxpedar4jrht0xsn7dqcjq7q685gfll3zc04dd9evtdt6efu3959gqkyymrq" } }, + "policy_id": "d7460ed544294a066fa9a265ab9eb66d83a17b5d229f5570cd5759d3", "reference_input": { - "id": "1937972de617091b6e206074461f7e0f3045ff027f7f93185268ab2a524a489b", - "index": 0 + "id": "1f140c298f650529607c6a3c21321b4c5967557c6a54224a7b2b941a5cbc5c22", + "index": 1 } }, { - "asset_name": "546f6b656e43", + "asset_name": "546f6b656e4f", + "operation": { + "burn": { + "quantity": 21 + } + }, + "policy_script_template": "cosigner#0" + }, + { "operation": { "mint": { - "quantity": 14, - "receiving_address": "FHnt4NL7yPY5Wp7qtoL8XbJpnKJzV2FQmyD9c1WK9PJ6d9rvHyH2sQK6HjhajCw" + "quantity": 9 } }, + "policy_id": "5f67f8682a26e1582d16c615eeea6a2eb6e0eab4ccac4d5985e65278", "reference_input": { - "id": "68214bb2080a650207234440797862191c6e7378770961370e7740212ebe3452", - "index": 0 + "id": "f3853e7b882a27d8a1f2291628145c4acc003491a0f8131c351e5c297918487b", + "index": 1 } }, { + "asset_name": "546f6b656e5a", "operation": { "burn": { - "quantity": 21 + "quantity": 9 } }, - "reference_input": { - "id": "8f060914100c11376b4b12371beb3c026342054a680746535e255b417d0c5d51", - "index": 0 - } + "policy_script_template": "cosigner#0" }, { "operation": { "burn": { - "quantity": 22 + "quantity": 6 } }, "policy_script_template": { @@ -2303,2808 +2254,1361 @@ }, { "operation": { - "burn": { - "quantity": 26 + "mint": { + "quantity": 24, + "receiving_address": "FHnt4NL7yPXkHjRqSZh9Sdv2pSQpwEsE6qZ22dKKDPEqMhhgW8m9GMuPv4nuJKh" } }, "policy_script_template": "cosigner#0" }, { - "asset_name": "546f6b656e44", + "asset_name": "546f6b656e42", "operation": { "mint": { - "quantity": 16 + "quantity": 26, + "receiving_address": "addr_test1qq6gf39k2hf6hxg5s56p3yzmyusn97gk7ljsclywls3jxyda68uhwg7datqkfx8sj7hdj96jywx544zzgv6w70k3cegs88x66k" } }, + "policy_id": "e4170e5522780cef29915e78bdf6b09434aaf32d7edcdd0777d3d517", "reference_input": { - "id": "346b9c610f303d43336e4c1a657e4e28665c312d0b715f0112dadb323cb73636", + "id": "5260184c4f50c93e570f40333b5a47cc023702397269a95d4667710cd1162a92", "index": 0 } - } - ], - "payments": [ + }, { - "address": "FHnt4NL7yPXnJK5WibcYQyZtX65eToPNAqACYsd5DVWXMXnRJYGjqMF5JtLs5Z3", - "amount": { - "quantity": 71, - "unit": "lovelace" + "operation": { + "mint": { + "quantity": 29, + "receiving_address": "FHnt4NL7yPXyXpB2AU2Mwud3Qyfdv1tzeqxGd2hvWJCtdJqW5yNwmzGJMUQCZ1c" + } }, - "assets": [ - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 11 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 59 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 13 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 9 + "policy_script_template": "cosigner#0" + }, + { + "asset_name": "546f6b656e45", + "operation": { + "burn": { + "quantity": 26 } - ] + }, + "policy_script_template": "cosigner#0" }, { - "address": "addr_test1yrthfny85ph78syxzmx6a53ukp28al0aaejgkmrv56xaa6mzaarxgsnrl0pu9fzp3vgxtxsqkz5uz86tkra4vgct04jqhjs442", - "amount": { - "quantity": 125, - "unit": "lovelace" + "operation": { + "burn": { + "quantity": 13 + } }, - "assets": [] + "policy_script_template": "cosigner#0" }, { - "address": "addr_test1wq6npny6ulegj5g34xdh5qscfhtupn48gf83vvkh89gmr4cl3n4xr", - "amount": { - "quantity": 104, - "unit": "lovelace" + "asset_name": "546f6b656e49", + "operation": { + "burn": { + "quantity": 2 + } }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 10 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 14 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 20 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 15 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 16 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 3 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 7 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 29 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 12 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 17 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 27 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 13 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 7 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 28 - } - ] - }, - { - "address": "FHnt4NL7yPXqoj3cCn7PJE5CBfuahQCNDS7ViAsBR8WWd1ADci3JV42CvjFRRGu", - "amount": { - "quantity": 194, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 20 - } - ] - }, - { - "address": "addr_test1zpfdc02rkmfyvh5kzzwwwk4kr2l9a8qa3g7feehl3ga022xs3e5pj28mz9hglqqsjznnunltzu23a3t7qw2rjqf3r7ds8v3uq8", - "amount": { - "quantity": 226, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 27 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 1 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 14 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 9 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 16 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 29 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 14 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 16 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 12 - } - ] - }, - { - "address": "addr_test1xqtg4tmkrddxdx84thxsdqvdnpmfp9s7d87h3ac0szwvrp2jms758dkjge0fvyyuuadtvx47t6wpmz3unnn0lz36755qxql3yv", - "amount": { - "quantity": 156, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "addr_test1ypv97ww3yhw5akq8wpj885mfl8p9cjlvsx5r9grffqh85qaxger5hr65xynp2p4kcfeaxp7826dyadkfddpd6j3f2g9q344076", - "amount": { - "quantity": 60, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 29 - } - ] - }, - { - "address": "FHnt4NL7yPXt3K14nP8RBVEXx459bu5ShAr6E1Qf1ptyyT5DsRuTEvvTAcw9GRg", - "amount": { - "quantity": 62, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "addr_test1wq6npny6ulegj5g34xdh5qscfhtupn48gf83vvkh89gmr4cl3n4xr", - "amount": { - "quantity": 136, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e42", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 22 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 15 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 22 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 20 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 21 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 24 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 7 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 16 - } - ] - }, - { - "address": "addr_test1vzxzcuyzjzs6uvusg0adjpda02qj7uce8e7lprqmt8ywa7q3vgcnx", - "amount": { - "quantity": 122, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 3 - } - ] - }, - { - "address": "FHnt4NL7yPXsvX8ZqEbNAFM5EisHZoFDmQUi3GGSbTbCEHLrtsEpJsqyU38Z1Bk", - "amount": { - "quantity": 177, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e41", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 13 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 5 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 26 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 11 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 19 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 19 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 36 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 25 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 18 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 3 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 17 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 25 - } - ] - } - ], - "withdrawal": "self" - }, - { - "delegations": [ - { - "quit": { - "stake_key_index": "6745" - } - }, - { - "quit": { - "stake_key_index": "4300" - } - }, - { - "quit": { - "stake_key_index": "13058" - } - } - ], - "encoding": "base16", - "metadata": { - "5": { - "map": [ - { - "k": { - "string": "􉶏毢" - }, - "v": { - "list": [ - { - "string": "䉖󷎌" - } - ] - } - } - ] - } - }, - "mint_burn": [ - { - "asset_name": "546f6b656e56", - "operation": { - "mint": { - "quantity": 14, - "receiving_address": "addr_test1zpqwwejh5taq5d4j3vs8uhsehtzuffusjv8mrezxx2dnpauhndjgd9ftwq4mlrzsphvsyy3l7733d09m7k5n8v8mzqhq9jhz97" - } - }, - "reference_input": { - "id": "87dc2fa6aa52107f532462392f1c4e9e1b190a490ded5c6e6bf60b7727035d5a", - "index": 1 - } - }, - { - "asset_name": "546f6b656e57", - "operation": { - "mint": { - "quantity": 7, - "receiving_address": "addr_test1qp3qxef2gafflfudvz44jfyfdyczcl08z60fu8m432a4gszmr2eyhr4ya290kj67qwrtrhlhk2w875hz4xvt2xek0gus9xcx78" - } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } - } - ], - "payments": [ - { - "address": "FHnt4NL7yPY1kM4UWnoGnYtgohkFV6sQTuMhVG69mA6s2iY6ELVgPzf2g67cXus", - "amount": { - "quantity": 0, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 21 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 2 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 6 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 12 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 1 - } - ] - }, - { - "address": "FHnt4NL7yPXkSeFwwYTwk1FU73q4AENBL9EVe2dCihyN4PTg3nMZ26gDWAMw1Qi", - "amount": { - "quantity": 159, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e41", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 16 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 10 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 11 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 24 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 64 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 9 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 1 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 6 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 9 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 10 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 23 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 26 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 8 - } - ] - }, - { - "address": "FHnt4NL7yPYJyNw3xBhsXte6X48iBZYkqGFhwi1kHutsjEXDrhEMswGWYayZEnw", - "amount": { - "quantity": 192, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "FHnt4NL7yPXtivc7ppo19oEJTqdzkFriMUb1tKErU5NvxZWRN465uTjqMTZ4rVi", - "amount": { - "quantity": 133, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e41", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 15 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 10 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 1 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 13 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 30 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 25 - } - ] - }, - { - "address": "addr_test1xpfdc02rkmfyvh5kzzwwwk4kr2l9a8qa3g7feehl3ga0228zp9gwpfw4843hxvenn40nl2tpu4spgpn4pkxunrqs9wvs4mh4yn", - "amount": { - "quantity": 247, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 24 - } - ] - }, - { - "address": "FHnt4NL7yPYFoGMKr3HcaqwLaJgpHHFcoRDoEdNWepbWp7LGCeXVv3nXJRCDX6A", - "amount": { - "quantity": 255, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 41 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 35 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 15 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 23 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 4 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 6 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 11 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 2 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 71 - } - ] - }, - { - "address": "FHnt4NL7yPXjTt45iWYiK5KuTKbjTxAEmXtnV847c7ZsL2VazB7UVcwvoESsWSD", - "amount": { - "quantity": 220, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 2 - } - ] - }, - { - "address": "FHnt4NL7yPYBZCvMMmuz1riFUFjt3S5SeqXrSDVAbZrE455TXJGhFd8aKGg6d1J", - "amount": { - "quantity": 221, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "FHnt4NL7yPYFPhzqSveXAcZoYdrVoixDAB1UJuLY9i7nhrMyZn1eki5ERSLbxvA", - "amount": { - "quantity": 46, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e41", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 13 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 1 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 17 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 27 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 4 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 18 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 16 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 15 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 1 - } - ] - }, - { - "address": "addr_test1xz858v6vcw35ha9qwrnaa48ncdp03wu9e0vcc3xuagh934p4xrxf4elj39g3r2vm0gppsnwhcr82wsj0zcedww23k8tse0r0tg", - "amount": { - "quantity": 64, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e41", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 14 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 16 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 10 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 12 - } - ] - }, - { - "address": "addr_test1qr7lnxea9u3ctphmudj7qul2pspkgnmdt2ev26x456sl7jg88tg0p9nwvpjr0tuavn9324sjz0kgvmp8tzswcq4lgfrsfdn6hd", - "amount": { - "quantity": 114, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 13 - } - ] - }, - { - "address": "addr_test1zqfz24cdru9fs7p2hk0agf0860h3rqj5ce7hsyafl3ulsjcqsrduxvf7fdnsx7hkgeuwstfuskm0w4y25q9y735n9cuscaguwq", - "amount": { - "quantity": 87, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 9 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 1 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 11 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 30 - } - ] - } - ] - }, - { - "delegations": [ - { - "join": { - "pool": "pool1dpg4x7jw9ausk03ftd0366nzf4cqx4fm2vpzxx6xqdt9cmwulrp", - "stake_key_index": "113" - } - }, - { - "quit": { - "stake_key_index": "12801" - } - }, - { - "join": { - "pool": "pool1vgepyp33vglngrp5feejclqzxqnkgtnsv40qud278g89qk6qps5", - "stake_key_index": "80" - } - }, - { - "quit": { - "stake_key_index": "5019" - } - }, - { - "join": { - "pool": "pool1qc2hu7qf9ya9kdmvpsjkw73qvcwkw73cratyjxnxyu8h690v0w6", - "stake_key_index": "5" - } - }, - { - "join": { - "pool": "pool10q0k77tld4lp7hsugvd8v6q3233x6cj7z4t4jvjjpyp9cqdwxha", - "stake_key_index": "8" - } - }, - { - "join": { - "pool": "pool1fvj3xkn8qq6quresgszhs4ptxq53j3rpw35zutqwdvu45ez8nyu", - "stake_key_index": "51" - } - }, - { - "join": { - "pool": "pool1relj7cmv2vrxgrnvx4fjz8pp0a4hcajp09hpvj6rw4l85rn7kea", - "stake_key_index": "15" - } - }, - { - "join": { - "pool": "pool10d5p5uchgdtnzer5pamky7e2pve5ka3fqekxwl35qge4uyhleal", - "stake_key_index": "108" - } - }, - { - "quit": { - "stake_key_index": "13196" - } - }, - { - "join": { - "pool": "pool105hx5xec2qmy59zcxuxp7kn2zggrzyff2ewzqzrkgay5w5tzuuu", - "stake_key_index": "105" - } - }, - { - "join": { - "pool": "pool1f9vnq43h9cps7rc6xst5gm24pawsq9ff05ppvfzq93w4qmk4cqk", - "stake_key_index": "17" - } - }, - { - "join": { - "pool": "pool1qf48yt2fpfrrza278al45jnkwu6h5y6x2uxkz220wun8x7z0skn", - "stake_key_index": "95" - } - }, - { - "quit": { - "stake_key_index": "561" - } - }, - { - "join": { - "pool": "pool1yv9yvtp2gglrckgmfgvrj0gg834s7lesxyrn27zgdeekqvmh9c9", - "stake_key_index": "14" - } - }, - { - "join": { - "pool": "pool1tvn454gu0glzzz6sdjq92qjkra3kv0q324qyqz209f48jnkzn6h", - "stake_key_index": "125" - } - }, - { - "join": { - "pool": "pool1wakq7763p4gp69r58vl4cvchwcfzk5n60a4nkdsr9vwkqk67xkj", - "stake_key_index": "75" - } - }, - { - "join": { - "pool": "pool19vjysnmq0dtjwzm8vsysuzqjweqrggvqvctxq33stu28uhfjdug", - "stake_key_index": "32" - } - }, - { - "join": { - "pool": "pool1yvn4jvq9dvhnzspeysy42q6yxvur5dq8237y66mxppn45gvfg5y", - "stake_key_index": "30" - } - }, - { - "join": { - "pool": "pool1rqsr5htlgynjq9nl0de4wvjp9e3skkt28fuqul27gcsquk7kfp0", - "stake_key_index": "57" - } - }, - { - "quit": { - "stake_key_index": "209" - } - }, - { - "join": { - "pool": "pool1fvx8gw6hdfdzujm0sp89y0r22cj46mgh0pmrxdpt2vzk54cdy0v", - "stake_key_index": "26" - } - }, - { - "quit": { - "stake_key_index": "11444" - } - }, - { - "quit": { - "stake_key_index": "8991" - } - }, - { - "quit": { - "stake_key_index": "3909" - } - }, - { - "join": { - "pool": "pool1wswrwmzgp9h4sreq2qkhx6quggppzk6ddecqclshradnytavgkw", - "stake_key_index": "119" - } - }, - { - "join": { - "pool": "pool1fu2zk5e6vsdzy5edddhhxfq50fypglppq98xvh6tr3tz64x420r", - "stake_key_index": "38" - } - }, - { - "quit": { - "stake_key_index": "9542" - } - }, - { - "quit": { - "stake_key_index": "3182" - } - }, - { - "quit": { - "stake_key_index": "4278" - } - } - ], - "encoding": "base64", - "metadata": { - "1": { - "bytes": "597aa8610ba72266271577363d5f785617163130341b0026ca5f" - } - }, - "mint_burn": [ - { - "operation": { - "mint": { - "quantity": 19, - "receiving_address": "addr_test1zpzy8xlyhlcq469z0pvj750qz809hcwgltqtyqmz6t06r0fwlmtjalmdc9e5lf3875ywyvcraquzm7p4x2ful0rzl95st76zvw" - } - }, - "reference_input": { - "id": "3d4b4cd50124ce4a2a1c867a487c1f2d55b447a421d73a185ef50a72197d314e", - "index": 1 - } - }, - { - "operation": { - "burn": { - "quantity": 9 - } - }, - "reference_input": { - "id": "775d713a8e627e022d406f293557aa58511c1c7fa70aaac3641075164d510940", - "index": 0 - } - }, - { - "asset_name": "546f6b656e56", - "operation": { - "mint": { - "quantity": 1, - "receiving_address": "addr_test1zz208lpkes2hgvw8fq502xcjpac9zf0tdpqsfpuhk0xzx9stvld0dh8ymlmj0qwmy7w39kxpenry2ywzuryfw2qzf7uqv858s9" - } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } - }, - { - "operation": { - "mint": { - "quantity": 18, - "receiving_address": "addr_test1wq6npny6ulegj5g34xdh5qscfhtupn48gf83vvkh89gmr4cl3n4xr" - } - }, - "reference_input": { - "id": "4268386473677c4223c83e20357d7b276c78105f0e224d5266084e222c152641", - "index": 1 - } - }, - { - "asset_name": "546f6b656e56", - "operation": { - "mint": { - "quantity": 15, - "receiving_address": "FHnt4NL7yPXrZWJhioZ7P4Kw55fopmDNeEQrZ9Ewkb68Pxp3YYwKwRLW2y6SmAw" - } - }, - "reference_input": { - "id": "66c4564f361a61270f048b792d0c7a097e2be627691036664e2a2a5e76272f22", - "index": 1 - } - }, - { - "asset_name": "546f6b656e43", - "operation": { - "burn": { - "quantity": 5 - } - }, - "reference_input": { - "id": "7e6d1e57d10742dd146215634e3b273a7c144a38326f311a4ae62c3f4c795719", - "index": 1 - } - }, - { - "asset_name": "546f6b656e41", - "operation": { - "mint": { - "quantity": 10, - "receiving_address": "addr_test1qq760f2k5rlgvdplexma9vuqes3ystg8gldxfqhkxr0rny5jj0lm6rgxhnm56wvnqk6tkcgcrjgw3sx98l50z7823sxq2hzml4" - } - }, - "reference_input": { - "id": "2e3f3215173185f13a014075294d4f760e755e34fd6041797c7f027008057e52", - "index": 1 - } - }, - { - "asset_name": "546f6b656e44", - "operation": { - "burn": { - "quantity": 9 - } - }, - "reference_input": { - "id": "547553390952446125743c7246137f1276522ee15a24dd30066c4f2b4378271f", - "index": 0 - } - }, - { - "asset_name": "546f6b656e44", - "operation": { - "burn": { - "quantity": 19 - } - }, - "reference_input": { - "id": "a1690d235f58065b27a95a507da0234121391e627a422ec06470441f23320a91", - "index": 0 - } - }, - { - "asset_name": "546f6b656e51", - "operation": { - "burn": { - "quantity": 7 - } - }, - "reference_input": { - "id": "b8e260d36e8dad6709937e5601c2632c131ff76d6b7d5d3951110c568f02616c", - "index": 1 - } - }, - { - "asset_name": "546f6b656e4c", - "operation": { - "mint": { - "quantity": 1, - "receiving_address": "FHnt4NL7yPYD2vvC81DPpVAa73xMvDAW1BVWC8zSZaMRcshw4C1YfXESX5eQEE2" - } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } - }, - { - "operation": { - "mint": { - "quantity": 8 - } - }, - "policy_script_template": "cosigner#0" - }, - { - "asset_name": "546f6b656e43", - "operation": { - "mint": { - "quantity": 13, - "receiving_address": "FHnt4NL7yPXiQQDVDPcac86eFoot2nsAz4VR2odxz4qqWuhEsDRmTdXgDdqHWar" - } - }, - "reference_input": { - "id": "712a6c164e6d51751240217a0923238817a750596f7a1f7f6d170b3db9413b0e", - "index": 0 - } - }, - { - "operation": { - "burn": { - "quantity": 11 - } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } - }, - { - "asset_name": "546f6b656e4f", - "operation": { - "burn": { - "quantity": 18 - } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } - }, - { - "asset_name": "546f6b656e41", - "operation": { - "mint": { - "quantity": 22, - "receiving_address": "addr_test1vpe53cerjgyz39tv8cpfjsf778mry2rmfv7pqd7n44c63dc7k7xq5" - } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } - }, - { - "asset_name": "546f6b656e50", - "operation": { - "burn": { - "quantity": 16 - } - }, - "reference_input": { - "id": "3735c86637420f1907521d022410728a12706159597d146824727161b41a64dc", - "index": 1 - } - }, - { - "asset_name": "546f6b656e4d", - "operation": { - "mint": { - "quantity": 22, - "receiving_address": "FHnt4NL7yPXvfwR5hSQqtSC48QyTtcw5ho1qzkiWqZ9ppQr3f81HGpGkbERh1PM" - } - }, - "reference_input": { - "id": "675861703a401053c421d64d75c1a0587e130e6911363a3d1b76237cec767569", - "index": 1 - } - }, - { - "operation": { - "burn": { - "quantity": 16 - } - }, - "reference_input": { - "id": "047d7b2a0f1f3796906f161e335b7469486e1c3511234745521e146e0e1c4532", - "index": 0 - } - }, - { - "operation": { - "mint": { - "quantity": 13, - "receiving_address": "addr_test1wpu9ypxcu5alhdn256m2agcwxfdjwf252may9y53quggmhsu46rs4" - } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } - }, - { - "operation": { - "mint": { - "quantity": 30, - "receiving_address": "FHnt4NL7yPY6UuBCssaGZuYZXSKkVtMCnoW7FCW9MN5xdxMjov9tMZ7hZxCgArM" - } - }, - "reference_input": { - "id": "2c6c4b3f2cf6008e5f120c1919031e5269f26ce2913e422226565f3ca8585158", - "index": 1 - } - }, - { - "asset_name": "546f6b656e4c", - "operation": { - "burn": { - "quantity": 16 - } - }, - "reference_input": { - "id": "126e730f2c4f1e09713a6c4253332959cf1d9b2107225d213075387c0154351e", - "index": 1 - } - }, - { - "operation": { - "mint": { - "quantity": 13, - "receiving_address": "addr_test1vrguwl488tzry2f5z32sg2selc9j5qs2mj2drmh9j2hm0cqcnepwt" - } - }, - "policy_script_template": "cosigner#0" - }, - { - "operation": { - "burn": { - "quantity": 6 - } - }, - "reference_input": { - "id": "1dde684a34726344314d199503fa851f7f591771466564df5a5c4c0c6d36254a", - "index": 0 - } - }, - { - "operation": { - "mint": { - "quantity": 27, - "receiving_address": "addr_test1qrjkwn2x9v2kd3klr8v2kjkq0ayle9vpwzvl6ln932z08flf8fny0tarnn652lqsuaf52ljmvqc6hmzud8wp7dpkt40sr95emg" - } - }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] - } - } - ], - "payments": [ - { - "address": "addr_test1zza2leunuv8r8uwh2kpz2dvvzpfxt84p05avrw2p4fpdgnj40nfju5tnnaghn3h6tv4mf2awdxk9nsquvlmm644s2n7q0mc85x", - "amount": { - "quantity": 27, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e42", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 22 - } - ] - }, - { - "address": "addr_test1xrh9fd42039u2jsz537fnazfx7j7x4tn2zme7rxlvfyc9ymqhdcq50efz7k37y3x8klv4y8d4edzgk770mskra2njq7q22ltay", - "amount": { - "quantity": 9, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 24 - } - ] - }, - { - "address": "FHnt4NL7yPXzCE6K7QoUxsodDLh26innxLf63neHvt2VF3S7dtHh9xCptrpWpHZ", - "amount": { - "quantity": 73, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e41", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 5 - } - ] - }, - { - "address": "addr_test1xrew6al06d57xcx22xmcmeezzncy6u0jxj06z9r6r83jlpyf6kuqdxjqmmlpg3avyz70uc5wnf2m7jr83q2hqjrff3hqp706wu", - "amount": { - "quantity": 206, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "addr_test1wqsck3e6pf25f8kpv9jsxgueqk6r4vgl8jcvr0aww6dp07gmkur2j", - "amount": { - "quantity": 85, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 4 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 6 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 28 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 18 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 17 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 33 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 16 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 15 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 23 - } - ] - }, - { - "address": "FHnt4NL7yPY9HwPpVxyMd5byicy3GkyjfKmUjWVvU2R29p5hP1oo72Dg3Et6E48", - "amount": { - "quantity": 28, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 49 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 5 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 18 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 23 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 7 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 47 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 18 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 19 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 8 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 22 - } - ] - }, - { - "address": "FHnt4NL7yPXqYMizeZpKq2RP5i8JE5hPoNMzv9gJXRSnE2uBLFDWqjGBjsZhXQR", - "amount": { - "quantity": 2, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 10 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 5 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 28 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 27 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 22 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 16 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 24 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 10 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 14 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 8 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 28 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 13 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 17 - } - ] - }, - { - "address": "addr_test1vprhr4fp4q2tctvyvymj7wpsu4gkynmhdmx82ee9phg40psrh7lft", - "amount": { - "quantity": 254, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "addr_test1wzcjk6m0z5r7en07jwusmzv26pe68skpt00jm97e7zc3epqp3lale", - "amount": { - "quantity": 188, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 27 - } - ] - }, - { - "address": "addr_test1vzlph9puy0lcsq9wpj6z4dcasg9gd7u5xrgpeh7evvq0e2syna938", - "amount": { - "quantity": 68, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "FHnt4NL7yPXu41vyRyVJZr3BtcDwTc3vziR43ni9JN1bM32vfyQCvZLFCkR2ze8", - "amount": { - "quantity": 174, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 19 - } - ] - }, - { - "address": "FHnt4NL7yPXso2svWi7E7u6wBiuyv1pJuenKT4sV6ysYg32sGbaZSCwtEj1oGJ2", - "amount": { - "quantity": 211, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "FHnt4NL7yPY9AFMozzZg2EPaNpfpJ2xpijEhT4kNRnQFCQiZ8ia5AokfHh42rtN", - "amount": { - "quantity": 75, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 22 - } - ] - }, - { - "address": "addr_test1wz5xw2w25n6t7sh3ywg22axecagvkj3e0vdaf4vhkv2ywnc5v4nwr", - "amount": { - "quantity": 95, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e45", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 19 - } - ] - }, - { - "address": "addr_test1vr5shze0szc0xrmzyjye34275c0dh396ru2nzl6fvnlqhccx655l4", - "amount": { - "quantity": 8, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e42", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 10 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 1 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 59 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 4 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 21 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 45 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 25 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 22 - } - ] - }, - { - "address": "FHnt4NL7yPYKwgQKGwYQN7c7qpdsBtwEVKgyqBkTCzYmn42PnizDYA1D3EjyymJ", - "amount": { - "quantity": 20, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 21 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 43 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 16 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 17 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 8 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 14 - } - ] - }, - { - "address": "addr_test1wpdszv6xcmx728ez7fwrgwe8nuepuytwyaxhtc9kgpehd4gax0hvz", - "amount": { - "quantity": 249, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 1 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 32 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 22 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 11 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 1 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 17 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 23 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 37 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 37 - } - ] - }, - { - "address": "FHnt4NL7yPYCUTHZmX5WQeJCxPrKVHt3xfPXBuj83qkMHNCfB31g5cbad84Hbyj", - "amount": { - "quantity": 126, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "FHnt4NL7yPXvmkR59hFALGyUCvu7vPgkVb8xkTY46tYVDoXwPsv4ELzKCNXsbeL", - "amount": { - "quantity": 44, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e41", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 34 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 4 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 8 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 15 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 25 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 22 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 23 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 2 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 30 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 2 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 26 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 14 - } - ] - }, - { - "address": "FHnt4NL7yPY85y2Nc2cEtPx1qS7io21cQYn3xzpsz3gTY9ZbQB1jBX6vu1iM6qR", - "amount": { - "quantity": 254, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 30 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 26 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 3 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 35 - } - ] - }, - { - "address": "addr_test1zrfl0ef7mg9c9z45s7uml96tlx2x2f82nmh3fz6el3w9dq8hvh3k463p4zr0u7xr0u27dzpdp8kw6zdm36af58duvt3qscg645", - "amount": { - "quantity": 122, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "addr_test1zq7plfmaj0yrwgsszsa63838rmaaauhj930r7gnjn2vq2zp9ytdl76qk203at3zpfsyqhs3cu0arqttpdqpw3ylhcdkqfrj40v", - "amount": { - "quantity": 78, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 5 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 1 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 24 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 1 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 18 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 31 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 23 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 19 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 16 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 43 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 4 - } - ] - }, - { - "address": "FHnt4NL7yPY774qPzmN1kuG97EfnSFTdgPZd52GcXFSne6mku3xqYxJ5hfVccrj", - "amount": { - "quantity": 158, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "addr_test1yp8qnkpvh7hhvyqups5nd7tf9f6sjjk570q4mhkqyner8lzjms758dkjge0fvyyuuadtvx47t6wpmz3unnn0lz36755q0vknh0", - "amount": { - "quantity": 47, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 40 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 16 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 24 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 7 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 18 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 28 - } - ] - }, - { - "address": "FHnt4NL7yPXharVatMp7StYhhnEYcBME6hmubQUaFePcyr9MDGPpW6DSbVhJzkg", - "amount": { - "quantity": 18, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 14 - } - ] - }, - { - "address": "addr_test1wr2yzgn42ws0r2t9lmnavzs0wf9ndrw3hhduyzrnplxwhncaya5f8", - "amount": { - "quantity": 113, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e42", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 18 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 2 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 25 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 4 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 25 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 25 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 7 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 6 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 19 + "policy_script_template": "cosigner#0" + }, + { + "operation": { + "mint": { + "quantity": 27 } - ] + }, + "policy_id": "3399ba28f8d830050da3e5589a5add4085294ebd8f99de4cd89a516d", + "reference_input": { + "id": "73736c064e1e0f4c29266a244b054d1a113969cf32457d36e0792c417b3f2254", + "index": 0 + } + }, + { + "operation": { + "burn": { + "quantity": 27 + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } } - ] + ], + "withdrawal": "self" }, { "delegations": [ { "join": { - "pool": "pool1zs89s2mjxarxknmx89sxvtzr8afx28340y6jgp3gr4rqksp2n6h", - "stake_key_index": "104" + "pool": "pool10sfpsrfzd4ekszntwf5yx8elr9rr7xqkz48xwgfy25rpulggpyn", + "stake_key_index": "96" + } + }, + { + "join": { + "pool": "pool19qhxjymct5y5uptefe94sj3mvqnpy3c3feqyvp2hv9a5g6yqj0c", + "stake_key_index": "85" } }, { "quit": { - "stake_key_index": "12457" + "stake_key_index": "4464" } }, { "quit": { - "stake_key_index": "4021" + "stake_key_index": "3286" } }, { - "join": { - "pool": "pool1quv5q6n5qy8ysc6dzad4wge3fsw4w72nsq9zc3pezvf3w5eajfg", - "stake_key_index": "103" + "quit": { + "stake_key_index": "7399" } }, { "join": { - "pool": "pool1rcu36uqd8qpq6yzlrvnzqfp5r95ysf6rgs94u3e4yclhgm685ja", - "stake_key_index": "69" + "pool": "pool19djnxjtczdyztqp5f5er6gqkf9nq25nv8a2yj329yy29v8qae7g", + "stake_key_index": "75" } }, { - "join": { - "pool": "pool1pg34uv3e8qqqwdmqfqyhsytsp3v3ygrv254xvnpctegqkq0yjwm", - "stake_key_index": "119" + "quit": { + "stake_key_index": "3672" + } + }, + { + "quit": { + "stake_key_index": "5972" + } + }, + { + "quit": { + "stake_key_index": "10515" } }, { "join": { - "pool": "pool1q5x85urntdhk5anlw5fskw6dwv73w9grry05jsg4t3052gaaxnf", - "stake_key_index": "111" + "pool": "pool1q5skc3jrvgr56ajmxq9x2an5vqnjy4gmv44qvcfyfga9wgtxs7d", + "stake_key_index": "29" } }, { "quit": { - "stake_key_index": "8762" + "stake_key_index": "12575" + } + }, + { + "join": { + "pool": "pool1vu7yw9m8fp5hyucr0ea4j4zxqgz46rp209ukzreyxuw4s087s2n", + "stake_key_index": "109" } }, { "join": { - "pool": "pool1f5nqxfekqgc8vkn309p9v6ff9f04kmpnp44ny52vy3rnq9a4sve", - "stake_key_index": "120" + "pool": "pool1ddgjc42kd5uxs06nzshq5hza9g8jvpewyspng5t98ejrvanjyc3", + "stake_key_index": "97" + } + } + ], + "encoding": "base16", + "mint_burn": [ + { + "operation": { + "mint": { + "quantity": 25, + "receiving_address": "FHnt4NL7yPY1GFAnFZAnCU8HBp1Bvyv2vFqRzg2mGvK9h4acXc2neYk94q3aoR4" + } + }, + "policy_id": "e5cffbc350ffe54274a0aab36253dbf45b35ab34c992ab3d32c546dc", + "reference_input": { + "id": "03166a3353df7653000a0421156f19340ce397434968fc2c3f43672a6a4c1313", + "index": 0 + } + }, + { + "operation": { + "mint": { + "quantity": 22, + "receiving_address": "FHnt4NL7yPYEWdvrFtY9NuGvbyxwk3q153TxQcfmnrK8j6geyx9b5czqFpBC1L8" + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } + }, + { + "operation": { + "mint": { + "quantity": 16, + "receiving_address": "FHnt4NL7yPY2CpNiD3ezuJ3LLqnULQvcxe4seLzGSjQ5TcqdokrXdb5He7Kf3Su" + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } + }, + { + "asset_name": "546f6b656e55", + "operation": { + "burn": { + "quantity": 29 + } + }, + "policy_id": "e49374079f367f6e8f704f15869917a740cb1b2a77792a2e5bdac7bf", + "reference_input": { + "id": "361970952f1f2a0a4e3700064c19ab852b53650c48474a5478112126069f5e4c", + "index": 1 + } + }, + { + "asset_name": "546f6b656e45", + "operation": { + "burn": { + "quantity": 5 + } + }, + "policy_id": "89bd205bc52ff7f15ae59d842441fb3b393f9eb5b03b7c3b1317bbfd", + "reference_input": { + "id": "64a344722a3b7a1e175a30986e7455fe05396e2b506058816a792f243016315c", + "index": 0 + } + }, + { + "asset_name": "546f6b656e4a", + "operation": { + "mint": { + "quantity": 23, + "receiving_address": "FHnt4NL7yPXnSSiLkJg6WTUK3z8S1ouYsWeipaVATeMtbHzrA7558TSMKEAnPNB" + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } + }, + { + "asset_name": "546f6b656e53", + "operation": { + "burn": { + "quantity": 25 + } + }, + "policy_script_template": "cosigner#0" + }, + { + "operation": { + "mint": { + "quantity": 18, + "receiving_address": "FHnt4NL7yPXyjodouwoVfpWYvospKPdUm1ppu21p6fnSqaTJo6FEd1xiNj2CZ33" + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + } + ] + } + }, + { + "asset_name": "546f6b656e56", + "operation": { + "mint": { + "quantity": 21, + "receiving_address": "addr_test1qzl9r7vr3j83qjym8nlmzx36fwxc9px35c57t6l0ckvx4qzzrtz2g0ktardre705yjcz9hhfw8altfdzn7tvnem5p37sv590ec" + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + } + ] + } + }, + { + "operation": { + "mint": { + "quantity": 15, + "receiving_address": "FHnt4NL7yPYFy2uK8HU68T3mRgvtejUwgwnFXGcvfS4yDKasSLCUWnAb6NKT1rP" + } + }, + "policy_id": "2d129547b3f19df432427bbf1b28fbca6c3e101aa03cfd964ecfc266", + "reference_input": { + "id": "2eaa3e5b17086fde03d4b71b1f58531396028121585f2c7b4de4048a355e5e09", + "index": 0 + } + }, + { + "asset_name": "546f6b656e50", + "operation": { + "mint": { + "quantity": 15, + "receiving_address": "FHnt4NL7yPXzxWzGUTUNsabbQPr8eUHi1dokqbAj1cR6emsaaabUWMq7R8HDcSq" + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + } + ] + } + }, + { + "asset_name": "546f6b656e57", + "operation": { + "mint": { + "quantity": 4, + "receiving_address": "addr_test1vq4perg29rw56a6a2zh7g3emyy2qtyjttqghuphgn76vn6gcdm9zz" + } + }, + "policy_id": "5aca96afdb81fdef788c1aa03e7a3ee25c3ed7bc690bd8ea91f759f8", + "reference_input": { + "id": "7e2b567e102b63110c6d2fc9550e25f152521b50644c2f6e52583f050f146708", + "index": 0 + } + }, + { + "asset_name": "546f6b656e46", + "operation": { + "burn": { + "quantity": 16 + } + }, + "policy_id": "acdfcfd789eb41485b2eb398896c7638a8f82e3e1c078e28a4391cc6", + "reference_input": { + "id": "0f5f8334024f3c7869003146313208743c2f7f31291b17595774793c6ee91e0a", + "index": 0 } }, { - "quit": { - "stake_key_index": "3742" - } + "asset_name": "546f6b656e41", + "operation": { + "mint": { + "quantity": 6 + } + }, + "policy_script_template": "cosigner#0" }, { - "join": { - "pool": "pool1ypsszaedwdj37xmj955xqyfrxul5s32n95g5zapvwa2xus4ddjs", - "stake_key_index": "15" - } + "asset_name": "546f6b656e53", + "operation": { + "burn": { + "quantity": 14 + } + }, + "policy_script_template": "cosigner#0" }, { - "join": { - "pool": "pool1rcukzt63z4f9jyr79qx4sagswd43sgnzvgu8wtgqvufrqrmd9qg", - "stake_key_index": "64" + "asset_name": "546f6b656e4a", + "operation": { + "burn": { + "quantity": 8 + } + }, + "policy_id": "7e0622aabc5a8e1080c5aa184be3d8701997dae784b99284a525ce4f", + "reference_input": { + "id": "0f263859642146285b526948505b450651d520041d42565d2703d49c372670e6", + "index": 1 } }, { - "quit": { - "stake_key_index": "5414" - } + "asset_name": "546f6b656e4b", + "operation": { + "burn": { + "quantity": 17 + } + }, + "policy_script_template": "cosigner#0" }, { - "join": { - "pool": "pool1peu3x8cxv3e82ez38yg8696ntam8y3zxzcv46uz6wq95wdcdq75", - "stake_key_index": "41" + "asset_name": "546f6b656e44", + "operation": { + "mint": { + "quantity": 28, + "receiving_address": "addr_test1vr84szqxpdcts0wss59vvhs8gfd9sxat3k6uhw5rrqr4d3qaucx2d" + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] } - }, + } + ], + "withdrawal": "self" + }, + { + "encoding": "base64", + "metadata": { + "14": { + "map": [ + { + "k": { + "string": "𫅊" + }, + "v": { + "map": [] + } + }, + { + "k": { + "string": "󴎵𤇋" + }, + "v": { + "int": 3 + } + }, + { + "k": { + "string": "󸆝䬗􀁑" + }, + "v": { + "bytes": "673e704c4d400e6f6a581978686034222551007d30551a120a4b2071370a4534aa57646b1062" + } + } + ] + } + }, + "mint_burn": [ { - "quit": { - "stake_key_index": "13465" + "operation": { + "mint": { + "quantity": 16, + "receiving_address": "FHnt4NL7yPY4TC2WN9rhgiW86f6NZN8AkGd7ARfApoUXK2LJUoo5WAFoBQijizK" + } + }, + "policy_id": "f5c7d0afcac2a232de24f5a42079d90db6499a9e8fa8029602310cad", + "reference_input": { + "id": "4d075910a41b13754d7e0f215c0a15ec6967221aee367de45328684374bd5d72", + "index": 0 } }, { - "join": { - "pool": "pool19gyh29g5tcjxcr6mwg33qhchpacx6m6rqg7nkqm0rpq86tnzjt4", - "stake_key_index": "24" + "operation": { + "mint": { + "quantity": 20 + } + }, + "policy_id": "dd1e43d5b0491dd59a1d36116b272abfd81f9276f95f3679e79d4aa9", + "reference_input": { + "id": "9000ba65373b3f620d6e0b7b001d577f02427c4a1b492048090b215bdc775a66", + "index": 1 } }, { - "quit": { - "stake_key_index": "10023" + "operation": { + "mint": { + "quantity": 29, + "receiving_address": "addr_test1yruecte4jw08sqwte3kkj4zy2wd8euhww37cy8v39sftqp7du5q7dv06ch0q2czzhmpdlgp7snvwejwfet92hwu95nes4n8ehw" + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] } }, { - "quit": { - "stake_key_index": "4496" + "operation": { + "burn": { + "quantity": 8 + } + }, + "policy_id": "146ecc69ebe4c7bda39a3f3d087bc9755a2950a11fd9d41df2cd3420", + "reference_input": { + "id": "5d082e29494531430749d73c723637644726299a750e5a164c675176423df651", + "index": 0 } }, { - "quit": { - "stake_key_index": "5761" + "operation": { + "burn": { + "quantity": 30 + } + }, + "policy_id": "62316e45ee5226c2572052e021cd94a903f816c14cc298e91feb7126", + "reference_input": { + "id": "57f50668025e4a166d4d353cf10e005138ae761d2203596a7f61b438bc26743f", + "index": 1 } }, { - "quit": { - "stake_key_index": "13591" - } + "operation": { + "mint": { + "quantity": 8 + } + }, + "policy_script_template": "cosigner#0" }, { - "quit": { - "stake_key_index": "10674" + "asset_name": "546f6b656e55", + "operation": { + "burn": { + "quantity": 25 + } + }, + "policy_id": "5c315d606c070346f00b35da72c722d3ab591f0d134ebd2de24b513e", + "reference_input": { + "id": "506c0b7cdc6f5e601fbb2b115e211a6147366b051b7e4a627964334b706c1158", + "index": 0 } }, { - "quit": { - "stake_key_index": "7317" + "operation": { + "mint": { + "quantity": 6, + "receiving_address": "FHnt4NL7yPY3nk9xpF998rtpPEM4u5EjLsStkEpLu9seqWWsH2hmji82jFUwhzg" + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + } + ] } - }, + } + ], + "payments": [ { - "quit": { - "stake_key_index": "8887" - } + "address": "addr_test1xqplzc08l8m62js5vv6zld53z52lf0kchr9qwaaaenr7j4mla495eap3euvtzl6wecmdfr2lf5wsj87xasq2q7anz88se9vsx3", + "amount": { + "quantity": 72, + "unit": "lovelace" + }, + "assets": [] }, { - "join": { - "pool": "pool1pq74smewwuq9jrr5fvlz56zupskxswjx9dmqv7s4xd6j5cwecc3", - "stake_key_index": "70" - } + "address": "FHnt4NL7yPXuQd9yyNTVSU7cBv6J5DvA6CSyrP1b39btuSeL3AVhTZ2eEBM9HaE", + "amount": { + "quantity": 100, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e42", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 24 + } + ] }, { - "quit": { - "stake_key_index": "13927" - } + "address": "addr_test1vr2dnex4c9q0e224f7406gfgt27ddnys6f97nzyuw58ejfshhpm5t", + "amount": { + "quantity": 225, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e45", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 11 + } + ] }, { - "join": { - "pool": "pool1yfq35yppfqeq2ne4xuphczs4gfw464spxu7ruvs2zet4cx6dd2r", - "stake_key_index": "64" - } + "address": "addr_test1xr2yzgn42ws0r2t9lmnavzs0wf9ndrw3hhduyzrnplxwhncz9qnc8tsewtke4ls3g7q5rx0x075p4p9kr95j4l2z7g9ss5wnsn", + "amount": { + "quantity": 125, + "unit": "lovelace" + }, + "assets": [] }, { - "quit": { - "stake_key_index": "13679" - } + "address": "addr_test1wq8v4k4qf8epnu7kntku4rm2n05u73gzzr4jpvxaz0frmhcvlvv57", + "amount": { + "quantity": 10, + "unit": "lovelace" + }, + "assets": [] }, { - "join": { - "pool": "pool125er2km2duqzwcc48d3r6cj0y324fqrc8al4xe22dvhn679wz7l", - "stake_key_index": "35" - } - } - ], - "encoding": "base16", - "metadata": { - "20": { - "map": [ + "address": "FHnt4NL7yPXnvth77tmZm2smxocAtNmJy6AAqcJwQq9Ko419o8d4yqLnAFj15Bn", + "amount": { + "quantity": 156, + "unit": "lovelace" + }, + "assets": [ { - "k": { - "string": "䢒􉤔󾇣􎒿" - }, - "v": { - "list": [ - { - "list": [] - }, - { - "map": [] - } - ] - } + "asset_name": "546f6b656e44", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 29 } ] - } - }, - "payments": [ + }, { - "address": "FHnt4NL7yPY1NxFXr8znvGWHwDqAxktHKkCiRejVbxFbKXuWhuzfMyRLdXbqazS", + "address": "FHnt4NL7yPXpz6ovyLwf5PN8uwafok2YcxxBY3sMjpjdTzFGMSXRKnpuJBDFTdd", "amount": { - "quantity": 212, + "quantity": 146, + "unit": "lovelace" + }, + "assets": [] + }, + { + "address": "FHnt4NL7yPXgd7HD8j72bXv49b6LBibD4s3rv8X8jXTWxVo8mEF8XV2kQ241nbD", + "amount": { + "quantity": 95, + "unit": "lovelace" + }, + "assets": [] + }, + { + "address": "addr_test1zzk2ydghvnejajufn8nhfwfulqyrgaxa8wwwmt6f0macwkj54kxmhaqd4uh9nr8c9drhul0g5gm3dhdk8jxmre324a4sfphfk3", + "amount": { + "quantity": 50, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e44", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 26 + "asset_name": "546f6b656e45", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 7 } ] }, { - "address": "addr_test1wphmgwsewvmmzv64vlk2a3ahu6l3pwd3kpsgdt59jvz5tjcjmz3s9", + "address": "addr_test1qrqswdm9x2yh2hs442fad3x7flv4mxr82gxks9argfz4njuexmrakqad5hrm5qmr6wmhcx6grjddrayqasnv96dzf03qxmrnzy", "amount": { - "quantity": 169, + "quantity": 46, "unit": "lovelace" }, "assets": [ { "asset_name": "546f6b656e44", "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 20 + "quantity": 22 }, { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 9 + "asset_name": "546f6b656e45", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 18 }, { - "asset_name": "546f6b656e44", + "asset_name": "546f6b656e43", "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 27 + "quantity": 7 }, { "asset_name": "546f6b656e45", "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 17 + }, + { + "asset_name": "546f6b656e41", + "policy_id": "22222222222222222222222222222222222222222222222222222222", "quantity": 23 }, { "asset_name": "546f6b656e43", "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 15 + "quantity": 28 }, { "asset_name": "546f6b656e45", "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 13 + "quantity": 17 }, { "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 2 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 14 - }, - { - "asset_name": "546f6b656e42", "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 25 + "quantity": 9 }, { - "asset_name": "546f6b656e44", + "asset_name": "546f6b656e45", "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 10 + "quantity": 11 } ] }, { - "address": "FHnt4NL7yPXyhDjaRsd5AMzQ38PyMDGTWvtG1nUQCYtn4gJhNbeRWSATur2NK5b", + "address": "addr_test1xzcsaegrdr9l2ltv20xvnmtkc7ckkdeevedwy7e5mhaq0hk5gy3825aq7x5ktlh86c9q7ujtx6xar0wmcgy8xr7va08s68qhpy", "amount": { - "quantity": 165, + "quantity": 27, "unit": "lovelace" }, "assets": [] }, { - "address": "FHnt4NL7yPXinpAG2AAq6KkQqPygfSiJretdnc9saQosefrLV8qYcJYzbXHF9So", + "address": "addr_test1wpzhlugglh498sz8jtv5jh3s48a7ym4vazg8am3zdlknk2cpgphan", "amount": { - "quantity": 160, + "quantity": 200, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 26 + "asset_name": "546f6b656e45", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 5 } ] }, { - "address": "addr_test1qqafp9gldc0rh0ct9shr47kynuzk4jsz86u9swj8k557qnflm87pd9aefj8parwn4qmer9g08ulplu02ystwa33ykgmsy36k9l", + "address": "addr_test1wqt9pem24qmmyptd7zs7uy7umzue6shlqvsht3e9e2knsfgvsu8n2", "amount": { - "quantity": 12, + "quantity": 157, "unit": "lovelace" }, "assets": [] }, { - "address": "FHnt4NL7yPYDK75iMm79z68HhoFpa2Jbx4j4nJGp9qJxtBFg99BxxRpmqfcgWMq", + "address": "FHnt4NL7yPYH2djhYKdtjTX22uPCgSXC2J7MPExar3wh5YPX6ghhMApZqLfxAHP", "amount": { - "quantity": 19, + "quantity": 115, "unit": "lovelace" }, "assets": [] }, { - "address": "FHnt4NL7yPXnWmLNpDyXjwCaMkhmEGfuQnR9iyYiechCFMBtiscuK6MvwWAndSY", + "address": "FHnt4NL7yPXkCeBa6dCBQVP3CTyqMdroi6uNpuMihKMhFoeAfd8tRkXfteQk7S3", + "amount": { + "quantity": 89, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e43", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 11 + } + ] + }, + { + "address": "addr_test1zzwn4hyrmvlpw8yzudfmu6764t44dtfk8x8vw0v5xacxhje8jkla8uv2ky9rc53cvsetz6rq3sxry4msn5jfe8xvjz9sux7p6s", + "amount": { + "quantity": 75, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e41", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 8 + }, + { + "asset_name": "546f6b656e45", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 10 + } + ] + }, + { + "address": "addr_test1vqrr333gyserm507c0ptlk8gacrcrxcrm40uwf0enexcu4gc2kvu6", "amount": { "quantity": 34, "unit": "lovelace" }, + "assets": [ + { + "asset_name": "546f6b656e43", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 28 + } + ] + }, + { + "address": "FHnt4NL7yPXwQUMc95mL8ezq493LpayuFtUFLSYSLcSHLYauNDr7JiDcGpYH1x1", + "amount": { + "quantity": 7, + "unit": "lovelace" + }, "assets": [] }, { - "address": "FHnt4NL7yPYAcfy5E7Co52gupsBeyAVYvcmBNmoJuyjV8LuSJFRUJmjCVqPkSn4", + "address": "FHnt4NL7yPXkey1bzyMXpjEnbAdc19kyLAadPoMEeMuBjZWEiJaLxiFv5768eVH", + "amount": { + "quantity": 208, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e42", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 30 + } + ] + }, + { + "address": "FHnt4NL7yPY4x2xN1Xv9YMu2yTAAu6ouS7adkL56pAQtAMgrrhs6iBAL6d3XkB6", "amount": { - "quantity": 138, + "quantity": 235, "unit": "lovelace" }, "assets": [ { "asset_name": "546f6b656e41", "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 16 + "quantity": 44 }, { "asset_name": "546f6b656e45", + "policy_id": "11111111111111111111111111111111111111111111111111111111", + "quantity": 4 + }, + { + "asset_name": "546f6b656e42", "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 11 + "quantity": 16 + }, + { + "asset_name": "546f6b656e44", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 20 }, { "asset_name": "546f6b656e41", "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 26 + "quantity": 13 + }, + { + "asset_name": "546f6b656e41", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 7 }, { "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 19 + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 4 }, { "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 47 + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 26 + } + ] + }, + { + "address": "addr_test1vpvcdffqyyvneelyw22cuurc3cps74uqzancgtvk805nrrgcaudw2", + "amount": { + "quantity": 107, + "unit": "lovelace" + }, + "assets": [] + }, + { + "address": "FHnt4NL7yPXrVpWGnfJTaQK3iRdKxVqh3FDaHCQDLD9Jgq2WtgZWiJQKLyhQFBS", + "amount": { + "quantity": 161, + "unit": "lovelace" + }, + "assets": [ + { + "asset_name": "546f6b656e45", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 15 }, { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 24 + "asset_name": "546f6b656e43", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 26 }, { - "asset_name": "546f6b656e45", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 25 + "asset_name": "546f6b656e41", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 4 + } + ] + }, + { + "address": "addr_test1vrz00mmpasxk0xjwmxxc23z62k87pgfjwnftxp63vu6gk4swg4wf0", + "amount": { + "quantity": 16, + "unit": "lovelace" + }, + "assets": [] + } + ], + "withdrawal": "self" + }, + { + "delegations": [ + { + "join": { + "pool": "pool104h42ccrg9k47a6gfqk56lccfd5yw7ewpqxxsaqzffk4v82sufv", + "stake_key_index": "44" + } + }, + { + "quit": { + "stake_key_index": "16274" + } + }, + { + "quit": { + "stake_key_index": "7808" + } + }, + { + "join": { + "pool": "pool1gfx5zjrxtv4rv528ds9z55mfq9a56mevwfmywvsr2ynxw8yldcr", + "stake_key_index": "2" + } + }, + { + "join": { + "pool": "pool1gepq2lj9w5tz7fr60cuxxjzhry68ulmrt9ljgfqctyszqp3q5ea", + "stake_key_index": "76" + } + }, + { + "join": { + "pool": "pool185jpk63fqc2nsgmdvamhwyrmd4xx7lsrt5spsqp00pfqy4g5e9a", + "stake_key_index": "71" + } + }, + { + "join": { + "pool": "pool1xcg5uhs4qvdrjhtq9d4r20ps8uhjx9c5tqdzcjgr2e2s2yasylk", + "stake_key_index": "34" + } + }, + { + "join": { + "pool": "pool129pq57ertcj3ga6wrgvpcfgj9e3kgeetz9ynwtemgcr5kqw9p3z", + "stake_key_index": "114" + } + }, + { + "quit": { + "stake_key_index": "4667" + } + }, + { + "join": { + "pool": "pool10f2nqkffrec5qdc0z35z62g2dpx55ms5t9u8kpjsy34zjn9d0dp", + "stake_key_index": "107" + } + }, + { + "join": { + "pool": "pool1yuj550n6vqtj5hzjvssk72cpvuwhuszcg32xj52aga0y68jufjp", + "stake_key_index": "108" + } + }, + { + "join": { + "pool": "pool1rytkx360fd3ssdec93mr7y3zgqyrc32vycyn2u36x3wnjfrqkv8", + "stake_key_index": "40" + } + }, + { + "quit": { + "stake_key_index": "9462" + } + }, + { + "quit": { + "stake_key_index": "9523" + } + }, + { + "quit": { + "stake_key_index": "212" + } + } + ], + "metadata": { + "3": { + "map": [ + { + "k": { + "string": "𢄂" + }, + "v": { + "list": [ + { + "bytes": "d61d69cf2d53e83e27137a75" + }, + { + "list": [ + { + "bytes": "a73b34ba4ea0735e05aa61610f7252564631490d4e252f7e1a7574187f7e7d0f2710" + } + ] + } + ] + } } ] + } + }, + "mint_burn": [ + { + "asset_name": "546f6b656e41", + "operation": { + "burn": { + "quantity": 14 + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } }, { - "address": "addr_test1wzlrpdmujc5crrvwlyfner8sxu2hjls4ly6la0d06dtsezsudfcru", - "amount": { - "quantity": 77, - "unit": "lovelace" + "operation": { + "burn": { + "quantity": 18 + } }, - "assets": [] + "policy_id": "c32c6e7d2991dce2b763d21a76c9e3015585f940747302866dfade9a", + "reference_input": { + "id": "7f67293f4f1235034a062f7438421b4a4b1f1a007618062b2b6c6e360a544136", + "index": 0 + } }, { - "address": "FHnt4NL7yPYEUApf6ETT5vqiY6ET3CJPNvVanogU6iN9BBtafqzZNA2fDBt8atz", - "amount": { - "quantity": 208, - "unit": "lovelace" + "operation": { + "burn": { + "quantity": 0 + } }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 1 + "policy_id": "1436913c451b3f5edc73b29f6d84e8406020c108a80818cd0126ca3f", + "reference_input": { + "id": "7a505331041675032f740f256d246dc1291268274f483e101e073a102b5c7461", + "index": 0 + } + }, + { + "asset_name": "546f6b656e4f", + "operation": { + "burn": { + "quantity": 21 } - ] + }, + "policy_id": "97fb516fe9f8b93e47992c5a3a44252a5f57f949ace70d47bae07c6c", + "reference_input": { + "id": "2c191c7a0b693a2f2d2ba4bda5743d6b5b120f7e60011e6720019c6d607f7a2f", + "index": 0 + } }, { - "address": "addr_test1xz6agmxjqhnp6lgm692fu9wdnhlv03mc0r90zkd2n23mywqwgcpvtml527fdt9pa42yqry3ym80e569xvhnrfpv7sp8q7tlvkq", - "amount": { - "quantity": 43, - "unit": "lovelace" + "operation": { + "burn": { + "quantity": 15 + } }, - "assets": [ - { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 1 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", + "policy_id": "deb2c4b77ac61b4c6063311213b34b08281eb8ed0e35dc804d7dfb04", + "reference_input": { + "id": "197c1f314d0858334ed26d0a31850a394646c9175058763170210d7a3529771a", + "index": 1 + } + }, + { + "operation": { + "burn": { "quantity": 11 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 6 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 35 } - ] + }, + "policy_id": "287427b2ebe854fee2d790da825e22299b9c0dd112ca733bcb65234a", + "reference_input": { + "id": "3a39b5b171ea131be4e87032407a1e4d5a761d5a496a1945a06b207562456b19", + "index": 1 + } }, { - "address": "addr_test1qrathq05tp7d43wknzu9m3yezshj47wa3jjmksuy5plks55hpjfpmnqn4s2uu768h3vusm67fxv5umxqaqhugdrd5pfsdl94p0", - "amount": { - "quantity": 59, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 14 + "asset_name": "546f6b656e4c", + "operation": { + "mint": { + "quantity": 25, + "receiving_address": "FHnt4NL7yPY6jyw2bZSakYXfiF7ER7hcXwhdKaUziJLU7NM7Brciky67W1RENJP" } - ] + }, + "policy_script_template": "cosigner#0" }, { - "address": "FHnt4NL7yPXmbbXawrWPYQcgxmUF41qwLpbYfrUBddYVEvEf2omWCekemxbDmqC", - "amount": { - "quantity": 183, - "unit": "lovelace" + "operation": { + "mint": { + "quantity": 28, + "receiving_address": "FHnt4NL7yPY9pY3BMkkQ4ahKVpRBasYXWsD5fBXWL9jtpRqgareyUyF3fdEFFWD" + } }, - "assets": [] + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + } + ] + } }, { - "address": "addr_test1vzc5wwzteh4e37dn8lz078vf5zltp60d4fqmq2s0l037v7sdt6t72", - "amount": { - "quantity": 189, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 8 + "operation": { + "mint": { + "quantity": 26, + "receiving_address": "FHnt4NL7yPY5ebSTcmHszyEAY93E79dcmS1tAHuqqyMbnG8y7Vtjt4KvZLEdLv3" } - ] + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + } + ] + } }, { - "address": "FHnt4NL7yPXqquzrHQ7NSuYPHMhnZbYLfZSuvPfxzmwCXLvVKqm5UES2vBzybbd", - "amount": { - "quantity": 17, - "unit": "lovelace" + "asset_name": "546f6b656e4a", + "operation": { + "mint": { + "quantity": 16 + } }, - "assets": [] + "policy_id": "f4ca3a8d4ea053ceeb6a2967472f8b1a4ffeab733e1e50b3e511e57d", + "reference_input": { + "id": "747f0021202c052baa30247d44786c77752346786a6f5d5060630d7a183d1843", + "index": 1 + } }, { - "address": "FHnt4NL7yPXimpN2EtJXTdowvgBHpjCNjx2wgQfZPsrHwaRzxyuDdfuf32Asd73", - "amount": { - "quantity": 164, - "unit": "lovelace" + "operation": { + "burn": { + "quantity": 22 + } }, - "assets": [] + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } }, { - "address": "FHnt4NL7yPY3rxK8oN2Dx59E1MV1NG5kZuSVWJGEiCUPVZhShnuBpkDY2F6HVbY", - "amount": { - "quantity": 59, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e45", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 27 + "operation": { + "burn": { + "quantity": 15 } - ] + }, + "policy_id": "fae6b965cd6b695735b590aa659e7dcfb45dc7533900277f79b61b89", + "reference_input": { + "id": "ec3a2f3e41120f5f034e3b42621ffc28707e4f0f3a696d6b21700536581c6a7d", + "index": 1 + } }, { - "address": "addr_test1vqrvyc3a305he8uyun3l2ne9d6rxnkjzxav4f7ugj0qwlfsw80dxq", - "amount": { - "quantity": 253, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 28 + "operation": { + "burn": { + "quantity": 16 } - ] - }, + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + } + ] + } + } + ], + "payments": [ { - "address": "FHnt4NL7yPY2DfLvrnrnYFZerJWJ15C8enfAw372USP83MFff9TGm4wzSxqbEjx", + "address": "FHnt4NL7yPXsGYuzjdDuNxhoZiaUBsYfLbHDFPPvPvAtSMTen6BhEP5r2yT851o", "amount": { - "quantity": 35, + "quantity": 90, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e43", + "asset_name": "546f6b656e45", "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 14 + "quantity": 1 }, { - "asset_name": "546f6b656e41", + "asset_name": "546f6b656e43", "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 16 + "quantity": 2 }, { - "asset_name": "546f6b656e45", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 24 + "asset_name": "546f6b656e44", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 5 }, { "asset_name": "546f6b656e45", "policy_id": "22222222222222222222222222222222222222222222222222222222", "quantity": 4 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 18 - } - ] - }, - { - "address": "addr_test1xzjyhtmahjvq9mzth8vq2gmzpm9wdp9pyk3uyswzujf72ttcqzkgyfzq7u0d3ye60mhxv8503sghgkgkhg97qvzqtejqt6uewk", - "amount": { - "quantity": 175, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "FHnt4NL7yPYEXW7Hf8hmhJ3NJVpJ2uqExF91VEKVxzhHQVmGWS37MycGqTVEANP", - "amount": { - "quantity": 20, - "unit": "lovelace" - }, - "assets": [ + }, { "asset_name": "546f6b656e43", "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 19 + "quantity": 28 } ] }, { - "address": "FHnt4NL7yPXoWuD8aK283NPMeY9yyzGuEGDyYbttG6BnVuHsLgocNCJncALg4nN", + "address": "FHnt4NL7yPXhLjZ1zEH4K5M6ZaHNCKjwwTwDJPH2ehrmcHFownu3kHsyw9FvTvz", "amount": { - "quantity": 203, + "quantity": 137, "unit": "lovelace" }, - "assets": [] + "assets": [ + { + "asset_name": "546f6b656e41", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 25 + } + ] }, { - "address": "FHnt4NL7yPYKWcFLJ44rTCQ4TzpsiCSrEV1cJ3DGjUwdMuU15BDL2qqpvcwXC23", + "address": "FHnt4NL7yPYKP5JUigXyj8aGGn52N4o8riU99fxwkeS9mxNUtbH2ybNHr7hV5dQ", "amount": { - "quantity": 11, + "quantity": 73, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 26 - }, - { - "asset_name": "546f6b656e44", + "asset_name": "546f6b656e45", "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 9 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 22 - }, - { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 5 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 20 + "quantity": 25 }, { "asset_name": "546f6b656e43", "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 13 + "quantity": 28 }, { "asset_name": "546f6b656e42", "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 28 + "quantity": 18 }, { - "asset_name": "546f6b656e43", + "asset_name": "546f6b656e44", "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 21 + "quantity": 9 }, { - "asset_name": "546f6b656e43", + "asset_name": "546f6b656e41", "policy_id": "44444444444444444444444444444444444444444444444444444444", "quantity": 25 + }, + { + "asset_name": "546f6b656e42", + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 23 } ] }, { - "address": "addr_test1vzzcq372cc94jd9ymdyq64m894xp3zd44ufey7x4ket79cqavq9h0", + "address": "addr_test1qrrepr00rv9v740c7mvukmt7kdc55esslfrjfmh9qm0umzkrq0yam03ygla378rla9zgkvyy0833rvcm25nhfznu5dzsxfeq6v", "amount": { - "quantity": 24, + "quantity": 26, "unit": "lovelace" }, - "assets": [ - { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 14 - } - ] + "assets": [] }, { - "address": "addr_test1wpqlpetx9f77w2muth20f8qgvt35cdt2e3hp0655p7n8mpcysvzvg", + "address": "FHnt4NL7yPXuRap6Nqvquqe3EwYNCWwVKqb6N1LzckExhpw8WVNFswQA4ck4n4E", "amount": { - "quantity": 252, + "quantity": 212, "unit": "lovelace" }, "assets": [] }, { - "address": "FHnt4NL7yPY6fHdKdqyfzT1mAJn1V15c9kptG8Ki8tpKPZGoj7x1RZzrMZM9Ag1", + "address": "FHnt4NL7yPYDLRShsPLWv6DWTVNe2dJhggbmYjGikHgVC58SL5DwHUNWsmjGbf1", "amount": { - "quantity": 49, + "quantity": 231, "unit": "lovelace" }, "assets": [ - { - "asset_name": "546f6b656e41", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 19 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 23 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 7 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 19 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 6 - }, { "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 38 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 15 - }, - { - "asset_name": "546f6b656e45", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 5 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 10 - }, - { - "asset_name": "546f6b656e45", "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 51 + "quantity": 23 } ] + }, + { + "address": "FHnt4NL7yPXrbve8ApMzf7rugnd2NG5nWsd573zJrTzJDB2a6BjPyJ14tkB5dyi", + "amount": { + "quantity": 183, + "unit": "lovelace" + }, + "assets": [] } ], "withdrawal": "self" }, { "delegations": [ - { - "join": { - "pool": "pool1xyy4c06jpdsj6scjv3sr22gp8s2sgmcc8y0xc0r4qa58qywg272", - "stake_key_index": "82" - } - }, - { - "quit": { - "stake_key_index": "13536" - } - }, { "quit": { - "stake_key_index": "6469" - } - }, - { - "join": { - "pool": "pool1v3e97j64w375w8f5vs3jjkrpzeanq5td93phglp3f3jj2nhd9y4", - "stake_key_index": "55" + "stake_key_index": "7307" } }, { "quit": { - "stake_key_index": "4190" + "stake_key_index": "1455" } } ], - "encoding": "base64", - "metadata": { - "3": { - "map": [] - } - }, "mint_burn": [ { "operation": { - "burn": { - "quantity": 6 + "mint": { + "quantity": 29, + "receiving_address": "addr_test1qz27pk4kxvte27ae0wnq50aj972xedz88pmc6rjzcgtzts5xcehkr09yklnn3qlrqf6hzgf86zfevv4n6vvv6uae4xuscg4u0r" } }, "policy_script_template": { @@ -5117,83 +3621,78 @@ } }, { - "asset_name": "546f6b656e43", "operation": { "burn": { - "quantity": 21 + "quantity": 23 } }, - "policy_script_template": "cosigner#0" + "policy_id": "6f58d65bb1c61ee0052565d109aefb268989e31d6e254d0324f54a25", + "reference_input": { + "id": "751348501f52652afd6ab6742d126e58150dd233d57be33ce61b531ab9236334", + "index": 0 + } }, { - "asset_name": "546f6b656e48", + "asset_name": "546f6b656e57", "operation": { - "burn": { - "quantity": 29 + "mint": { + "quantity": 17, + "receiving_address": "FHnt4NL7yPXw8zBLWDabfdV56LwTzZfQ1F4VdnFnzG9BoNsTg66oEsGVFtRQwZR" } }, + "policy_id": "2b7aec3e7d7fe7623600c11c47d650beab4f0ca9a8ee76373e4bd0d2", "reference_input": { - "id": "564b3b72bf5f6f6a09295d1a21130250ea15d278661f4c3a0e3921447e7a7d02", - "index": 1 + "id": "62167ac239312c76641d33133e623c1f3153dc1b5e0e764a171c50fe1bb9524f", + "index": 0 } }, { - "asset_name": "546f6b656e52", + "asset_name": "546f6b656e42", "operation": { "mint": { - "quantity": 0, - "receiving_address": "FHnt4NL7yPXhYBUuHmssCJxSofPgrBzttF2b7UpYDJxF84Dc3FF91KxGJzrEFtj" + "quantity": 0 } }, - "policy_script_template": "cosigner#0" + "policy_id": "cda5fa25c77d31fd182e9424acde794500f185f53499f22209ca7833", + "reference_input": { + "id": "797b014a0262805d06632649c9ad3c4b40fd183de64d5a4f4d58e07a5e6f9248", + "index": 1 + } }, { + "asset_name": "546f6b656e4c", "operation": { - "burn": { - "quantity": 15 + "mint": { + "quantity": 1, + "receiving_address": "addr_test1xpfdc02rkmfyvh5kzzwwwk4kr2l9a8qa3g7feehl3ga022rz8kdhjn4edy2v5qyvuzrd3n85k9xw57s8pz4urrystrgs5l7m89" } }, - "reference_input": { - "id": "241a0a16164ead2b0069203b9049606b68045c0b4f52292f102d7606754d7d63", - "index": 0 - } + "policy_script_template": "cosigner#0" }, { - "asset_name": "546f6b656e4f", + "asset_name": "546f6b656e4c", "operation": { - "burn": { - "quantity": 23 + "mint": { + "quantity": 17, + "receiving_address": "FHnt4NL7yPXvGbPgRPo676KNPepFQeQvHx6xiwbfe7GEz7LB14L3znq1z9kvTZU" } }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] - } + "policy_script_template": "cosigner#0" }, { + "asset_name": "546f6b656e54", "operation": { "burn": { - "quantity": 9 + "quantity": 20 } }, - "reference_input": { - "id": "0941a01a7a5e7b2b107b7750690d0d2726c33205266725342d82943c6f3f580b", - "index": 0 - } + "policy_script_template": "cosigner#0" }, { - "asset_name": "546f6b656e45", + "asset_name": "546f6b656e49", "operation": { "mint": { - "quantity": 25, - "receiving_address": "FHnt4NL7yPY7VYzad3bUkZTtDhGd4n9XmNbYYJc38wA71tuK7T2RXKqKCnUwm7U" + "quantity": 6 } }, "policy_script_template": { @@ -5201,19 +3700,15 @@ "cosigner#0", { "active_from": 100 - }, - { - "active_until": 150 } ] } }, { - "asset_name": "546f6b656e4f", + "asset_name": "546f6b656e55", "operation": { "mint": { - "quantity": 6, - "receiving_address": "FHnt4NL7yPXgTFpzV7s1QxbTgHQeFiRYA29zBWvakCK2Yt45xN6KpfRPMb14jy1" + "quantity": 1 } }, "policy_script_template": { @@ -5221,31 +3716,89 @@ "cosigner#0", { "active_from": 100 - }, - { - "active_until": 150 } ] } }, { - "asset_name": "546f6b656e49", + "asset_name": "546f6b656e57", + "operation": { + "burn": { + "quantity": 0 + } + }, + "policy_id": "6ada75b13869f723c2b5e9099f8e552e91941ebf8efab2e61025eda1", + "reference_input": { + "id": "003be17a21f006383b30721d635d3ac151ca550e110357781e6e365a444f0f17", + "index": 0 + } + }, + { + "asset_name": "546f6b656e52", "operation": { "mint": { - "quantity": 11, - "receiving_address": "addr_test1wzgjg8fl600txkk9ymheq248mhg65kw7pdu4e7l9c54n59gzkv94a" + "quantity": 1, + "receiving_address": "addr_test1wznaxkkhnfxttq77ljqdr60qj3zusnsxy7nrqdh9xx8v5fq2sqzd2" + } + }, + "policy_id": "8f9147e4966d694d36bbb8ecd5f1e8fd59682a1f3d7120c6c34034ca", + "reference_input": { + "id": "3fd826670e7f0e7540318348a82110737f3a06a9337baf764c491173e024b86c", + "index": 1 + } + }, + { + "asset_name": "546f6b656e4c", + "operation": { + "burn": { + "quantity": 3 + } + }, + "policy_id": "51e2b059d71a82950f4508a75ae799dd85369078f246e19e68250644", + "reference_input": { + "id": "3b39407c051e5665420a870246511eb77546461b482456251539e0380d416140", + "index": 0 + } + }, + { + "operation": { + "mint": { + "quantity": 22, + "receiving_address": "addr_test1qqgsl0uadsv423sus0xnkv36fvmhr3vcqvp5ldes52vyahshtjgzqh0jeg9q30wjc7wevfj5skxnnscu76cwjuxcdkhsc3wasl" } }, + "policy_id": "9383b6d6f41e4c1d97b275218cc17474f5a588823b06fa024ae8f910", "reference_input": { - "id": "2b387191360e5b943875484f5c28766a34614e323e3e430a1b4461767513623f", + "id": "3bd16b6957077c34c14e6e78f15ad61d11380d7f0e29176c3098df592922c176", "index": 1 } }, { + "asset_name": "546f6b656e46", + "operation": { + "burn": { + "quantity": 17 + } + }, + "policy_id": "14aa05b0821374bf8aa7d63c066c349a457f5bee83e1dd08abf9c23d", + "reference_input": { + "id": "4d482b40145a330d027c2f174177425d32286b104836044b212a9a1f177bf04a", + "index": 1 + } + }, + { + "operation": { + "mint": { + "quantity": 9 + } + }, + "policy_script_template": "cosigner#0" + }, + { + "asset_name": "546f6b656e45", "operation": { - "mint": { - "quantity": 0, - "receiving_address": "FHnt4NL7yPYGakxtCHhqByiPpuRNfqM8kgJzr3P2k8r86RdGn7P3kPC46Tj2qkS" + "burn": { + "quantity": 7 } }, "policy_script_template": { @@ -5259,34 +3812,38 @@ } ] } - } - ], - "withdrawal": "self" - }, - { - "encoding": "base64", - "metadata": { - "15": { - "string": "跾" - } - }, - "mint_burn": [ + }, { "operation": { "burn": { - "quantity": 13 + "quantity": 18 } }, + "policy_id": "a67cd7d9047cae98ccb7c0214eec750f1f1a04a0daeccf75eeb73b53", "reference_input": { - "id": "8f178a6029e2121a0e2b5824012075765b1a4238a00b6c58784c7f603470316a", - "index": 1 + "id": "6cce361a99321b0716eb3144ba0d103d602390586d0063702157275b59426eda", + "index": 0 } }, { - "asset_name": "546f6b656e4f", "operation": { - "burn": { - "quantity": 1 + "mint": { + "quantity": 13, + "receiving_address": "FHnt4NL7yPY6dda9U116um1MiU2PhMNJX4B2igjK2pdNDsCZkwwtxR9Cz4sFrV5" + } + }, + "policy_id": "ad66e8335bac55f2ba473c3dcd56395e50b5f67112ddb7c443df44bb", + "reference_input": { + "id": "1e47751f46117a1c5476ab2bc57c2a64165219604a2a1b2b183913020f1e2828", + "index": 0 + } + }, + { + "asset_name": "546f6b656e41", + "operation": { + "mint": { + "quantity": 27, + "receiving_address": "addr_test1zq6npny6ulegj5g34xdh5qscfhtupn48gf83vvkh89gmr4am2ceyap83qtjjjqsm48zu9czhgfl4sjm2v7595pwacwmqt3xl9t" } }, "policy_script_template": { @@ -5299,21 +3856,37 @@ } }, { - "asset_name": "546f6b656e59", "operation": { - "burn": { - "quantity": 14 + "mint": { + "quantity": 16, + "receiving_address": "FHnt4NL7yPXrmAGY8pGSFDHpquqBpBXvWqDvnZHFJChggESuPXZLbQgUDChd5t3" } }, + "policy_id": "5bd5474497df7b8916eb8c912d4025f10b277347faeaa030dbca2a18", "reference_input": { - "id": "4d3854653370cc00566209360572645f270a550b3ba41e456077f6737f77103e", - "index": 0 + "id": "5d1b1f500f4a66385e665eb65cdd4c1b21a53f46063567374474006c05f2853b", + "index": 1 } }, { + "asset_name": "546f6b656e47", "operation": { "burn": { - "quantity": 1 + "quantity": 7 + } + }, + "policy_id": "8caa0613047f5af59f6508930c152bed0d1f650e6d3e2af190fdb9aa", + "reference_input": { + "id": "221b008f0a0d66652069c81454343b773756646016086d3c240b5e4a2e49792d", + "index": 1 + } + }, + { + "asset_name": "546f6b656e47", + "operation": { + "mint": { + "quantity": 17, + "receiving_address": "FHnt4NL7yPYFApyUo5tf3AfD5g8aLeF1RCEMuYr5BxPrCRsj3nuCF8tYws84doE" } }, "policy_script_template": { @@ -5321,9 +3894,6 @@ "cosigner#0", { "active_from": 100 - }, - { - "active_until": 150 } ] } @@ -5331,18 +3901,30 @@ { "operation": { "mint": { - "quantity": 1 + "quantity": 1, + "receiving_address": "FHnt4NL7yPXmLPKvr8CPMQhPQtozX9CcdgGwLZkp35Kc9dBhaShBjyGHMYsAfwj" } }, + "policy_id": "0ea76b914f266eba8817821aef8c2c95398d74d6b97c039041c9fcf2", "reference_input": { - "id": "100475d6143a275001222c793b6b1c4415cf16a010e73f72492fe14a21231129", - "index": 1 + "id": "2135472c7d7a6835234858890513363576337a0d50273c38080a0b600d161729", + "index": 0 } }, + { + "asset_name": "546f6b656e44", + "operation": { + "mint": { + "quantity": 16, + "receiving_address": "FHnt4NL7yPY7DS1rbdhjWa3US366ZdLSx2XT5iNCzkhGZauKaYejJAe8S44ayTg" + } + }, + "policy_script_template": "cosigner#0" + }, { "operation": { "burn": { - "quantity": 29 + "quantity": 16 } }, "policy_script_template": { @@ -5355,118 +3937,237 @@ } }, { + "asset_name": "546f6b656e49", "operation": { "burn": { - "quantity": 23 + "quantity": 4 } }, + "policy_id": "513f4ced34f263a212a18777e1d45b4b46e367b030edcf84e541ab9f", "reference_input": { - "id": "343d38520d6d18463e543463000870a43d017f1d6f5b2e2dca362656590f0c3e", - "index": 1 + "id": "722b436fed3868764c6925b8596e4574be435f264e1bfc1b43fed57275ad2f36", + "index": 0 + } + } + ] + }, + { + "delegations": [ + { + "join": { + "pool": "pool1wp04qa3aycc4whs4f98kvdfztvjs6hc2pelj2yfzd58qwmwry48", + "stake_key_index": "84" } }, { - "asset_name": "546f6b656e42", + "quit": { + "stake_key_index": "2035" + } + }, + { + "quit": { + "stake_key_index": "15558" + } + }, + { + "join": { + "pool": "pool18dehk93wfdgxqz3ufe6qxaggxcs3j9p4f9ghg4mv9u4gqek4h6v", + "stake_key_index": "77" + } + }, + { + "quit": { + "stake_key_index": "6555" + } + }, + { + "join": { + "pool": "pool1wyn8k9z70cuygas9qf356wsrdadpj6rrspxcqhg484nqukjtrxq", + "stake_key_index": "57" + } + }, + { + "quit": { + "stake_key_index": "3575" + } + }, + { + "quit": { + "stake_key_index": "11863" + } + }, + { + "quit": { + "stake_key_index": "16042" + } + }, + { + "quit": { + "stake_key_index": "9578" + } + }, + { + "join": { + "pool": "pool1tanzv53q05uqsjc4pex8vfzxwaur2efedy73cqslpcszut9ntqa", + "stake_key_index": "127" + } + }, + { + "join": { + "pool": "pool1wcvnjcm00dtp68tap50rv4nl0v7466jpdg83ugnawalqqznf6sp", + "stake_key_index": "55" + } + }, + { + "quit": { + "stake_key_index": "3925" + } + }, + { + "quit": { + "stake_key_index": "8740" + } + }, + { + "join": { + "pool": "pool12ccz2ppe2dk56ncp9y8zq9c4yptpc5n4zcmjqgt9pp2xjmavlkz", + "stake_key_index": "61" + } + } + ], + "encoding": "base16", + "metadata": { + "8": { + "int": 0 + } + }, + "mint_burn": [ + { "operation": { - "burn": { - "quantity": 26 + "mint": { + "quantity": 15, + "receiving_address": "addr_test1zr2yzgn42ws0r2t9lmnavzs0wf9ndrw3hhduyzrnplxwhnct634gth7acztszs2706z5mv3l9sn6z7rmn2dtp9xk0jdqnecqjj" } }, + "policy_id": "30f2e1d2771f5112644c7eece37d3239086bff6f79fed2c2558b018c", "reference_input": { - "id": "0b60ec1817504c2e5e71471a165b5f2c215928437b5c51482e0c0a2f53444119", - "index": 1 + "id": "212f052642498e020d5f692371721623170936631d557910006e3604087f1977", + "index": 0 } }, { - "asset_name": "546f6b656e45", "operation": { "burn": { - "quantity": 26 + "quantity": 29 } }, + "policy_id": "72734bcbdfce2142ba03e91a646226f1de5cf640aaeb246e2d47a95d", "reference_input": { - "id": "74635e553c60142461f3640179e7436e76302c5a72ef206c646d550418464e73", - "index": 1 + "id": "143c4c7521f5623f3e6c4156171931eb592b54395c7d4d727c086e0c6a7a4e8d", + "index": 0 } }, { - "asset_name": "546f6b656e43", "operation": { - "mint": { - "quantity": 27, - "receiving_address": "FHnt4NL7yPXzetDFA1vSXzHEdpZFyhBEmHd3L3m5UCuotGqReeyZbTknw75Agqd" + "burn": { + "quantity": 20 } }, + "policy_id": "3b58eab3aaafe05a084adac63ca2e1307d78e942d371e314e8b514f3", "reference_input": { - "id": "1f0842612e70b15b383a66b31a76793850250d106f1a1208d84b2276105b4d77", - "index": 1 + "id": "76283b423c4774131b2b1051404b3c2a8a142b7247231c2c3849731d5e6b4d3b", + "index": 0 } }, { "asset_name": "546f6b656e4b", "operation": { - "burn": { - "quantity": 25 + "mint": { + "quantity": 9, + "receiving_address": "FHnt4NL7yPY1XG11DS4jmYYr3F5jisWUDFKteq4aWNk4bi3C5ZUGLeUgABAGpFu" } }, - "reference_input": { - "id": "2d263c3c2e06640c5a18dd50257b354a490113236d41203302673c887c0e362b", - "index": 1 + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] } }, { + "asset_name": "546f6b656e46", "operation": { "mint": { - "quantity": 25 + "quantity": 6, + "receiving_address": "FHnt4NL7yPYKiJGWsAq2qdBgvwoZ1TrnT1KJueCzfS33vLBwr3yFLSnUNu5n2Ax" } }, + "policy_id": "45256fb5ae38bab4cc78ba23eabf7508ca84560c90392994bef2c4b0", "reference_input": { - "id": "6752207935554601ed70550d974a59987040ad08141d58434cfb0f482549543d", - "index": 1 + "id": "71c1a65a64217b7d1e5f2ee61e3c5e3077022546040e573100d16b1d9036250a", + "index": 0 } }, { - "asset_name": "546f6b656e42", + "asset_name": "546f6b656e59", "operation": { - "mint": { - "quantity": 12, - "receiving_address": "addr_test1yz236dsfdhwwj82kwph508fk725y7vwrg45zrl8n7ex59dw7ny5jwzv2hk42akrfdqeuueku2gxrwnhhljzzw3e6y2rq8kupnm" + "burn": { + "quantity": 21 } }, + "policy_id": "420358c1842169757e0c0ddb0a8a6e3a7e424b3ec090bb051a2da01f", "reference_input": { - "id": "03537e653739411e5270275c181171687d74dd397e7552b6733427371b6b1c52", + "id": "a2473e4d6768e389417c54aa06095a13023d70177a568909926e31528a31bc1c", "index": 0 } }, { - "asset_name": "546f6b656e51", "operation": { "burn": { - "quantity": 30 + "quantity": 25 } }, + "policy_id": "397bdd98c720c56f8d6520be94a965f8485c9b17111e5176d1e30604", "reference_input": { - "id": "8d1e3a30695a9d08324662097e6fe617dbc97e171a5e34076856346d0846ca46", - "index": 0 + "id": "673d5e6a005553546400a24a748f7e7e5a83431634571c746734fe721329756b", + "index": 1 + } + }, + { + "operation": { + "mint": { + "quantity": 2, + "receiving_address": "addr_test1ypwnzwjp6gt4zp7dxe0yxja76mxr4pswf306jzwusucru8k5gy3825aq7x5ktlh86c9q7ujtx6xar0wmcgy8xr7va08s5tslnd" + } + }, + "policy_id": "f42072f9d3592a65a5b9bcb6ada3f996801fbec05d57d5038408333e", + "reference_input": { + "id": "721a0d39af20496cd45b6d126900be687a6b5c1f7016204746653e4e3b1d9a11", + "index": 1 } }, { - "asset_name": "546f6b656e4e", "operation": { "mint": { - "quantity": 8, - "receiving_address": "FHnt4NL7yPXzbeXrEUm3wCGXY6WzSxoiHRL9ayvnEWs7DhwnerBHNjSfiCFk3aR" + "quantity": 25 } }, + "policy_id": "f6643041eb0953c63e81704a441a826847ff29bc3b5983c05dd2c6d8", "reference_input": { - "id": "03607c3d376a2e5f564e51bd5b49364e6116776248f1432430446bcc25e27d69", + "id": "52a4dc3c01ed06061357574832794a44705f7a1d4d213b1d174e2b456d67472e", "index": 1 } }, { + "asset_name": "546f6b656e56", "operation": { "burn": { - "quantity": 11 + "quantity": 12 } }, "policy_script_template": { @@ -5479,85 +4180,84 @@ } }, { - "asset_name": "546f6b656e53", + "operation": { + "burn": { + "quantity": 12 + } + }, + "policy_script_template": "cosigner#0" + }, + { "operation": { "mint": { - "quantity": 25, - "receiving_address": "FHnt4NL7yPY5yf382E8vcJLrUZtE6ZUNQXAWWQmzZ544BYP9ktTbgi5uCF4E1C8" + "quantity": 30 } }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] + "policy_id": "fe4b163390f4b5434abfbd6e9d260341f9c3d80a57f4c4bd7bf497e1", + "reference_input": { + "id": "3a62523b060d1c364b665a121a394276164e64eb3021b3176268124890392024", + "index": 0 } }, { - "asset_name": "546f6b656e59", "operation": { "burn": { - "quantity": 28 + "quantity": 5 } }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - }, - { - "active_until": 150 - } - ] + "policy_id": "a611c6f20585af1972500ec7a65baf8ea4aa692da6c9f0fc55a52c26", + "reference_input": { + "id": "2f4517080f1e261c321a047a3d721b3267122a013811692502b66a70037c2869", + "index": 0 } }, { "operation": { "mint": { - "quantity": 14, - "receiving_address": "addr_test1xpz29adjeduqszw2jdm8p9mxeazfve5m9qrrycxpll265lwz0ema5fmfmmkj84nrkg58lqyhpr2wug8r8w7tn5aw0zxq0ps04u" + "quantity": 13, + "receiving_address": "addr_test1yzkrx247tzjphrav4mtd7ghzgdms7tfja8m288qzscwafupzls3mn0cpelxvhc8exfzq6w5vnzj2nuylz2ftxznugzls2sypjf" } }, "policy_script_template": "cosigner#0" }, { - "asset_name": "546f6b656e4c", "operation": { "burn": { - "quantity": 22 + "quantity": 11 } }, - "policy_script_template": { - "all": [ - "cosigner#0", - { - "active_from": 100 - } - ] + "policy_id": "d4c9bf240238e494c0c062225b2d3a49982ba4e4d0cbeb34cc6fe991", + "reference_input": { + "id": "42d20e35584138662f5679cc0475662e037f601277641c7e13795231b221310d", + "index": 0 } }, { - "asset_name": "546f6b656e50", "operation": { - "burn": { - "quantity": 12 + "mint": { + "quantity": 1, + "receiving_address": "FHnt4NL7yPXhaXV3CENMraWz1zPYcT6RHqcPffmXMZHo8d1ZuubhNg39nTSkNM2" } }, + "policy_id": "bfc6724f26b5a11874453c0849baecbe68789b27ad06019efafcb746", "reference_input": { - "id": "735c140c4c1b394011063e254f35e535160157042271b667c81e43793e0e4bf4", - "index": 0 + "id": "6f2e53931e783d6c6d3264166d1a07c43f7c17401173b5a0545f6a727f5bc91a", + "index": 1 } }, { + "operation": { + "mint": { + "quantity": 23 + } + }, + "policy_script_template": "cosigner#0" + }, + { + "asset_name": "546f6b656e54", "operation": { "burn": { - "quantity": 18 + "quantity": 30 } }, "policy_script_template": { @@ -5570,21 +4270,23 @@ } }, { + "asset_name": "546f6b656e56", "operation": { - "burn": { - "quantity": 13 + "mint": { + "quantity": 19, + "receiving_address": "addr_test1wrz6979y5hlrrptachhyt0evr0f6tcw9py97r2gx3acn2sg67p8nq" } }, + "policy_id": "554d7ea335a408b5cfa05afdcea169147aaed0fb37247cac59b69ae8", "reference_input": { - "id": "94625815027a3f39336d5edf0416822569799c49e93b5b4b06051a39253ca228", - "index": 1 + "id": "611c4f5670607c595f5c7b6809091a7d39233f8e6362002352be19660171294a", + "index": 0 } }, { - "asset_name": "546f6b656e55", "operation": { "burn": { - "quantity": 8 + "quantity": 7 } }, "policy_script_template": { @@ -5597,294 +4299,255 @@ } }, { - "asset_name": "546f6b656e49", "operation": { "mint": { - "quantity": 14, - "receiving_address": "FHnt4NL7yPYFbTLj2B1qpVbRuh6xXSFVhojMzKasjHNHU7wuBbCVzmfhqqDjU3r" + "quantity": 23, + "receiving_address": "FHnt4NL7yPYDDZJ7Pzu4rSqit25xjj38uvKe7QgoVn2VSUuZ6ABPU3A8AK8f1cC" } }, - "reference_input": { - "id": "5006c223c6355d7a6f674b280d7e742b6774303f5e6f524e010d452e1f0d565f", - "index": 0 - } + "policy_script_template": "cosigner#0" }, { - "asset_name": "546f6b656e51", "operation": { "mint": { - "quantity": 16, - "receiving_address": "addr_test1wrk3rmp03w4x4vsuw8svt0dekyg67lukgykedemkxt93l0cefmkps" + "quantity": 7 } }, "policy_script_template": "cosigner#0" }, { - "asset_name": "546f6b656e4e", + "asset_name": "546f6b656e4d", "operation": { "mint": { - "quantity": 17, - "receiving_address": "addr_test1vq3hsgn747w0vwenxt6wp8qqzvn5d8u2vfufp6yttz6xthgns4564" + "quantity": 4, + "receiving_address": "addr_test1qz7f8fz62n64h9kdexw06auxrz5hzuuw84yjmze0ayx3e6nulrjxmgdzx6fpw2nzxdnqy792k3c6pneuk79fdc9846ase24wcp" } }, + "policy_id": "d0cb3c135245662b2de475300668cf1460eb3c59cd94efa1e0073f3c", "reference_input": { - "id": "b4344961307a6e73d53227647d1c1756585f2910a078210e5a3d752e472b505e", + "id": "4fe43a742e6d2a5443277d38284563ca8924243e4f1a393b5502094a505a0125", "index": 0 } + }, + { + "operation": { + "burn": { + "quantity": 23 + } + }, + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] + } } ], "payments": [ { - "address": "addr_test1vpt3gsp7jfn0kt4xa3t88k3ac955x0ve875rh0wrkggcrmqyxxyxf", + "address": "addr_test1wrynxe0kjkj546l494hs2dd0gvzn5cpdjg3uvn89qqwt7fcfvuee6", "amount": { - "quantity": 208, + "quantity": 143, + "unit": "lovelace" + }, + "assets": [] + }, + { + "address": "addr_test1xpg5jwg90qmqyxfkdtn2mj30gywpur65k2rpwczxjp0kuu0434cgd7wns2xkj8ec6grluzu2u70c7f3n9rf0ftjyhqnskuflxm", + "amount": { + "quantity": 17, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e43", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 29 + "asset_name": "546f6b656e44", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 15 } ] }, { - "address": "FHnt4NL7yPY86CEER3sjgohE1jCMCBnn1baN5uhLBLMMzsHtyb785a8NX8w4vQJ", + "address": "addr_test1qrq473d6mla99ud42ap2suua4dnyy2pl0asfdyr9qhmw78qvp4kewtv9yy0pf9gcv7jjmhx7kewym2j5dyuq423wpyesthydey", "amount": { - "quantity": 146, + "quantity": 7, "unit": "lovelace" }, "assets": [] }, { - "address": "FHnt4NL7yPXkx4aJsHi89hkRqFTsNQPHqJwBsKbNi1uCtRu28ABT43x2CRHb7hz", + "address": "FHnt4NL7yPY5gGxi19eaZUnuCGmCN53aN96NCvtfviGoZdv1t5U7rcfni1H8SPr", "amount": { - "quantity": 153, + "quantity": 177, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e43", + "asset_name": "546f6b656e42", "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 27 + "quantity": 42 }, { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 53 + "asset_name": "546f6b656e44", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 23 }, { - "asset_name": "546f6b656e44", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 8 + "asset_name": "546f6b656e45", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 12 }, { - "asset_name": "546f6b656e42", + "asset_name": "546f6b656e41", + "policy_id": "22222222222222222222222222222222222222222222222222222222", + "quantity": 54 + }, + { + "asset_name": "546f6b656e43", "policy_id": "22222222222222222222222222222222222222222222222222222222", "quantity": 6 }, { - "asset_name": "546f6b656e44", + "asset_name": "546f6b656e45", "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 25 + "quantity": 6 + }, + { + "asset_name": "546f6b656e41", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 14 }, { "asset_name": "546f6b656e42", "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 23 + "quantity": 4 }, { - "asset_name": "546f6b656e44", + "asset_name": "546f6b656e43", "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 17 + "quantity": 1 }, { - "asset_name": "546f6b656e45", + "asset_name": "546f6b656e44", "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 5 + "quantity": 14 }, { - "asset_name": "546f6b656e45", + "asset_name": "546f6b656e42", "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 9 + "quantity": 4 } ] }, { - "address": "addr_test1qqqkqa2ncwnfca00cp2d9z3a3cpaxz6lu8v33ndhxfy74gf89a465ywmzg63uks604nj2c7hgeumyfk3kfffylu2jjksr942tg", - "amount": { - "quantity": 153, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "addr_test1qzlj6uml949g8ncxws58l7q8sev8anjnprc7cgev5xm8raj9mdyz9eu2z0jxdrhngahqn4typrm5kzqhuz9cureqxplqx65kxy", + "address": "addr_test1qp37l5d2y0eps3ldyhu33d5nrj5nu807sjvttruuy4mtukcd9v33yd2nqqt79n8wkkjwag9c03vgee0yae82mp6qyreq7gqu2m", "amount": { - "quantity": 2, + "quantity": 223, "unit": "lovelace" }, "assets": [ { - "asset_name": "546f6b656e41", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 7 - }, - { - "asset_name": "546f6b656e44", + "asset_name": "546f6b656e45", "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 15 + "quantity": 55 }, { - "asset_name": "546f6b656e42", + "asset_name": "546f6b656e41", "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 18 + "quantity": 59 }, { - "asset_name": "546f6b656e44", + "asset_name": "546f6b656e45", "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 30 + "quantity": 14 }, { - "asset_name": "546f6b656e41", + "asset_name": "546f6b656e43", "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 4 + "quantity": 5 }, { - "asset_name": "546f6b656e42", + "asset_name": "546f6b656e43", "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 5 + "quantity": 22 }, { - "asset_name": "546f6b656e42", - "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 12 + "asset_name": "546f6b656e44", + "policy_id": "33333333333333333333333333333333333333333333333333333333", + "quantity": 26 }, { - "asset_name": "546f6b656e43", + "asset_name": "546f6b656e41", "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 31 - } - ] - }, - { - "address": "addr_test1zq6npny6ulegj5g34xdh5qscfhtupn48gf83vvkh89gmr4aklhew6hyf3hzegds922t4vmj8s5azp0xmk4td7zmkepuqueukre", - "amount": { - "quantity": 237, - "unit": "lovelace" - }, - "assets": [] - }, - { - "address": "addr_test1vzad7ua3tpv87k6hmtzhceehp6g9v22j3he0v88wpzn66ms6khyf4", - "amount": { - "quantity": 215, - "unit": "lovelace" - }, - "assets": [ - { - "asset_name": "546f6b656e42", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 30 + "quantity": 11 }, { "asset_name": "546f6b656e42", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 1 + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 8 }, { "asset_name": "546f6b656e43", - "policy_id": "22222222222222222222222222222222222222222222222222222222", - "quantity": 17 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 11 + "policy_id": "44444444444444444444444444444444444444444444444444444444", + "quantity": 39 }, { - "asset_name": "546f6b656e42", + "asset_name": "546f6b656e45", "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 5 + "quantity": 22 } ] }, { - "address": "FHnt4NL7yPY4tSvbCmUSLuvQxQseRbvRk7Mg8GhXtHdAscdSrvBgxw3qMCo4wGJ", + "address": "addr_test1xzwxate7jxvynf6mjx7yltq64ypcjvpelxxd0ka0gp27j23shmw0r9pedyl0pt5h9lrsqah46wka2plshj57vpg0fctqlx4dv6", "amount": { - "quantity": 86, + "quantity": 72, "unit": "lovelace" }, "assets": [] }, { - "address": "FHnt4NL7yPXnqQ23Gxq4qbJLeR23hbQfmKwjeykHj8P89cptBduqPrEwkALBbzV", + "address": "FHnt4NL7yPXjXYqfbecoRbVKNx3uFe4oGiKXu8HHKgzjqFroyWGAbcfYi36pk6X", "amount": { - "quantity": 130, + "quantity": 176, "unit": "lovelace" }, - "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 17 - } - ] + "assets": [] }, { - "address": "addr_test1xr6ft60wym5lxlk2pweevdauwalrasz3mt63zh07kfhax9rtydakpugrfz7xuxzs2gtyeus2glgnshu8lf2l7kvhufrskfgvlt", + "address": "FHnt4NL7yPY89MNw3wpYqcFHMqRTkezpTXqyXCra3NS6sdyb581JiRU7U5gp1HU", "amount": { - "quantity": 157, + "quantity": 224, "unit": "lovelace" }, - "assets": [] + "assets": [ + { + "asset_name": "546f6b656e45", + "policy_id": "00000000000000000000000000000000000000000000000000000000", + "quantity": 6 + } + ] }, { - "address": "FHnt4NL7yPYJ7QqhrsotDVed4MSyKTkYuSgqB3HbMvDwwVYn5KHTA1tRPvE5eoo", + "address": "FHnt4NL7yPXz9TmJPayk1CCy4ZqFy2YzGjSvLrY5dziS16Ek1xin3vLonLy9rs5", "amount": { - "quantity": 186, + "quantity": 177, "unit": "lovelace" }, "assets": [ - { - "asset_name": "546f6b656e43", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 28 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "00000000000000000000000000000000000000000000000000000000", - "quantity": 8 - }, - { - "asset_name": "546f6b656e41", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 7 - }, { "asset_name": "546f6b656e45", - "policy_id": "11111111111111111111111111111111111111111111111111111111", - "quantity": 12 - }, - { - "asset_name": "546f6b656e42", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 28 - }, - { - "asset_name": "546f6b656e44", - "policy_id": "33333333333333333333333333333333333333333333333333333333", - "quantity": 4 - }, - { - "asset_name": "546f6b656e41", "policy_id": "44444444444444444444444444444444444444444444444444444444", - "quantity": 29 + "quantity": 2 } ] } ] } ], - "seed": 1553526325 + "seed": -1216434032 } \ No newline at end of file diff --git a/lib/wallet/test/data/Cardano/Wallet/Api/ApiMintBurnDataTestnet0.json b/lib/wallet/test/data/Cardano/Wallet/Api/ApiMintBurnDataTestnet0.json index d505078fccd..4da77df7606 100644 --- a/lib/wallet/test/data/Cardano/Wallet/Api/ApiMintBurnDataTestnet0.json +++ b/lib/wallet/test/data/Cardano/Wallet/Api/ApiMintBurnDataTestnet0.json @@ -1,33 +1,10 @@ { "samples": [ - { - "asset_name": "546f6b656e4d", - "operation": { - "burn": { - "quantity": 7 - } - }, - "reference_input": { - "id": "0f7a6c100d41352e416b2549520120d52a483539ed22315591108752085d425c", - "index": 0 - } - }, - { - "operation": { - "mint": { - "quantity": 7 - } - }, - "reference_input": { - "id": "655a22276642634d474639793134467121032e1903264c1b38491272554d07a8", - "index": 0 - } - }, { "operation": { "mint": { - "quantity": 26, - "receiving_address": "FHnt4NL7yPXtKMNKWpYBDKfarp5eFKr6JPdUZh8JnBXqd6V2vm7kbQBNzxfeKru" + "quantity": 6, + "receiving_address": "FHnt4NL7yPXsuGx1BoTNhrX2ojBW4oSF76EK9dWi4B1PWmLtaezB37zakqB6uQ2" } }, "policy_script_template": { @@ -43,9 +20,22 @@ } }, { + "asset_name": "546f6b656e43", "operation": { "burn": { - "quantity": 13 + "quantity": 27 + } + }, + "policy_id": "3339df769eb0ae5b10b9d24f05c9523497627b70fb05a427f9411641", + "reference_input": { + "id": "573572ed5419c341412f8a702b1f6c8d2338d8316d07215f3ffc015f1633053a", + "index": 0 + } + }, + { + "operation": { + "mint": { + "quantity": 19 } }, "policy_script_template": { @@ -58,68 +48,83 @@ } }, { - "asset_name": "546f6b656e42", + "asset_name": "546f6b656e43", "operation": { "burn": { - "quantity": 17 + "quantity": 4 } }, + "policy_id": "b5ba75bae15a5330431945a11aa11dbb0c37d26d0fd60f19b500be9e", "reference_input": { - "id": "cf3350f420027389226b48ce4e1dd72859054756694b0b6c4573755a1e077552", - "index": 1 + "id": "80784fb73ab44d183761264b604368fbbc01ed5c781ae96f16e114117748e831", + "index": 0 } }, { + "asset_name": "546f6b656e57", "operation": { "mint": { - "quantity": 17, - "receiving_address": "addr_test1wqw2xldvx8wfj78gjenwumx2xv3m74n6qgdsr2fhsjxm8wcxs9rxv" + "quantity": 21, + "receiving_address": "FHnt4NL7yPXkC2mivpehyq6fPPMkFumVbryp33yAewrJos8JPAuPsbxgFPCL12z" } }, + "policy_id": "33a3b75ac4f64a95e243b43ead610483f70a634482a071f6eaf3dbc5", "reference_input": { - "id": "047c1a694929823f754926b7734d595215317d7b0f62007266485e32357308ee", + "id": "6b507f2f0c0b236205a823685c094b335b12543ebb0dba5a3fac0f7a4818470e", "index": 0 } }, { "operation": { "mint": { - "quantity": 19, - "receiving_address": "FHnt4NL7yPY9cDvFzoXWntoM4SfuP1GNeNBp52cuNaF6GH9LVrqTgR1x63zGWUv" + "quantity": 25, + "receiving_address": "addr_test1wqkq3mg4uvxsqu8rwc0uzrtrx9rqc4zsavga5hvjqj39nfgr7gw54" } }, - "reference_input": { - "id": "20617129573a23071e171d1f431e9a2b0b593da60ec76b4342da56845d4c047a", - "index": 0 + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + }, + { + "active_until": 150 + } + ] } }, { - "asset_name": "546f6b656e53", "operation": { - "burn": { - "quantity": 27 + "mint": { + "quantity": 24 } }, - "policy_script_template": "cosigner#0" + "policy_id": "82a13541ef1c72da1ffdd8b8a707619854dde6ab049538d5c368f258", + "reference_input": { + "id": "2a44c496892079f70a570e440e224c740d6fbc664041783e5829648b627e17ab", + "index": 1 + } }, { - "asset_name": "546f6b656e48", "operation": { - "mint": { - "quantity": 0, - "receiving_address": "addr_test1vzkhfr5w6xhkqyp5kyp8nkw7dpzqxs2fadrx5w55ngy4mecgn4r82" + "burn": { + "quantity": 21 } }, - "reference_input": { - "id": "3f69ea785425165e705d213414056f1b6b6163384a991a794bb63f0c50146461", - "index": 0 + "policy_script_template": { + "all": [ + "cosigner#0", + { + "active_from": 100 + } + ] } }, { - "asset_name": "546f6b656e4c", + "asset_name": "546f6b656e45", "operation": { "mint": { - "quantity": 21 + "quantity": 12 } }, "policy_script_template": { @@ -133,7 +138,21 @@ } ] } + }, + { + "asset_name": "546f6b656e4b", + "operation": { + "mint": { + "quantity": 1, + "receiving_address": "FHnt4NL7yPXjdrWg9JTLRpyzSLfonHwYSwg18tvNLRRR7hhVV1G533yuUVBekVy" + } + }, + "policy_id": "e9297fb13eef4b46d132a19e8127f7f584c370c6c4704987699b9438", + "reference_input": { + "id": "c213e8765f445376301335112a6c69d078e4432b1500183531487231c8e5512d", + "index": 1 + } } ], - "seed": -1584764791 + "seed": -431520963 } \ 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 74fba5b891a..0a970de7d02 100644 --- a/lib/wallet/test/unit/Cardano/Wallet/Api/TypesSpec.hs +++ b/lib/wallet/test/unit/Cardano/Wallet/Api/TypesSpec.hs @@ -2084,6 +2084,7 @@ instance HasSNetworkId n => Arbitrary (ApiMintBurnDataFromScript n) where instance HasSNetworkId n => Arbitrary (ApiMintBurnDataFromInput n) where arbitrary = ApiMintBurnDataFromInput <$> (ReferenceInput <$> arbitrary) + <*> arbitrary <*> oneof [ Just . ApiT <$> genTokenName , pure Nothing diff --git a/specifications/api/mint-burn.md b/specifications/api/mint-burn.md index 1b2437aa1a2..e10802d8d99 100644 --- a/specifications/api/mint-burn.md +++ b/specifications/api/mint-burn.md @@ -33,9 +33,22 @@ Specifically: } ``` -2. Using a refence input that contains a minting script. +2. Getting policy id using the same script template as in point 1. It is realized by calling `POST` on `/wallets/{walletId}/policy-id` endpoint with `POST` data: - In the `mint_burn` field, the array element contains `reference_input`. This field specifies a transaction input (pair of transaction ID and output index) which will be added as a reference input and is assumed to contain the minting script. (If the corresponding output was created using the method above, the appropriate output index is `0`). + ``` + { + "policy_script_template": + { "all": + [ "cosigner#0", + { "active_from": 120 } + ] + } + } + ``` + +3. Using a refence input that contains a minting script. + + In the `mint_burn` field, the array element contains `reference_input` and `policy_id`. The first field specifies a transaction input (pair of transaction ID and output index) which will be added as a reference input and is assumed to contain the minting script. (If the corresponding output was created using the method above, the appropriate output index is `0`). The `policy_id` field is obtained from the response of request realized in point 2. Example `POST` data for the endpoint with reference input: @@ -47,6 +60,7 @@ Specifically: { "id": "464917d2bac71df96269c2d7c34dcb83183b8a3a3253c06e9d6a8bd0681422c9", "index": 0 }, + "policy_id": "7191ae0e1286891fe5c027a5dc041b7401689938e18e14ec83cf74fb", "asset_name": "ab12", "operation": { "mint" : diff --git a/specifications/api/swagger.yaml b/specifications/api/swagger.yaml index b7e125046f0..61f06febbcb 100644 --- a/specifications/api/swagger.yaml +++ b/specifications/api/swagger.yaml @@ -3657,8 +3657,10 @@ components: required: - operation - reference_input + - policy_id properties: reference_input: *referenceInput + policy_id: *assetPolicyId asset_name: *assetName operation: *ApiMintBurnOperation