diff --git a/.gitignore b/.gitignore index acb78b5c4e4..1b8da7efc30 100644 --- a/.gitignore +++ b/.gitignore @@ -28,3 +28,6 @@ cabal.sandbox.config ### Nix ### result* .stack-to-nix.cache + +### auto-generated faulty JSON golden tests ### +*.faulty.json diff --git a/lib/core-integration/src/Test/Integration/Scenario/API/Shelley/Wallets.hs b/lib/core-integration/src/Test/Integration/Scenario/API/Shelley/Wallets.hs index 7d1809a69a0..24c40f31740 100644 --- a/lib/core-integration/src/Test/Integration/Scenario/API/Shelley/Wallets.hs +++ b/lib/core-integration/src/Test/Integration/Scenario/API/Shelley/Wallets.hs @@ -23,6 +23,7 @@ import Cardano.Wallet.Api.Types , ApiAddress , ApiByronWallet , ApiCoinSelection + , ApiCoinSelectionInput (derivationPath) , ApiNetworkInformation , ApiT (..) , ApiTransaction @@ -34,7 +35,12 @@ import Cardano.Wallet.Api.Types , WalletStyle (..) ) import Cardano.Wallet.Primitive.AddressDerivation - ( PassphraseMaxLength (..), PassphraseMinLength (..), PaymentAddress ) + ( DerivationType (..) + , Index (..) + , PassphraseMaxLength (..) + , PassphraseMinLength (..) + , PaymentAddress + ) import Cardano.Wallet.Primitive.AddressDerivation.Byron ( ByronKey ) import Cardano.Wallet.Primitive.AddressDerivation.Icarus @@ -42,15 +48,17 @@ import Cardano.Wallet.Primitive.AddressDerivation.Icarus import Cardano.Wallet.Primitive.AddressDerivation.Shelley ( ShelleyKey ) import Cardano.Wallet.Primitive.AddressDiscovery.Sequential - ( AddressPoolGap (..) ) + ( AddressPoolGap (..), coinTypeAda, purposeCIP1852 ) import Cardano.Wallet.Primitive.SyncProgress ( SyncProgress (..) ) import Cardano.Wallet.Primitive.Types - ( walletNameMaxLength, walletNameMinLength ) + ( DerivationIndex (..), walletNameMaxLength, walletNameMinLength ) import Control.Monad ( forM_ ) import Data.Generics.Internal.VL.Lens ( view, (^.) ) +import Data.List + ( isPrefixOf ) import Data.List.NonEmpty ( NonEmpty ((:|)) ) import Data.Proxy @@ -915,9 +923,18 @@ spec = describe "SHELLEY_WALLETS" $ do targetAddress : _ <- fmap (view #id) <$> listAddresses @n ctx target let amount = Quantity minUTxOValue let payment = AddressAmount targetAddress amount + let hasValidDerivationPath input = + ( length (derivationPath input) == 5 ) + && + ( [ ApiT $ DerivationIndex $ getIndex purposeCIP1852 + , ApiT $ DerivationIndex $ getIndex coinTypeAda + , ApiT $ DerivationIndex $ getIndex @'Hardened minBound + ] `isPrefixOf` NE.toList (derivationPath input) + ) selectCoins @_ @'Shelley ctx source (payment :| []) >>= flip verify [ expectResponseCode HTTP.status200 , expectField #inputs (`shouldSatisfy` (not . null)) + , expectField #inputs (`shouldSatisfy` all hasValidDerivationPath) , expectField #outputs (`shouldSatisfy` ((> 1) . length)) , expectField #outputs (`shouldSatisfy` (payment `elem`)) ] diff --git a/lib/core/src/Cardano/Wallet.hs b/lib/core/src/Cardano/Wallet.hs index 9e0537ffb21..2ab2a0834a4 100644 --- a/lib/core/src/Cardano/Wallet.hs +++ b/lib/core/src/Cardano/Wallet.hs @@ -248,6 +248,7 @@ import Cardano.Wallet.Primitive.AddressDiscovery.Sequential , defaultAddressPoolGap , mkSeqStateFromRootXPrv , mkUnboundedAddressPoolGap + , purposeBIP44 , shrinkPool ) import Cardano.Wallet.Primitive.CoinSelection @@ -291,6 +292,7 @@ import Cardano.Wallet.Primitive.Types , ChimericAccount (..) , Coin (..) , DelegationCertificate (..) + , DerivationIndex , Direction (..) , FeePolicy (LinearFee) , GenesisParameters (..) @@ -306,9 +308,11 @@ import Cardano.Wallet.Primitive.Types , SortOrder (..) , TransactionInfo (..) , Tx + , TxIn , TxMeta (..) , TxMetadata , TxOut (..) + , TxOut (..) , TxStatus (..) , UTxO (..) , UTxOStatistics @@ -604,7 +608,7 @@ createIcarusWallet -> (k 'RootK XPrv, Passphrase "encryption") -> ExceptT ErrWalletAlreadyExists IO WalletId createIcarusWallet ctx wid wname credentials = db & \DBLayer{..} -> do - let s = mkSeqStateFromRootXPrv @n credentials $ + let s = mkSeqStateFromRootXPrv @n credentials purposeBIP44 $ mkUnboundedAddressPoolGap 10000 let (hist, cp) = initWallet block0 gp s let addrs = map address . concatMap (view #outputs . fst) $ hist @@ -614,6 +618,7 @@ createIcarusWallet ctx wid wname credentials = db & \DBLayer{..} -> do (shrinkPool @n (liftPaymentAddress @n) addrs g (Seq.externalPool s)) (Seq.pendingChangeIxs s) (Seq.rewardAccountKey s) + (Seq.derivationPrefix s) now <- lift getCurrentTime let meta = WalletMetadata { name = wname @@ -1624,7 +1629,7 @@ signTx -> WalletId -> Passphrase "raw" -> Maybe TxMetadata - -> UnsignedTx + -> UnsignedTx (TxIn, TxOut) -> ExceptT ErrSignPayment IO (Tx, TxMeta, UTCTime, SealedTx) signTx ctx wid pwd md (UnsignedTx inpsNE outsNE) = db & \DBLayer{..} -> do withRootKey @_ @s ctx wid pwd ErrSignPaymentWithRootKey $ \xprv scheme -> do @@ -1660,6 +1665,7 @@ selectCoinsExternal , HasLogger WalletLog ctx , HasTransactionLayer t k ctx , e ~ ErrValidateSelection t + , IsOurs s Address ) => ctx -> WalletId @@ -1667,22 +1673,49 @@ selectCoinsExternal -> NonEmpty TxOut -> Quantity "lovelace" Word64 -> Maybe TxMetadata - -> ExceptT (ErrSelectCoinsExternal e) IO UnsignedTx + -> ExceptT + (ErrSelectCoinsExternal e) + IO + (UnsignedTx (TxIn, TxOut, NonEmpty DerivationIndex)) selectCoinsExternal ctx wid argGenChange payments withdrawal md = do cs <- withExceptT ErrSelectCoinsExternalUnableToMakeSelection $ selectCoinsForPayment @ctx @s @t @k @e ctx wid payments withdrawal md - cs' <- db & \DBLayer{..} -> + (cs', s') <- db & \DBLayer{..} -> withExceptT ErrSelectCoinsExternalNoSuchWallet $ mapExceptT atomically $ do cp <- withNoSuchWallet wid $ readCheckpoint $ PrimaryKey wid (cs', s') <- assignChangeAddresses argGenChange cs (getState cp) putCheckpoint (PrimaryKey wid) (updateState s' cp) - pure cs' + pure (cs', s') UnsignedTx - <$> ensureNonEmpty (inputs cs') ErrSelectCoinsExternalUnableToAssignInputs - <*> ensureNonEmpty (outputs cs') ErrSelectCoinsExternalUnableToAssignOutputs + <$> (fullyQualifiedInputs s' cs' >>= flip ensureNonEmpty + ErrSelectCoinsExternalUnableToAssignInputs) + <*> ensureNonEmpty (outputs cs') + ErrSelectCoinsExternalUnableToAssignOutputs where db = ctx ^. dbLayer @s @k + + fullyQualifiedInputs + :: s + -> CoinSelection + -> ExceptT + (ErrSelectCoinsExternal e) + IO + [(TxIn, TxOut, NonEmpty DerivationIndex)] + fullyQualifiedInputs s cs = + traverse withDerivationPath (inputs cs) + where + withDerivationPath + :: (TxIn, TxOut) + -> ExceptT + (ErrSelectCoinsExternal e) + IO + (TxIn, TxOut, NonEmpty DerivationIndex) + withDerivationPath (txin, txout) = do + case fst $ isOurs (address txout) s of + Nothing -> throwE $ ErrSelectCoinsExternalUnableToAssignInputs wid + Just path -> pure (txin, txout, path) + ensureNonEmpty :: forall a. [a] -> (WalletId -> ErrSelectCoinsExternal e) @@ -1805,15 +1838,15 @@ mkTxMeta interpretTime blockHeader wState tx cs expiry = ourCoins :: TxOut -> Maybe Natural ourCoins (TxOut addr (Coin val)) = - if fst (isOurs addr wState) - then Just (fromIntegral val) - else Nothing + case fst (isOurs addr wState) of + Just{} -> Just (fromIntegral val) + Nothing -> Nothing ourWithdrawal :: (ChimericAccount, Coin) -> Maybe Natural ourWithdrawal (acct, (Coin val)) = - if fst (isOurs acct wState) - then Just (fromIntegral val) - else Nothing + case fst (isOurs acct wState) of + Just{} -> Just (fromIntegral val) + Nothing -> Nothing -- | Broadcast a (signed) transaction to the network. submitTx diff --git a/lib/core/src/Cardano/Wallet/Api/Server.hs b/lib/core/src/Cardano/Wallet/Api/Server.hs index 84cb558d18b..47fdaf605fd 100644 --- a/lib/core/src/Cardano/Wallet/Api/Server.hs +++ b/lib/core/src/Cardano/Wallet/Api/Server.hs @@ -259,6 +259,7 @@ import Cardano.Wallet.Primitive.AddressDiscovery.Sequential , defaultAddressPoolGap , mkSeqStateFromAccountXPub , mkSeqStateFromRootXPrv + , purposeCIP1852 ) import Cardano.Wallet.Primitive.CoinSelection ( CoinSelection (..), changeBalance, inputBalance ) @@ -283,6 +284,7 @@ import Cardano.Wallet.Primitive.Types , Block , BlockHeader (..) , Coin (..) + , DerivationIndex (..) , Hash (..) , NetworkParameters (..) , PassphraseScheme (..) @@ -349,6 +351,8 @@ import Data.Generics.Labels () import Data.List ( isInfixOf, isSubsequenceOf, sortOn ) +import Data.List.NonEmpty + ( NonEmpty ) import Data.Map.Strict ( Map ) import Data.Maybe @@ -602,7 +606,7 @@ postShelleyWallet -> WalletPostData -> Handler ApiWallet postShelleyWallet ctx generateKey body = do - let state = mkSeqStateFromRootXPrv (rootXPrv, pwd) g + let state = mkSeqStateFromRootXPrv (rootXPrv, pwd) purposeCIP1852 g void $ liftHandler $ initWorker @_ @s @k ctx wid (\wrk -> W.createWallet @(WorkerCtx ctx) @s @k wrk wid wName state) (\wrk -> W.restoreWallet @(WorkerCtx ctx) @s @t @k wrk wid) @@ -638,7 +642,7 @@ postAccountWallet -> AccountPostData -> Handler w postAccountWallet ctx mkWallet liftKey coworker body = do - let state = mkSeqStateFromAccountXPub (liftKey accXPub) g + let state = mkSeqStateFromAccountXPub (liftKey accXPub) purposeCIP1852 g void $ liftHandler $ initWorker @_ @s @k ctx wid (\wrk -> W.createWallet @(WorkerCtx ctx) @s @k wrk wid wName state) (\wrk -> W.restoreWallet @(WorkerCtx ctx) @s @t @k wrk wid) @@ -1107,6 +1111,7 @@ selectCoins , s ~ SeqState n k , SoftDerivation k , ctx ~ ApiLayer s t k + , IsOurs s Address ) => ctx -> ArgGenChange s @@ -1574,7 +1579,7 @@ assignMigrationAddresses -- ^ Target addresses -> [CoinSelection] -- ^ Migration data for the source wallet. - -> [UnsignedTx] + -> [UnsignedTx (TxIn, TxOut)] assignMigrationAddresses addrs selections = fst $ foldr accumulate ([], cycle addrs) selections where @@ -1582,7 +1587,7 @@ assignMigrationAddresses addrs selections = (\addrsSelected -> makeTx sel addrsSelected : txs) (splitAt (length $ change sel) addrsAvailable) - makeTx :: CoinSelection -> [Address] -> UnsignedTx + makeTx :: CoinSelection -> [Address] -> UnsignedTx (TxIn, TxOut) makeTx sel addrsSelected = UnsignedTx (NE.fromList (sel ^. #inputs)) (NE.fromList (zipWith TxOut addrsSelected (sel ^. #change))) @@ -1771,7 +1776,10 @@ rndStateChange ctx (ApiT wid) pwd = pure (xprv, preparePassphrase scheme pwd) -- | Makes an 'ApiCoinSelection' from the given 'UnsignedTx'. -mkApiCoinSelection :: forall n. UnsignedTx -> ApiCoinSelection n +mkApiCoinSelection + :: forall n. () + => UnsignedTx (TxIn, TxOut, NonEmpty DerivationIndex) + -> ApiCoinSelection n mkApiCoinSelection (UnsignedTx inputs outputs) = ApiCoinSelection (mkApiCoinSelectionInput <$> inputs) @@ -1781,13 +1789,16 @@ mkApiCoinSelection (UnsignedTx inputs outputs) = mkAddressAmount (TxOut addr (Coin c)) = AddressAmount (ApiT addr, Proxy @n) (Quantity $ fromIntegral c) - mkApiCoinSelectionInput :: (TxIn, TxOut) -> ApiCoinSelectionInput n - mkApiCoinSelectionInput (TxIn txid index, TxOut addr (Coin c)) = + mkApiCoinSelectionInput + :: (TxIn, TxOut, NonEmpty DerivationIndex) + -> ApiCoinSelectionInput n + mkApiCoinSelectionInput (TxIn txid index, TxOut addr (Coin c), path) = ApiCoinSelectionInput { id = ApiT txid , index = index , address = (ApiT addr, Proxy @n) , amount = Quantity $ fromIntegral c + , derivationPath = ApiT <$> path } mkApiTransaction diff --git a/lib/core/src/Cardano/Wallet/Api/Types.hs b/lib/core/src/Cardano/Wallet/Api/Types.hs index dfcfff11324..1f780f59e02 100644 --- a/lib/core/src/Cardano/Wallet/Api/Types.hs +++ b/lib/core/src/Cardano/Wallet/Api/Types.hs @@ -42,10 +42,6 @@ module Cardano.Wallet.Api.Types -- * API Types , ApiAddress (..) - , ApiAddressDerivationPath (..) - , ApiAddressDerivationSegment (..) - , ApiAddressDerivationType (..) - , ApiRelativeAddressIndex (..) , ApiEpochInfo (..) , ApiSelectCoinsData (..) , ApiCoinSelection (..) @@ -151,6 +147,7 @@ import Cardano.Mnemonic ) import Cardano.Wallet.Primitive.AddressDerivation ( Depth (..) + , DerivationType (..) , Index (..) , NetworkDiscriminant (..) , Passphrase (..) @@ -174,6 +171,7 @@ import Cardano.Wallet.Primitive.Types , ChimericAccount (..) , Coin (..) , DecentralizationLevel (..) + , DerivationIndex (..) , Direction (..) , EpochLength (..) , EpochNo (..) @@ -206,7 +204,7 @@ import Control.Applicative import Control.Arrow ( left ) import Control.Monad - ( guard, (<=<), (>=>) ) + ( guard, (>=>) ) import Data.Aeson ( FromJSON (..) , SumEncoding (..) @@ -248,6 +246,8 @@ import Data.Proxy ( Proxy (..) ) import Data.Quantity ( Percentage, Quantity (..) ) +import Data.Scientific + ( Scientific, toBoundedInteger ) import Data.String ( IsString ) import Data.Text @@ -276,6 +276,8 @@ import GHC.TypeLits ( Nat, Symbol ) import Numeric.Natural ( Natural ) +import Safe + ( readMay ) import Servant.API ( MimeRender (..), MimeUnrender (..), OctetStream ) import Web.HttpApiData @@ -370,33 +372,6 @@ data ApiAddress (n :: NetworkDiscriminant) = ApiAddress , state :: !(ApiT AddressState) } deriving (Eq, Generic, Show) -newtype ApiAddressDerivationPath = ApiAddressDerivationPath - { unApiAddressDerivationPath :: NonEmpty ApiAddressDerivationSegment - } deriving (Eq, Generic, Show) - -data ApiAddressDerivationSegment = ApiAddressDerivationSegment - { derivationIndex :: !ApiRelativeAddressIndex - , derivationType :: !ApiAddressDerivationType - } deriving (Eq, Generic, Show) - --- | Represents a type of address derivation. --- --- Note that the values of this type are a strict subset of those provided --- by 'DerivationType' from 'Cardano.Wallet.Primitive.AddressDerivation'. --- -data ApiAddressDerivationType - = Hardened - | Soft - deriving (Bounded, Enum, Eq, Generic, Show) - --- | Represents a relative address index. --- --- The range of this type is exactly half that of a 'Word32'. --- -newtype ApiRelativeAddressIndex = ApiRelativeAddressIndex - { unApiRelativeAddressIndex :: Word31 - } deriving (Bounded, Enum, Eq, Generic, Show) - data ApiEpochInfo = ApiEpochInfo { epochNumber :: !(ApiT EpochNo) , epochStartTime :: !UTCTime @@ -415,6 +390,7 @@ data ApiCoinSelectionInput (n :: NetworkDiscriminant) = ApiCoinSelectionInput { id :: !(ApiT (Hash "Tx")) , index :: !Word32 , address :: !(ApiT Address, Proxy n) + , derivationPath :: NonEmpty (ApiT DerivationIndex) , amount :: !(Quantity "lovelace" Natural) } deriving (Eq, Generic, Show) @@ -969,44 +945,46 @@ instance DecodeAddress n => FromJSON (ApiAddress n) where instance EncodeAddress n => ToJSON (ApiAddress n) where toJSON = genericToJSON defaultRecordTypeOptions -instance ToJSON ApiAddressDerivationPath where - toJSON = toJSON . unApiAddressDerivationPath -instance FromJSON ApiAddressDerivationPath where - parseJSON = fmap ApiAddressDerivationPath . parseJSON - -instance ToJSON ApiAddressDerivationSegment where - toJSON = genericToJSON defaultRecordTypeOptions -instance FromJSON ApiAddressDerivationSegment where - parseJSON = genericParseJSON defaultRecordTypeOptions - -instance ToJSON (ApiAddressDerivationType) where - toJSON = genericToJSON defaultSumTypeOptions -instance FromJSON (ApiAddressDerivationType) where - parseJSON = genericParseJSON defaultSumTypeOptions +instance ToJSON (ApiT DerivationIndex) where + toJSON (ApiT (DerivationIndex ix)) + | ix >= firstHardened = toJSON (show (ix - firstHardened) <> "H") + | otherwise = toJSON (show ix) + where + firstHardened = getIndex @'Hardened minBound -instance ToJSON ApiRelativeAddressIndex where - toJSON = toJSON . fromEnum -instance FromJSON ApiRelativeAddressIndex where - parseJSON = eitherToParser . integerToIndex <=< parseJSON +instance FromJSON (ApiT DerivationIndex) where + parseJSON value = ApiT <$> (parseJSON value >>= parseAsText) where - integerToIndex :: Integer -> Either String ApiRelativeAddressIndex - integerToIndex i - | i < minIntegerBound = Left errorMessage - | i > maxIntegerBound = Left errorMessage - | otherwise = Right - $ ApiRelativeAddressIndex - $ fromIntegral i - - minIntegerBound = toInteger $ unApiRelativeAddressIndex minBound - maxIntegerBound = toInteger $ unApiRelativeAddressIndex maxBound - - errorMessage = mconcat - [ "A relative address index must be a natural number between " - , show minIntegerBound - , " and " - , show maxIntegerBound - , "." - ] + firstHardened = getIndex @'Hardened minBound + + parseAsText :: Text -> Aeson.Parser DerivationIndex + parseAsText txt = + if "H" `T.isSuffixOf` txt then do + DerivationIndex ix <- castNumber (T.init txt) >>= parseAsScientific + pure $ DerivationIndex $ ix + firstHardened + else + castNumber txt >>= parseAsScientific + + parseAsScientific :: Scientific -> Aeson.Parser DerivationIndex + parseAsScientific x = + case toBoundedInteger x of + Just ix | ix < firstHardened -> pure $ DerivationIndex ix + _ -> fail $ mconcat + [ "A derivation index must be a natural number between " + , show (getIndex @'Soft minBound) + , " and " + , show (getIndex @'Soft maxBound) + , "." + ] + + castNumber :: Text -> Aeson.Parser Scientific + castNumber txt = + case readMay (T.unpack txt) of + Nothing -> + fail "expected a number as string with an optional 'H' \ + \suffix (e.g. \"1815H\" or \"44\"" + Just s -> + pure s instance FromJSON ApiEpochInfo where parseJSON = genericParseJSON defaultRecordTypeOptions diff --git a/lib/core/src/Cardano/Wallet/DB/Sqlite.hs b/lib/core/src/Cardano/Wallet/DB/Sqlite.hs index 6a44a76049f..9626013500a 100644 --- a/lib/core/src/Cardano/Wallet/DB/Sqlite.hs +++ b/lib/core/src/Cardano/Wallet/DB/Sqlite.hs @@ -102,6 +102,12 @@ import Cardano.Wallet.Primitive.AddressDerivation , SoftDerivation (..) , WalletKey (..) ) +import Cardano.Wallet.Primitive.AddressDerivation.Icarus + ( IcarusKey ) +import Cardano.Wallet.Primitive.AddressDerivation.Jormungandr + ( JormungandrKey ) +import Cardano.Wallet.Primitive.AddressDerivation.Shelley + ( ShelleyKey ) import Cardano.Wallet.Primitive.Slotting ( TimeInterpreter, epochOf, firstSlotInEpoch, startTime ) import Control.Concurrent.MVar @@ -211,6 +217,7 @@ withDBLayer :: forall s k a. ( PersistState s , PersistPrivateKey (k 'RootK) + , WalletKey k ) => Tracer IO DBLog -- ^ Logging object @@ -336,10 +343,12 @@ data SqlColumnStatus -- startup. -- migrateManually - :: Tracer IO DBLog + :: WalletKey k + => Tracer IO DBLog + -> Proxy k -> DefaultFieldValues -> ManualMigration -migrateManually tr defaultFieldValues = +migrateManually tr proxy defaultFieldValues = ManualMigration $ \conn -> do assignDefaultPassphraseScheme conn @@ -360,6 +369,8 @@ migrateManually tr defaultFieldValues = removeOldTxParametersTable conn addAddressStateIfMissing conn + + addSeqStateDerivationPrefixIfMissing conn where -- NOTE -- Wallets created before the 'PassphraseScheme' was introduced have no @@ -507,6 +518,35 @@ migrateManually tr defaultFieldValues = _ <- Sqlite.step query Sqlite.finalize query + addSeqStateDerivationPrefixIfMissing :: Sqlite.Connection -> IO () + addSeqStateDerivationPrefixIfMissing conn + | isIcarusDatabase = do + addColumn_ conn True (DBField SeqStateDerivationPrefix) icarusPrefix + + | isShelleyDatabase = do + addColumn_ conn True (DBField SeqStateDerivationPrefix) shelleyPrefix + + | isJormungandrDatabase = do + addColumn_ conn True (DBField SeqStateDerivationPrefix) jormungandrPrefix + + | otherwise = + return () + where + isIcarusDatabase = + keyTypeDescriptor proxy == keyTypeDescriptor (Proxy @IcarusKey) + icarusPrefix = T.pack $ show $ toText + $ Seq.DerivationPrefix (Seq.purposeBIP44, Seq.coinTypeAda, minBound) + + isShelleyDatabase = + keyTypeDescriptor proxy == keyTypeDescriptor (Proxy @ShelleyKey) + shelleyPrefix = T.pack $ show $ toText + $ Seq.DerivationPrefix (Seq.purposeCIP1852, Seq.coinTypeAda, minBound) + + isJormungandrDatabase = + keyTypeDescriptor proxy == keyTypeDescriptor (Proxy @JormungandrKey) + jormungandrPrefix = + shelleyPrefix + -- | Determines whether a field is present in its parent table. isFieldPresent :: Sqlite.Connection -> DBField -> IO SqlColumnStatus isFieldPresent conn field = do @@ -583,6 +623,7 @@ newDBLayer :: forall s k. ( PersistState s , PersistPrivateKey (k 'RootK) + , WalletKey k ) => Tracer IO DBLog -- ^ Logging object @@ -596,7 +637,7 @@ newDBLayer trace defaultFieldValues mDatabaseFile timeInterpreter = do ctx@SqliteContext{runQuery} <- either throwIO pure =<< startSqliteBackend - (migrateManually trace defaultFieldValues) + (migrateManually trace (Proxy @k) defaultFieldValues) migrateAll trace mDatabaseFile @@ -1601,6 +1642,7 @@ instance , seqStateInternalGap = iGap , seqStateAccountXPub = serializeXPub accountXPub , seqStateRewardXPub = serializeXPub (Seq.rewardAccountKey st) + , seqStateDerivationPrefix = Seq.derivationPrefix st } insertAddressPool @n wid sl intPool insertAddressPool @n wid sl extPool @@ -1611,13 +1653,13 @@ instance selectState (wid, sl) = runMaybeT $ do st <- MaybeT $ selectFirst [SeqStateWalletId ==. wid] [] - let SeqState _ eGap iGap accountBytes rewardBytes = entityVal st + let SeqState _ eGap iGap accountBytes rewardBytes prefix = entityVal st let accountXPub = unsafeDeserializeXPub accountBytes let rewardXPub = unsafeDeserializeXPub rewardBytes intPool <- lift $ selectAddressPool @n wid sl iGap accountXPub extPool <- lift $ selectAddressPool @n wid sl eGap accountXPub pendingChangeIxs <- lift $ selectSeqStatePendingIxs wid - pure $ Seq.SeqState intPool extPool pendingChangeIxs rewardXPub + pure $ Seq.SeqState intPool extPool pendingChangeIxs rewardXPub prefix insertAddressPool :: forall n k c. (PaymentAddress n k, Typeable c) diff --git a/lib/core/src/Cardano/Wallet/DB/Sqlite/TH.hs b/lib/core/src/Cardano/Wallet/DB/Sqlite/TH.hs index 36aa97bd437..cbcd866b1bc 100644 --- a/lib/core/src/Cardano/Wallet/DB/Sqlite/TH.hs +++ b/lib/core/src/Cardano/Wallet/DB/Sqlite/TH.hs @@ -232,11 +232,12 @@ UTxO sql=utxo -- Sequential scheme address discovery state -- which does not belong to a particular checkpoint. SeqState - seqStateWalletId W.WalletId sql=wallet_id - seqStateExternalGap W.AddressPoolGap sql=external_gap - seqStateInternalGap W.AddressPoolGap sql=internal_gap - seqStateAccountXPub B8.ByteString sql=account_xpub - seqStateRewardXPub B8.ByteString sql=reward_xpub + seqStateWalletId W.WalletId sql=wallet_id + seqStateExternalGap W.AddressPoolGap sql=external_gap + seqStateInternalGap W.AddressPoolGap sql=internal_gap + seqStateAccountXPub B8.ByteString sql=account_xpub + seqStateRewardXPub B8.ByteString sql=reward_xpub + seqStateDerivationPrefix W.DerivationPrefix sql=derivation_prefix Primary seqStateWalletId Foreign Wallet seq_state seqStateWalletId ! ON DELETE CASCADE diff --git a/lib/core/src/Cardano/Wallet/DB/Sqlite/Types.hs b/lib/core/src/Cardano/Wallet/DB/Sqlite/Types.hs index 3eff55e0e6c..f2426a33198 100644 --- a/lib/core/src/Cardano/Wallet/DB/Sqlite/Types.hs +++ b/lib/core/src/Cardano/Wallet/DB/Sqlite/Types.hs @@ -29,7 +29,11 @@ import Cardano.Slotting.Slot import Cardano.Wallet.Primitive.AddressDerivation ( AccountingStyle (..), Passphrase (..), PassphraseScheme (..) ) import Cardano.Wallet.Primitive.AddressDiscovery.Sequential - ( AddressPoolGap (..), getAddressPoolGap, mkAddressPoolGap ) + ( AddressPoolGap (..) + , DerivationPrefix + , getAddressPoolGap + , mkAddressPoolGap + ) import Cardano.Wallet.Primitive.Types ( Address (..) , AddressState (..) @@ -633,9 +637,8 @@ instance PersistField AddressState where instance PersistFieldSql AddressState where sqlType _ = sqlType (Proxy @Text) - ---------------------------------------------------------------------------- --- Settings +-- PoolMetadataSource instance PersistField PoolMetadataSource where @@ -644,3 +647,13 @@ instance PersistField PoolMetadataSource where instance PersistFieldSql PoolMetadataSource where sqlType _ = sqlType (Proxy @Text) + +---------------------------------------------------------------------------- +-- DerivationPrefix + +instance PersistField DerivationPrefix where + toPersistValue = toPersistValue . toText + fromPersistValue = fromPersistValueFromText + +instance PersistFieldSql DerivationPrefix where + sqlType _ = sqlType (Proxy @Text) diff --git a/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation.hs b/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation.hs index 7651541bb24..701a791c73f 100644 --- a/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation.hs +++ b/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation.hs @@ -35,6 +35,9 @@ module Cardano.Wallet.Primitive.AddressDerivation Depth (..) , Index (..) , AccountingStyle (..) + , utxoExternal + , utxoInternal + , mutableAccount , DerivationType (..) , HardDerivation (..) , SoftDerivation (..) @@ -142,13 +145,10 @@ import qualified Data.Text.Encoding as T HD Hierarchy -------------------------------------------------------------------------------} --- | Key Depth in the derivation path, according to BIP-0039 / BIP-0044 +-- | Key Depth in the derivation path, according to BIP-0044 / CIP-1852 -- --- @m | purpose' | cointype' | account' | change | address@ --- --- We do not manipulate purpose, cointype and change paths directly, so they are --- left out of the sum type. -data Depth = RootK | AccountK | AddressK +-- @m | purpose' | cointype' | account' | role | address@ +data Depth = RootK | PurposeK | CoinTypeK | AccountK | RoleK | AddressK -- | Marker for addresses type engaged. We want to handle three cases here. -- The first two are pertinent to UTxO accounting @@ -158,6 +158,8 @@ data Depth = RootK | AccountK | AddressK -- (b) internal change is for addresses used to handle the change of a -- the transaction within a given wallet -- (c) the addresses for a reward (chimeric) account +-- +-- FIXME: rename this to 'Role' or 'HDRole' data AccountingStyle = UTxOExternal | UTxOInternal @@ -186,6 +188,21 @@ instance ToText AccountingStyle where instance FromText AccountingStyle where fromText = fromTextToBoundedEnum SnakeLowerCase +-- | smart-constructor for getting a derivation index that refers to external +-- utxo. +utxoExternal :: Index 'Soft 'RoleK +utxoExternal = toEnum $ fromEnum UTxOExternal + +-- | smart-constructor for getting a derivation index that refers to internal +-- utxo. +utxoInternal :: Index 'Soft 'RoleK +utxoInternal = toEnum $ fromEnum UTxOInternal + +-- | smart-constructor for getting a derivation index that refers to stake +-- key level (a.k.a mutable account) +mutableAccount :: Index 'Soft 'RoleK +mutableAccount = toEnum $ fromEnum MutableAccount + -- | A derivation index, with phantom-types to disambiguate derivation type. -- -- @ diff --git a/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation/Byron.hs b/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation/Byron.hs index 9c2db3a18aa..1484a79399f 100644 --- a/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation/Byron.hs +++ b/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation/Byron.hs @@ -28,7 +28,7 @@ module Cardano.Wallet.Primitive.AddressDerivation.Byron ( -- * Types ByronKey(..) - , DerivationPath + , DerivationPathFrom -- * Generation , unsafeGenerateKeyFromSeed @@ -117,26 +117,26 @@ import qualified Data.ByteString.Char8 as B8 data ByronKey (depth :: Depth) key = ByronKey { getKey :: key -- ^ The raw private or public key. - , derivationPath :: DerivationPath depth + , derivationPath :: DerivationPathFrom depth -- ^ The address derivation indices for the level of this key. , payloadPassphrase :: Passphrase "addr-derivation-payload" -- ^ Used for encryption of payload containing address derivation path. } deriving stock (Generic) -instance (NFData key, NFData (DerivationPath depth)) => NFData (ByronKey depth key) -deriving instance (Show key, Show (DerivationPath depth)) => Show (ByronKey depth key) -deriving instance (Eq key, Eq (DerivationPath depth)) => Eq (ByronKey depth key) +instance (NFData key, NFData (DerivationPathFrom depth)) => NFData (ByronKey depth key) +deriving instance (Show key, Show (DerivationPathFrom depth)) => Show (ByronKey depth key) +deriving instance (Eq key, Eq (DerivationPathFrom depth)) => Eq (ByronKey depth key) -- | The hierarchical derivation indices for a given level/depth. -type family DerivationPath (depth :: Depth) :: * where +type family DerivationPathFrom (depth :: Depth) :: * where -- The root key is generated from the seed. - DerivationPath 'RootK = + DerivationPathFrom 'RootK = () -- The account key is generated from the root key and account index. - DerivationPath 'AccountK = + DerivationPathFrom 'AccountK = Index 'WholeDomain 'AccountK -- The address key is generated from the account key and address index. - DerivationPath 'AddressK = + DerivationPathFrom 'AddressK = (Index 'WholeDomain 'AccountK, Index 'WholeDomain 'AddressK) instance WalletKey ByronKey where @@ -224,7 +224,7 @@ generateKeyFromSeed = unsafeGenerateKeyFromSeed () -- testing, in practice, seeds are used to represent root keys, and one should -- use 'generateKeyFromSeed'. unsafeGenerateKeyFromSeed - :: DerivationPath depth + :: DerivationPathFrom depth -> SomeMnemonic -> Passphrase "encryption" -> ByronKey depth XPrv @@ -278,7 +278,7 @@ mkByronKeyFromMasterKey mkByronKeyFromMasterKey = unsafeMkByronKeyFromMasterKey () unsafeMkByronKeyFromMasterKey - :: DerivationPath depth + :: DerivationPathFrom depth -> XPrv -> ByronKey depth XPrv unsafeMkByronKeyFromMasterKey derivationPath masterKey = ByronKey diff --git a/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation/Icarus.hs b/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation/Icarus.hs index 3e91b4051c8..464112e6b14 100644 --- a/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation/Icarus.hs +++ b/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation/Icarus.hs @@ -69,7 +69,7 @@ import Cardano.Wallet.Primitive.AddressDerivation import Cardano.Wallet.Primitive.AddressDiscovery ( IsOurs (..) ) import Cardano.Wallet.Primitive.AddressDiscovery.Sequential - ( SeqState ) + ( SeqState, coinTypeAda, purposeBIP44 ) import Cardano.Wallet.Primitive.Types ( Address (..), Hash (..), invariant, testnetMagic ) import Control.Arrow @@ -100,8 +100,6 @@ import Data.Maybe ( fromMaybe ) import Data.Proxy ( Proxy (..) ) -import Data.Word - ( Word32 ) import GHC.Generics ( Generic ) import GHC.TypeLits @@ -130,31 +128,6 @@ newtype IcarusKey (depth :: Depth) key = instance (NFData key) => NFData (IcarusKey depth key) --- | Purpose is a constant set to 44' (or 0x8000002C) following the original --- BIP-44 specification. --- --- It indicates that the subtree of this node is used according to this --- specification. --- --- Hardened derivation is used at this level. -purposeIndex :: Word32 -purposeIndex = 0x8000002C - --- | One master node (seed) can be used for unlimited number of independent --- cryptocoins such as Bitcoin, Litecoin or Namecoin. However, sharing the --- same space for various cryptocoins has some disadvantages. --- --- This level creates a separate subtree for every cryptocoin, avoiding reusing --- addresses across cryptocoins and improving privacy issues. --- --- Coin type is a constant, set for each cryptocoin. For Cardano this constant --- is set to 1815' (or 0x80000717). 1815 is the birthyear of our beloved Ada --- Lovelace. --- --- Hardened derivation is used at this level. -coinTypeIndex :: Word32 -coinTypeIndex = 0x80000717 - -- | The minimum seed length for 'generateKeyFromSeed' and 'unsafeGenerateKeyFromSeed'. minSeedLengthBytes :: Int minSeedLengthBytes = 16 @@ -322,9 +295,9 @@ instance HardDerivation IcarusKey where (Passphrase pwd) (IcarusKey rootXPrv) (Index accIx) = let purposeXPrv = -- lvl1 derivation; hardened derivation of purpose' - deriveXPrv DerivationScheme2 pwd rootXPrv purposeIndex + deriveXPrv DerivationScheme2 pwd rootXPrv (getIndex purposeBIP44) coinTypeXPrv = -- lvl2 derivation; hardened derivation of coin_type' - deriveXPrv DerivationScheme2 pwd purposeXPrv coinTypeIndex + deriveXPrv DerivationScheme2 pwd purposeXPrv (getIndex coinTypeAda) acctXPrv = -- lvl3 derivation; hardened derivation of account' index deriveXPrv DerivationScheme2 pwd coinTypeXPrv accIx in @@ -415,7 +388,7 @@ instance PaymentAddress n IcarusKey err = ErrInvalidAddress (proxy, k) Proxy instance IsOurs (SeqState n IcarusKey) ChimericAccount where - isOurs _account state = (False, state) + isOurs _account state = (Nothing, state) {------------------------------------------------------------------------------- Storing and retrieving keys diff --git a/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation/Jormungandr.hs b/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation/Jormungandr.hs index 4214e58cd3a..e4528db30a7 100644 --- a/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation/Jormungandr.hs +++ b/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation/Jormungandr.hs @@ -5,6 +5,7 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE RoleAnnotations #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} @@ -77,18 +78,24 @@ import Cardano.Wallet.Primitive.AddressDerivation , deriveRewardAccount , fromHex , hex + , mutableAccount , networkDiscriminantVal ) import Cardano.Wallet.Primitive.AddressDiscovery ( IsOurs (..) ) import Cardano.Wallet.Primitive.AddressDiscovery.Sequential - ( SeqState, rewardAccountKey ) + ( DerivationPrefix (..) + , SeqState (..) + , coinTypeAda + , purposeCIP1852 + , rewardAccountKey + ) import Cardano.Wallet.Primitive.Types - ( Address (..), Hash (..), invariant ) + ( Address (..), DerivationIndex (..), Hash (..), invariant ) import Control.DeepSeq ( NFData (..) ) import Control.Monad - ( when, (<=<) ) + ( guard, when, (<=<) ) import Crypto.Hash ( Digest, HashAlgorithm, hash ) import Data.Binary.Put @@ -102,7 +109,7 @@ import Data.Proxy import Data.Text.Class ( TextDecodingError (..) ) import Data.Word - ( Word32, Word8 ) + ( Word8 ) import GHC.Generics ( Generic ) import GHC.Stack @@ -111,6 +118,7 @@ import GHC.Stack import qualified Data.ByteArray as BA import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as BL +import qualified Data.List.NonEmpty as NE {------------------------------------------------------------------------------- Sequential Derivation @@ -142,33 +150,6 @@ addrSingleSize = 1 + publicKeySize addrGroupedSize :: Int addrGroupedSize = addrSingleSize + publicKeySize --- | Purpose is a constant set to 1852' (or 0x8000073c) following the BIP-44 --- extension for Cardano: --- --- https://github.com/input-output-hk/implementation-decisions/blob/e2d1bed5e617f0907bc5e12cf1c3f3302a4a7c42/text/1852-hd-chimeric.md --- --- It indicates that the subtree of this node is used according to this --- specification. --- --- Hardened derivation is used at this level. -purposeIndex :: Word32 -purposeIndex = 0x8000073c - --- | One master node (seed) can be used for unlimited number of independent --- cryptocoins such as Bitcoin, Litecoin or Namecoin. However, sharing the --- same space for various cryptocoins has some disadvantages. --- --- This level creates a separate subtree for every cryptocoin, avoiding reusing --- addresses across cryptocoins and improving privacy issues. --- --- Coin type is a constant, set for each cryptocoin. For Cardano this constant --- is set to 1815' (or 0x80000717). 1815 is the birthyear of our beloved Ada --- Lovelace. --- --- Hardened derivation is used at this level. -coinTypeIndex :: Word32 -coinTypeIndex = 0x80000717 - -- | The minimum seed length for 'generateKeyFromSeed' and -- 'unsafeGenerateKeyFromSeed'. minSeedLengthBytes :: Int @@ -210,9 +191,9 @@ instance HardDerivation JormungandrKey where (Passphrase pwd) (JormungandrKey rootXPrv) (Index accIx) = let purposeXPrv = -- lvl1 derivation; hardened derivation of purpose' - deriveXPrv DerivationScheme2 pwd rootXPrv purposeIndex + deriveXPrv DerivationScheme2 pwd rootXPrv (getIndex purposeCIP1852) coinTypeXPrv = -- lvl2 derivation; hardened derivation of coin_type' - deriveXPrv DerivationScheme2 pwd purposeXPrv coinTypeIndex + deriveXPrv DerivationScheme2 pwd purposeXPrv (getIndex coinTypeAda) acctXPrv = -- lvl3 derivation; hardened derivation of account' index deriveXPrv DerivationScheme2 pwd coinTypeXPrv accIx in @@ -436,8 +417,18 @@ instance MkKeyFingerprint JormungandrKey (Proxy (n :: NetworkDiscriminant), Jorm instance IsOurs (SeqState n JormungandrKey) ChimericAccount where - isOurs account state = - (account == ourAccount, state) + isOurs account state@SeqState{derivationPrefix} = + let + DerivationPrefix (purpose, coinType, accountIx) = derivationPrefix + path = NE.fromList + [ DerivationIndex $ getIndex purpose + , DerivationIndex $ getIndex coinType + , DerivationIndex $ getIndex accountIx + , DerivationIndex $ getIndex mutableAccount + , DerivationIndex $ getIndex @'Soft minBound + ] + in + (guard (account == ourAccount) *> Just path, state) where ourAccount = toChimericAccount $ rewardAccountKey state diff --git a/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation/Shelley.hs b/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation/Shelley.hs index 08a866baa84..a33aacd3ee7 100644 --- a/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation/Shelley.hs +++ b/lib/core/src/Cardano/Wallet/Primitive/AddressDerivation/Shelley.hs @@ -5,6 +5,7 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE RoleAnnotations #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} @@ -24,7 +25,6 @@ module Cardano.Wallet.Primitive.AddressDerivation.Shelley -- * Constants , minSeedLengthBytes - -- * Generation and derivation , generateKeyFromSeed , unsafeGenerateKeyFromSeed @@ -74,17 +74,23 @@ import Cardano.Wallet.Primitive.AddressDerivation , deriveRewardAccount , fromHex , hex + , mutableAccount ) import Cardano.Wallet.Primitive.AddressDiscovery ( IsOurs (..) ) import Cardano.Wallet.Primitive.AddressDiscovery.Sequential - ( SeqState, rewardAccountKey ) + ( DerivationPrefix (..) + , SeqState (..) + , coinTypeAda + , purposeCIP1852 + , rewardAccountKey + ) import Cardano.Wallet.Primitive.Types - ( Address (..), Hash (..), invariant ) + ( Address (..), DerivationIndex (..), Hash (..), invariant ) import Control.DeepSeq ( NFData (..) ) import Control.Monad - ( (<=<) ) + ( guard, (<=<) ) import Crypto.Hash ( hash ) import Crypto.Hash.Algorithms @@ -103,14 +109,13 @@ import Data.Proxy ( Proxy (..) ) import Data.Text.Class ( TextDecodingError (..) ) -import Data.Word - ( Word32 ) import GHC.Generics ( Generic ) import qualified Data.ByteArray as BA import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as BL +import qualified Data.List.NonEmpty as NE {------------------------------------------------------------------------------- Sequential Derivation @@ -130,33 +135,6 @@ newtype ShelleyKey (depth :: Depth) key = instance (NFData key) => NFData (ShelleyKey depth key) --- | Purpose is a constant set to 1852' (or 0x8000073c) following the BIP-44 --- extension for Cardano: --- --- https://github.com/input-output-hk/implementation-decisions/blob/e2d1bed5e617f0907bc5e12cf1c3f3302a4a7c42/text/1852-hd-chimeric.md --- --- It indicates that the subtree of this node is used according to this --- specification. --- --- Hardened derivation is used at this level. -purposeIndex :: Word32 -purposeIndex = 0x8000073c - --- | One master node (seed) can be used for unlimited number of independent --- cryptocoins such as Bitcoin, Litecoin or Namecoin. However, sharing the --- same space for various cryptocoins has some disadvantages. --- --- This level creates a separate subtree for every cryptocoin, avoiding reusing --- addresses across cryptocoins and improving privacy issues. --- --- Coin type is a constant, set for each cryptocoin. For Cardano this constant --- is set to 1815' (or 0x80000717). 1815 is the birthyear of our beloved Ada --- Lovelace. --- --- Hardened derivation is used at this level. -coinTypeIndex :: Word32 -coinTypeIndex = 0x80000717 - -- | The minimum seed length for 'generateKeyFromSeed' and -- 'unsafeGenerateKeyFromSeed'. minSeedLengthBytes :: Int @@ -197,9 +175,9 @@ instance HardDerivation ShelleyKey where (Passphrase pwd) (ShelleyKey rootXPrv) (Index accIx) = let purposeXPrv = -- lvl1 derivation; hardened derivation of purpose' - deriveXPrv DerivationScheme2 pwd rootXPrv purposeIndex + deriveXPrv DerivationScheme2 pwd rootXPrv (getIndex purposeCIP1852) coinTypeXPrv = -- lvl2 derivation; hardened derivation of coin_type' - deriveXPrv DerivationScheme2 pwd purposeXPrv coinTypeIndex + deriveXPrv DerivationScheme2 pwd purposeXPrv (getIndex coinTypeAda) acctXPrv = -- lvl3 derivation; hardened derivation of account' index deriveXPrv DerivationScheme2 pwd coinTypeXPrv accIx in @@ -350,8 +328,18 @@ instance MkKeyFingerprint ShelleyKey (Proxy (n :: NetworkDiscriminant), ShelleyK instance IsOurs (SeqState n ShelleyKey) ChimericAccount where - isOurs account state = - (account == ourAccount, state) + isOurs account state@SeqState{derivationPrefix} = + let + DerivationPrefix (purpose, coinType, accountIx) = derivationPrefix + path = NE.fromList + [ DerivationIndex $ getIndex purpose + , DerivationIndex $ getIndex coinType + , DerivationIndex $ getIndex accountIx + , DerivationIndex $ getIndex mutableAccount + , DerivationIndex $ getIndex @'Soft minBound + ] + in + (guard (account == ourAccount) *> Just path, state) where ourAccount = toChimericAccount $ rewardAccountKey state diff --git a/lib/core/src/Cardano/Wallet/Primitive/AddressDiscovery.hs b/lib/core/src/Cardano/Wallet/Primitive/AddressDiscovery.hs index abc3b5b3142..f4036c24df0 100644 --- a/lib/core/src/Cardano/Wallet/Primitive/AddressDiscovery.hs +++ b/lib/core/src/Cardano/Wallet/Primitive/AddressDiscovery.hs @@ -34,7 +34,9 @@ import Cardano.Crypto.Wallet import Cardano.Wallet.Primitive.AddressDerivation ( Depth (..), Passphrase (..) ) import Cardano.Wallet.Primitive.Types - ( Address (..), AddressState (..) ) + ( Address (..), AddressState (..), DerivationIndex (..) ) +import Data.List.NonEmpty + ( NonEmpty ) -- | Checks whether or not a given entity belongs to us. -- @@ -58,8 +60,8 @@ class IsOurs s entity where isOurs :: entity -> s - -> (Bool, s) - -- ^ Checks whether an entity is ours or not. + -> (Maybe (NonEmpty DerivationIndex), s) + -- ^ Returns derivation path if the entity is ours, otherwise Nothing. -- | More powerful than 'isOurs', this abstractions offer the underlying state -- the ability to find / compute the address private key corresponding to a diff --git a/lib/core/src/Cardano/Wallet/Primitive/AddressDiscovery/Random.hs b/lib/core/src/Cardano/Wallet/Primitive/AddressDiscovery/Random.hs index a4ea6dacb36..8a766114329 100644 --- a/lib/core/src/Cardano/Wallet/Primitive/AddressDiscovery/Random.hs +++ b/lib/core/src/Cardano/Wallet/Primitive/AddressDiscovery/Random.hs @@ -63,12 +63,12 @@ import Cardano.Wallet.Primitive.AddressDerivation.Byron import Cardano.Wallet.Primitive.AddressDiscovery ( CompareDiscovery (..) , GenChange (..) - , IsOurs (..) + , IsOurs (isOurs) , IsOwned (..) , KnownAddresses (..) ) import Cardano.Wallet.Primitive.Types - ( Address (..), AddressState (..), ChimericAccount ) + ( Address (..), AddressState (..), ChimericAccount, DerivationIndex (..) ) import Control.Arrow ( second ) import Control.DeepSeq @@ -77,10 +77,10 @@ import Control.Monad ( join ) import Data.Digest.CRC32 ( crc32 ) +import Data.List.NonEmpty + ( NonEmpty (..) ) import Data.Map ( Map ) -import Data.Maybe - ( isJust ) import Data.Proxy ( Proxy (..) ) import Data.Set @@ -96,6 +96,7 @@ import GHC.TypeLits import System.Random ( RandomGen, StdGen, mkStdGen, randomR ) +import qualified Data.List.NonEmpty as NE import qualified Data.Map as Map import qualified Data.Set as Set @@ -203,13 +204,14 @@ instance RndStateLike (RndState n) where -- to decrypt the address derivation path. instance IsOurs (RndState n) Address where isOurs addr st = - (isJust path, maybe id (addDiscoveredAddress addr Used) path st) + ( toDerivationIndexes <$> path + , maybe id (addDiscoveredAddress addr Used) path st + ) where path = addressToPath addr (hdPassphrase st) instance IsOurs (RndState n) ChimericAccount where - -- Chimeric accounts are not supported, so always return 'False'. - isOurs _account state = (False, state) + isOurs _account state = (Nothing, state) instance IsOwned (RndState n) ByronKey where isOwned st (key, pwd) addr = @@ -224,6 +226,12 @@ addressToPath (Address addr) pwd = do payload <- deserialiseCbor decodeAddressPayload addr join $ deserialiseCbor (decodeAddressDerivationPath pwd) payload +toDerivationIndexes :: DerivationPath -> NonEmpty DerivationIndex +toDerivationIndexes (acctIx, addrIx) = NE.fromList + [ DerivationIndex $ getIndex acctIx + , DerivationIndex $ getIndex addrIx + ] + -- | Initialize the HD random address discovery state from a root key and RNG -- seed. mkRndState :: ByronKey 'RootK XPrv -> Int -> RndState n @@ -370,10 +378,10 @@ instance RndStateLike (RndAnyState n p) where instance KnownNat p => IsOurs (RndAnyState n p) Address where isOurs addr@(Address bytes) st@(RndAnyState inner) = case isOurs addr inner of - (True, inner') -> - (True, RndAnyState inner') + (Just path, inner') -> + (Just path, RndAnyState inner') - (False, _) | crc32 bytes < p -> + (Nothing, _) | crc32 bytes < p -> let (path, gen') = findUnusedPath (gen inner) (accountIndex inner) (unavailablePaths inner) @@ -381,10 +389,10 @@ instance KnownNat p => IsOurs (RndAnyState n p) Address where inner' = addDiscoveredAddress addr Used path (inner { gen = gen' }) in - (True, RndAnyState inner') + (Just (toDerivationIndexes path), RndAnyState inner') - (False, _) -> - (False, st) + (Nothing, _) -> + (Nothing, st) where p = floor (double (maxBound :: Word32) * double (natVal (Proxy @p)) / 1000) @@ -392,7 +400,7 @@ instance KnownNat p => IsOurs (RndAnyState n p) Address where double = fromIntegral instance IsOurs (RndAnyState n p) ChimericAccount where - isOurs _account state = (False, state) + isOurs _account state = (Nothing, state) instance KnownNat p => IsOwned (RndAnyState n p) ByronKey where isOwned _ _ _ = Nothing diff --git a/lib/core/src/Cardano/Wallet/Primitive/AddressDiscovery/Sequential.hs b/lib/core/src/Cardano/Wallet/Primitive/AddressDiscovery/Sequential.hs index e2b7453c5b2..c48ae17d8ef 100644 --- a/lib/core/src/Cardano/Wallet/Primitive/AddressDiscovery/Sequential.hs +++ b/lib/core/src/Cardano/Wallet/Primitive/AddressDiscovery/Sequential.hs @@ -55,6 +55,10 @@ module Cardano.Wallet.Primitive.AddressDiscovery.Sequential -- ** State , SeqState (..) + , DerivationPrefix (..) + , purposeBIP44 + , purposeCIP1852 + , coinTypeAda , mkSeqStateFromRootXPrv , mkSeqStateFromAccountXPub @@ -72,7 +76,7 @@ import Cardano.Wallet.Primitive.AddressDerivation , Depth (..) , DerivationType (..) , HardDerivation (..) - , Index + , Index (..) , KeyFingerprint (..) , MkKeyFingerprint (..) , NetworkDiscriminant (..) @@ -82,6 +86,8 @@ import Cardano.Wallet.Primitive.AddressDerivation , SoftDerivation (..) , WalletKey (..) , deriveRewardAccount + , utxoExternal + , utxoInternal ) import Cardano.Wallet.Primitive.AddressDiscovery ( CompareDiscovery (..) @@ -91,7 +97,12 @@ import Cardano.Wallet.Primitive.AddressDiscovery , KnownAddresses (..) ) import Cardano.Wallet.Primitive.Types - ( Address (..), AddressState (..), ChimericAccount (..), invariant ) + ( Address (..) + , AddressState (..) + , ChimericAccount (..) + , DerivationIndex (..) + , invariant + ) import Control.Applicative ( (<|>) ) import Control.DeepSeq @@ -104,10 +115,10 @@ import Data.Digest.CRC32 ( crc32 ) import Data.Function ( (&) ) +import Data.List.NonEmpty + ( NonEmpty (..) ) import Data.Map.Strict ( Map ) -import Data.Maybe - ( isJust ) import Data.Proxy ( Proxy (..) ) import Data.Text.Class @@ -128,6 +139,7 @@ import GHC.TypeLits ( KnownNat, Nat, natVal ) import qualified Data.List as L +import qualified Data.List.NonEmpty as NE import qualified Data.Map.Strict as Map import qualified Data.Set as Set import qualified Data.Text as T @@ -551,6 +563,8 @@ data SeqState (n :: NetworkDiscriminant) k = SeqState -- (cf: 'PendingIxs') , rewardAccountKey :: k 'AddressK XPub -- ^ Reward account public key associated with this wallet + , derivationPrefix :: DerivationPrefix + -- ^ Derivation path prefix from a root key up to the internal account } deriving stock (Generic) @@ -568,13 +582,89 @@ instance => NFData (SeqState n k) instance PersistPublicKey (k 'AccountK) => Buildable (SeqState n k) where - build (SeqState intP extP chgs _) = "SeqState:\n" + build (SeqState intP extP chgs _ path) = "SeqState:\n" + <> indentF 4 ("Derivation prefix: " <> build (toText path)) <> indentF 4 (build intP) <> indentF 4 (build extP) <> indentF 4 ("Change indexes: " <> indentF 4 chgsF) where chgsF = blockListF' "-" build (pendingIxsToList chgs) +-- | Each 'SeqState' is like a bucket of addresses associated with an 'account'. +-- An 'account' corresponds to a subset of an HD tree as defined in BIP-0039. +-- +-- cardano-wallet implements two similar HD schemes on top of BIP-0039 that are: +-- +-- - BIP-0044 (for so-called Icarus wallets) +-- - CIP-1815 (for so-called Shelley and Jormungandr wallets) +-- +-- Both scheme works by considering 5 levels of derivation from an initial root +-- key (see also 'Depth' from Cardano.Wallet.Primitive.AddressDerivation). A +-- SeqState keeps track of indexes from the two last levels of a derivation +-- branch. The 'DerivationPrefix' defines the first three indexes chosen for +-- this particular 'SeqState'. +newtype DerivationPrefix = DerivationPrefix + ( Index 'Hardened 'PurposeK + , Index 'Hardened 'CoinTypeK + , Index 'Hardened 'AccountK + ) deriving (Show, Generic, Eq, Ord) + +instance NFData DerivationPrefix + +instance ToText DerivationPrefix where + toText (DerivationPrefix (purpose, coinType, account)) + = T.intercalate "/" + $ map (T.pack . show) + [getIndex purpose, getIndex coinType, getIndex account] + +instance FromText DerivationPrefix where + fromText txt = + DerivationPrefix <$> case T.splitOn "/" txt of + [purposeT, coinTypeT, accountT] -> (,,) + <$> fromText purposeT + <*> fromText coinTypeT + <*> fromText accountT + _ -> + Left $ TextDecodingError "expected exactly 3 derivation paths" + + +-- | Purpose is a constant set to 44' (or 0x8000002C) following the original +-- BIP-44 specification. +-- +-- It indicates that the subtree of this node is used according to this +-- specification. +-- +-- Hardened derivation is used at this level. +purposeBIP44 :: Index 'Hardened 'PurposeK +purposeBIP44 = toEnum 0x8000002C + +-- | Purpose is a constant set to 1852' (or 0x8000073c) following the BIP-44 +-- extension for Cardano: +-- +-- https://github.com/input-output-hk/implementation-decisions/blob/e2d1bed5e617f0907bc5e12cf1c3f3302a4a7c42/text/1852-hd-chimeric.md +-- +-- It indicates that the subtree of this node is used according to this +-- specification. +-- +-- Hardened derivation is used at this level. +purposeCIP1852 :: Index 'Hardened 'PurposeK +purposeCIP1852 = toEnum 0x8000073c + +-- | One master node (seed) can be used for unlimited number of independent +-- cryptocoins such as Bitcoin, Litecoin or Namecoin. However, sharing the +-- same space for various cryptocoins has some disadvantages. +-- +-- This level creates a separate subtree for every cryptocoin, avoiding reusing +-- addresses across cryptocoins and improving privacy issues. +-- +-- Coin type is a constant, set for each cryptocoin. For Cardano this constant +-- is set to 1815' (or 0x80000717). 1815 is the birthyear of our beloved Ada +-- Lovelace. +-- +-- Hardened derivation is used at this level. +coinTypeAda :: Index 'Hardened 'CoinTypeK +coinTypeAda = toEnum 0x80000717 + -- | Construct a Sequential state for a wallet from root private key and password. mkSeqStateFromRootXPrv :: forall n k. @@ -585,9 +675,10 @@ mkSeqStateFromRootXPrv , Bounded (Index (AddressIndexDerivationType k) 'AddressK) ) => (k 'RootK XPrv, Passphrase "encryption") + -> Index 'Hardened 'PurposeK -> AddressPoolGap -> SeqState n k -mkSeqStateFromRootXPrv (rootXPrv, pwd) g = +mkSeqStateFromRootXPrv (rootXPrv, pwd) purpose g = let accXPrv = deriveAccountPrivateKey pwd rootXPrv minBound @@ -597,8 +688,10 @@ mkSeqStateFromRootXPrv (rootXPrv, pwd) g = mkAddressPool @n (publicKey accXPrv) g [] intPool = mkAddressPool @n (publicKey accXPrv) g [] + prefix = + DerivationPrefix ( purpose, coinTypeAda, minBound ) in - SeqState intPool extPool emptyPendingIxs rewardXPub + SeqState intPool extPool emptyPendingIxs rewardXPub prefix -- | Construct a Sequential state for a wallet from public account key. mkSeqStateFromAccountXPub @@ -608,9 +701,10 @@ mkSeqStateFromAccountXPub , MkKeyFingerprint k Address ) => k 'AccountK XPub + -> Index 'Hardened 'PurposeK -> AddressPoolGap -> SeqState n k -mkSeqStateFromAccountXPub accXPub g = +mkSeqStateFromAccountXPub accXPub purpose g = let -- This matches the reward address for "normal wallets". The accountXPub -- is the first account, minBound being the first Soft index @@ -620,8 +714,10 @@ mkSeqStateFromAccountXPub accXPub g = mkAddressPool @n accXPub g [] intPool = mkAddressPool @n accXPub g [] + prefix = + DerivationPrefix ( purpose, coinTypeAda, minBound ) in - SeqState intPool extPool emptyPendingIxs rewardXPub + SeqState intPool extPool emptyPendingIxs rewardXPub prefix -- NOTE -- We have to scan both the internal and external chain. Note that, the @@ -632,17 +728,38 @@ instance ( SoftDerivation k , MkKeyFingerprint k (Proxy n, k 'AddressK XPub) , MkKeyFingerprint k Address - ) => IsOurs (SeqState n k) Address where - isOurs addr (SeqState !s1 !s2 !ixs !rpk) = + ) => IsOurs (SeqState n k) Address + where + isOurs addr (SeqState !s1 !s2 !ixs !rpk !prefix) = let + DerivationPrefix (purpose, coinType, accountIx) = prefix (internal, !s1') = lookupAddress @n (const Used) addr s1 (external, !s2') = lookupAddress @n (const Used) addr s2 + !ixs' = case internal of Nothing -> ixs Just ix -> updatePendingIxs ix ixs - ours = isJust (internal <|> external) + + ours = case (external, internal) of + (Just addrIx, _) -> Just $ NE.fromList + [ DerivationIndex $ getIndex purpose + , DerivationIndex $ getIndex coinType + , DerivationIndex $ getIndex accountIx + , DerivationIndex $ getIndex utxoExternal + , DerivationIndex $ getIndex addrIx + ] + + (_, Just addrIx) -> Just $ NE.fromList + [ DerivationIndex $ getIndex purpose + , DerivationIndex $ getIndex coinType + , DerivationIndex $ getIndex accountIx + , DerivationIndex $ getIndex utxoInternal + , DerivationIndex $ getIndex addrIx + ] + + _ -> Nothing in - (ixs' `deepseq` ours `deepseq` ours, SeqState s1' s2' ixs' rpk) + (ixs' `deepseq` ours `deepseq` ours, SeqState s1' s2' ixs' rpk prefix) instance ( SoftDerivation k @@ -656,23 +773,24 @@ instance type ArgGenChange (SeqState n k) = (k 'AddressK XPub -> k 'AddressK XPub -> Address) - genChange mkAddress (SeqState intPool extPool pending rpk) = + genChange mkAddress (SeqState intPool extPool pending rpk path) = let (ix, pending') = nextChangeIndex intPool pending accountXPub = accountPubKey intPool addressXPub = deriveAddressPublicKey accountXPub UTxOInternal ix addr = mkAddress addressXPub rpk in - (addr, SeqState intPool extPool pending' rpk) + (addr, SeqState intPool extPool pending' rpk path) instance - ( SoftDerivation k + ( IsOurs (SeqState n k) Address + , SoftDerivation k , MkKeyFingerprint k (Proxy n, k 'AddressK XPub) , MkKeyFingerprint k Address , AddressIndexDerivationType k ~ 'Soft ) => IsOwned (SeqState n k) k where - isOwned (SeqState !s1 !s2 _ _) (rootPrv, pwd) addr = + isOwned (SeqState !s1 !s2 _ _ _) (rootPrv, pwd) addr = let xPrv1 = lookupAndDeriveXPrv s1 xPrv2 = lookupAndDeriveXPrv s2 @@ -698,7 +816,7 @@ instance , MkKeyFingerprint k Address , SoftDerivation k ) => CompareDiscovery (SeqState n k) where - compareDiscovery (SeqState !s1 !s2 _ _) a1 a2 = + compareDiscovery (SeqState !s1 !s2 _ _ _) a1 a2 = case (ix a1 s1 <|> ix a1 s2, ix a2 s1 <|> ix a2 s2) of (Nothing, Nothing) -> EQ (Nothing, Just _) -> GT @@ -773,10 +891,11 @@ mkSeqAnyState , Bounded (Index (AddressIndexDerivationType k) 'AddressK) ) => (k 'RootK XPrv, Passphrase "encryption") + -> Index 'Hardened 'PurposeK -> AddressPoolGap -> SeqAnyState n k p -mkSeqAnyState credentials poolGap = SeqAnyState - { innerState = mkSeqStateFromRootXPrv credentials poolGap +mkSeqAnyState credentials purpose poolGap = SeqAnyState + { innerState = mkSeqStateFromRootXPrv credentials purpose poolGap } instance @@ -791,10 +910,11 @@ instance edge = Map.size (indexedKeys $ externalPool inner) ix = toEnum (edge - fromEnum (gap $ externalPool inner)) pool' = extendAddressPool @n ix (externalPool inner) + path = DerivationIndex (getIndex ix) :| [] in - (True, SeqAnyState (inner { externalPool = pool' })) + (Just path, SeqAnyState (inner { externalPool = pool' })) | otherwise = - (False, st) + (Nothing, st) where p = floor (double sup * double (natVal (Proxy @p)) / 1000) where @@ -805,7 +925,7 @@ instance instance IsOurs (SeqAnyState n k p) ChimericAccount where - isOurs _account state = (False, state) + isOurs _account state = (Nothing, state) instance ( SoftDerivation k diff --git a/lib/core/src/Cardano/Wallet/Primitive/Model.hs b/lib/core/src/Cardano/Wallet/Primitive/Model.hs index 363ecd08c63..f58aac48a5b 100644 --- a/lib/core/src/Cardano/Wallet/Primitive/Model.hs +++ b/lib/core/src/Cardano/Wallet/Primitive/Model.hs @@ -96,7 +96,7 @@ import Data.Generics.Labels import Data.List.NonEmpty ( NonEmpty (..) ) import Data.Maybe - ( catMaybes ) + ( catMaybes, isJust ) import Data.Quantity ( Quantity (..) ) import Data.Set @@ -304,7 +304,7 @@ totalBalance pending (Quantity rewards) wallet@(Wallet _ _ s _) = else rewards where hasPendingWithdrawals = - anyS (anyM (\acct _ -> fst (isOurs acct s)) . withdrawals) + anyS (anyM (\acct _ -> isJust $ fst (isOurs acct s)) . withdrawals) where anyS predicate = not . Set.null . Set.filter predicate anyM predicate = not . Map.null . Map.filterWithKey predicate @@ -368,16 +368,16 @@ prefilterBlock b u0 = runState $ do -> State s (Maybe DelegationCertificate) ourDelegation cert = state (isOurs $ dlgCertAccount cert) <&> \case - False -> Nothing - True -> Just cert + Nothing -> Nothing + Just{} -> Just cert ourWithdrawal :: IsOurs s ChimericAccount => (ChimericAccount, Coin) -> State s (Maybe (ChimericAccount, Coin)) ourWithdrawal (acct, amt) = state (isOurs acct) <&> \case - False -> Nothing - True -> Just (acct, amt) + Nothing -> Nothing + Just{} -> Just (acct, amt) mkTxMeta :: Natural -> Direction -> TxMeta mkTxMeta amt dir = TxMeta { status = InLedger @@ -443,7 +443,6 @@ utxoOurs tx = runState $ toUtxo <$> forM (zip [0..] (outputs tx)) filterOut where toUtxo = UTxO . Map.fromList . catMaybes filterOut (ix, out) = do - predicate <- state $ isOurs $ address out - return $ if predicate - then Just (TxIn (txId tx) ix, out) - else Nothing + state (isOurs $ address out) <&> \case + Just{} -> Just (TxIn (txId tx) ix, out) + Nothing -> Nothing diff --git a/lib/core/src/Cardano/Wallet/Primitive/Types.hs b/lib/core/src/Cardano/Wallet/Primitive/Types.hs index 9333c308479..1325ff90518 100644 --- a/lib/core/src/Cardano/Wallet/Primitive/Types.hs +++ b/lib/core/src/Cardano/Wallet/Primitive/Types.hs @@ -61,6 +61,7 @@ module Cardano.Wallet.Primitive.Types -- * Address , Address (..) , AddressState (..) + , DerivationIndex (..) -- * Delegation and stake pools , CertificatePublicationTime (..) @@ -965,9 +966,9 @@ instance ToText TxStatus where -- -- See 'Tx' for a signed transaction. -- -data UnsignedTx = UnsignedTx +data UnsignedTx input = UnsignedTx { unsignedInputs - :: NonEmpty (TxIn, TxOut) + :: NonEmpty input , unsignedOutputs :: NonEmpty TxOut } @@ -1168,6 +1169,28 @@ instance Buildable AddressState where instance NFData AddressState +-- | A thin wrapper around derivation indexes. This can be used to represent +-- derivation path as homogeneous lists of 'DerivationIndex'. This is slightly +-- more convenient than having to carry heterogeneous lists of 'Index depth type' +-- and works fine because: +-- +-- 1. The 'depth' matters not because what the depth captures is actually the +-- position of the index in that list. It makes sense to carry at the type +-- level when manipulating standalone indexes to avoid mistakes, but when +-- treating them as a part of a list it is redundant. +-- +-- 2. The derivationType is captured by representing indexes as plain Word32. +-- The Soft / Hardened notation is for easing human-readability but in the +-- end, a soft index is simply a value < 2^31, whereas a "hardened" index is +-- simply a value >= 2^31. Therefore, instead of representing indexes as +-- derivationType + relative index within 0 and 2^31, we can represent them +-- as just an index between 0 and 2^32, which is what DerivationIndex does. +newtype DerivationIndex + = DerivationIndex Word32 + deriving (Show, Eq, Ord, Generic) + +instance NFData DerivationIndex + {------------------------------------------------------------------------------- Coin -------------------------------------------------------------------------------} diff --git a/lib/core/test/bench/db/Main.hs b/lib/core/test/bench/db/Main.hs index 0df46f1f7ef..c5810180136 100644 --- a/lib/core/test/bench/db/Main.hs +++ b/lib/core/test/bench/db/Main.hs @@ -84,11 +84,14 @@ import Cardano.Wallet.Primitive.AddressDiscovery.Random ( DerivationPath, RndState (..), mkRndState ) import Cardano.Wallet.Primitive.AddressDiscovery.Sequential ( AddressPool + , DerivationPrefix (..) , SeqState (..) + , coinTypeAda , defaultAddressPoolGap , emptyPendingIxs , mkAddressPool , mkSeqStateFromRootXPrv + , purposeCIP1852 ) import Cardano.Wallet.Primitive.Model ( Wallet, initWallet, unsafeInitWallet ) @@ -319,6 +322,7 @@ bgroupWriteSeqState db = bgroup "SeqState" (mkPool a i) emptyPendingIxs rewardAccount + defaultPrefix | i <- [1..n] ] @@ -574,6 +578,7 @@ withDB :: forall s k. ( PersistState s , PersistPrivateKey (k 'RootK) + , WalletKey k ) => Tracer IO DBLog -> (DBLayer IO s k -> Benchmark) @@ -584,6 +589,7 @@ setupDB :: forall s k. ( PersistState s , PersistPrivateKey (k 'RootK) + , WalletKey k ) => Tracer IO DBLog -> IO (FilePath, SqliteContext, DBLayer IO s k) @@ -749,7 +755,7 @@ testCpByron = snd $ initWallet block0 dummyGenesisParameters initDummyRndState {-# NOINLINE initDummySeqState #-} initDummySeqState :: SeqState 'Mainnet JormungandrKey initDummySeqState = - mkSeqStateFromRootXPrv (xprv, mempty) defaultAddressPoolGap + mkSeqStateFromRootXPrv (xprv, mempty) purposeCIP1852 defaultAddressPoolGap where mnemonic = unsafePerformIO $ SomeMnemonic . entropyToMnemonic @15 @@ -779,6 +785,13 @@ testWid = WalletId (hash ("test" :: ByteString)) testPk :: PrimaryKey WalletId testPk = PrimaryKey testWid +defaultPrefix :: DerivationPrefix +defaultPrefix = DerivationPrefix + ( purposeCIP1852 + , coinTypeAda + , minBound + ) + ourAccount :: JormungandrKey 'AccountK XPub ourAccount = publicKey $ unsafeGenerateKeyFromSeed (seed, Nothing) mempty where diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiAddressDerivationPath.json b/lib/core/test/data/Cardano/Wallet/Api/ApiAddressDerivationPath.json index 5e900184ce8..060e0bfda82 100644 --- a/lib/core/test/data/Cardano/Wallet/Api/ApiAddressDerivationPath.json +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiAddressDerivationPath.json @@ -1,697 +1,221 @@ { - "seed": -176155923881836647, + "seed": 2453672272451951742, "samples": [ [ - { - "derivation_index": 15652, - "derivation_type": "soft" - }, - { - "derivation_index": 16266, - "derivation_type": "hardened" - }, - { - "derivation_index": 15291, - "derivation_type": "soft" - }, - { - "derivation_index": 16742, - "derivation_type": "hardened" - }, - { - "derivation_index": 17896, - "derivation_type": "hardened" - }, - { - "derivation_index": 30655, - "derivation_type": "hardened" - }, - { - "derivation_index": 17383, - "derivation_type": "hardened" - }, - { - "derivation_index": 18245, - "derivation_type": "hardened" - }, - { - "derivation_index": 5168, - "derivation_type": "hardened" - } + "666587165", + "1359030679H", + "1798243549H", + "49570321H", + "1464041277", + "1317282788H", + "752057091", + "147901444", + "667312224", + "2078344037H", + "294943034", + "1799077546", + "840879791H", + "281322944H", + "1483580270H", + "2076907717H", + "298365862", + "1680746759", + "1930021112", + "622816136", + "715841756H", + "701404648H" ], [ - { - "derivation_index": 3951, - "derivation_type": "soft" - }, - { - "derivation_index": 20747, - "derivation_type": "hardened" - }, - { - "derivation_index": 15056, - "derivation_type": "hardened" - }, - { - "derivation_index": 4424, - "derivation_type": "soft" - }, - { - "derivation_index": 4442, - "derivation_type": "soft" - }, - { - "derivation_index": 18035, - "derivation_type": "hardened" - }, - { - "derivation_index": 11174, - "derivation_type": "hardened" - }, - { - "derivation_index": 7492, - "derivation_type": "hardened" - }, - { - "derivation_index": 17745, - "derivation_type": "soft" - }, - { - "derivation_index": 6583, - "derivation_type": "hardened" - }, - { - "derivation_index": 14135, - "derivation_type": "hardened" - }, - { - "derivation_index": 13952, - "derivation_type": "soft" - }, - { - "derivation_index": 30087, - "derivation_type": "soft" - }, - { - "derivation_index": 24919, - "derivation_type": "soft" - }, - { - "derivation_index": 11779, - "derivation_type": "soft" - }, - { - "derivation_index": 19363, - "derivation_type": "soft" - }, - { - "derivation_index": 5944, - "derivation_type": "hardened" - }, - { - "derivation_index": 5256, - "derivation_type": "soft" - }, - { - "derivation_index": 19934, - "derivation_type": "hardened" - }, - { - "derivation_index": 12006, - "derivation_type": "soft" - } + "1120465846", + "900845289H", + "409689366H", + "1978699718", + "1977370396", + "1969939304", + "1237879111", + "1218341290", + "1878064905H", + "418535227", + "4344800H", + "1338484974H", + "1719623875H", + "774130948", + "807723520" ], [ - { - "derivation_index": 487, - "derivation_type": "soft" - }, - { - "derivation_index": 13348, - "derivation_type": "soft" - }, - { - "derivation_index": 557, - "derivation_type": "soft" - }, - { - "derivation_index": 14844, - "derivation_type": "soft" - }, - { - "derivation_index": 6580, - "derivation_type": "hardened" - }, - { - "derivation_index": 10857, - "derivation_type": "hardened" - }, - { - "derivation_index": 25312, - "derivation_type": "soft" - }, - { - "derivation_index": 21569, - "derivation_type": "soft" - }, - { - "derivation_index": 14615, - "derivation_type": "hardened" - } + "220344814H", + "1669228719H", + "652206598", + "140021551H", + "2096962369H", + "62998410", + "829037574", + "450510147H", + "6984553", + "436756371H", + "394034265", + "189378070H", + "1204312973H", + "2108649549", + "1993526766H", + "547059486", + "1653231656H" ], [ - { - "derivation_index": 9523, - "derivation_type": "soft" - }, - { - "derivation_index": 25599, - "derivation_type": "soft" - }, - { - "derivation_index": 16440, - "derivation_type": "soft" - }, - { - "derivation_index": 17036, - "derivation_type": "hardened" - }, - { - "derivation_index": 23, - "derivation_type": "hardened" - }, - { - "derivation_index": 3979, - "derivation_type": "soft" - }, - { - "derivation_index": 7632, - "derivation_type": "hardened" - }, - { - "derivation_index": 8064, - "derivation_type": "soft" - }, - { - "derivation_index": 3355, - "derivation_type": "soft" - }, - { - "derivation_index": 22295, - "derivation_type": "hardened" - }, - { - "derivation_index": 3351, - "derivation_type": "soft" - }, - { - "derivation_index": 17514, - "derivation_type": "hardened" - }, - { - "derivation_index": 9194, - "derivation_type": "soft" - }, - { - "derivation_index": 30919, - "derivation_type": "hardened" - }, - { - "derivation_index": 15120, - "derivation_type": "soft" - }, - { - "derivation_index": 14585, - "derivation_type": "hardened" - }, - { - "derivation_index": 817, - "derivation_type": "hardened" - }, - { - "derivation_index": 10511, - "derivation_type": "soft" - }, - { - "derivation_index": 25923, - "derivation_type": "soft" - }, - { - "derivation_index": 28904, - "derivation_type": "hardened" - }, - { - "derivation_index": 28726, - "derivation_type": "soft" - } + "5756598", + "1450052606", + "328612720", + "660632278", + "2081075074", + "1969198928H", + "1892752480", + "758842516", + "1743703303", + "1713595441", + "1841229258", + "549454582H", + "1537343407", + "317440731", + "614874181", + "154347780H", + "1823421556H", + "2106677000", + "1570259628H", + "918898287", + "2094121548H", + "1356189977", + "1055235100H", + "299852864", + "1423981442", + "1556099542", + "906062462", + "847996014", + "724245856", + "1865801181" ], [ - { - "derivation_index": 18888, - "derivation_type": "soft" - }, - { - "derivation_index": 8602, - "derivation_type": "hardened" - }, - { - "derivation_index": 6719, - "derivation_type": "hardened" - }, - { - "derivation_index": 29096, - "derivation_type": "hardened" - }, - { - "derivation_index": 15096, - "derivation_type": "soft" - }, - { - "derivation_index": 26478, - "derivation_type": "soft" - }, - { - "derivation_index": 17987, - "derivation_type": "soft" - }, - { - "derivation_index": 19895, - "derivation_type": "hardened" - }, - { - "derivation_index": 19274, - "derivation_type": "hardened" - }, - { - "derivation_index": 3899, - "derivation_type": "hardened" - }, - { - "derivation_index": 12544, - "derivation_type": "soft" - }, - { - "derivation_index": 15515, - "derivation_type": "soft" - }, - { - "derivation_index": 19346, - "derivation_type": "hardened" - }, - { - "derivation_index": 14408, - "derivation_type": "hardened" - }, - { - "derivation_index": 12851, - "derivation_type": "hardened" - }, - { - "derivation_index": 5764, - "derivation_type": "hardened" - } + "744642568H", + "991984351", + "1161244574H", + "787368365", + "544851160", + "1486748736H", + "874849871H", + "1514164216", + "212618640", + "737292798H", + "1507763168", + "2110582449H", + "549327274H", + "1843785711", + "863760448H", + "1561302082H", + "592295228", + "135833091H", + "776084343H", + "1628297002", + "1681949541", + "1461662497", + "1279981630", + "1919275233", + "1349009402", + "1716379507", + "1062481222H", + "1405612989H" ], [ - { - "derivation_index": 14607, - "derivation_type": "soft" - }, - { - "derivation_index": 1078, - "derivation_type": "soft" - }, - { - "derivation_index": 21900, - "derivation_type": "soft" - }, - { - "derivation_index": 994, - "derivation_type": "hardened" - }, - { - "derivation_index": 12195, - "derivation_type": "hardened" - }, - { - "derivation_index": 29935, - "derivation_type": "soft" - }, - { - "derivation_index": 26675, - "derivation_type": "hardened" - }, - { - "derivation_index": 11989, - "derivation_type": "hardened" - }, - { - "derivation_index": 14242, - "derivation_type": "soft" - }, - { - "derivation_index": 17437, - "derivation_type": "soft" - }, - { - "derivation_index": 5480, - "derivation_type": "hardened" - }, - { - "derivation_index": 18580, - "derivation_type": "soft" - }, - { - "derivation_index": 12971, - "derivation_type": "hardened" - }, - { - "derivation_index": 32573, - "derivation_type": "hardened" - }, - { - "derivation_index": 11596, - "derivation_type": "hardened" - }, - { - "derivation_index": 13892, - "derivation_type": "hardened" - }, - { - "derivation_index": 10411, - "derivation_type": "soft" - }, - { - "derivation_index": 11103, - "derivation_type": "hardened" - }, - { - "derivation_index": 10443, - "derivation_type": "hardened" - }, - { - "derivation_index": 23833, - "derivation_type": "hardened" - }, - { - "derivation_index": 24433, - "derivation_type": "hardened" - }, - { - "derivation_index": 2415, - "derivation_type": "hardened" - }, - { - "derivation_index": 32404, - "derivation_type": "hardened" - }, - { - "derivation_index": 5278, - "derivation_type": "soft" - }, - { - "derivation_index": 10290, - "derivation_type": "soft" - }, - { - "derivation_index": 26764, - "derivation_type": "soft" - }, - { - "derivation_index": 18996, - "derivation_type": "hardened" - }, - { - "derivation_index": 19333, - "derivation_type": "soft" - }, - { - "derivation_index": 31996, - "derivation_type": "hardened" - } + "1286367190", + "1408686181H", + "2130712582", + "1943058370H", + "594721855H", + "2137976182H", + "1277201816H", + "64065798H", + "997922167", + "1692929269H", + "949883107H", + "345887445", + "1670305263", + "743013424", + "1758285166H", + "1557658219", + "531163201", + "1679435020H", + "241896544H", + "574560818", + "1777861530", + "157869575", + "2065159655", + "2037028085", + "1424615927H" ], [ - { - "derivation_index": 10702, - "derivation_type": "soft" - }, - { - "derivation_index": 20761, - "derivation_type": "soft" - }, - { - "derivation_index": 32174, - "derivation_type": "soft" - }, - { - "derivation_index": 996, - "derivation_type": "soft" - }, - { - "derivation_index": 2640, - "derivation_type": "soft" - }, - { - "derivation_index": 28917, - "derivation_type": "hardened" - }, - { - "derivation_index": 8897, - "derivation_type": "soft" - }, - { - "derivation_index": 24595, - "derivation_type": "soft" - }, - { - "derivation_index": 11628, - "derivation_type": "hardened" - }, - { - "derivation_index": 850, - "derivation_type": "soft" - }, - { - "derivation_index": 9013, - "derivation_type": "hardened" - }, - { - "derivation_index": 31078, - "derivation_type": "hardened" - }, - { - "derivation_index": 26734, - "derivation_type": "hardened" - }, - { - "derivation_index": 32761, - "derivation_type": "hardened" - }, - { - "derivation_index": 2876, - "derivation_type": "soft" - }, - { - "derivation_index": 25297, - "derivation_type": "hardened" - }, - { - "derivation_index": 22349, - "derivation_type": "soft" - }, - { - "derivation_index": 5065, - "derivation_type": "hardened" - } + "749647453H", + "1099364669", + "1583698903", + "764121793H", + "1370170189", + "1299429951", + "451166027H", + "1383285838", + "826185980", + "1138906841", + "78190606H", + "1494443359", + "1275257712H", + "2128772909", + "237134234H", + "2130408147H", + "128541851", + "778583603H", + "2031156017", + "1842408902H", + "583814238H", + "722524153H", + "1353825121", + "419410152", + "2086577147H", + "1535175840", + "66560388H", + "603930321", + "72639973", + "1908847430" ], [ - { - "derivation_index": 18505, - "derivation_type": "soft" - }, - { - "derivation_index": 7943, - "derivation_type": "soft" - }, - { - "derivation_index": 14511, - "derivation_type": "hardened" - }, - { - "derivation_index": 20530, - "derivation_type": "soft" - }, - { - "derivation_index": 9474, - "derivation_type": "soft" - }, - { - "derivation_index": 26421, - "derivation_type": "soft" - }, - { - "derivation_index": 4004, - "derivation_type": "hardened" - }, - { - "derivation_index": 19256, - "derivation_type": "soft" - }, - { - "derivation_index": 2047, - "derivation_type": "hardened" - }, - { - "derivation_index": 18397, - "derivation_type": "soft" - }, - { - "derivation_index": 17531, - "derivation_type": "hardened" - }, - { - "derivation_index": 28411, - "derivation_type": "hardened" - }, - { - "derivation_index": 1533, - "derivation_type": "hardened" - }, - { - "derivation_index": 9350, - "derivation_type": "soft" - }, - { - "derivation_index": 19848, - "derivation_type": "soft" - }, - { - "derivation_index": 8223, - "derivation_type": "soft" - }, - { - "derivation_index": 1099, - "derivation_type": "hardened" - }, - { - "derivation_index": 13051, - "derivation_type": "soft" - } + "1744492721", + "1911426640H", + "456020075", + "1779129788", + "16851663", + "557959505", + "1160380857H", + "1184090320", + "558975526", + "1724999748H", + "325955667H", + "1456977023H", + "2053908374H", + "65657194H", + "882256910H", + "1572143076H", + "1401901564", + "280378626", + "420344080H", + "2002341602H" ], [ - { - "derivation_index": 1671, - "derivation_type": "hardened" - }, - { - "derivation_index": 11112, - "derivation_type": "hardened" - }, - { - "derivation_index": 9398, - "derivation_type": "hardened" - }, - { - "derivation_index": 14696, - "derivation_type": "hardened" - }, - { - "derivation_index": 22926, - "derivation_type": "hardened" - }, - { - "derivation_index": 17314, - "derivation_type": "hardened" - }, - { - "derivation_index": 13105, - "derivation_type": "soft" - }, - { - "derivation_index": 12373, - "derivation_type": "soft" - }, - { - "derivation_index": 20781, - "derivation_type": "hardened" - }, - { - "derivation_index": 30401, - "derivation_type": "hardened" - }, - { - "derivation_index": 22774, - "derivation_type": "soft" - }, - { - "derivation_index": 13067, - "derivation_type": "soft" - } + "1626840370H", + "63737014H", + "1206937288", + "1828425496H", + "1000005464H", + "664161890", + "1746193974", + "501661611" ], [ - { - "derivation_index": 30409, - "derivation_type": "soft" - }, - { - "derivation_index": 2827, - "derivation_type": "soft" - }, - { - "derivation_index": 17985, - "derivation_type": "hardened" - }, - { - "derivation_index": 14847, - "derivation_type": "hardened" - }, - { - "derivation_index": 16116, - "derivation_type": "hardened" - }, - { - "derivation_index": 8392, - "derivation_type": "soft" - }, - { - "derivation_index": 7251, - "derivation_type": "soft" - }, - { - "derivation_index": 25, - "derivation_type": "hardened" - }, - { - "derivation_index": 22483, - "derivation_type": "hardened" - }, - { - "derivation_index": 32338, - "derivation_type": "soft" - }, - { - "derivation_index": 17112, - "derivation_type": "hardened" - }, - { - "derivation_index": 23607, - "derivation_type": "hardened" - }, - { - "derivation_index": 208, - "derivation_type": "soft" - }, - { - "derivation_index": 22058, - "derivation_type": "soft" - }, - { - "derivation_index": 11297, - "derivation_type": "soft" - }, - { - "derivation_index": 14206, - "derivation_type": "soft" - } + "1341296565H" ] ] } \ No newline at end of file diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiAddressDerivationSegment.json b/lib/core/test/data/Cardano/Wallet/Api/ApiAddressDerivationSegment.json index 68470d2ed29..e5e9a10b661 100644 --- a/lib/core/test/data/Cardano/Wallet/Api/ApiAddressDerivationSegment.json +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiAddressDerivationSegment.json @@ -1,45 +1,15 @@ { - "seed": 2918394954490276671, + "seed": 4093926663681590444, "samples": [ - { - "derivation_index": 18641, - "derivation_type": "soft" - }, - { - "derivation_index": 937, - "derivation_type": "hardened" - }, - { - "derivation_index": 18048, - "derivation_type": "soft" - }, - { - "derivation_index": 13275, - "derivation_type": "soft" - }, - { - "derivation_index": 24220, - "derivation_type": "soft" - }, - { - "derivation_index": 23068, - "derivation_type": "hardened" - }, - { - "derivation_index": 16593, - "derivation_type": "hardened" - }, - { - "derivation_index": 14337, - "derivation_type": "soft" - }, - { - "derivation_index": 5088, - "derivation_type": "soft" - }, - { - "derivation_index": 21706, - "derivation_type": "soft" - } + "73694104", + "359965862", + "1782207101H", + "722856414H", + "915114417H", + "1451716877H", + "1723494398H", + "1607171056H", + "1759974484", + "2129205663H" ] } \ No newline at end of file diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiCoinSelectionInputTestnet0.json b/lib/core/test/data/Cardano/Wallet/Api/ApiCoinSelectionInputTestnet0.json index 96f1bcfddba..302b027fdfc 100644 --- a/lib/core/test/data/Cardano/Wallet/Api/ApiCoinSelectionInputTestnet0.json +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiCoinSelectionInputTestnet0.json @@ -1,95 +1,279 @@ { - "seed": 5052956414130988799, + "seed": 7544799786101543150, "samples": [ { "amount": { - "quantity": 127, + "quantity": 1, "unit": "lovelace" }, "address": "", - "id": "37110f18464b6618436e07447f1323ca58690228230d59075171151632082426", - "index": 23209 + "id": "5d184f79144e7d01152627016b52ac83e5664a78650742186943483e273e5922", + "derivation_path": [ + "16895", + "24445", + "28035", + "9265", + "6506", + "28150", + "17767", + "3489", + "22158", + "23408", + "5682", + "16194", + "18186", + "8576", + "13947", + "8460", + "11894", + "9022", + "26973", + "872", + "21146", + "28944" + ], + "index": 18765 }, { "amount": { - "quantity": 22, + "quantity": 180, "unit": "lovelace" }, "address": "", - "id": "d2352e79365f3747495e33826a71fd2c284237717429100b88613df26a0e781f", - "index": 30147 + "id": "3622097d2f6e3e75156e2143234c19434b8e416046100ef035455e565d434729", + "derivation_path": [ + "19530", + "23915", + "24805", + "4884" + ], + "index": 2516 }, { "amount": { - "quantity": 183, + "quantity": 53, "unit": "lovelace" }, "address": "", - "id": "20385d56713ded3852124a6951728a65650a48d31ce457072865034209792984", - "index": 30535 + "id": "660649072eae34711f621d3842513860708f4206364d70682d3f2a304a578f0b", + "derivation_path": [ + "14704", + "23871", + "15665", + "32057", + "4159", + "3128", + "16716", + "11185", + "10703", + "8148", + "11808", + "4127", + "6771" + ], + "index": 18228 }, { "amount": { - "quantity": 168, + "quantity": 146, "unit": "lovelace" }, "address": "", - "id": "4845450c7237327c145b0449bc5469797e344e324a32125d1562237b4c473dfe", - "index": 32386 + "id": "67537b470e5f52043a0665515b5663688a6d68a478146e67c52f67e01560110e", + "derivation_path": [ + "16368", + "26581", + "11496", + "24149", + "32067", + "20333", + "9155", + "27428", + "23447", + "28472", + "19179", + "31028", + "1817", + "19417", + "17887", + "30722", + "434", + "5307", + "8281", + "18688", + "25202", + "18290", + "29944", + "8506" + ], + "index": 25009 }, { "amount": { - "quantity": 109, + "quantity": 147, "unit": "lovelace" }, "address": "", - "id": "226f1568174336354d0f19653973d258790f5be971ec2f36380d5585590e2066", - "index": 11246 + "id": "299f755b61254197247c254b2a3fee013e202510852f123e193c634f7c13643e", + "derivation_path": [ + "22439", + "31918", + "32353", + "12251", + "26768", + "26437", + "31993", + "22417", + "30061", + "19697", + "29669", + "15191", + "6747", + "15494", + "5283" + ], + "index": 11225 }, { "amount": { - "quantity": 158, + "quantity": 236, "unit": "lovelace" }, "address": "", - "id": "1b408a4e1f1537350c7413e44dd6083a6858616fe7d74a3b30722d7b7b7b7135", - "index": 27755 + "id": "7e42261a69776a14497af731df166665183548f6555e14202b757512091fbf19", + "derivation_path": [ + "9076", + "22552", + "25965", + "21131", + "2643", + "3110", + "27234", + "19606", + "6662" + ], + "index": 1300 }, { "amount": { - "quantity": 229, + "quantity": 107, "unit": "lovelace" }, "address": "", - "id": "1d616f6a6a30ad162c34090f04730f81737328c37d6115b72419f32f72252e6b", - "index": 28496 + "id": "200c5f095d3e5208784678260c3e163a204d24667c59051a3f586243574766f8", + "derivation_path": [ + "20602", + "5672", + "17211", + "7593", + "28753", + "23149", + "9857", + "27430", + "25119", + "22397", + "19295", + "7251", + "32159" + ], + "index": 23745 }, { "amount": { - "quantity": 117, + "quantity": 131, "unit": "lovelace" }, "address": "", - "id": "08466d797e2817ed77551f4c649d7d1f322b3d48ec4553227b7f2d20043e787e", - "index": 26850 + "id": "7c02070949238e317a67281ca94564273b3b434f083ef1062e635c288f3f5665", + "derivation_path": [ + "21196", + "25372", + "3945", + "23352", + "10370", + "32673", + "7267", + "21429", + "5791", + "23999", + "15330", + "14783", + "7123", + "12481", + "15903", + "25315", + "947", + "14017", + "22692" + ], + "index": 3574 }, { "amount": { - "quantity": 66, + "quantity": 44, "unit": "lovelace" }, "address": "", - "id": "5d0c53774926340e77796c1274c28175674e4bd3154e3064057218eb7e700200", - "index": 8391 + "id": "ed2e382771255b073c362b30b83f2cb41e4b09561d3d010e2187674343787821", + "derivation_path": [ + "6942", + "13519", + "15118", + "8426", + "3638", + "26762", + "14923", + "28399", + "5993", + "19323", + "32649", + "15288", + "8284", + "9075", + "32512", + "1680", + "24175", + "2361", + "15240", + "26849", + "18116", + "4031", + "18939", + "13867", + "19855", + "28032", + "30827", + "27149" + ], + "index": 1827 }, { "amount": { - "quantity": 35, + "quantity": 30, "unit": "lovelace" }, "address": "", - "id": "050b54675269372e0bd9850493907a2e2f247f79690d532e795025144708334f", - "index": 1421 + "id": "01fc6914453423225d16296158904ace3e76041c13006408fa76d14820497a91", + "derivation_path": [ + "10502", + "2805", + "19218", + "5488", + "23887", + "19485", + "28787", + "28946", + "8165", + "112", + "22397", + "4372", + "19439", + "28032", + "27624", + "32131", + "27624" + ], + "index": 28604 } ] } \ No newline at end of file diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiCoinSelectionTestnet0.json b/lib/core/test/data/Cardano/Wallet/Api/ApiCoinSelectionTestnet0.json index aeca939c765..e8af72602b7 100644 --- a/lib/core/test/data/Cardano/Wallet/Api/ApiCoinSelectionTestnet0.json +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiCoinSelectionTestnet0.json @@ -1,333 +1,511 @@ { - "seed": -2773712990627456331, + "seed": 2752656951393770049, "samples": [ { "inputs": [ { "amount": { - "quantity": 245, - "unit": "lovelace" - }, - "address": "", - "id": "381fc8324b323f13f1470f0641ef6cfd255537f54e27772b4d2c4a372d602893", - "index": 1895 - }, - { - "amount": { - "quantity": 183, - "unit": "lovelace" - }, - "address": "", - "id": "225173205e28723813446207237b2c1f3804531b64286e2910627b126c527d48", - "index": 7527 - }, - { - "amount": { - "quantity": 45, + "quantity": 61, "unit": "lovelace" }, "address": "", - "id": "1d742aa1124143cc3935756171026057780145261009152e627c445e6ee75b40", - "index": 4672 + "id": "659450171b5f1a6932461524583c7308656bd86dfa7a3e427a300c40545816e7", + "derivation_path": [ + "27518", + "13101", + "14855", + "7206", + "22582", + "15409", + "21729", + "4392", + "29783", + "15372", + "14411", + "15338", + "17867", + "12991", + "4744", + "12812", + "26640", + "26354", + "521", + "24283", + "21797", + "30843", + "31443", + "4349", + "8929", + "16061", + "6666" + ], + "index": 25180 }, { "amount": { - "quantity": 139, - "unit": "lovelace" - }, - "address": "", - "id": "08ba0a176030a2aa482f7307287f0c838b0844484f0c2b6c0279421463029066", - "index": 17387 - } - ], - "outputs": [ - { - "amount": { - "quantity": 234, - "unit": "lovelace" - }, - "address": "" - } - ] - }, - { - "inputs": [ - { - "amount": { - "quantity": 155, + "quantity": 222, "unit": "lovelace" }, "address": "", - "id": "4c4b2397263b2f2a2b44744a2c2a5d7e351e3717694334f95b16166f752e2827", - "index": 28439 + "id": "5c1a350b52101c7e7b7d63562068f53d7014d99f07790d145e093d30230d062b", + "derivation_path": [ + "3683" + ], + "index": 30496 }, { "amount": { - "quantity": 40, + "quantity": 109, "unit": "lovelace" }, "address": "", - "id": "415ffb0c022971032b608d3046c0052870953751a4782e3366547c5b9846097a", - "index": 21476 + "id": "59765d722c0b793e0c462a0b95b838dc2f81360df415075269481d5b1000293b", + "derivation_path": [ + "30738", + "4647", + "26784", + "27841" + ], + "index": 27201 }, { "amount": { - "quantity": 1, + "quantity": 200, "unit": "lovelace" }, "address": "", - "id": "38436b683332169f1419235ae87635121e3b290727735c7ed35669507f65223a", - "index": 23290 + "id": "4afa7f216a33794c99736a4b3d226d5842612562e310065126537d8f5b304f4b", + "derivation_path": [ + "15454", + "30398", + "18226", + "27766", + "12861", + "18596" + ], + "index": 32032 }, { "amount": { - "quantity": 145, + "quantity": 238, "unit": "lovelace" }, "address": "", - "id": "2c1e7b00617d1e786f73364c18304a0333020e571c8c2f4b105756b737217608", - "index": 15715 + "id": "65d1936084747a657e313ddb5e141f3c739e483f843d5f1822c2180f2afe1928", + "derivation_path": [ + "5746", + "479" + ], + "index": 29221 }, { "amount": { - "quantity": 66, + "quantity": 220, "unit": "lovelace" }, "address": "", - "id": "026409003a13192d224b7f002064342a113d50223f4d6f1d014a603a40010b23", - "index": 25119 + "id": "69716c5e106512696636ff4e58710085b31e317b51440d50221e00e32c45de60", + "derivation_path": [ + "32725", + "8147", + "298", + "7511", + "20893", + "30757", + "31172", + "17786", + "21252", + "17429", + "17097", + "2618", + "31651", + "26996", + "17478", + "5968", + "25970", + "26233", + "25317", + "8430", + "8902", + "18405", + "23246", + "29306", + "6297", + "32767" + ], + "index": 4806 }, { "amount": { - "quantity": 95, + "quantity": 255, "unit": "lovelace" }, "address": "", - "id": "247d96243663446b4d205cec74120036706625730c1a1208540b2f6053bc7a20", - "index": 6799 + "id": "3d63392555637714e4e861232344613f3d416a733a107dc33a2e7f332b2d2d29", + "derivation_path": [ + "28428", + "26722", + "29314", + "24590", + "7761", + "16590", + "19900", + "25169", + "5417", + "2910", + "6406", + "16710", + "16491", + "20850", + "20912" + ], + "index": 25206 }, { "amount": { - "quantity": 134, + "quantity": 42, "unit": "lovelace" }, "address": "", - "id": "1addac284707ad582ca16a791c56f44359234a523e1d0714293374b0997c5260", - "index": 7607 + "id": "b346541ee16f1e575f0a2e2c77249c63645a1737532e7e1d6f6ca21a741e7e44", + "derivation_path": [ + "27116", + "32036", + "18135", + "4351", + "7624", + "2140", + "8978", + "2569", + "2896", + "32651", + "10824", + "4982", + "26938", + "21379" + ], + "index": 9720 }, { "amount": { - "quantity": 28, + "quantity": 144, "unit": "lovelace" }, "address": "", - "id": "0941ab0600041422261c3d37579f635b585343732a7f70116e47488d40041560", - "index": 28396 + "id": "51149d3a653b051f415f417f2d434bcde1064434323943362d7a27d6760bd237", + "derivation_path": [ + "14414", + "5868", + "17053", + "10158", + "27404" + ], + "index": 19089 }, { "amount": { - "quantity": 241, + "quantity": 220, "unit": "lovelace" }, "address": "", - "id": "035b3b3449062d1715505d1b0c51051d14013e2b7d063b4c260c17536f6e0828", - "index": 6240 + "id": "3269642b6a43621c4b5e1d5464424c8a1d7d5a2f462a452016702f433b0b4761", + "derivation_path": [ + "21619" + ], + "index": 13778 }, { "amount": { - "quantity": 253, + "quantity": 121, "unit": "lovelace" }, "address": "", - "id": "7529ef4002272d0c6e3110545d3a6a161e91210d0729350793197e6617744565", - "index": 18642 + "id": "52707b1b1c12254f7c314522db613e3a670c6751113459015520340d5f771138", + "derivation_path": [ + "10842", + "21571", + "19054", + "17012", + "7787", + "391", + "31036", + "15230", + "16449", + "9525", + "29423", + "32549", + "27158", + "31973", + "15782", + "4850", + "22144", + "15768", + "23850", + "4761", + "15411", + "4535", + "5979", + "12192" + ], + "index": 32006 }, { "amount": { - "quantity": 139, + "quantity": 161, "unit": "lovelace" }, "address": "", - "id": "4868097f236eb455e9398a79522702611725426e0e734f68394dc259658a7467", - "index": 27234 + "id": "f92a213978302500ba5f5965465f1454a23f4f531d5b3e01120163a11af53110", + "derivation_path": [ + "10347", + "10091", + "2699", + "14986", + "6522", + "31074", + "5682", + "22282", + "21213", + "10520", + "7170", + "30927", + "23259", + "32021", + "13704", + "22943" + ], + "index": 16652 + }, + { + "amount": { + "quantity": 113, + "unit": "lovelace" + }, + "address": "", + "id": "4d47404307340f221b53200f176d53582d0d742673322c0e675d15091c290f6a", + "derivation_path": [ + "28969", + "21115", + "7111", + "30167", + "9977", + "21950", + "31236", + "16247", + "1917", + "13150", + "21128", + "12908", + "19511", + "12471", + "9873", + "27920" + ], + "index": 26491 + }, + { + "amount": { + "quantity": 181, + "unit": "lovelace" + }, + "address": "", + "id": "95499677dd7b8b667be8115e8c2941ca1b6279640d22614b2e1b62296255dda3", + "derivation_path": [ + "28727", + "23697", + "23376", + "11282", + "29705", + "30392", + "2584", + "1065", + "12143", + "14790", + "19060", + "15296", + "25025", + "22925", + "16346", + "18739", + "3591", + "18138", + "9907", + "29874", + "32754" + ], + "index": 26941 + }, + { + "amount": { + "quantity": 97, + "unit": "lovelace" + }, + "address": "", + "id": "7dd93e17313910f76cc913440ee6ad751d2f744a5f602c144e9470bd46009b64", + "derivation_path": [ + "25760", + "30793", + "14400", + "21141", + "10391" + ], + "index": 1368 }, { "amount": { - "quantity": 17, + "quantity": 95, "unit": "lovelace" }, "address": "", - "id": "30144164222bf25f1d105e7e5d590e5409453539306744552c527b621f42502d", - "index": 17440 + "id": "760edd2b263127df4c6f5f751a60acdd6e75031113571d4e5c7f0a5a79301d46", + "derivation_path": [ + "5810", + "19867", + "11420", + "12537", + "12906", + "10236", + "1432", + "28123" + ], + "index": 9559 }, { "amount": { - "quantity": 218, + "quantity": 82, "unit": "lovelace" }, "address": "", - "id": "117c6c7f116915921b181f32c9791d71400e32412b0b0405056a796138495b4a", - "index": 12989 + "id": "5e284b2403055363337a4e29c67f297951c477545c11352d950c8e28372e274e", + "derivation_path": [ + "4985" + ], + "index": 30239 } ], "outputs": [ { "amount": { - "quantity": 237, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 67, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 80, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 242, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 123, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 123, + "quantity": 142, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 157, + "quantity": 54, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 43, + "quantity": 38, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 161, + "quantity": 217, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 207, + "quantity": 47, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 192, + "quantity": 13, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 109, + "quantity": 16, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 56, + "quantity": 103, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 179, + "quantity": 33, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 175, + "quantity": 78, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 184, + "quantity": 174, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 123, + "quantity": 67, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 85, + "quantity": 169, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 193, + "quantity": 116, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 66, + "quantity": 164, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 225, + "quantity": 122, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 55, + "quantity": 102, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 215, + "quantity": 227, "unit": "lovelace" }, "address": "" @@ -338,1709 +516,2282 @@ "inputs": [ { "amount": { - "quantity": 248, - "unit": "lovelace" - }, - "address": "", - "id": "3d0c4c161a6d7b6f98b801da7a205c7beb02310e359d766b552439082f095032", - "index": 20839 - }, - { - "amount": { - "quantity": 53, - "unit": "lovelace" - }, - "address": "", - "id": "921775057e6b3079508723690d63666938971f4771262e9d501f6a2e0a66a670", - "index": 22268 - }, - { - "amount": { - "quantity": 216, - "unit": "lovelace" - }, - "address": "", - "id": "5d7f5f4d55f93116410a724d447c1c1d3a301a52620c4e7d387ed2464ac99877", - "index": 23922 - }, - { - "amount": { - "quantity": 163, - "unit": "lovelace" - }, - "address": "", - "id": "080114335c4cf234f75b5b7d575038457397bb413ab215881c1964e019751279", - "index": 30216 - }, - { - "amount": { - "quantity": 2, - "unit": "lovelace" - }, - "address": "", - "id": "5266d14870055c117d6365671cf84d085b32191e5d4c63736669547f12650646", - "index": 6126 - }, - { - "amount": { - "quantity": 27, - "unit": "lovelace" - }, - "address": "", - "id": "5130716a38256e440a5c56b810544a611f69456809b051055247212494347561", - "index": 8701 - }, - { - "amount": { - "quantity": 129, - "unit": "lovelace" - }, - "address": "", - "id": "165a4a9d357f5a6c33715168c4632e4c04734916856914588b43c5e639633a0e", - "index": 29472 - }, - { - "amount": { - "quantity": 89, - "unit": "lovelace" - }, - "address": "", - "id": "3f3d77117f1f5b457b3145694f28a934436f1268ed19670c73682a5e3d6b144c", - "index": 1074 - }, - { - "amount": { - "quantity": 87, + "quantity": 142, "unit": "lovelace" }, "address": "", - "id": "174984a10911443c5c104434e2261553714e47346f661bade124416427572208", - "index": 11391 + "id": "52767ba5686740327419234c7bc12cb76650343e3a117d1ed320b0225e377992", + "derivation_path": [ + "18481", + "17696", + "1245" + ], + "index": 25488 }, { "amount": { - "quantity": 124, + "quantity": 167, "unit": "lovelace" }, "address": "", - "id": "405e20d0525630750523c45d3d58522306d0fe06101e71027a221e77c721b772", - "index": 32689 + "id": "12377edf23aa556c2a2a5664515b261eb205aa067745742f276a2f14205757f9", + "derivation_path": [ + "7589", + "27120", + "14104", + "9127", + "30159", + "19571", + "2233", + "27454", + "26640", + "18919", + "5117", + "5679", + "28870", + "17930", + "18472", + "31831", + "14149", + "11289", + "18141", + "29459", + "25478", + "20840" + ], + "index": 24271 }, { "amount": { - "quantity": 242, + "quantity": 149, "unit": "lovelace" }, "address": "", - "id": "0a76151a74400b59263d52326a72684b7f4cbe165d5c357c3f65056313350a16", - "index": 2169 - }, + "id": "445902767030794e9755a35f552ab65741144f3354de6e05416763314e19060c", + "derivation_path": [ + "28499", + "18385", + "23272", + "4959", + "410", + "30728", + "9944", + "31710", + "18950", + "1455", + "2339", + "28346", + "30000", + "14246", + "29289", + "6581", + "20612", + "31087", + "27184", + "21196", + "28006", + "6892", + "18547", + "11729", + "12230", + "5731" + ], + "index": 13934 + } + ], + "outputs": [ { "amount": { - "quantity": 160, + "quantity": 220, "unit": "lovelace" }, - "address": "", - "id": "42417aee2fa16a6f766e6205373c36c332340c424c13553b00973aba7e7a6521", - "index": 669 + "address": "" }, { "amount": { - "quantity": 111, + "quantity": 132, "unit": "lovelace" }, - "address": "", - "id": "fd60265f795e2f030279686c483379d102456b820def843b8c226b656c2477d6", - "index": 5555 + "address": "" }, { "amount": { - "quantity": 103, + "quantity": 20, "unit": "lovelace" }, - "address": "", - "id": "3e360b2b112c772a4c3a4e0d994c775c7acac3e4796129466f4a1d5f248840cb", - "index": 26999 + "address": "" }, { "amount": { - "quantity": 69, + "quantity": 221, "unit": "lovelace" }, - "address": "", - "id": "bb4b2e6b9c5d7ae14a420a4c2a3c732e7e59686b7ab7b8321fc06a0d33794641", - "index": 13190 + "address": "" }, { "amount": { - "quantity": 185, + "quantity": 253, "unit": "lovelace" }, - "address": "", - "id": "6028025b383f0b35636342b843223557be365a241fac4e0344587b9cc0360836", - "index": 25813 + "address": "" }, { "amount": { - "quantity": 193, + "quantity": 235, "unit": "lovelace" }, - "address": "", - "id": "7f045bd319515d3a3ac4075e7002753b5d54444857001e3702597e1e52113633", - "index": 16986 + "address": "" }, { "amount": { - "quantity": 106, + "quantity": 145, "unit": "lovelace" }, - "address": "", - "id": "3223715615730911356a250c0329562d715145764016f6722099148f604d6608", - "index": 15339 + "address": "" }, { "amount": { - "quantity": 250, + "quantity": 212, "unit": "lovelace" }, - "address": "", - "id": "5757232126a2570263433a207c4457647f726821456943b8435dc1a407fc2548", - "index": 10009 + "address": "" }, { "amount": { - "quantity": 38, + "quantity": 175, "unit": "lovelace" }, - "address": "", - "id": "d0eb594736725542440f61216c4548a34b122e8c1c784c69af0d7128774f4661", - "index": 29815 + "address": "" }, { "amount": { - "quantity": 151, + "quantity": 236, "unit": "lovelace" }, - "address": "", - "id": "2a5b05500124d801726a6b027f1b20e15067013770635c79146e7316304b2314", - "index": 3302 + "address": "" }, { "amount": { - "quantity": 249, + "quantity": 46, "unit": "lovelace" }, - "address": "", - "id": "0ebe7130318e1b63a348405e6ebc81635a0c5a1f7a331829247b5a54661d1779", - "index": 22531 + "address": "" }, { "amount": { - "quantity": 120, + "quantity": 141, "unit": "lovelace" }, - "address": "", - "id": "40070ea3190c633c2f7ffb7e336867e8007f176f171e332b4c97aa1d546f1d19", - "index": 30303 + "address": "" }, { "amount": { - "quantity": 12, + "quantity": 98, "unit": "lovelace" }, - "address": "", - "id": "7d177c1a42220b3dde043f24645f5804ed4a242e621a7a151239736aa42f60f5", - "index": 6585 + "address": "" }, { "amount": { - "quantity": 162, + "quantity": 127, "unit": "lovelace" }, - "address": "", - "id": "47aa4a333d6071541c631169504a566f32787fda3c282c2be24b44423020edee", - "index": 21479 + "address": "" }, { "amount": { - "quantity": 66, + "quantity": 215, "unit": "lovelace" }, - "address": "", - "id": "056c3e5200335c15b41b6cc44c23245c4a200b78777d23357f533461916a5814", - "index": 22082 + "address": "" }, { "amount": { - "quantity": 131, + "quantity": 172, "unit": "lovelace" }, - "address": "", - "id": "f1686b1b5b0a517129603a53197402edf1134f86055033080f2b673b0d4a3633", - "index": 535 + "address": "" }, { "amount": { - "quantity": 167, - "unit": "lovelace" - }, - "address": "", - "id": "c60d64351ba75f1d2239875e732d0307a121300d52255a372d4c2ff7b051bb8d", - "index": 2094 - } - ], - "outputs": [ - { - "amount": { - "quantity": 8, + "quantity": 238, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 102, + "quantity": 10, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 90, + "quantity": 108, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 49, + "quantity": 104, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 41, + "quantity": 170, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 144, + "quantity": 78, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 62, + "quantity": 28, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 18, + "quantity": 6, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 237, + "quantity": 66, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 43, + "quantity": 85, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 100, + "quantity": 84, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 248, + "quantity": 52, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 46, + "quantity": 208, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 168, + "quantity": 63, "unit": "lovelace" }, "address": "" - }, + } + ] + }, + { + "inputs": [ { "amount": { - "quantity": 6, + "quantity": 238, "unit": "lovelace" }, - "address": "" + "address": "", + "id": "574e025d702239520d0d38787e363433011c7672012a24ec566d697e607d5e68", + "derivation_path": [ + "10918", + "16880", + "13623", + "26037", + "6776", + "1928", + "20162", + "28097", + "642", + "18259", + "11300", + "29837", + "24199", + "21156", + "21319", + "4577", + "13189", + "10782", + "27498", + "13347", + "30100", + "15382", + "14906", + "16121", + "5605", + "5174", + "27744", + "14113", + "2719" + ], + "index": 23467 }, { "amount": { - "quantity": 81, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 215, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 160, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 147, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 221, - "unit": "lovelace" - }, - "address": "" - } - ] - }, - { - "inputs": [ - { - "amount": { - "quantity": 211, - "unit": "lovelace" - }, - "address": "", - "id": "746b6256fb45455f4329763e35173b714e16127c1f661a1a7a0202001321777f", - "index": 8540 - }, - { - "amount": { - "quantity": 137, - "unit": "lovelace" - }, - "address": "", - "id": "1208661b7622795d368910bc9f5d4d184e2a7454de11066d0d6803466f1f457f", - "index": 27277 - }, - { - "amount": { - "quantity": 81, - "unit": "lovelace" - }, - "address": "", - "id": "6739161ffd6d015edf3c337a34a01255955bd4432e635a767b6c18003779520c", - "index": 29105 - }, - { - "amount": { - "quantity": 209, - "unit": "lovelace" - }, - "address": "", - "id": "3e190139714358056f1d0c4511362d312e001803197b9e02502c49102b4a0439", - "index": 27239 - }, - { - "amount": { - "quantity": 51, - "unit": "lovelace" - }, - "address": "", - "id": "3d0c2e4e775c367f1f76ed630c56d61f38407c240226875444430b0d54625d47", - "index": 24912 - }, - { - "amount": { - "quantity": 203, - "unit": "lovelace" - }, - "address": "", - "id": "5e2c7f7e402e5e0a6a5d2c387a9b320f3641733a2b195136540acf79394448de", - "index": 11369 - }, - { - "amount": { - "quantity": 112, - "unit": "lovelace" - }, - "address": "", - "id": "3c3862146b0f3f1f250f2f143c2d08340f28555c0440a77c6047156f2974755a", - "index": 7814 - }, - { - "amount": { - "quantity": 196, - "unit": "lovelace" - }, - "address": "", - "id": "7c6431177b44d57a614b05635341456c2e6d50183677792525297476ca1c4f66", - "index": 22324 - }, - { - "amount": { - "quantity": 233, - "unit": "lovelace" - }, - "address": "", - "id": "651d4b07696f1f72705244336c5f0d215d941c313959813b4f19514d4240793a", - "index": 28977 - }, - { - "amount": { - "quantity": 47, - "unit": "lovelace" - }, - "address": "", - "id": "7604bf4437786371220204122ddcb54d6342e351521114d1354272fb4a642d26", - "index": 20424 - }, - { - "amount": { - "quantity": 140, - "unit": "lovelace" - }, - "address": "", - "id": "5f1696b70d7e18091d4e57600e2a770365af94652941612669165d616f78735b", - "index": 12156 - }, - { - "amount": { - "quantity": 49, - "unit": "lovelace" - }, - "address": "", - "id": "0179ec891578c84ece62933f7b5d0274314753117ea957127c72071f1ac8442e", - "index": 2630 - }, - { - "amount": { - "quantity": 207, - "unit": "lovelace" - }, - "address": "", - "id": "463763610e30e03052a754eca12dacfd1739ce5c6033435963604f635d31407b", - "index": 16501 - }, - { - "amount": { - "quantity": 145, - "unit": "lovelace" - }, - "address": "", - "id": "19310bbe14125d17576f67182e411124260a48664909057e2a3a412574301366", - "index": 19802 - }, - { - "amount": { - "quantity": 34, - "unit": "lovelace" - }, - "address": "", - "id": "046a784f0b774ae129331505202c1b020b5e75062e43252468b391214a6bbf71", - "index": 21717 - }, - { - "amount": { - "quantity": 117, - "unit": "lovelace" - }, - "address": "", - "id": "7e7b6c6868c55e731335584d2e28185c0d768a88404a108a0b276a706f3f1a20", - "index": 7010 - } - ], - "outputs": [ - { - "amount": { - "quantity": 239, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 43, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 71, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 150, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 208, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 162, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 176, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 207, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 193, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 114, - "unit": "lovelace" - }, - "address": "" - } - ] - }, - { - "inputs": [ - { - "amount": { - "quantity": 235, - "unit": "lovelace" - }, - "address": "", - "id": "023c3bf2206b159c616b70522b573553cd16454b2b6feda5190e2a311f3d1019", - "index": 3611 - }, - { - "amount": { - "quantity": 242, - "unit": "lovelace" - }, - "address": "", - "id": "5f13b4085d5f5e421b8013003b8b25cc186d12057c75d93c261560f21c3b3909", - "index": 21012 - }, - { - "amount": { - "quantity": 149, - "unit": "lovelace" - }, - "address": "", - "id": "31250b3717d3481a6664687c286e58041d0aee08462e181e2d7f4b67375fdedc", - "index": 18234 - }, - { - "amount": { - "quantity": 254, - "unit": "lovelace" - }, - "address": "", - "id": "4c234354596d544860135e13304bac3eff543d3300e6414e3c32613b457d2118", - "index": 12223 - }, - { - "amount": { - "quantity": 4, - "unit": "lovelace" - }, - "address": "", - "id": "4bb51a08596e2f640f024521775b601ecd0a386252166e00336de381181d2972", - "index": 21379 - }, - { - "amount": { - "quantity": 226, - "unit": "lovelace" - }, - "address": "", - "id": "506746695fb5054df44a0d683b535da03b117d1b2b6d6f4e7d6322023f51397d", - "index": 17891 - }, - { - "amount": { - "quantity": 190, - "unit": "lovelace" - }, - "address": "", - "id": "183d22225d766d32688c6b7ddf0d7dc47ecb577e6529283b31621f6c112c550f", - "index": 11762 - }, - { - "amount": { - "quantity": 127, - "unit": "lovelace" - }, - "address": "", - "id": "19f673db6228122048cb885a614843394a2c155b2f34175006361d2e653669a5", - "index": 21468 - }, - { - "amount": { - "quantity": 248, - "unit": "lovelace" - }, - "address": "", - "id": "2524124df8fe263629235477731a5c75132b8e60020fec441d5c29596e5b2730", - "index": 12738 - }, - { - "amount": { - "quantity": 86, - "unit": "lovelace" - }, - "address": "", - "id": "38035479265551235d0e437fd263050f226a3f6878600d2de83c5a7b2b3a533b", - "index": 15392 - }, - { - "amount": { - "quantity": 47, - "unit": "lovelace" - }, - "address": "", - "id": "71345855ed0931407d6b54443d5566be63bd7150cb5c1d4339af2e3ca00c3eee", - "index": 19718 - }, - { - "amount": { - "quantity": 169, - "unit": "lovelace" - }, - "address": "", - "id": "3f397c53239b5717611f1c5a27bed1276c4a0100c776681912f73b124e564b9f", - "index": 31181 - }, - { - "amount": { - "quantity": 238, - "unit": "lovelace" - }, - "address": "", - "id": "7b1d411125545444222716002973160b443f71d84a675d374c312929682d1b2c", - "index": 28660 - }, - { - "amount": { - "quantity": 102, - "unit": "lovelace" - }, - "address": "", - "id": "17130d7c0252673c6d106e3f661f73110a07670a31003b05303a357648923309", - "index": 26968 - }, - { - "amount": { - "quantity": 215, - "unit": "lovelace" - }, - "address": "", - "id": "2a0830472f182e1b461733727a4e357a264f52354a473d763d71761964026f6b", - "index": 12734 - }, - { - "amount": { - "quantity": 255, - "unit": "lovelace" - }, - "address": "", - "id": "06633f1b5e254c4b7f3e6e6f7e8e6c586c576c670476432d9a4a823279c61c6b", - "index": 32163 - }, - { - "amount": { - "quantity": 118, - "unit": "lovelace" - }, - "address": "", - "id": "4e69e56ab00a75301843be21af5a23674b57424d22538d540f4c140056442100", - "index": 28586 - }, - { - "amount": { - "quantity": 238, - "unit": "lovelace" - }, - "address": "", - "id": "1904757a692f5117d9e72e4a295a526f94571c50cc6a584ee64f43aa354d3b22", - "index": 28909 - }, - { - "amount": { - "quantity": 103, - "unit": "lovelace" - }, - "address": "", - "id": "043b2066080374755c4c03010c3bc211e508054b1d14777c4e1d6e6a39304771", - "index": 10355 - }, - { - "amount": { - "quantity": 102, - "unit": "lovelace" - }, - "address": "", - "id": "6e11552c74770c8d7a1e0f53454b04841b761d6c782728432b1f4d611776c912", - "index": 17599 - }, - { - "amount": { - "quantity": 7, - "unit": "lovelace" - }, - "address": "", - "id": "064a151f07170e35741c51826a479e2263cd360cb9233f15090912733b4e3a3a", - "index": 2789 - }, - { - "amount": { - "quantity": 35, - "unit": "lovelace" - }, - "address": "", - "id": "3e59c3a42904006c4aa60f6f557c564630352743344860da09ba70524c736c01", - "index": 2418 - }, - { - "amount": { - "quantity": 174, - "unit": "lovelace" - }, - "address": "", - "id": "a34c4261395765de95175c6b023693aa6c946440654541092d4f61760f467f1f", - "index": 6960 - }, - { - "amount": { - "quantity": 239, - "unit": "lovelace" - }, - "address": "", - "id": "50590d3c475970313019635b43c74b5f48cfaf6138d715722751d223426c4a44", - "index": 31167 - }, - { - "amount": { - "quantity": 7, - "unit": "lovelace" - }, - "address": "", - "id": "7b723b75ebc60d096aef2738096f6e3a17075da97dff1a704705b7b5bb282815", - "index": 8930 - }, - { - "amount": { - "quantity": 196, - "unit": "lovelace" - }, - "address": "", - "id": "012d545b4d4c19494852013671a81942681911402979346f78e767721a502559", - "index": 1348 - }, - { - "amount": { - "quantity": 214, - "unit": "lovelace" - }, - "address": "", - "id": "85206966fe461b73591a6c1697615f71484f8f756b1f2f11204b74742d7f252f", - "index": 29252 - }, - { - "amount": { - "quantity": 61, - "unit": "lovelace" - }, - "address": "", - "id": "573a6309215d6867263ab3584848422bfdfd460206675113136c69383a3035fa", - "index": 6358 - }, - { - "amount": { - "quantity": 49, + "quantity": 131, "unit": "lovelace" }, "address": "", - "id": "389e27154578fa395a98579402343e311d0110646f17365c23094b7d1d0b3a0d", - "index": 24216 - }, - { - "amount": { - "quantity": 63, - "unit": "lovelace" - }, - "address": "", - "id": "04dd3d60f63a63645ca619510b096471866445d00f5d571f39d54c221bc82237", - "index": 31740 - } - ], - "outputs": [ - { - "amount": { - "quantity": 128, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 178, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 22, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 184, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 58, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 101, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 102, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 208, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 188, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 221, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 151, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 82, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 10, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 46, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 142, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 0, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 57, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 52, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 218, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 31, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 112, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 33, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 137, - "unit": "lovelace" - }, - "address": "" - } - ] - }, - { - "inputs": [ + "id": "5f23682e2f063e556519226d622e33b72640309612247251715982310c3d4669", + "derivation_path": [ + "30520", + "10964", + "14832", + "5574", + "26068", + "21859", + "16712", + "4108", + "1321", + "8920", + "29725", + "30895", + "16471", + "5972", + "13503", + "3716", + "14919", + "12054", + "7697" + ], + "index": 28067 + }, { "amount": { - "quantity": 226, + "quantity": 49, "unit": "lovelace" }, "address": "", - "id": "1c7d012c017c753137d9ced4640716270b2368f0401e126f4d0c500999773642", - "index": 22458 + "id": "8969663a377b6373b5163872040d2c103a34735a6f213529c036183268180b02", + "derivation_path": [ + "15364", + "15729", + "370", + "11866", + "15682", + "20495", + "31604", + "23019", + "17355", + "15994", + "23969", + "15653", + "2913", + "21256", + "3011", + "23567", + "21076", + "25762" + ], + "index": 1826 }, { "amount": { - "quantity": 191, + "quantity": 2, "unit": "lovelace" }, "address": "", - "id": "4e1c693e4e1639316765540216236e5f06176343140136563cc7452b234c085f", - "index": 2290 + "id": "42345425ac7d036f118b1b7f5d04c18561517d1212314c6c347d6f533758341e", + "derivation_path": [ + "30004", + "14054", + "19286", + "12354", + "8157", + "16566", + "8475", + "27777", + "26311" + ], + "index": 22842 }, { "amount": { - "quantity": 192, + "quantity": 15, "unit": "lovelace" }, "address": "", - "id": "52724a1a1f7a657159186d417c65450f7161791c17421f8cc37a2b2d86117517", - "index": 18335 + "id": "413e183cfb294046e7356e937105254d4539214218223c7521298930594f235a", + "derivation_path": [ + "14871", + "27255", + "3972", + "15296", + "9294", + "26028", + "10842", + "6507", + "24876", + "25160", + "23960", + "31107", + "7538", + "14681", + "22669", + "1202", + "14931" + ], + "index": 17046 }, { "amount": { - "quantity": 149, + "quantity": 216, "unit": "lovelace" }, "address": "", - "id": "412a404d32adc72b4063537b762d0055414948ab55071208b311125d6934e645", - "index": 15 + "id": "653f24137448336b174878ac135176d730734a7a385313189c51a8bf3f334451", + "derivation_path": [ + "17521", + "6173", + "31261", + "24933", + "13542", + "25993", + "26075", + "28303", + "15940", + "703", + "2579", + "15479", + "9631" + ], + "index": 13409 }, { "amount": { - "quantity": 22, + "quantity": 115, "unit": "lovelace" }, "address": "", - "id": "48347c42314248012d496835c77901700c570847054b205b1371493e296b3ecd", - "index": 11252 + "id": "67085019010a44201b66712304375c2f120e3a4127bc6cf02c2b1e46299e4c4b", + "derivation_path": [ + "8461", + "12417", + "18156", + "24171", + "4691", + "2094", + "7312", + "29387", + "26704", + "4447", + "25166" + ], + "index": 25555 }, { "amount": { - "quantity": 35, + "quantity": 26, "unit": "lovelace" }, "address": "", - "id": "643b5d507f4d1a057b3927255426145d06031e01372a2b3510416f1c4e331308", - "index": 23404 + "id": "75243358d107c53211236e7c217684481d4d096f112f6db53c421d7038135b23", + "derivation_path": [ + "16459", + "3695", + "15994", + "27408", + "8433", + "678", + "31067", + "7941", + "21514", + "31748", + "8519", + "28225", + "8545", + "14386", + "1871", + "2228", + "15284", + "24997", + "31907", + "19078", + "13586" + ], + "index": 2301 }, { "amount": { - "quantity": 184, + "quantity": 243, "unit": "lovelace" }, "address": "", - "id": "624825c8081a400c451e5e2a2550262f995c1f7d0e155a5d2a1ffc05130c692f", - "index": 21333 + "id": "d5763a6b716d693a77c865540f7d4533123f4d647630330bdc501a79050b2213", + "derivation_path": [ + "28340", + "11714", + "1986", + "27253", + "2925", + "27098", + "16223", + "1831", + "2889", + "23243" + ], + "index": 9925 + }, + { + "amount": { + "quantity": 246, + "unit": "lovelace" + }, + "address": "", + "id": "3e0e6070666f026a19347e5d172d5ab90f49982b0236293a5f7b9ba2652f390c", + "derivation_path": [ + "25451", + "8493", + "27107", + "11832", + "10535", + "26959", + "25921", + "2501", + "6918", + "12367", + "14576", + "13465", + "6685", + "6187", + "18889", + "18133", + "28347", + "10429", + "7541", + "27322", + "3763", + "11152" + ], + "index": 2112 + }, + { + "amount": { + "quantity": 59, + "unit": "lovelace" + }, + "address": "", + "id": "28320715722a25592a7a7549640aea72760e42e02b4f51332c2618792d786772", + "derivation_path": [ + "20054", + "16379", + "12603", + "21007", + "30491", + "5346", + "23299", + "17155", + "8272", + "3413", + "1896", + "16870" + ], + "index": 25836 }, { "amount": { - "quantity": 164, + "quantity": 88, "unit": "lovelace" }, "address": "", - "id": "840a0244981a8e3157333f0b2b724300400864087c52187b336a731e60542a55", - "index": 3452 + "id": "2b496322774c67387c0e46450b3c31253b752c5d35312c2e39217f0f830a7d66", + "derivation_path": [ + "13734", + "30691", + "461", + "21455", + "23769", + "19240", + "4757", + "11196", + "2833", + "18599", + "9248", + "6782", + "23234", + "31445", + "27981", + "578" + ], + "index": 10483 }, { "amount": { - "quantity": 200, + "quantity": 169, "unit": "lovelace" }, "address": "", - "id": "44184e267e6502210610594b51317325264358135227d362547f47bffe0200a8", - "index": 16103 + "id": "5248b7011229735d1168425e5f1a2d5d781920293b323c5a417e0851c2a92f73", + "derivation_path": [ + "15428", + "20570", + "25924" + ], + "index": 20418 }, { "amount": { - "quantity": 142, + "quantity": 79, "unit": "lovelace" }, "address": "", - "id": "3c38266f3f1a0d2f756b4cb50e0c647614d6eb0661710b4ff6bd16710330375e", - "index": 24637 + "id": "1461481d02a5316a0056300388ec359c00210d1862f136200e68cf3f7f2c4f6e", + "derivation_path": [ + "14076", + "7732", + "20628", + "14245", + "17155", + "7278", + "21068", + "24986", + "26114", + "6137", + "1237", + "21598", + "15577", + "24571", + "19408", + "4655", + "176", + "2299", + "29932", + "128", + "17377", + "10912", + "26163" + ], + "index": 15901 }, { "amount": { - "quantity": 169, + "quantity": 196, "unit": "lovelace" }, "address": "", - "id": "38565472084bc74b062357235b4631066f41a0fe209cea0c770d40525358b77d", - "index": 8589 + "id": "4418084a46bf4047250d97546a62de48424707b6663e66176f7b003f70327d7e", + "derivation_path": [ + "8374", + "19118", + "25703", + "29914", + "25337", + "22036", + "12712", + "31887", + "30714", + "23450", + "14178", + "7734", + "2140", + "3046", + "30176", + "14229", + "12866", + "18759", + "8505", + "23945", + "30829", + "9301", + "29168" + ], + "index": 18102 }, { "amount": { - "quantity": 197, + "quantity": 196, "unit": "lovelace" }, "address": "", - "id": "5e2637200a4d235536b475bf331837406918361c440232a8632b3d341f7a9559", - "index": 12218 + "id": "17ae5572e826bc6814637555437cf0b646451d60675b3a797b4b1a611c0f2145", + "derivation_path": [ + "25149", + "18563", + "5476", + "2812", + "24265", + "19309", + "3300", + "31240", + "1390", + "8555", + "13168" + ], + "index": 27921 + }, + { + "amount": { + "quantity": 156, + "unit": "lovelace" + }, + "address": "", + "id": "044d0772de0446126dcdd2060e5102d6716b573d9bd7096d28456e386d6c902b", + "derivation_path": [ + "18736", + "32389", + "6636", + "4128", + "7528", + "24101", + "11980", + "10461", + "28851", + "30304", + "3414", + "18388", + "29917", + "24064", + "30933", + "17222", + "23488", + "31600", + "26005", + "8137", + "1515" + ], + "index": 31863 }, { "amount": { - "quantity": 3, + "quantity": 254, "unit": "lovelace" }, "address": "", - "id": "16742d602f3c82021230a07d0b84186d16ee2f3f5667084d2c532a712c24a532", - "index": 21031 + "id": "47721c19295c01c9726151403cb552185044120b1071373494384f6e104c626e", + "derivation_path": [ + "3322", + "7261", + "11661", + "20316", + "1082", + "28259", + "16810", + "758", + "24583", + "26554", + "6171", + "2542", + "18044" + ], + "index": 2995 }, { "amount": { - "quantity": 108, + "quantity": 128, "unit": "lovelace" }, "address": "", - "id": "645b1d247f6ed54f6578e857222f7823116330053e6b223b3f5d3a60084f5f06", - "index": 17857 + "id": "4e55426370394f0341d95ad43e389c46a62e2b686e1178d1771c3b46001c6a45", + "derivation_path": [ + "19207", + "31100" + ], + "index": 21626 }, { "amount": { - "quantity": 65, + "quantity": 229, "unit": "lovelace" }, "address": "", - "id": "6578223cfa30027b3774552a1f777c4e73896b332648371953321614e57a6f57", - "index": 5447 + "id": "625fa344435e5e282f2eea7b5415972c21752864194e4bf77e16525351362f8b", + "derivation_path": [ + "20385", + "19630", + "5342", + "23256", + "6114", + "21493", + "14255", + "9250", + "31172", + "9055", + "8663", + "7566", + "28206", + "30712", + "6133", + "12859", + "10278", + "7742", + "23217" + ], + "index": 13833 }, { "amount": { - "quantity": 90, + "quantity": 6, "unit": "lovelace" }, "address": "", - "id": "77445c8a4e0f06055a4a0d4a102d2f9e514b846faf7f1b6c5948433e7d063743", - "index": 837 + "id": "153331351a720251624c47786d320aca0b7b36543d0370585a00310201095e02", + "derivation_path": [ + "30425", + "22756", + "16536", + "263", + "25584", + "25201", + "16374", + "14363", + "10930", + "27357", + "26696", + "727", + "22490", + "21566", + "17653", + "26115", + "18820", + "13420", + "16839", + "22065", + "4143", + "26492", + "5749", + "3117", + "26576", + "2829" + ], + "index": 29696 }, { "amount": { - "quantity": 195, + "quantity": 46, "unit": "lovelace" }, "address": "", - "id": "130d334772f54c3b543e00077cd1097d4d0d1f075cd59a7c4b6e3720521da692", - "index": 2227 + "id": "7b13592c185b6fb33e306e382c0625343420ae1620a754a4214a43460d6d232a", + "derivation_path": [ + "11971", + "23614", + "15863", + "13291", + "16028", + "12070", + "20018", + "22211", + "18734", + "3798", + "29212", + "21396", + "9271", + "19114", + "31755", + "29007", + "6836", + "8773", + "12750" + ], + "index": 10299 }, { "amount": { - "quantity": 29, + "quantity": 19, "unit": "lovelace" }, "address": "", - "id": "427a242b4e2d663b07366f75583454a03ffd4b19c330493fe70e20984f931d6e", - "index": 5711 + "id": "3539321b7e35772d71405255445e493de24c1c48400c5e3e527dec6256fc6063", + "derivation_path": [ + "4158", + "26269", + "6579", + "17373", + "23197", + "4435", + "1146", + "11929", + "29174", + "10251", + "22831", + "13618", + "25094", + "9327", + "13290", + "21656", + "18236", + "26021", + "1384" + ], + "index": 20403 }, { "amount": { - "quantity": 25, + "quantity": 191, "unit": "lovelace" }, "address": "", - "id": "8c207648225e4e1f734206650a7f4039194958662b2225317c3f0d324d1b7e18", - "index": 7707 + "id": "9b0453242b20457ea6614c0a0d8a0e592b16272c60482d372f3b57343e4e1433", + "derivation_path": [ + "7644", + "29583", + "27575", + "26975", + "3700", + "20077", + "1208", + "5078", + "22000", + "25494", + "3945", + "17472", + "6570", + "29967", + "25210", + "5812", + "4708", + "10796", + "12684", + "19148" + ], + "index": 31485 + }, + { + "amount": { + "quantity": 16, + "unit": "lovelace" + }, + "address": "", + "id": "5c25c429a668e04e1e095c3d7d1c6123383d1c0e193e4d264707162b7669270b", + "derivation_path": [ + "22121", + "18148", + "3962", + "18352", + "6556", + "126", + "3018", + "17004", + "7050", + "25405", + "5790", + "20514", + "32401", + "11206", + "7575", + "89", + "18056", + "10699", + "6404", + "32754", + "23968", + "17189", + "29363", + "12831", + "8264", + "25558" + ], + "index": 5545 }, { "amount": { - "quantity": 230, + "quantity": 6, "unit": "lovelace" }, "address": "", - "id": "3a7c2c5f3a324975ce5c121545490915c870556013db497f5732d55779097e2a", - "index": 10911 + "id": "645c517d1ea74d70268723c7cc6979763c2c261922253552766e7bed7a3a0a34", + "derivation_path": [ + "32375", + "30728", + "3501", + "18634", + "10830", + "11958", + "18519", + "29689", + "5021", + "22634", + "10054", + "19266", + "30091", + "15168", + "4194", + "548", + "18777", + "26435", + "12478", + "28517", + "27462", + "31977", + "4609", + "2266", + "26178", + "10635", + "22247" + ], + "index": 21985 }, { "amount": { - "quantity": 208, + "quantity": 28, "unit": "lovelace" }, "address": "", - "id": "56374b66841d403b4e3b4c422135683c713d22d0496d4155072d1407481e0f17", - "index": 5337 + "id": "1c79617132534e476c6c03347f751a294023015a5d5c363b011b14bbc2adbc51", + "derivation_path": [ + "20357", + "17016", + "28457", + "16791", + "31820", + "2292", + "5777", + "124", + "16426", + "12183", + "10194", + "11183", + "2866", + "28789", + "23086", + "8262", + "19864", + "9968", + "5205", + "22903", + "14565", + "17659", + "14814", + "17089", + "15930", + "2894", + "26467", + "3373", + "5079", + "18388", + "7428" + ], + "index": 15646 + } + ], + "outputs": [ + { + "amount": { + "quantity": 143, + "unit": "lovelace" + }, + "address": "" }, { "amount": { - "quantity": 230, + "quantity": 189, + "unit": "lovelace" + }, + "address": "" + } + ] + }, + { + "inputs": [ + { + "amount": { + "quantity": 148, "unit": "lovelace" }, "address": "", - "id": "35887b5016252a184e2567081800c3886c15113c4a5f23cf14124d2476261f46", - "index": 13327 + "id": "0304123005592062743943982a757008581b590d76691679a159115c656e0f61", + "derivation_path": [ + "17322" + ], + "index": 3232 }, { "amount": { - "quantity": 152, + "quantity": 197, "unit": "lovelace" }, "address": "", - "id": "7d5c7c167f1d201b36750e2f3e45db78215c5753522d723e443d6fa05f764b16", - "index": 18100 + "id": "664c53661a1b2224912c321b315a18494f20d2577819797e56311a7ad14acd65", + "derivation_path": [ + "6716", + "20169", + "3424", + "26027", + "32386", + "20218", + "6939", + "30793", + "11961", + "29520", + "29859", + "7706", + "4525", + "28284", + "13794", + "4054", + "4602", + "9215", + "14566", + "13394", + "705", + "7442", + "9874", + "10408", + "3851", + "14270", + "30708", + "16791", + "21038", + "30745" + ], + "index": 1149 }, { "amount": { - "quantity": 249, + "quantity": 81, "unit": "lovelace" }, "address": "", - "id": "2f3c7945b279266eaf00bf7a3e7b68486c4f5a750b652d098d793622205a7d25", - "index": 9446 + "id": "71324a5e32462d20205f6c562e9429583e0c5f0f6d834d45724bd05409a25557", + "derivation_path": [ + "27784", + "20587" + ], + "index": 25645 }, { "amount": { - "quantity": 245, + "quantity": 181, "unit": "lovelace" }, "address": "", - "id": "67b8565259842b517b23171680d138a80f1d2b19cd202370017a6f006f763235", - "index": 11919 + "id": "42c0ffd3710a3554230344425b1699c868df304d193a306a74e94e5d66365a11", + "derivation_path": [ + "31927", + "60", + "1762", + "32374", + "27590", + "14220", + "10451", + "32042", + "17376", + "6961", + "26336", + "11338", + "4732" + ], + "index": 12842 }, { "amount": { - "quantity": 133, + "quantity": 181, "unit": "lovelace" }, "address": "", - "id": "af653d466c234824087f416f5c4059594a9a197ab8590f7006324543693af3de", - "index": 7505 + "id": "50721e0300be7c43037b2ec0770270574c4f07bd8b194d3c6310d17982567f6a", + "derivation_path": [ + "8713", + "8019" + ], + "index": 15757 } ], "outputs": [ { "amount": { - "quantity": 170, + "quantity": 147, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 35, + "quantity": 208, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 180, + "quantity": 114, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 100, + "quantity": 188, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 69, + "quantity": 111, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 8, + "quantity": 194, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 9, + "quantity": 113, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 226, + "quantity": 169, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 196, + "quantity": 155, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 139, + "quantity": 149, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 223, + "quantity": 118, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 28, + "quantity": 127, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 240, + "quantity": 29, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 147, + "quantity": 216, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 188, + "quantity": 227, "unit": "lovelace" }, "address": "" - }, + } + ] + }, + { + "inputs": [ { "amount": { - "quantity": 60, + "quantity": 170, "unit": "lovelace" }, - "address": "" + "address": "", + "id": "7a542f5668607725473b1919f1a308bc444411487917104f54da4cd068383574", + "derivation_path": [ + "12915", + "25030", + "27807", + "5997", + "18680", + "14684", + "20839", + "4470", + "18891" + ], + "index": 5535 }, { "amount": { - "quantity": 104, + "quantity": 17, "unit": "lovelace" }, - "address": "" + "address": "", + "id": "6c4f021bef5617ad767d6744517d4c09c82c5f298c68653b3a1316427ade7804", + "derivation_path": [ + "2321", + "6571" + ], + "index": 1994 }, { "amount": { - "quantity": 196, + "quantity": 227, "unit": "lovelace" }, - "address": "" + "address": "", + "id": "62b538216d0a7f3a1833d27f392e3b3b364c1b120b7e55eb4c6d51d66314d928", + "derivation_path": [ + "16114", + "1292", + "27839", + "30449", + "592", + "11317", + "4707", + "6149", + "11666", + "4028", + "24221", + "23174", + "18762", + "7425", + "8904", + "23064", + "2518", + "10513", + "15986", + "196" + ], + "index": 5234 }, { "amount": { - "quantity": 96, + "quantity": 74, "unit": "lovelace" }, - "address": "" + "address": "", + "id": "423ab325100b1d3a7f475e376970670b450c6f5a2e277b47fd03dd1d6d77042a", + "derivation_path": [ + "7962", + "8837", + "6550", + "28291", + "25694", + "6534", + "30012", + "32660", + "18486", + "19999", + "13612", + "718", + "30146", + "14407", + "8712", + "18950", + "9686", + "17674", + "6479", + "32083", + "8118" + ], + "index": 5994 }, { "amount": { - "quantity": 233, + "quantity": 130, "unit": "lovelace" }, - "address": "" + "address": "", + "id": "7c324358013375009d737d77840c38a1475534af62423c653f66426eb8fd7f01", + "derivation_path": [ + "5883", + "17210", + "14110", + "10373", + "18668", + "1413", + "968", + "25193", + "32265", + "1119", + "18163", + "12839", + "32525", + "22419", + "21089", + "3957", + "18690", + "11119", + "19272", + "6911", + "9228", + "18237" + ], + "index": 31944 }, { "amount": { - "quantity": 253, + "quantity": 120, "unit": "lovelace" }, - "address": "" + "address": "", + "id": "0cc457e84f026a7d287d225b059e6c2011404c744f4a2e0017f8500678048f0f", + "derivation_path": [ + "26992", + "20884", + "24851", + "4411", + "22115", + "19408", + "9696", + "16525", + "6675", + "5777", + "167", + "13476", + "8734", + "19200", + "13965", + "11242", + "2180", + "29625", + "3590", + "17186", + "32252", + "11971", + "7438", + "23814", + "4532", + "2064", + "27894", + "21983", + "3299", + "6718" + ], + "index": 6327 }, { "amount": { - "quantity": 179, + "quantity": 198, "unit": "lovelace" }, - "address": "" - } - ] - }, - { - "inputs": [ + "address": "", + "id": "212f38c419197325255f0c661719129c0703721d4870367f726a1a64e4602c50", + "derivation_path": [ + "31029", + "29065", + "27203", + "3037", + "22151", + "10498", + "24627", + "12090", + "2445", + "29717", + "21161", + "24470", + "1158", + "11391", + "23057", + "28713", + "28233", + "13157", + "9223", + "29625", + "25683", + "5777", + "407", + "32239", + "28725", + "3913", + "15937" + ], + "index": 14826 + }, + { + "amount": { + "quantity": 70, + "unit": "lovelace" + }, + "address": "", + "id": "d4570e6e331e471c276823116e06303b7b6559160fd52c754c556ec564452942", + "derivation_path": [ + "10852", + "31334", + "10461", + "11304", + "854", + "6394" + ], + "index": 14188 + }, { "amount": { - "quantity": 241, + "quantity": 158, "unit": "lovelace" }, "address": "", - "id": "69715748753d13583846be4e502c461631e56c7341532d331218522031284e67", - "index": 22841 + "id": "58100c4b6f50776126a9741d3b064c6cb57257175e6e7e6b0948479b295c336e", + "derivation_path": [ + "29021", + "10103", + "21731", + "15792", + "11608", + "13913", + "14356", + "16900", + "25186", + "3122", + "6326", + "314", + "18670", + "9806", + "14824", + "16711", + "9865", + "9708", + "19109", + "15424", + "28961", + "1538", + "23710", + "25757", + "29744", + "16183", + "3625", + "7331", + "9186", + "17548", + "220" + ], + "index": 21445 + }, + { + "amount": { + "quantity": 227, + "unit": "lovelace" + }, + "address": "", + "id": "512d16682afc606c21520e7d212a760e183b5d7a0668452144703e45015d1227", + "derivation_path": [ + "11657", + "20595", + "21845", + "31396", + "7417", + "1692", + "2900", + "28385", + "20274", + "13976", + "30770", + "10458", + "6492", + "22062", + "32524", + "1751", + "14172", + "13354" + ], + "index": 5271 + }, + { + "amount": { + "quantity": 204, + "unit": "lovelace" + }, + "address": "", + "id": "506173685003153065490974a53b17331650574f94596eb024176bd58e7d2211", + "derivation_path": [ + "28264", + "29538", + "21874", + "24441", + "11367", + "32586", + "28136", + "20766", + "32348", + "8706", + "14213", + "3356", + "30324", + "1991", + "13784", + "3331", + "29458", + "8943", + "5273", + "23934", + "10094", + "1097", + "16516", + "3510", + "21083", + "30045" + ], + "index": 22098 }, { "amount": { - "quantity": 38, + "quantity": 35, "unit": "lovelace" }, "address": "", - "id": "5f6a6c666a4b1e715d766e4f595d000e0462432f618ef26b2f0a611d797502c5", - "index": 28018 + "id": "5a27751d7aeb08456d4b2f72e6293a5a0506696dd40e221009068e272e3d072a", + "derivation_path": [ + "375", + "12150", + "31791", + "17544", + "8786", + "5802", + "443", + "13117", + "9571", + "29167", + "7258", + "20321", + "17779", + "27191", + "21871", + "28617", + "30137", + "26443", + "25088", + "32628" + ], + "index": 26382 + }, + { + "amount": { + "quantity": 93, + "unit": "lovelace" + }, + "address": "", + "id": "22f1764d084fa44e2ce4eb4b7e38ec660eea63187609114c193d225d074e201b", + "derivation_path": [ + "17374", + "17449", + "10807", + "23683", + "27881", + "12403", + "19078", + "24615", + "24555", + "767", + "6494", + "27155", + "3392", + "22226", + "3402", + "5", + "20885", + "18345", + "10957", + "1170", + "21564", + "10588", + "14154", + "28749", + "19904", + "18969", + "19701", + "8747", + "18214", + "28673" + ], + "index": 13936 }, { "amount": { - "quantity": 235, + "quantity": 62, "unit": "lovelace" }, "address": "", - "id": "0a045d030fc8781c4f7c7c2c6727415f1e417a2a0b632d2d284779073d164b54", - "index": 21900 + "id": "3a633f190a4f69803ba98a154d2a6e591e1d2432ac3f290b052bb46224703308", + "derivation_path": [ + "32490", + "29141", + "2015", + "7458", + "19185", + "22880", + "19643", + "23863", + "11259", + "6454" + ], + "index": 20748 }, { "amount": { - "quantity": 55, + "quantity": 254, "unit": "lovelace" }, "address": "", - "id": "067a6611346a55230828de1802607665fe245910487701147c521f684c442756", - "index": 32490 + "id": "70605d2a294b5c187752930d60126a6357400b7f715576273f4f0b2208577308", + "derivation_path": [ + "22803", + "809", + "7055", + "30955", + "25932" + ], + "index": 1620 }, { "amount": { - "quantity": 199, + "quantity": 226, "unit": "lovelace" }, "address": "", - "id": "543c51560d5495341c4b33002b7623766b007b18587a150b7f380811776db7b3", - "index": 2567 + "id": "1f366b744f2053fd7a5a4361425f0e57037889287a0e74346b5b38150a123320", + "derivation_path": [ + "660" + ], + "index": 14860 }, { "amount": { - "quantity": 240, + "quantity": 135, "unit": "lovelace" }, "address": "", - "id": "30186c29617b4df846083b2c41510b041be6516fdf69563219536923486e7a7f", - "index": 4022 + "id": "c22c188e113661470f5d29589f5a0d64148d7c45b4386d606c4b1c096c0f6e3e", + "derivation_path": [ + "24395", + "21627", + "24712", + "6750", + "29791", + "8645", + "18047", + "15655", + "4941" + ], + "index": 10900 + }, + { + "amount": { + "quantity": 159, + "unit": "lovelace" + }, + "address": "", + "id": "b15336b3140620046f095d4239292235a2650f2c044952676644461d21eb2bec", + "derivation_path": [ + "3940", + "17933", + "7989", + "7093", + "11851", + "5164", + "24453", + "18668", + "21015", + "15567", + "18153", + "4935", + "21575", + "5979", + "21392", + "21474", + "2145", + "6436", + "12769", + "24733", + "32304", + "23619", + "32395", + "20314", + "12032", + "14035", + "20080", + "29149", + "25994" + ], + "index": 31155 }, { "amount": { - "quantity": 23, + "quantity": 254, "unit": "lovelace" }, "address": "", - "id": "287f2a6632145b3074c061572c6b694f382d5a35e9255b110d2c456f48093f27", - "index": 32669 + "id": "2a27375bf3696678087f53550a3b3d4d011d63390e9e6373a400f25b5934d666", + "derivation_path": [ + "22877", + "28142", + "2279", + "8865", + "11276", + "26282", + "27688", + "19389" + ], + "index": 30077 + }, + { + "amount": { + "quantity": 126, + "unit": "lovelace" + }, + "address": "", + "id": "2bc43175dd4142a8018d7bd43b4500307e0c472e182778794ecf7a6e7f116b3a", + "derivation_path": [ + "31344", + "28947", + "31503", + "30434", + "18315", + "2959", + "14710", + "4450", + "21656", + "24300", + "16899", + "3857", + "16272", + "9060", + "10816", + "19989", + "28512", + "6955", + "15641", + "28288", + "15558", + "31228", + "15300", + "14517", + "23454", + "10848", + "10365" + ], + "index": 21527 }, { "amount": { - "quantity": 236, + "quantity": 74, "unit": "lovelace" }, "address": "", - "id": "60c2131d29550d052318b4702c2c7cb43a571f3014c5615c9d0032ef07415f75", - "index": 32432 + "id": "170f01303e476330061c2267c74c5f6d5440c3621d4436850922e39a7c532565", + "derivation_path": [ + "30664", + "20246", + "21130", + "17280", + "30180", + "25757", + "32487", + "2604", + "30160", + "11526", + "28482", + "11937", + "16277", + "20930", + "14310", + "10954", + "17693", + "3233", + "13217", + "18884", + "19047", + "19304", + "27195" + ], + "index": 20530 }, { "amount": { - "quantity": 66, + "quantity": 214, "unit": "lovelace" }, "address": "", - "id": "4b85631ae1642a355576773d5d565473e02a27761468131ba2498055ea407b22", - "index": 25035 + "id": "75022463f2992c4046383d357d2642ff746e5259c9716f493e7d5e15485c6b0a", + "derivation_path": [ + "21914", + "3838", + "7287", + "11145", + "4395", + "31249", + "12479" + ], + "index": 28382 }, { "amount": { - "quantity": 90, + "quantity": 85, "unit": "lovelace" }, "address": "", - "id": "20592da82346463d71394b390f520a485e6f467a3b5826156f263b6b2d3044ba", - "index": 1782 + "id": "495c064307624823525e41443e57452d1002a1d0524b4f1d3d5f913e2f2a4077", + "derivation_path": [ + "19995", + "28959", + "14650", + "30758", + "11253", + "906", + "22041", + "14563", + "7671", + "12070", + "23057", + "12402", + "99", + "17714", + "26693", + "11293", + "19445", + "15995", + "26657", + "5890", + "7579", + "8394", + "4215", + "15207" + ], + "index": 14923 + } + ], + "outputs": [ + { + "amount": { + "quantity": 146, + "unit": "lovelace" + }, + "address": "" }, { "amount": { - "quantity": 103, + "quantity": 4, "unit": "lovelace" }, - "address": "", - "id": "146c7b499a1a667b4d1836042b47456c8749412037db3f0c6a164062751e2d0f", - "index": 31251 + "address": "" }, { "amount": { - "quantity": 248, + "quantity": 209, "unit": "lovelace" }, - "address": "", - "id": "3f5c2f3af927957f134b32f211f9900d601b693a3b53286284686a111f775b35", - "index": 18932 + "address": "" }, { "amount": { - "quantity": 158, + "quantity": 65, "unit": "lovelace" }, - "address": "", - "id": "7870996e3a587046385679263d66163b20374d521e495f3c531e5157106e1763", - "index": 27296 + "address": "" }, { "amount": { - "quantity": 158, + "quantity": 133, "unit": "lovelace" }, - "address": "", - "id": "2f73050707487bd747606ae4081f0f3e40265f34d11b5b13377a38f539061f3a", - "index": 6931 + "address": "" }, { "amount": { - "quantity": 28, + "quantity": 157, "unit": "lovelace" }, - "address": "", - "id": "61475555ced91707eb4122382d0512493f4832771d4f22352b138a6f068c6e08", - "index": 21428 + "address": "" }, { "amount": { - "quantity": 228, + "quantity": 66, "unit": "lovelace" }, - "address": "", - "id": "6c2f4843670a40ce542e771c6f1968325d6f050b1d771e3c3ad62f42ca564e2d", - "index": 1384 + "address": "" }, { "amount": { - "quantity": 83, + "quantity": 99, "unit": "lovelace" }, - "address": "", - "id": "551a0a5d09013833193943024a1a1fefc27076383d36747b50cead1f592d7c46", - "index": 9269 + "address": "" }, { "amount": { - "quantity": 254, + "quantity": 163, + "unit": "lovelace" + }, + "address": "" + }, + { + "amount": { + "quantity": 40, + "unit": "lovelace" + }, + "address": "" + }, + { + "amount": { + "quantity": 11, + "unit": "lovelace" + }, + "address": "" + } + ] + }, + { + "inputs": [ + { + "amount": { + "quantity": 59, "unit": "lovelace" }, "address": "", - "id": "f447492a454f68131c1e652132620e8d2ccf1379366e4d305a4847026b7c1409", - "index": 15306 + "id": "6ad0766d51526e562c7b633e5b3419307a8d326f710656677d15022a79644768", + "derivation_path": [ + "9368", + "31362", + "11542", + "29182", + "18738", + "27073", + "20355" + ], + "index": 14671 }, { "amount": { - "quantity": 240, + "quantity": 19, "unit": "lovelace" }, "address": "", - "id": "3d13470c0715c12025632f4c516dcc735042de25e2212de701c9c11b2639373b", - "index": 2416 + "id": "274c17937c223fbd6074e8ef4c187a62381f56ab247bdfddfd418d2615a22553", + "derivation_path": [ + "27085", + "29648", + "23644", + "15750", + "4347", + "10752", + "4517", + "21667", + "20741", + "14147", + "2781", + "27567", + "20470", + "6206", + "1279", + "16472", + "16695", + "19712", + "12570", + "30789", + "25318" + ], + "index": 4906 + }, + { + "amount": { + "quantity": 232, + "unit": "lovelace" + }, + "address": "", + "id": "3b4c543c0a271956653d3ad587460fea6f4b4460c4485c5a5c27176865c21038", + "derivation_path": [ + "12031", + "20695", + "7577", + "8372", + "18080", + "17893", + "4645", + "18263", + "20621", + "26765", + "3802", + "2368", + "7664", + "5364", + "28947", + "31451", + "31867", + "7296", + "23830", + "32254", + "25407", + "14343", + "6780", + "20787", + "28254", + "10147" + ], + "index": 10124 }, { "amount": { - "quantity": 138, + "quantity": 71, "unit": "lovelace" }, "address": "", - "id": "064ff7777dc43b162f4e626772033926c8e8874b1f5055af62170a207a400379", - "index": 22382 + "id": "23eb7c4a7228346e8b715e1768f967111cad720b4626404f2021447946361e6a", + "derivation_path": [ + "15219", + "30203", + "2096", + "2050", + "12564" + ], + "index": 14402 }, { "amount": { - "quantity": 137, + "quantity": 4, "unit": "lovelace" }, "address": "", - "id": "4376262d731281214514450a0f381b2408585e6d594bbc37867739412e671f26", - "index": 27728 + "id": "01487c55553037a95a003764655add410e352e4f7c786471273d484f7c326a59", + "derivation_path": [ + "4496", + "19445", + "4683", + "24596", + "25112", + "17954", + "2790", + "26694", + "21782" + ], + "index": 11007 }, { "amount": { - "quantity": 214, + "quantity": 75, "unit": "lovelace" }, "address": "", - "id": "2e5c5d1917ba347e180a6d5c3b440465111d0a481f7b640a1305067b4401a01e", - "index": 7483 + "id": "6d16064327587c417c5736e12c227a7206276f6422115e56a6573f0f4e7e4f4e", + "derivation_path": [ + "17608", + "2289", + "1944", + "16470", + "14325", + "27374", + "16155", + "20567", + "8433", + "7649", + "30598", + "25207", + "7577", + "13876", + "32126" + ], + "index": 22171 }, { "amount": { - "quantity": 68, + "quantity": 160, "unit": "lovelace" }, "address": "", - "id": "2b544f7710680d762d456b4a4cf86c2502c97c424a4a243d5518172605d55b7f", - "index": 6282 + "id": "2146340e7c1c077cd8259d32dd33725c512450c2b7377d1d4671e235004e710f", + "derivation_path": [ + "32579", + "32664", + "13772", + "10815", + "26745", + "29684", + "2956", + "15551" + ], + "index": 20878 }, { "amount": { - "quantity": 33, + "quantity": 144, "unit": "lovelace" }, "address": "", - "id": "4d293e45afba6a100ff7342ade2564403b4d372a6140243f7a265c466e417b1d", - "index": 23755 + "id": "5b6f96767c666d0719148c399068022d5d0077785b8f15456e73383d5b31185b", + "derivation_path": [ + "19750", + "4442", + "8706", + "9682", + "2115", + "2132", + "31771" + ], + "index": 29875 } ], "outputs": [ { "amount": { - "quantity": 154, + "quantity": 218, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 198, + "quantity": 213, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 89, + "quantity": 188, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 216, + "quantity": 206, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 207, + "quantity": 193, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 172, + "quantity": 130, "unit": "lovelace" }, "address": "" @@ -2054,508 +2805,864 @@ }, { "amount": { - "quantity": 130, + "quantity": 166, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 148, + "quantity": 172, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 86, + "quantity": 203, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 211, + "quantity": 132, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 150, + "quantity": 191, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 235, + "quantity": 251, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 140, + "quantity": 221, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 110, + "quantity": 93, "unit": "lovelace" }, "address": "" - } - ] - }, - { - "inputs": [ + }, + { + "amount": { + "quantity": 8, + "unit": "lovelace" + }, + "address": "" + }, + { + "amount": { + "quantity": 253, + "unit": "lovelace" + }, + "address": "" + }, + { + "amount": { + "quantity": 146, + "unit": "lovelace" + }, + "address": "" + }, + { + "amount": { + "quantity": 75, + "unit": "lovelace" + }, + "address": "" + }, { "amount": { - "quantity": 43, + "quantity": 214, "unit": "lovelace" }, - "address": "", - "id": "6333a3d842477e6f0a696d2ba63e5d752b42524b061f46a92a20003f24341c3c", - "index": 697 + "address": "" }, { "amount": { - "quantity": 191, + "quantity": 171, "unit": "lovelace" }, - "address": "", - "id": "641c5d48762305406b9b339e5e14015330417e62691c4b05353a244c52c9124d", - "index": 22430 + "address": "" }, { "amount": { - "quantity": 63, + "quantity": 15, "unit": "lovelace" }, - "address": "", - "id": "32dd7317006723530db21b390c690c490f1c586f78736373616c3d3b56605454", - "index": 16160 + "address": "" }, { "amount": { - "quantity": 153, + "quantity": 63, "unit": "lovelace" }, - "address": "", - "id": "702b45017646558d15140b041a5d79e1605a4c594639a26f171c1b6abd39192f", - "index": 13890 + "address": "" }, { "amount": { - "quantity": 176, + "quantity": 147, "unit": "lovelace" }, - "address": "", - "id": "38a93bfa3eba3c6e360212c70f185a131267034127092c2330590d393343166d", - "index": 13360 - }, + "address": "" + } + ] + }, + { + "inputs": [ { "amount": { - "quantity": 87, + "quantity": 85, "unit": "lovelace" }, "address": "", - "id": "1e02c80d47b477bd1519302a592fad190b151f7f5d55255e95281e2b6d6b8268", - "index": 12259 - }, + "id": "390d3b665e4a4f083031075c404077251d3a00233718255d212473400975187e", + "derivation_path": [ + "7547", + "26093", + "878", + "18914", + "20711", + "26933", + "15621", + "13445", + "4057", + "456", + "21290", + "4998", + "30901", + "22773", + "178", + "25582", + "20494", + "28696", + "32744", + "25585", + "4791", + "30043", + "18604", + "11840", + "8539", + "19425" + ], + "index": 22821 + } + ], + "outputs": [ { "amount": { - "quantity": 194, + "quantity": 103, "unit": "lovelace" }, - "address": "", - "id": "ee79577aff320c7269073f09c2135b1c567b6a5e454510d5cf39285047481156", - "index": 17994 + "address": "" }, { "amount": { - "quantity": 47, + "quantity": 55, "unit": "lovelace" }, - "address": "", - "id": "ec0d8f5014107b3f021a411a4de732685f57246e0e994c0e530d201a24105e14", - "index": 2166 + "address": "" }, { "amount": { - "quantity": 238, + "quantity": 74, "unit": "lovelace" }, - "address": "", - "id": "6a3f390b70207477741551465e0462310c06370305770609283f4357a2267a5c", - "index": 9653 + "address": "" }, { "amount": { - "quantity": 5, + "quantity": 186, "unit": "lovelace" }, - "address": "", - "id": "1e3d0c6a9c31733052503009793d3d09195402116d7c75564e26364358714c75", - "index": 9729 + "address": "" }, { "amount": { - "quantity": 88, + "quantity": 229, "unit": "lovelace" }, - "address": "", - "id": "e07c1f7009567b2227eb51226b2d6ef2277e0b783f1e317d2c5f543129376552", - "index": 9734 + "address": "" }, { "amount": { - "quantity": 192, + "quantity": 116, "unit": "lovelace" }, - "address": "", - "id": "e27d56522972390b086e6c25534a467812605b262b5d5f62bc24301350920655", - "index": 28647 + "address": "" }, { "amount": { - "quantity": 209, + "quantity": 5, "unit": "lovelace" }, - "address": "", - "id": "0269144a7419410f106a6e23400362e27f5925592a84f0080e58095b5b36042d", - "index": 6508 + "address": "" }, { "amount": { "quantity": 201, "unit": "lovelace" }, - "address": "", - "id": "26e57b0d12f4650f68b4607a161c7c0f5c7f743216c142337f123c3d055e7437", - "index": 1591 - } - ], - "outputs": [ + "address": "" + }, { "amount": { - "quantity": 136, + "quantity": 46, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 145, + "quantity": 66, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 96, + "quantity": 92, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 23, + "quantity": 54, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 133, + "quantity": 212, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 46, + "quantity": 171, "unit": "lovelace" }, "address": "" - } - ] - }, - { - "inputs": [ + }, { "amount": { - "quantity": 157, + "quantity": 140, "unit": "lovelace" }, - "address": "", - "id": "2203344a1f5d0f5eb22302590c1273a9a8441b229e38716130687b05e4f8686f", - "index": 31072 + "address": "" }, { "amount": { - "quantity": 26, + "quantity": 184, "unit": "lovelace" }, - "address": "", - "id": "03394e7d72ee430d54464233477c3a445f5f17376e5d071e895a7d6713163e76", - "index": 19098 + "address": "" }, { "amount": { - "quantity": 187, + "quantity": 54, "unit": "lovelace" }, - "address": "", - "id": "455d61cbef2a46592f3a812e7d4d10740a42383b29169c2e2c430b5a56d24c09", - "index": 22473 + "address": "" }, { "amount": { - "quantity": 104, + "quantity": 101, "unit": "lovelace" }, - "address": "", - "id": "421e150e6ff038110e2cbe430c3b543e2471092c620c682b117d1f2544e62a54", - "index": 4767 + "address": "" }, { "amount": { - "quantity": 73, + "quantity": 81, "unit": "lovelace" }, - "address": "", - "id": "183f219b1d1c1a79624a471cd78b19653167292c6c0c296c0774505c3a6b7a60", - "index": 13093 - }, + "address": "" + } + ] + }, + { + "inputs": [ { "amount": { - "quantity": 128, + "quantity": 145, "unit": "lovelace" }, "address": "", - "id": "1d389803311d2324532c1205765072a969642b4b4e7c0b043148bf5e74660c2c", - "index": 22548 + "id": "46035d5dbda8f117165b6a4047124a43185b2c761b74701b74da147e3c02491b", + "derivation_path": [ + "15189", + "9935", + "20179", + "2981", + "13604", + "15980", + "26321", + "17286", + "9054", + "1360", + "23977", + "9450", + "15668", + "22999", + "1645", + "21084", + "21642", + "9285", + "26121", + "1445", + "17265", + "5206", + "26941", + "30524", + "3299", + "1073", + "29171", + "7059", + "20254" + ], + "index": 1076 }, { "amount": { - "quantity": 38, + "quantity": 215, "unit": "lovelace" }, "address": "", - "id": "393c144f3dcd346f4e8e5cfc3a3b044265700ee70b2e2118ed686935082c4a06", - "index": 32070 + "id": "c45b12e72d615b2941363274b87114080a4d354bfc1b267a946500100649b101", + "derivation_path": [ + "17285", + "278", + "9708", + "11252", + "3709", + "13447", + "32697", + "17512", + "1352", + "26254", + "17294", + "24259", + "32468", + "28157" + ], + "index": 22947 }, { "amount": { - "quantity": 20, + "quantity": 152, "unit": "lovelace" }, "address": "", - "id": "61645c964be776eb1b5e079a520ae10f0b6619973f1750689f2b40c705367754", - "index": 3736 + "id": "7b2c40776b5e9730e80b2b54e37959df09322b1f27113c4151d05f0647b28573", + "derivation_path": [ + "2213", + "3776", + "7944", + "17591", + "32438", + "8016", + "6428", + "31478", + "12018", + "3706", + "21145", + "9253", + "5366", + "7086", + "24890", + "15480", + "16350", + "21324", + "1075", + "11810", + "2890", + "24889", + "14392", + "30072", + "18829", + "28997", + "8352" + ], + "index": 30558 + }, + { + "amount": { + "quantity": 15, + "unit": "lovelace" + }, + "address": "", + "id": "5699214c1c72683974636a116da7104af8102131ba3924786500254c3ec8423b", + "derivation_path": [ + "31298", + "14401", + "20828", + "22197", + "15571", + "15566", + "1749", + "20869", + "30118", + "4465", + "14411", + "21123", + "26767", + "16791", + "14785", + "8412", + "10535", + "25130", + "1279", + "23861", + "17205", + "12842", + "13858" + ], + "index": 1529 }, { "amount": { - "quantity": 101, + "quantity": 213, "unit": "lovelace" }, "address": "", - "id": "2be21a0dda9502714349340a7d6613d52673542aa76844562605413e79055ef9", - "index": 26554 + "id": "76795f5922450c808092267c77247f796cda420d9d3b511b6a620f513e0d3225", + "derivation_path": [ + "8020", + "8165", + "28181", + "30414", + "27947", + "16865", + "30827", + "29680", + "21354", + "12228", + "8300", + "31080", + "18271", + "24518", + "14520" + ], + "index": 32116 }, { "amount": { - "quantity": 190, + "quantity": 145, "unit": "lovelace" }, "address": "", - "id": "97395058591c010a3d503e3e01860dce294e762a3c180d756802ac1a2d621c2f", - "index": 5986 + "id": "244a53c5235731235a2218bfb119501760670c061a12d76bd75e655f76314fd5", + "derivation_path": [ + "5838", + "8286", + "17183", + "2240", + "24672", + "5779", + "16454", + "9126", + "3597", + "20884", + "27901", + "32636", + "14291", + "16195", + "18133", + "11184", + "26397", + "16229", + "3791", + "16153", + "27349", + "1081", + "13896", + "4534" + ], + "index": 17606 }, { "amount": { - "quantity": 87, + "quantity": 164, "unit": "lovelace" }, "address": "", - "id": "1378530ba9505d7902ce0f483793795b223e063c7a323f3f49117f19c4446d49", - "index": 3172 + "id": "0742465d0963722c567a54394d2f25df1438383b67476b5b7ad975055623b527", + "derivation_path": [ + "6712", + "25399", + "6712", + "850", + "7598", + "11156", + "14519", + "5806", + "32092", + "4580", + "13568", + "16132", + "2669", + "6800", + "7325", + "12586", + "2939", + "6086", + "381", + "10819", + "154", + "23738", + "28878", + "1272", + "15133", + "18325", + "9180" + ], + "index": 30317 }, { "amount": { - "quantity": 213, + "quantity": 63, "unit": "lovelace" }, "address": "", - "id": "5b3126e290972e4d4042152a7b682f0b719fbff6c4417c265f2a7466742d54dd", - "index": 20374 + "id": "03732b18701e236b16b8b844201229138539335748334e056a4369665d6126be", + "derivation_path": [ + "22462", + "6739", + "26830", + "17919", + "28207", + "15933", + "20734", + "5474", + "9529", + "3571", + "20312" + ], + "index": 29920 }, { "amount": { - "quantity": 250, + "quantity": 125, "unit": "lovelace" }, "address": "", - "id": "69601b34780d28b1346c4d3871130f7bbf04ae9f7a17310f852d674bc52c0d28", - "index": 14385 + "id": "6668797f06582a586939c07262703403166b4c5049e145036d6acd362e7d2073", + "derivation_path": [ + "1901", + "17228", + "21757", + "15934", + "27979" + ], + "index": 5156 }, { "amount": { - "quantity": 243, + "quantity": 40, "unit": "lovelace" }, "address": "", - "id": "4c756532786a484858603997e8dd3b630c0a52787f49f54a14305522f62f477e", - "index": 25857 + "id": "6127bb58684b3e317c390f447963406e5a4906456c550207ce414443660b714d", + "derivation_path": [ + "2033", + "30405", + "15345", + "10202", + "15880", + "16891", + "24296", + "25974", + "1381", + "23085", + "29969", + "21523", + "5072", + "1526", + "21937", + "23738", + "8823", + "29167" + ], + "index": 22258 }, { "amount": { - "quantity": 61, + "quantity": 84, "unit": "lovelace" }, "address": "", - "id": "4418505e668436a8559918536b0a71cb5121761e3a6e199a7d287659018a0965", - "index": 13440 + "id": "3f117b7e395f317b757f0d3878163204f617020609402f384b7a01556130463b", + "derivation_path": [ + "13002", + "22071", + "12596", + "2043", + "3501" + ], + "index": 31390 }, { "amount": { - "quantity": 221, + "quantity": 76, "unit": "lovelace" }, "address": "", - "id": "44685a616d7e6e77605a056a0600180904264c257897411d510c7b784c085508", - "index": 26277 + "id": "a60d3ec00dad520574520a58735f1b1a487e6926170087596b364042067a483d", + "derivation_path": [ + "19159", + "6193", + "11718", + "18469", + "28523", + "930", + "29430", + "14160", + "22575", + "19656", + "11306", + "1240", + "31199", + "26355", + "7262", + "2292", + "1305", + "23558", + "26958", + "3783", + "607", + "30024", + "28922", + "13399", + "27279", + "14480", + "30496", + "4511", + "3585", + "5610", + "32543" + ], + "index": 9851 + }, + { + "amount": { + "quantity": 14, + "unit": "lovelace" + }, + "address": "", + "id": "274c1b535157601204407f7832057424577570650a3e002859372c767f5a463b", + "derivation_path": [ + "23034", + "4463", + "2176", + "27435", + "6972", + "31475", + "10951", + "7140", + "25788", + "7567", + "900", + "12905" + ], + "index": 1756 + }, + { + "amount": { + "quantity": 205, + "unit": "lovelace" + }, + "address": "", + "id": "20043c7f599b7237541b293a1d01176d5c217c76112ce21024232b6d1b78441c", + "derivation_path": [ + "5534", + "5910", + "16361", + "7358", + "4063", + "18784", + "24993", + "5603", + "8665", + "2007", + "21385", + "32333", + "8721", + "5547", + "26472", + "10932", + "32708", + "19399", + "29698", + "6489", + "6366", + "22303" + ], + "index": 15775 }, { "amount": { - "quantity": 4, + "quantity": 57, "unit": "lovelace" }, "address": "", - "id": "583b0d6133283d594e3f7e450d660f3e0a6253d2096d767e5ae0283e18363247", - "index": 26846 + "id": "464b6d3b6249414a6197dc4b59e70100dc396a08586d7c40ce4ec75541006d78", + "derivation_path": [ + "5703", + "13585", + "3747", + "28937", + "9971", + "1588", + "19997", + "27621", + "29772", + "23684", + "24821", + "27034", + "12174", + "4157", + "21942", + "8932", + "25685", + "21345", + "7580", + "11361", + "3459", + "19469", + "27827" + ], + "index": 6840 } ], "outputs": [ { "amount": { - "quantity": 19, - "unit": "lovelace" - }, - "address": "" - }, - { - "amount": { - "quantity": 132, + "quantity": 246, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 231, + "quantity": 50, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 11, + "quantity": 98, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 76, + "quantity": 254, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 161, + "quantity": 138, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 8, + "quantity": 18, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 24, + "quantity": 176, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 240, + "quantity": 14, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 129, + "quantity": 26, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 148, + "quantity": 196, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 35, + "quantity": 38, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 172, + "quantity": 15, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 202, + "quantity": 10, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 17, + "quantity": 123, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 199, + "quantity": 95, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 180, + "quantity": 208, "unit": "lovelace" }, "address": "" @@ -2566,392 +3673,1052 @@ "inputs": [ { "amount": { - "quantity": 56, + "quantity": 162, "unit": "lovelace" }, "address": "", - "id": "30526a2d3204141e2f6b0a3b1f4c3502122351a341a60f406e3e5f460167303c", - "index": 4234 + "id": "59d8481b272ad25e6233385515372bfc097ebe68d2364168513f4b6e443d163c", + "derivation_path": [ + "24468", + "20069", + "9155", + "20071", + "31814", + "9268", + "30630", + "30405", + "13019", + "14446", + "9327", + "17985", + "30811" + ], + "index": 13054 + }, + { + "amount": { + "quantity": 30, + "unit": "lovelace" + }, + "address": "", + "id": "19ae5b79305821630f4e0b44b9501f3d7c68340f66451a8a286cf45002074e2b", + "derivation_path": [ + "30003", + "29786", + "26374", + "2966", + "1112", + "9209", + "23605", + "2175", + "28116", + "22793", + "23446", + "3895", + "27387", + "29665", + "22160", + "25041", + "1864", + "30211", + "13047", + "7050", + "26815", + "7876", + "21450", + "749", + "14663", + "25530", + "15020", + "20391", + "10334", + "5930" + ], + "index": 12704 }, { "amount": { - "quantity": 117, + "quantity": 175, "unit": "lovelace" }, "address": "", - "id": "a157683f987d404e099555476a12b56d8039e2552d0d7b860a1c477b1bc75d2f", - "index": 17648 + "id": "4b5df56e24450a3e6c3c074d17704b6ccc3a52680a5321339729ed0e4807b376", + "derivation_path": [ + "11729", + "12480", + "7969", + "6054", + "28163", + "16501", + "6031", + "10568", + "14536", + "261", + "6836", + "31219", + "4880", + "26763", + "30177", + "4456", + "22123", + "2561", + "1476" + ], + "index": 18908 + }, + { + "amount": { + "quantity": 16, + "unit": "lovelace" + }, + "address": "", + "id": "4113192b4e311fe51e0d392b302f700f04605e5b241627ea177c16b9242e6365", + "derivation_path": [ + "23212", + "31187", + "27272", + "32512", + "22146", + "23653", + "28719", + "4495", + "639", + "9771", + "25262", + "18683", + "3752", + "23260", + "16585", + "14295", + "28433" + ], + "index": 16521 }, { "amount": { - "quantity": 111, + "quantity": 133, "unit": "lovelace" }, "address": "", - "id": "1ac62300393339e32a2d1b3478de6f144f236c032a7023af040d3e88255a102c", - "index": 12922 + "id": "1ef5101e757151732f08623d4259762f4c0ce8e823ed6f8c700460711d2a5e41", + "derivation_path": [ + "20856", + "24542", + "18367", + "7187", + "22929", + "8820", + "6190", + "10053", + "31710", + "10921", + "21749", + "23489", + "3355", + "18588", + "12625" + ], + "index": 13023 + }, + { + "amount": { + "quantity": 94, + "unit": "lovelace" + }, + "address": "", + "id": "613b6c4a090c0d683f735e796a3f1b4e472e2f6a0002160b3609120018303618", + "derivation_path": [ + "26519", + "18395", + "10080", + "4963", + "16608", + "23251", + "28572", + "22106", + "7594", + "29301", + "11284", + "24978", + "6408", + "19659", + "18626", + "20619", + "4554" + ], + "index": 8270 }, { "amount": { - "quantity": 252, + "quantity": 140, "unit": "lovelace" }, "address": "", - "id": "187a091b08777c206f7625527f48377952586519533854ef143f3b022638253b", - "index": 2882 + "id": "22886129ea50ac8b183bf0156852ed454f2949bd4fc7ff7723107a6827eb3303", + "derivation_path": [ + "28484", + "14728", + "31737", + "27972", + "24638", + "19930", + "42", + "9444", + "17018", + "13405", + "10987", + "14199", + "22671", + "12211", + "29657", + "28389", + "5294", + "16617", + "21250", + "11318", + "12110", + "11096", + "23938", + "24995", + "16079", + "221", + "16247", + "29691", + "8838" + ], + "index": 25828 }, { "amount": { - "quantity": 145, + "quantity": 184, "unit": "lovelace" }, "address": "", - "id": "65769969664c4b4259bc6d081968573108a6607a3473262836795f9c78686905", - "index": 25153 + "id": "d30d8472107b6822c945507cc2052ad44f2d5b7eda7165756f1d8540323a0200", + "derivation_path": [ + "1220", + "28058", + "3906", + "14132", + "23772", + "8080", + "10270", + "15025", + "4954" + ], + "index": 1280 }, { "amount": { - "quantity": 140, + "quantity": 124, "unit": "lovelace" }, "address": "", - "id": "1b323a4a6e674f43412510280b21321e413f49191555f6091d412a147779b4e0", - "index": 772 + "id": "3e7c0048451a043c04021f4b2f2f7fd97e61090e1a456f32bc42747edb23a876", + "derivation_path": [ + "27138", + "30974", + "17960", + "28476", + "15237" + ], + "index": 28887 }, { "amount": { - "quantity": 242, + "quantity": 96, "unit": "lovelace" }, "address": "", - "id": "77b13053664074213444422912b27f6d1d0f0a292f13612e6120660d023d7d63", - "index": 10428 + "id": "0d7d63a15a3948c770a354497a405a680e39714f373e471ce63b1c675c4f6c0a", + "derivation_path": [ + "3315", + "13683", + "22865", + "6750", + "2164", + "15011", + "8858", + "21317", + "1083", + "29302", + "3194", + "16340", + "31312", + "17345", + "12146", + "2885", + "4008", + "23481", + "31670", + "8771", + "24252" + ], + "index": 29456 }, { "amount": { - "quantity": 28, + "quantity": 170, "unit": "lovelace" }, "address": "", - "id": "49735f287e0f6455e4185460f8547c9829560c69e62e7e477ae3258dda270511", - "index": 14446 + "id": "721d2a406a4122203a0618214b61147f4861567a2bdec0120a6b58ad43713f50", + "derivation_path": [ + "23241", + "6910", + "1299", + "21941", + "21363", + "17140", + "13427", + "23991", + "493", + "29658", + "11342", + "9357", + "29160", + "19042", + "22537", + "14900", + "4260", + "30868", + "16809", + "32320", + "23040", + "29073", + "20728", + "15925" + ], + "index": 2375 }, { "amount": { - "quantity": 138, + "quantity": 114, "unit": "lovelace" }, "address": "", - "id": "2968682ef22a5071497879777812c677697e676b0c4b5fc2f922171e7e54773e", - "index": 1607 + "id": "2b5a267bcd73fe0639d367d13ea815385859454c304239176865f73a024c9a38", + "derivation_path": [ + "15965", + "15943", + "16419", + "12574", + "5560", + "19786", + "15903", + "22837", + "8705", + "21242", + "13508", + "24889", + "9735", + "4067", + "28368", + "2117", + "19086", + "26863", + "16758" + ], + "index": 3434 + }, + { + "amount": { + "quantity": 16, + "unit": "lovelace" + }, + "address": "", + "id": "2d31306718277d3e621d603c67654094506963750e22234d1726967f446a4623", + "derivation_path": [ + "4467", + "24747", + "3629", + "11293", + "7406", + "14718", + "20981", + "15281", + "25920", + "11922", + "24535", + "10922", + "15492", + "9541", + "2742", + "8709", + "29489", + "15018" + ], + "index": 19949 }, { "amount": { - "quantity": 152, + "quantity": 3, "unit": "lovelace" }, "address": "", - "id": "4b6c187d274f0848194f9b06663714207f0f8b7b23152d42202077733a7e3849", - "index": 11090 + "id": "2c6f5e317347364b873740002d3b5866cb1283263d266317501e4a0e18017a46", + "derivation_path": [ + "13260", + "22300", + "27540", + "9380", + "17825", + "18809", + "15155", + "6474", + "1539", + "18460", + "14246", + "31705", + "15005", + "21878", + "29521", + "22425", + "2438", + "9494", + "21462", + "26510", + "9343", + "26122" + ], + "index": 1363 }, { "amount": { - "quantity": 27, + "quantity": 3, "unit": "lovelace" }, "address": "", - "id": "575a8643113b5686ac541c02557a7c2b303421285443bc621929075c47277e1b", - "index": 14342 + "id": "81620a245a3815473a67420f323e6c30277d043a030b191a3805665c3603334a", + "derivation_path": [ + "10286", + "6545", + "10274", + "27118", + "8374", + "30025", + "6153", + "2977", + "20149", + "26039", + "8788", + "14246", + "12059", + "15173", + "16341" + ], + "index": 20909 }, { "amount": { - "quantity": 48, + "quantity": 190, "unit": "lovelace" }, "address": "", - "id": "521f45477d54ab774f2216634016505a322c16621195c0d8c10b506c31737f76", - "index": 8195 + "id": "791365712d2c5fe71528654b3941610707557511340e4b306f0e2b2c4b08390f", + "derivation_path": [ + "4554", + "11069", + "11721", + "7713", + "26657", + "23237", + "5028", + "12611", + "13985", + "23439", + "18685", + "17845", + "22565", + "15554", + "9649", + "1450", + "31093", + "16772", + "19608" + ], + "index": 24661 }, { "amount": { - "quantity": 195, + "quantity": 176, "unit": "lovelace" }, "address": "", - "id": "653e6ed06a0824c02f32792165f6762c482d622b261a4a5b615a5e4811ce4c16", - "index": 5251 + "id": "34a87065293a446b3cf947416db52639546a0a681d14671d6f2e76b3222a100c", + "derivation_path": [ + "24254", + "22129", + "30724", + "11118", + "24059", + "18659", + "14288", + "3089", + "26822", + "19702", + "24095", + "27271", + "4820", + "25109", + "13864", + "5958", + "23808", + "18197", + "6613", + "23444", + "10551", + "10855" + ], + "index": 3760 }, { "amount": { - "quantity": 118, + "quantity": 66, "unit": "lovelace" }, "address": "", - "id": "616934795d0f347c420efe0a960a0a190c6355380b274b6f6d3400119a2b5e73", - "index": 24612 + "id": "0c707874c1be0b31b6671a25277b0cae3efdc34a791035375a6179342e460be4", + "derivation_path": [ + "16741", + "17487", + "17295", + "28772", + "20391", + "143", + "30158", + "11316", + "26727", + "20474", + "14540", + "31830", + "3302", + "32598", + "18042", + "31760", + "19245", + "17155", + "7904", + "16246", + "15216", + "22934", + "15224", + "32750", + "8751", + "18831", + "26673", + "13361", + "1858", + "10126" + ], + "index": 23140 }, { "amount": { - "quantity": 101, + "quantity": 195, "unit": "lovelace" }, "address": "", - "id": "0e4936624eb65f08161d230916447f0a48fc0c54097b50687be553d50570621b", - "index": 28495 + "id": "07b9916c715020fc2f4a136f4442022c4055394126975a397d6d23694b4b1744", + "derivation_path": [ + "32700", + "23969", + "2774", + "28533", + "10530", + "27956" + ], + "index": 5807 }, { "amount": { - "quantity": 11, + "quantity": 85, "unit": "lovelace" }, "address": "", - "id": "1c6d308d4b298e7e50494d76fd62aa1f3816e7545d025364052be995975e0405", - "index": 2519 + "id": "1d7f1436897b046c643e6c003a70155d235d51290d41786376356d7a00ec083c", + "derivation_path": [ + "6425", + "11678", + "8281", + "4324", + "20319", + "15140", + "11204", + "20640", + "25841", + "604", + "15526", + "6785", + "15517", + "14219", + "17448", + "8054", + "13052", + "13166", + "13693", + "10468", + "3244", + "18185" + ], + "index": 4908 }, { "amount": { - "quantity": 77, + "quantity": 104, "unit": "lovelace" }, "address": "", - "id": "0e12192010777a392b1b45011c1d517bf748021c5d1c540d18ba447a402ac330", - "index": 28367 + "id": "d82e0f2e7d241021eb0f6158077931ca46940a385547132315607fec536aa706", + "derivation_path": [ + "21002" + ], + "index": 6064 }, { "amount": { - "quantity": 185, + "quantity": 199, "unit": "lovelace" }, "address": "", - "id": "3f7e9c6f06353f610a08096433432a3d1f3a1a651d17180d176b1b25370361d3", - "index": 4664 + "id": "5afd4f2362150c5f2c1c4363145f00dc3b5304470d7e5ae90134490a16563553", + "derivation_path": [ + "11209", + "24025", + "23883", + "22686", + "16299", + "7223", + "14935", + "10208", + "11589", + "31599", + "30296", + "17201", + "5007", + "4101", + "4441", + "303", + "7460", + "10363", + "6260", + "1551", + "18628", + "28934", + "32169", + "2111", + "28448", + "1541", + "2433", + "21293", + "1635", + "7349", + "18774" + ], + "index": 1000 }, { "amount": { - "quantity": 162, + "quantity": 145, "unit": "lovelace" }, "address": "", - "id": "0a380450656f750517045a3a4eb24a57c42f7e476d56fd08750f05791122156f", - "index": 13439 + "id": "3a097172665e00741e685b9144310c5a2494275c3e0d06f96d08092b0f5e2e5d", + "derivation_path": [ + "22714", + "13366", + "19963", + "24942", + "32627", + "27696", + "14312", + "10337", + "1523" + ], + "index": 9664 + } + ], + "outputs": [ + { + "amount": { + "quantity": 223, + "unit": "lovelace" + }, + "address": "" }, { "amount": { - "quantity": 17, + "quantity": 112, "unit": "lovelace" }, - "address": "", - "id": "5f292b037912605d6d06416a03563e4c1947676b5931271a064d0d7fd59a7b11", - "index": 27753 + "address": "" }, { "amount": { - "quantity": 72, + "quantity": 9, "unit": "lovelace" }, - "address": "", - "id": "da6a7f3028b5804480643adc24680c051a2551c84d586b6f1144047e6b6714b0", - "index": 4740 + "address": "" }, { "amount": { - "quantity": 195, + "quantity": 42, "unit": "lovelace" }, - "address": "", - "id": "6e083f58005a5f6046796f31e2644e1d3f0f4e66af1352431b0e210b014e53a1", - "index": 12220 + "address": "" }, { "amount": { - "quantity": 51, + "quantity": 59, "unit": "lovelace" }, - "address": "", - "id": "3517525962907904142d51151c60db1746414a4f1d1a0e71560f5d09646f2025", - "index": 13870 + "address": "" }, { "amount": { - "quantity": 146, + "quantity": 40, + "unit": "lovelace" + }, + "address": "" + } + ] + }, + { + "inputs": [ + { + "amount": { + "quantity": 37, + "unit": "lovelace" + }, + "address": "", + "id": "694e12080fac0b01e839133f482201477f0ba545fc5b0d9a381a444c2d2a0efb", + "derivation_path": [ + "26054", + "14111", + "18963", + "9141", + "23284", + "31847", + "30648", + "12355", + "29332", + "10947", + "25100", + "19706", + "2235", + "7367", + "10016", + "23551", + "18594", + "27888", + "4418", + "25221", + "12943", + "31772", + "20195", + "21579" + ], + "index": 5553 + }, + { + "amount": { + "quantity": 93, + "unit": "lovelace" + }, + "address": "", + "id": "2168ed1441626d225e0a002e325dce2bf36e560d523831a77856444f46565f4d", + "derivation_path": [ + "16323", + "8564", + "1894", + "11880", + "16741", + "6507", + "4075", + "7310", + "27468", + "25180", + "32090", + "28325", + "32367", + "5801", + "7029", + "22629", + "6847", + "8211", + "23029", + "5024", + "1872", + "20621", + "4119", + "28471", + "9201", + "28055", + "2178", + "10702", + "2981" + ], + "index": 15727 + }, + { + "amount": { + "quantity": 54, "unit": "lovelace" }, "address": "", - "id": "851566112e4b78782c2703563769e5454e5f237a7234584b1921f038183de29d", - "index": 16436 + "id": "5f1b516e0096257c18452c3cd2a979436064366b3e136725481d87d25e3d1d38", + "derivation_path": [ + "23761", + "21381", + "11590", + "28056", + "24116" + ], + "index": 3532 }, { "amount": { - "quantity": 157, + "quantity": 114, "unit": "lovelace" }, "address": "", - "id": "8b3f67255f32926e0d55276c78d84208794a5df20c2751409cfc726707a4577c", - "index": 25607 + "id": "3d1434963616275e456f43aedcf9395f7c507c325ebe26e7be5dc511654e2149", + "derivation_path": [ + "15868", + "194", + "8694", + "26193", + "16321", + "18678", + "16948", + "11285", + "28266", + "26411", + "3287" + ], + "index": 13583 }, { "amount": { - "quantity": 206, + "quantity": 230, "unit": "lovelace" }, "address": "", - "id": "196d332b6d0e172472297c184368400672fe46735b251e3456234139483d606c", - "index": 13883 + "id": "f71638466c481346494c367c657502f36427706b791c2a46286e486362af4115", + "derivation_path": [ + "24992", + "9460", + "7856", + "15636", + "12112", + "32106", + "29534", + "18205", + "3082", + "1085", + "20541", + "14285", + "24301", + "1094", + "12421", + "22258", + "11468", + "23212", + "7226", + "69", + "32071" + ], + "index": 26995 }, { "amount": { - "quantity": 252, + "quantity": 118, "unit": "lovelace" }, "address": "", - "id": "15257f4000291dc3aafd62783e625d16487a197d5b657b0b293b031d5f02174c", - "index": 18096 + "id": "5b044f3f33561b61200e6a2c0855012625064d604dc802297d285d48107f5149", + "derivation_path": [ + "20319", + "565", + "18127", + "10815", + "30004", + "11851", + "5643", + "11586", + "27046", + "25015", + "28101", + "8040", + "18901", + "25285", + "1247", + "15926", + "23358", + "16779", + "9230", + "12381", + "24848", + "18307", + "21398", + "3923", + "21881", + "28419" + ], + "index": 22274 } ], "outputs": [ { "amount": { - "quantity": 38, + "quantity": 229, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 171, + "quantity": 78, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 215, + "quantity": 209, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 135, + "quantity": 208, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 136, + "quantity": 189, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 183, + "quantity": 204, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 202, + "quantity": 109, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 234, + "quantity": 66, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 187, + "quantity": 115, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 17, + "quantity": 229, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 189, + "quantity": 86, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 114, + "quantity": 186, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 157, + "quantity": 126, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 54, + "quantity": 25, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 9, + "quantity": 110, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 38, + "quantity": 95, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 190, + "quantity": 238, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 79, + "quantity": 216, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 74, + "quantity": 246, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 229, + "quantity": 239, "unit": "lovelace" }, "address": "" }, { "amount": { - "quantity": 230, + "quantity": 243, + "unit": "lovelace" + }, + "address": "" + }, + { + "amount": { + "quantity": 165, "unit": "lovelace" }, "address": "" diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiDerivationPath.json b/lib/core/test/data/Cardano/Wallet/Api/ApiDerivationPath.json new file mode 100644 index 00000000000..8f79784ddff --- /dev/null +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiDerivationPath.json @@ -0,0 +1,202 @@ +{ + "seed": -2295817894099623866, + "samples": [ + [ + "106055901H", + "686062770", + "1429209097H" + ], + [ + "156163126", + "1390414012H", + "504573270H", + "808863359H", + "30751566", + "24309288H", + "1376351789H", + "1093186850H", + "770955634", + "311696751", + "1821368135H", + "709388429H", + "31622957H", + "208860251H" + ], + [ + "869859356", + "760580535H", + "1027746283H", + "423387416H", + "312421700", + "1162330781", + "1030497524", + "1141367074", + "847264953H", + "1463911221H", + "176218798", + "158817870", + "1741579515", + "1450675492", + "1623609846", + "1018007590H", + "242964213", + "392018821", + "701866038", + "1016921583", + "1320638973", + "1682299144H", + "292938014", + "1242494712H", + "67197650H", + "57199242H", + "269921354H", + "302986139H" + ], + [ + "1078818685H", + "1846342301H", + "908306783", + "724405636H", + "1662670608", + "2079685910H", + "741504529H", + "1598463283", + "1128108436H", + "409418101", + "1422613029H", + "1580832298H", + "1342640308H", + "1029353522", + "30242365H", + "1469320838", + "916689673", + "1764835056", + "292958949", + "107447763", + "1767932553", + "854479044H", + "520784652H", + "186168505", + "793002121", + "1860552346H", + "1673846301", + "24321731H", + "792773323", + "1467442987H", + "219190080" + ], + [ + "2032430638", + "929529187", + "592962276", + "1923413498H" + ], + [ + "137605179", + "1007038090", + "935580348", + "1111810241H", + "1151118302H", + "878498853", + "1005042450", + "349623922", + "1401710848", + "2007606233H", + "1279513408", + "1939472351H", + "1070724522", + "2106016483", + "1236776069H", + "267033396", + "679219746", + "859396415H", + "1948824454", + "718594513H", + "249900598", + "984841668", + "1778134831", + "179731270H", + "9729039H" + ], + [ + "1271117575H", + "1546436638" + ], + [ + "1495542700H", + "2033429507H", + "226501001H", + "494927455H", + "707119144", + "906444240", + "520157049", + "157293989H", + "1421383785H", + "710919479", + "1462991454H", + "267995966", + "2136797939", + "1057100912H", + "371793691H", + "613801089H", + "1301215128", + "1561229597H", + "1904568282", + "493510702", + "1267041637H", + "859391064H", + "2078417122H", + "2107783668", + "282339570H", + "1661812350H" + ], + [ + "1266800782", + "1647341134", + "1777045260H", + "122119991H", + "497113743", + "379054947H", + "305942122", + "304046331", + "1296485248H", + "649222510H", + "1760042508", + "1629098715", + "652278910", + "1260585093H", + "683283922", + "1372187908", + "114473364", + "1261046030H" + ], + [ + "1311009544H", + "1600231318H", + "659082934", + "371011593H", + "562599579H", + "176654320", + "1332120655H", + "894714531H", + "1226202702H", + "1426690765H", + "979547978H", + "1025871303", + "806881740H", + "314799384", + "1828687311H", + "627039070", + "1159740400H", + "358348279", + "230049332", + "1642836706H", + "2060468406H", + "1977782575H", + "1655391093H", + "1562301643", + "424519842H", + "1290722085H" + ] + ] +} \ No newline at end of file diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiDerivationSegment.json b/lib/core/test/data/Cardano/Wallet/Api/ApiDerivationSegment.json new file mode 100644 index 00000000000..e651eed1e81 --- /dev/null +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiDerivationSegment.json @@ -0,0 +1,15 @@ +{ + "seed": -8802247239741217203, + "samples": [ + "715470553", + "1918643601", + "1594680446", + "66679821H", + "1798176122", + "1005567920", + "1257776519", + "33732108H", + "1408834224H", + "1791803590" + ] +} \ No newline at end of file diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiDerivationType.json b/lib/core/test/data/Cardano/Wallet/Api/ApiDerivationType.json new file mode 100644 index 00000000000..d4f60037c1a --- /dev/null +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiDerivationType.json @@ -0,0 +1,15 @@ +{ + "seed": -7386091786928196139, + "samples": [ + "soft", + "soft", + "hardened", + "soft", + "hardened", + "soft", + "soft", + "hardened", + "soft", + "hardened" + ] +} \ No newline at end of file diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiTDerivationIndex.json b/lib/core/test/data/Cardano/Wallet/Api/ApiTDerivationIndex.json new file mode 100644 index 00000000000..958358a95bb --- /dev/null +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiTDerivationIndex.json @@ -0,0 +1,15 @@ +{ + "seed": 3561395127303670224, + "samples": [ + "9191", + "9627", + "842", + "18854", + "5565", + "31611", + "22239", + "26116", + "15271", + "24268" + ] +} \ No newline at end of file diff --git a/lib/core/test/data/icarusDerivationPrefix-v2020-10-07.sqlite b/lib/core/test/data/icarusDerivationPrefix-v2020-10-07.sqlite new file mode 100644 index 00000000000..4e044275978 Binary files /dev/null and b/lib/core/test/data/icarusDerivationPrefix-v2020-10-07.sqlite differ diff --git a/lib/core/test/data/shelleyDerivationPrefix-v2020-10-07.sqlite b/lib/core/test/data/shelleyDerivationPrefix-v2020-10-07.sqlite new file mode 100644 index 00000000000..4242a19030c Binary files /dev/null and b/lib/core/test/data/shelleyDerivationPrefix-v2020-10-07.sqlite differ diff --git a/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs b/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs index dc905bf087f..12a9e39c603 100644 --- a/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs +++ b/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs @@ -43,9 +43,6 @@ import Cardano.Wallet.Api.Types , AddressAmount (..) , ApiAccountPublicKey (..) , ApiAddress (..) - , ApiAddressDerivationPath (..) - , ApiAddressDerivationSegment (..) - , ApiAddressDerivationType (..) , ApiAddressInspect (..) , ApiBlockInfo (..) , ApiBlockReference (..) @@ -62,7 +59,6 @@ import Cardano.Wallet.Api.Types , ApiNtpStatus (..) , ApiPostRandomAddressData , ApiPutAddressesData (..) - , ApiRelativeAddressIndex (..) , ApiSelectCoinsData (..) , ApiSlotId (..) , ApiSlotReference (..) @@ -114,7 +110,9 @@ import Cardano.Wallet.Gen , shrinkTxMetadata ) import Cardano.Wallet.Primitive.AddressDerivation - ( HardDerivation (..) + ( DerivationType (..) + , HardDerivation (..) + , Index (..) , NetworkDiscriminant (..) , Passphrase (..) , PassphraseMaxLength (..) @@ -136,6 +134,7 @@ import Cardano.Wallet.Primitive.Types , AddressState (..) , ChimericAccount (..) , Coin (..) + , DerivationIndex (..) , Direction (..) , EpochNo (..) , Hash (..) @@ -312,10 +311,7 @@ spec = do "can perform roundtrip JSON serialization & deserialization, \ \and match existing golden files" $ do jsonRoundtripAndGolden $ Proxy @(ApiAddress ('Testnet 0)) - jsonRoundtripAndGolden $ Proxy @ApiAddressDerivationPath - jsonRoundtripAndGolden $ Proxy @ApiAddressDerivationSegment - jsonRoundtripAndGolden $ Proxy @ApiAddressDerivationType - jsonRoundtripAndGolden $ Proxy @ApiRelativeAddressIndex + jsonRoundtripAndGolden $ Proxy @(ApiT DerivationIndex) jsonRoundtripAndGolden $ Proxy @ApiEpochInfo jsonRoundtripAndGolden $ Proxy @(ApiSelectCoinsData ('Testnet 0)) jsonRoundtripAndGolden $ Proxy @(ApiCoinSelection ('Testnet 0)) @@ -458,25 +454,25 @@ spec = do |] `shouldBe` (Left @String @(ApiMnemonicT '[12]) msg) - it "ApiRelativeAddressIndex (too small)" $ do + it "ApiT DerivationIndex (too small)" $ do let message = mconcat [ "Error in $: " - , "\"A relative address index must be a natural number " - , "between 0 and 2147483647.\"" + , "A derivation index must be a natural number " + , "between 0 and 2147483647." ] - let value = pred $ toInteger $ unApiRelativeAddressIndex minBound + let value = show $ pred $ toInteger $ getIndex @'Soft minBound Aeson.parseEither parseJSON [aesonQQ|#{value}|] - `shouldBe` Left @String @ApiRelativeAddressIndex message + `shouldBe` Left @String @(ApiT DerivationIndex) message - it "ApiRelativeAddressIndex (too large)" $ do + it "ApiT DerivationIndex (too large)" $ do let message = mconcat [ "Error in $: " - , "\"A relative address index must be a natural number " - , "between 0 and 2147483647.\"" + , "A derivation index must be a natural number " + , "between 0 and 2147483647." ] - let value = succ $ toInteger $ unApiRelativeAddressIndex maxBound + let value = show $ succ $ toInteger $ getIndex @'Soft maxBound Aeson.parseEither parseJSON [aesonQQ|#{value}|] - `shouldBe` Left @String @ApiRelativeAddressIndex message + `shouldBe` Left @String @(ApiT DerivationIndex) message it "ApiT AddressPoolGap (too small)" $ do let msg = "Error in $: An address pool gap must be a natural number between " @@ -626,6 +622,7 @@ spec = do , index = index (x :: ApiCoinSelectionInput ('Testnet 0)) , address = address (x :: ApiCoinSelectionInput ('Testnet 0)) , amount = amount (x :: ApiCoinSelectionInput ('Testnet 0)) + , derivationPath = derivationPath (x :: ApiCoinSelectionInput ('Testnet 0)) } in x' === x .&&. show x' === show x @@ -906,20 +903,8 @@ instance Arbitrary (ApiAddress t) where <$> fmap (, Proxy @t) arbitrary <*> arbitrary -instance Arbitrary ApiAddressDerivationPath where - arbitrary = ApiAddressDerivationPath <$> arbitrary - shrink = genericShrink - -instance Arbitrary ApiAddressDerivationSegment where - arbitrary = ApiAddressDerivationSegment <$> arbitrary <*> arbitrary - shrink = genericShrink - -instance Arbitrary ApiAddressDerivationType where - arbitrary = arbitraryBoundedEnum - shrink = genericShrink - -instance Arbitrary ApiRelativeAddressIndex where - arbitrary = arbitraryBoundedEnum +instance Arbitrary DerivationIndex where + arbitrary = DerivationIndex <$> arbitrary shrink = genericShrink instance Arbitrary ApiEpochInfo where @@ -940,6 +925,7 @@ instance Arbitrary (ApiCoinSelectionInput n) where <*> arbitrary <*> fmap (, Proxy @n) arbitrary <*> arbitrary + <*> arbitrary shrink _ = [] instance Arbitrary AddressState where diff --git a/lib/core/test/unit/Cardano/Wallet/DB/Arbitrary.hs b/lib/core/test/unit/Cardano/Wallet/DB/Arbitrary.hs index 6b147101d66..c354163840c 100644 --- a/lib/core/test/unit/Cardano/Wallet/DB/Arbitrary.hs +++ b/lib/core/test/unit/Cardano/Wallet/DB/Arbitrary.hs @@ -61,7 +61,13 @@ import Cardano.Wallet.Primitive.AddressDiscovery import Cardano.Wallet.Primitive.AddressDiscovery.Random ( RndState (..) ) import Cardano.Wallet.Primitive.AddressDiscovery.Sequential - ( AddressPool, SeqState (..), mkAddressPool ) + ( AddressPool + , DerivationPrefix (..) + , SeqState (..) + , coinTypeAda + , mkAddressPool + , purposeCIP1852 + ) import Cardano.Wallet.Primitive.Model ( Wallet , blockchainParameters @@ -448,23 +454,15 @@ instance (Ord a, Arbitrary a) => Arbitrary (Range a) where instance Arbitrary Address where arbitrary = Address . B8.pack <$> vector addrSingleSize -instance Arbitrary (Index 'Soft 'AddressK) where +instance Arbitrary (Index 'Soft depth) where shrink _ = [] arbitrary = arbitraryBoundedEnum -instance Arbitrary (Index 'Hardened 'AccountK) where +instance Arbitrary (Index 'Hardened depth) where shrink _ = [] arbitrary = arbitraryBoundedEnum -instance Arbitrary (Index 'WholeDomain 'AccountK) where - shrink _ = [] - arbitrary = arbitraryBoundedEnum - -instance Arbitrary (Index 'Hardened 'AddressK) where - shrink _ = [] - arbitrary = arbitraryBoundedEnum - -instance Arbitrary (Index 'WholeDomain 'AddressK) where +instance Arbitrary (Index 'WholeDomain depth) where shrink _ = [] arbitrary = arbitraryBoundedEnum @@ -473,13 +471,21 @@ instance Arbitrary (Index 'WholeDomain 'AddressK) where -------------------------------------------------------------------------------} instance Arbitrary (SeqState 'Mainnet JormungandrKey) where - shrink (SeqState intPool extPool ixs rwd) = - (\(i, e, x) -> SeqState i e x rwd) <$> shrink (intPool, extPool, ixs) + shrink (SeqState intPool extPool ixs rwd prefix) = + (\(i, e, x) -> SeqState i e x rwd prefix) <$> shrink (intPool, extPool, ixs) arbitrary = SeqState <$> arbitrary <*> arbitrary <*> arbitrary <*> pure arbitraryRewardAccount + <*> pure defaultSeqStatePrefix + +defaultSeqStatePrefix :: DerivationPrefix +defaultSeqStatePrefix = DerivationPrefix + ( purposeCIP1852 + , coinTypeAda + , minBound + ) instance Arbitrary (JormungandrKey 'RootK XPrv) where shrink _ = [] diff --git a/lib/core/test/unit/Cardano/Wallet/DB/MVarSpec.hs b/lib/core/test/unit/Cardano/Wallet/DB/MVarSpec.hs index dfe46fa3c60..c50a90dbe83 100644 --- a/lib/core/test/unit/Cardano/Wallet/DB/MVarSpec.hs +++ b/lib/core/test/unit/Cardano/Wallet/DB/MVarSpec.hs @@ -5,6 +5,7 @@ {-# LANGUAGE RankNTypes #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TypeApplications #-} +{-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -fno-warn-orphans #-} @@ -53,4 +54,4 @@ instance Arbitrary DummyStateMVar where deriving instance NFData DummyStateMVar instance IsOurs DummyStateMVar Address where - isOurs _ num = (True, num) + isOurs _ num = (Nothing, num) diff --git a/lib/core/test/unit/Cardano/Wallet/DB/SqliteSpec.hs b/lib/core/test/unit/Cardano/Wallet/DB/SqliteSpec.hs index b2411ece658..4e3603d464c 100644 --- a/lib/core/test/unit/Cardano/Wallet/DB/SqliteSpec.hs +++ b/lib/core/test/unit/Cardano/Wallet/DB/SqliteSpec.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE FlexibleContexts #-} @@ -79,13 +80,18 @@ import Cardano.Wallet.Logging ( trMessageText ) import Cardano.Wallet.Primitive.AddressDerivation ( Depth (..) + , DerivationType (..) + , Index , NetworkDiscriminant (..) , Passphrase (..) , PersistPrivateKey + , WalletKey , encryptPassphrase ) import Cardano.Wallet.Primitive.AddressDerivation.Byron ( ByronKey (..) ) +import Cardano.Wallet.Primitive.AddressDerivation.Icarus + ( IcarusKey ) import Cardano.Wallet.Primitive.AddressDerivation.Jormungandr ( JormungandrKey (..), generateKeyFromSeed ) import Cardano.Wallet.Primitive.AddressDerivation.Shelley @@ -95,7 +101,14 @@ import Cardano.Wallet.Primitive.AddressDiscovery import Cardano.Wallet.Primitive.AddressDiscovery.Random ( RndState (..) ) import Cardano.Wallet.Primitive.AddressDiscovery.Sequential - ( SeqState (..), defaultAddressPoolGap, mkSeqStateFromRootXPrv ) + ( DerivationPrefix (..) + , SeqState (..) + , coinTypeAda + , defaultAddressPoolGap + , mkSeqStateFromRootXPrv + , purposeBIP44 + , purposeCIP1852 + ) import Cardano.Wallet.Primitive.Model ( FilteredBlock (..) , Wallet @@ -233,6 +246,22 @@ spec = do it "'migrate' db with no passphrase scheme set." testMigrationPassphraseScheme + it "'migrate' db with no 'derivation_prefix' for seq state (Icarus)" $ + testMigrationSeqStateDerivationPrefix @IcarusKey + "icarusDerivationPrefix-v2020-10-07.sqlite" + ( purposeBIP44 + , coinTypeAda + , minBound + ) + + it "'migrate' db with no 'derivation_prefix' for seq state (Shelley)" $ + testMigrationSeqStateDerivationPrefix @ShelleyKey + "shelleyDerivationPrefix-v2020-10-07.sqlite" + ( purposeCIP1852 + , coinTypeAda + , minBound + ) + sqliteSpecSeq :: Spec sqliteSpecSeq = withDB newMemoryDBLayer $ do describe "Sqlite" properties @@ -246,6 +275,43 @@ sqliteSpecRnd = withDB newMemoryDBLayer $ do it "Sequential state machine tests" (prop_sequential :: TestDBRnd -> Property) +testMigrationSeqStateDerivationPrefix + :: forall k s. + ( s ~ SeqState 'Mainnet k + , WalletKey k + , PersistState s + , PersistPrivateKey (k 'RootK) + ) + => String + -> ( Index 'Hardened 'PurposeK + , Index 'Hardened 'CoinTypeK + , Index 'Hardened 'AccountK + ) + -> IO () +testMigrationSeqStateDerivationPrefix dbName prefix = do + let orig = $(getTestData) dbName + withSystemTempDirectory "migration-db" $ \dir -> do + let path = dir "db.sqlite" + let ti = dummyTimeInterpreter + copyFile orig path + (logs, Just cp) <- captureLogging $ \tr -> do + withDBLayer @s @k tr defaultFieldValues (Just path) ti + $ \(_ctx, db) -> db & \DBLayer{..} -> atomically + $ do + [wid] <- listWallets + readCheckpoint wid + let migrationMsg = filter isMsgManualMigration logs + length migrationMsg `shouldBe` 1 + derivationPrefix (getState cp) `shouldBe` DerivationPrefix prefix + where + isMsgManualMigration :: DBLog -> Bool + isMsgManualMigration = \case + MsgManualMigrationNeeded field _ -> + fieldName field == + unDBName (fieldDB $ persistFieldDef DB.SeqStateDerivationPrefix) + _ -> + False + testMigrationPassphraseScheme :: forall s k. (k ~ ShelleyKey, s ~ SeqState 'Mainnet k) => IO () @@ -342,6 +408,7 @@ loggingSpec = withLoggingDB @(SeqState 'Mainnet JormungandrKey) @JormungandrKey newMemoryDBLayer :: ( PersistState s , PersistPrivateKey (k 'RootK) + , WalletKey k ) => IO (DBLayer IO s k) newMemoryDBLayer = snd . snd <$> newMemoryDBLayer' @@ -349,6 +416,7 @@ newMemoryDBLayer = snd . snd <$> newMemoryDBLayer' newMemoryDBLayer' :: ( PersistState s , PersistPrivateKey (k 'RootK) + , WalletKey k ) => IO (TVar [DBLog], (SqliteContext, DBLayer IO s k)) newMemoryDBLayer' = do @@ -361,6 +429,7 @@ newMemoryDBLayer' = do withLoggingDB :: ( PersistState s , PersistPrivateKey (k 'RootK) + , WalletKey k ) => SpecWith (IO [DBLog], DBLayer IO s k) -> Spec @@ -807,7 +876,7 @@ testCp :: Wallet (SeqState 'Mainnet JormungandrKey) testCp = snd $ initWallet block0 dummyGenesisParameters initDummyState where initDummyState :: SeqState 'Mainnet JormungandrKey - initDummyState = mkSeqStateFromRootXPrv (xprv, mempty) defaultAddressPoolGap + initDummyState = mkSeqStateFromRootXPrv (xprv, mempty) purposeCIP1852 defaultAddressPoolGap where mw = SomeMnemonic . unsafePerformIO . generate $ genMnemonic @15 xprv = generateKeyFromSeed (mw, Nothing) mempty @@ -865,7 +934,7 @@ testCpSeq :: Wallet (SeqState 'Mainnet JormungandrKey) testCpSeq = snd $ initWallet block0 dummyGenesisParameters initDummyStateSeq initDummyStateSeq :: SeqState 'Mainnet JormungandrKey -initDummyStateSeq = mkSeqStateFromRootXPrv (xprv, mempty) defaultAddressPoolGap +initDummyStateSeq = mkSeqStateFromRootXPrv (xprv, mempty) purposeCIP1852 defaultAddressPoolGap where mw = SomeMnemonic $ unsafePerformIO (generate $ genMnemonic @15) xprv = Seq.generateKeyFromSeed (mw, Nothing) mempty diff --git a/lib/core/test/unit/Cardano/Wallet/Primitive/AddressDiscovery/RandomSpec.hs b/lib/core/test/unit/Cardano/Wallet/Primitive/AddressDiscovery/RandomSpec.hs index 8ad56eca62d..5a4185ff02f 100644 --- a/lib/core/test/unit/Cardano/Wallet/Primitive/AddressDiscovery/RandomSpec.hs +++ b/lib/core/test/unit/Cardano/Wallet/Primitive/AddressDiscovery/RandomSpec.hs @@ -55,6 +55,8 @@ import Data.Function ( (&) ) import Data.List ( find ) +import Data.Maybe + ( isJust, isNothing ) import Data.Word ( Word32 ) import System.Random @@ -225,7 +227,7 @@ arbitraryMnemonic = either (error . show) id $ mkSomeMnemonic @'[12] checkIsOurs :: GoldenTest -> Expectation checkIsOurs GoldenTest{..} = do - fst (isOurs addr' rndState) `shouldBe` expected + isJust (fst $ isOurs addr' rndState) `shouldBe` expected where Right addr' = Address <$> convertFromBase Base16 addr (_, rndState) = rndStateFromMnem arbitraryMnemonic @@ -279,7 +281,7 @@ prop_derivedKeysAreOurs -> Index 'WholeDomain 'AddressK -> Property prop_derivedKeysAreOurs rnd@(Rnd st _ _) (Rnd st' _ _) addrIx = - fst (isOurs addr st) .&&. not (fst (isOurs addr st')) + isJust (fst $ isOurs addr st) .&&. isNothing (fst $ isOurs addr st') where addr = mkAddress rnd addrIx @@ -302,7 +304,7 @@ prop_changeAddressesBelongToUs -> Rnd -> Property prop_changeAddressesBelongToUs (Rnd st rk pwd) (Rnd st' _ _) = - fst (isOurs addr st) .&&. not (fst (isOurs addr st')) + isJust (fst $ isOurs addr st) .&&. isNothing (fst $ isOurs addr st') where (addr, _) = genChange (rk, pwd) st diff --git a/lib/core/test/unit/Cardano/Wallet/Primitive/AddressDiscovery/SequentialSpec.hs b/lib/core/test/unit/Cardano/Wallet/Primitive/AddressDiscovery/SequentialSpec.hs index b0675498713..66b466b2abd 100644 --- a/lib/core/test/unit/Cardano/Wallet/Primitive/AddressDiscovery/SequentialSpec.hs +++ b/lib/core/test/unit/Cardano/Wallet/Primitive/AddressDiscovery/SequentialSpec.hs @@ -26,7 +26,9 @@ import Cardano.Wallet.Primitive.AddressDerivation ( AccountingStyle (..) , DelegationAddress (..) , Depth (..) + , DerivationType (..) , HardDerivation (..) + , Index , KeyFingerprint , MkKeyFingerprint (..) , NetworkDiscriminant (..) @@ -49,11 +51,13 @@ import Cardano.Wallet.Primitive.AddressDiscovery import Cardano.Wallet.Primitive.AddressDiscovery.Sequential ( AddressPool , AddressPoolGap (..) + , DerivationPrefix (..) , MkAddressPoolGapError (..) , SeqState (..) , accountPubKey , accountingStyle , addresses + , coinTypeAda , defaultAddressPoolGap , emptyPendingIxs , gap @@ -63,12 +67,16 @@ import Cardano.Wallet.Primitive.AddressDiscovery.Sequential , mkSeqStateFromAccountXPub , mkSeqStateFromRootXPrv , mkUnboundedAddressPoolGap + , purposeCIP1852 + , purposeCIP1852 , shrinkPool ) import Cardano.Wallet.Primitive.Types ( Address (..), AddressState (..), ShowFmt (..) ) import Cardano.Wallet.Unsafe ( someDummyMnemonic ) +import Control.Arrow + ( first ) import Control.Monad ( forM, forM_, unless ) import Control.Monad.IO.Class @@ -97,7 +105,6 @@ import Test.QuickCheck , Positive (..) , Property , arbitraryBoundedEnum - , arbitraryBoundedEnum , checkCoverage , choose , classify @@ -138,6 +145,9 @@ spec = do it "defaultAddressPoolGap is valid" (property prop_defaultValid) + describe "DerivationPrefix" $ do + textRoundtrip (Proxy @DerivationPrefix) + let styles = [ Style (Proxy @'UTxOExternal) , Style (Proxy @'UTxOInternal) @@ -357,7 +367,7 @@ prop_genChangeGapFromRootXPrv g = where mw = someDummyMnemonic (Proxy @12) key = Jormungandr.unsafeGenerateKeyFromSeed (mw, Nothing) mempty - s0 = mkSeqStateFromRootXPrv (key, mempty) g + s0 = mkSeqStateFromRootXPrv (key, mempty) purposeCIP1852 g prop = length (fst $ changeAddresses [] s0) === fromEnum g @@ -373,7 +383,7 @@ prop_genChangeGapFromAccountXPub g = rootXPrv = Jormungandr.unsafeGenerateKeyFromSeed (mw, Nothing) mempty accIx = toEnum 0x80000000 accXPub = publicKey $ deriveAccountPrivateKey mempty rootXPrv accIx - s0 = mkSeqStateFromAccountXPub accXPub g + s0 = mkSeqStateFromAccountXPub accXPub purposeCIP1852 g prop = length (fst $ changeAddresses [] s0) === fromEnum g @@ -403,7 +413,7 @@ prop_lookupDiscovered :: (SeqState 'Mainnet JormungandrKey, Address) -> Property prop_lookupDiscovered (s0, addr) = - let (ours, s) = isOurs addr s0 in ours ==> prop s + let (ours, s) = isOurs addr s0 in isJust ours ==> prop s where mw = someDummyMnemonic (Proxy @12) key = Jormungandr.unsafeGenerateKeyFromSeed (mw, Nothing) mempty @@ -421,7 +431,7 @@ prop_compareKnownUnknown -> Property prop_compareKnownUnknown (s, ShowFmt known, ShowFmt addr) = case (fst $ isOurs known s, fst $ isOurs addr s) of - (True, False) -> cover 10 True "known-unknown" $ prop LT + (Just{}, Nothing) -> cover 10 True "known-unknown" $ prop LT _ -> property True where prop ordering = compareDiscovery s known addr === ordering @@ -446,7 +456,7 @@ prop_knownAddressesAreOurs :: SeqState 'Mainnet JormungandrKey -> Property prop_knownAddressesAreOurs s = - map (\x -> (ShowFmt x, fst (isOurs x s))) (fst <$> knownAddresses s) + map (\x -> (ShowFmt x, isJust $ fst $ isOurs x s)) (fst <$> knownAddresses s) === map (\x -> (ShowFmt x, True)) (fst <$> knownAddresses s) @@ -466,7 +476,7 @@ prop_changeIsOnlyKnownAfterGeneration prop_changeIsOnlyKnownAfterGeneration (intPool, extPool) = let s0 :: SeqState 'Mainnet JormungandrKey - s0 = SeqState intPool extPool emptyPendingIxs rewardAccount + s0 = SeqState intPool extPool emptyPendingIxs rewardAccount defaultPrefix addrs0 = fst <$> knownAddresses s0 (change, s1) = genChange (\k _ -> paymentAddress @'Mainnet k) s0 addrs1 = fst <$> knownAddresses s1 @@ -490,7 +500,7 @@ prop_oursAreUsed prop_oursAreUsed s = let (addr, status) = head $ knownAddresses s - (True, s') = isOurs addr s + (True, s') = first isJust $ isOurs addr s (addr', status') = head $ knownAddresses s' in (status' == Used .&&. addr === addr') @@ -609,6 +619,13 @@ unsafeMkAddressPoolGap g = case (mkAddressPoolGap $ fromIntegral g) of Right a -> a Left _ -> error $ "unsafeMkAddressPoolGap: bad argument: " <> show g +defaultPrefix :: DerivationPrefix +defaultPrefix = DerivationPrefix + ( purposeCIP1852 + , coinTypeAda + , minBound + ) + {------------------------------------------------------------------------------- Arbitrary Instances -------------------------------------------------------------------------------} @@ -627,6 +644,16 @@ instance Arbitrary AddressState where shrink _ = [] arbitrary = genericArbitrary +instance Arbitrary DerivationPrefix where + arbitrary = fmap DerivationPrefix $ (,,) + <$> arbitrary + <*> arbitrary + <*> arbitrary + +instance Arbitrary (Index 'Hardened depth) where + shrink _ = [] + arbitrary = arbitraryBoundedEnum + -- | In this context, Arbitrary addresses are either some known addresses -- derived from "our account key", or they just are some arbitrary addresses -- that are unknown to us. @@ -673,12 +700,12 @@ instance return $ mkAddressPool @'Mainnet ourAccount g (zip addrs statuses) instance Arbitrary (SeqState 'Mainnet JormungandrKey) where - shrink (SeqState intPool extPool ixs rwd) = - (\(i, e) -> SeqState i e ixs rwd) <$> shrink (intPool, extPool) + shrink (SeqState intPool extPool ixs rwd prefix) = + (\(i, e) -> SeqState i e ixs rwd prefix) <$> shrink (intPool, extPool) arbitrary = do intPool <- arbitrary extPool <- arbitrary - return $ SeqState intPool extPool emptyPendingIxs rewardAccount + return $ SeqState intPool extPool emptyPendingIxs rewardAccount defaultPrefix -- | Wrapper to encapsulate accounting style proxies that are so-to-speak, -- different types in order to easily map over them and avoid duplicating diff --git a/lib/core/test/unit/Cardano/Wallet/Primitive/AddressDiscoverySpec.hs b/lib/core/test/unit/Cardano/Wallet/Primitive/AddressDiscoverySpec.hs index ba781fe2503..e5dc6265ef3 100644 --- a/lib/core/test/unit/Cardano/Wallet/Primitive/AddressDiscoverySpec.hs +++ b/lib/core/test/unit/Cardano/Wallet/Primitive/AddressDiscoverySpec.hs @@ -38,6 +38,8 @@ import Cardano.Wallet.Primitive.AddressDiscovery.Random ( mkRndState ) import Control.Monad ( replicateM ) +import Data.Maybe + ( isJust, isNothing ) import Data.Proxy ( Proxy (..) ) import Test.Hspec @@ -81,8 +83,8 @@ prop_derivedKeysAreOurs -> ByronKey 'RootK XPrv -> Property prop_derivedKeysAreOurs seed encPwd accIx addrIx rk' = - resPos .&&. addr `elem` (fst <$> knownAddresses stPos') .&&. - not resNeg .&&. addr `notElem` (fst <$> knownAddresses stNeg') + isJust resPos .&&. addr `elem` (fst <$> knownAddresses stPos') .&&. + isNothing resNeg .&&. addr `notElem` (fst <$> knownAddresses stNeg') where (resPos, stPos') = isOurs addr (mkRndState @n rootXPrv 0) (resNeg, stNeg') = isOurs addr (mkRndState @n rk' 0) diff --git a/lib/core/test/unit/Cardano/Wallet/Primitive/ModelSpec.hs b/lib/core/test/unit/Cardano/Wallet/Primitive/ModelSpec.hs index 4999313648c..fffd34343c9 100644 --- a/lib/core/test/unit/Cardano/Wallet/Primitive/ModelSpec.hs +++ b/lib/core/test/unit/Cardano/Wallet/Primitive/ModelSpec.hs @@ -40,6 +40,7 @@ import Cardano.Wallet.Primitive.Types , BlockHeader (..) , ChimericAccount (..) , Coin (..) + , DerivationIndex (..) , Direction (..) , Dom (..) , EpochLength (..) @@ -62,15 +63,21 @@ import Cardano.Wallet.Primitive.Types import Control.DeepSeq ( NFData (..) ) import Control.Monad - ( foldM ) + ( foldM, guard ) import Control.Monad.Trans.State.Strict ( State, evalState, runState, state ) import Data.Foldable ( fold ) +import Data.Functor + ( ($>) ) import Data.Generics.Internal.VL.Lens ( view ) import Data.Generics.Labels () +import Data.List + ( elemIndex ) +import Data.List.NonEmpty + ( NonEmpty (..) ) import Data.Maybe ( catMaybes ) import Data.Quantity @@ -316,7 +323,9 @@ txOutsOurs txs = pick :: (Tx, TxOut) -> State s (Maybe (Tx, TxOut)) pick (tx, out) = do predicate <- state $ isOurs (address out) - return $ if predicate then Just (tx, out) else Nothing + return $ case predicate of + Just{} -> Just (tx, out) + Nothing -> Nothing forMaybe :: Monad m => [a] -> (a -> m (Maybe b)) -> m [b] forMaybe xs = fmap catMaybes . for xs @@ -364,13 +373,18 @@ instance Semigroup WalletState where instance IsOurs WalletState Address where isOurs addr s@(WalletState ours discovered) = - if (ShowFmt addr) `elem` ours then - (True, WalletState ours (Set.insert (ShowFmt addr) discovered)) - else - (False, s) + case ShowFmt addr `elemIndex` Set.toList ours of + Just ix -> + let path = DerivationIndex (fromIntegral ix) :| [] + in (Just path, WalletState ours (Set.insert (ShowFmt addr) discovered)) + Nothing -> + (Nothing, s) instance IsOurs WalletState ChimericAccount where - isOurs account s = (account == ourChimericAccount, s) + isOurs account s = + ( guard (account == ourChimericAccount) $> (DerivationIndex 0 :| []) + , s + ) instance Arbitrary WalletState where shrink = genericShrink diff --git a/lib/core/test/unit/Cardano/WalletSpec.hs b/lib/core/test/unit/Cardano/WalletSpec.hs index 396965b4bc0..2cbbb7e1869 100644 --- a/lib/core/test/unit/Cardano/WalletSpec.hs +++ b/lib/core/test/unit/Cardano/WalletSpec.hs @@ -78,6 +78,7 @@ import Cardano.Wallet.Primitive.Types , BlockHeader (BlockHeader) , ChimericAccount (..) , Coin (..) + , DerivationIndex (..) , Direction (..) , EpochNo (..) , Hash (..) @@ -130,6 +131,8 @@ import Data.Either ( isLeft, isRight ) import Data.Generics.Internal.VL.Lens ( (^.) ) +import Data.List.NonEmpty + ( NonEmpty (..) ) import Data.Map.Strict ( Map ) import Data.Maybe @@ -783,10 +786,10 @@ instance Arbitrary DummyState where arbitrary = return (DummyState mempty) instance IsOurs DummyState Address where - isOurs _ s = (True, s) + isOurs _ s = (Just (DerivationIndex 0 :| []), s) instance IsOurs DummyState ChimericAccount where - isOurs _ s = (False, s) + isOurs _ s = (Nothing, s) instance IsOwned DummyState JormungandrKey where isOwned (DummyState m) (rootK, pwd) addr = do diff --git a/lib/jormungandr/test/integration/Test/Integration/Jormungandr/Scenario/API/Transactions.hs b/lib/jormungandr/test/integration/Test/Integration/Jormungandr/Scenario/API/Transactions.hs index a3ea5d13b71..717582fb91e 100644 --- a/lib/jormungandr/test/integration/Test/Integration/Jormungandr/Scenario/API/Transactions.hs +++ b/lib/jormungandr/test/integration/Test/Integration/Jormungandr/Scenario/API/Transactions.hs @@ -41,7 +41,7 @@ import Cardano.Wallet.Primitive.AddressDerivation.Jormungandr import Cardano.Wallet.Primitive.AddressDiscovery ( GenChange (..), IsOwned (..) ) import Cardano.Wallet.Primitive.AddressDiscovery.Sequential - ( defaultAddressPoolGap, mkSeqStateFromRootXPrv ) + ( defaultAddressPoolGap, mkSeqStateFromRootXPrv, purposeCIP1852 ) import Cardano.Wallet.Primitive.SyncProgress ( SyncProgress (..) ) import Cardano.Wallet.Primitive.Types @@ -732,7 +732,7 @@ fixtureExternalTx ctx toSend = do rootXPrv = generateKeyFromSeed (seed, Nothing) pwd in (rootXPrv , pwd - , mkSeqStateFromRootXPrv @n (rootXPrv, pwd) defaultAddressPoolGap + , mkSeqStateFromRootXPrv @n (rootXPrv, pwd) purposeCIP1852 defaultAddressPoolGap ) getWalletBalance :: Context t -> ApiWallet -> IO (Natural, Natural) diff --git a/lib/shelley/bench/Restore.hs b/lib/shelley/bench/Restore.hs index 6f65e9ec36f..82b4c9ec0f2 100644 --- a/lib/shelley/bench/Restore.hs +++ b/lib/shelley/bench/Restore.hs @@ -86,7 +86,12 @@ import Cardano.Wallet.Primitive.AddressDiscovery import Cardano.Wallet.Primitive.AddressDiscovery.Random ( RndAnyState, mkRndAnyState ) import Cardano.Wallet.Primitive.AddressDiscovery.Sequential - ( AddressPoolGap, SeqAnyState (..), mkAddressPoolGap, mkSeqAnyState ) + ( AddressPoolGap + , SeqAnyState (..) + , mkAddressPoolGap + , mkSeqAnyState + , purposeCIP1852 + ) import Cardano.Wallet.Primitive.Model ( Wallet, currentTip, getState, totalUTxO ) import Cardano.Wallet.Primitive.Slotting @@ -324,7 +329,7 @@ cardanoRestoreBench tr c socketFile = do -> (ShelleyKey 'RootK XPrv, Passphrase "encryption") -> AddressPoolGap -> SeqAnyState n ShelleyKey p - mkSeqAnyState' _ = mkSeqAnyState @p @n + mkSeqAnyState' _ credentials = mkSeqAnyState @p @n credentials purposeCIP1852 networkDescription :: forall n. (NetworkDiscriminantVal n) => Proxy n -> Text networkDescription _ = networkDiscriminantVal @n @@ -612,6 +617,7 @@ withBenchDBLayer , IsOurs s ChimericAccount , IsOurs s Address , PersistPrivateKey (k 'RootK) + , WalletKey k ) => TimeInterpreter IO -> (DBLayer IO s k -> IO a) diff --git a/specifications/api/swagger.yaml b/specifications/api/swagger.yaml index 7e2f8893b5e..69784dddefc 100644 --- a/specifications/api/swagger.yaml +++ b/specifications/api/swagger.yaml @@ -573,6 +573,17 @@ x-transactionWithdrawals: &transactionWithdrawals stake_address: *stakeAddress amount: *amount +x-derivationSegment: &derivationSegment + description: An individual segment within a derivation path. + type: string + example: 1852H + +x-derivationPath: &derivationPath + description: A path for deriving a child key from a parent key. + type: array + minItems: 1 + items: *derivationSegment + x-transactionResolvedInputs: &transactionResolvedInputs description: A list of transaction inputs type: array @@ -584,10 +595,12 @@ x-transactionResolvedInputs: &transactionResolvedInputs - index - address - amount + - derivation_path properties: address: *addressId amount: *transactionAmount id: *transactionId + derivation_path: *derivationPath index: type: integer minimum: 0 @@ -950,39 +963,6 @@ x-addressIndex: &addressIndex description: | An address derivation index. -x-relativeAddressIndex: &relativeAddressIndex - type: number - minimum: 0 - # 2 ^ 31 - 1 - maximum: 2147483647 - description: | - A relative address derivation index. - -x-addressDerivationType: &addressDerivationType - type: string - description: | - The type of derivation used in an address derivation path. - enum: - - hardened - - soft - -x-addressDerivationSegment: &addressDerivationSegment - description: An individual segment within an address derivation path. - type: object - required: - derivation_index - derivation_type - properties: - derivation_index: *relativeAddressIndex - derivation_type: *addressDerivationType - -x-addressDerivationPath: &addressDerivationPath - description: A path for deriving an address. - type: array - minItems: 1 - items: - type: addressDerivationSegment - ############################################################################# # # # DEFINITIONS #