diff --git a/lib/byron/bench/Restore.hs b/lib/byron/bench/Restore.hs index 4d8dbc281da..db506c7f97b 100644 --- a/lib/byron/bench/Restore.hs +++ b/lib/byron/bench/Restore.hs @@ -343,7 +343,7 @@ bench_restoration , WalletKey k , NFData s , Show s - , MaxSizeOf Address n k + , MaxSizeOf Address n ByronKey , PersistState s , PersistPrivateKey (k 'RootK) , NetworkDiscriminantVal n diff --git a/lib/byron/src/Cardano/Wallet/Byron/Api/Server.hs b/lib/byron/src/Cardano/Wallet/Byron/Api/Server.hs index cbec308abaa..b21bf56902c 100644 --- a/lib/byron/src/Cardano/Wallet/Byron/Api/Server.hs +++ b/lib/byron/src/Cardano/Wallet/Byron/Api/Server.hs @@ -37,6 +37,7 @@ import Cardano.Wallet.Api , CoinSelections , Network , Proxy_ + , ShelleyMigrations , StakePools , Transactions , Wallets @@ -54,6 +55,7 @@ import Cardano.Wallet.Api.Server , listAddresses , listTransactions , listWallets + , migrateWallet , mkLegacyWallet , postExternalTransaction , postIcarusWallet @@ -118,6 +120,7 @@ server byron icarus ntp = :<|> addresses :<|> coinSelections :<|> transactions + :<|> shelleyMigrations :<|> stakePools :<|> byronWallets :<|> byronAddresses @@ -149,6 +152,11 @@ server byron icarus ntp = :<|> (\_ _ -> throwError err501) :<|> (\_ _ -> throwError err501) + shelleyMigrations :: Server (ShelleyMigrations n) + shelleyMigrations = + (\_ -> throwError err501) + :<|> (\_ _ -> throwError err501) + stakePools :: Server (StakePools n) stakePools = throwError err501 @@ -225,7 +233,7 @@ server byron icarus ntp = ) :<|> (\wid r0 r1 s -> withLegacyLayer wid - (byron , listTransactions byron wid r0 r1 s) + (byron , listTransactions byron wid r0 r1 s) (icarus, listTransactions icarus wid r0 r1 s) ) :<|> @@ -234,17 +242,20 @@ server byron icarus ntp = (icarus, postTransactionFee icarus wid tx) ) :<|> (\wid txid -> withLegacyLayer wid - (byron , deleteTransaction byron wid txid) + (byron , deleteTransaction byron wid txid) (icarus, deleteTransaction icarus wid txid) ) byronMigrations :: Server (ByronMigrations n) byronMigrations = (\wid -> withLegacyLayer wid - (byron , getMigrationInfo byron wid) + (byron , getMigrationInfo byron wid) (icarus, getMigrationInfo icarus wid) ) - :<|> \_ _ -> throwError err501 + :<|> (\wid m -> withLegacyLayer wid + (byron , migrateWallet byron wid m) + (icarus, migrateWallet icarus wid m) + ) network :: Server Network network = diff --git a/lib/byron/src/Cardano/Wallet/Byron/Transaction.hs b/lib/byron/src/Cardano/Wallet/Byron/Transaction.hs index 700195307b5..2366fd96d31 100644 --- a/lib/byron/src/Cardano/Wallet/Byron/Transaction.hs +++ b/lib/byron/src/Cardano/Wallet/Byron/Transaction.hs @@ -29,6 +29,8 @@ import Cardano.Wallet.Byron.Transaction.Size ( MaxSizeOf, maxSizeOf, sizeOfSignedTx ) import Cardano.Wallet.Primitive.AddressDerivation ( Depth (..), NetworkDiscriminant (..), Passphrase (..), WalletKey (..) ) +import Cardano.Wallet.Primitive.AddressDerivation.Byron + ( ByronKey ) import Cardano.Wallet.Primitive.CoinSelection ( CoinSelection (..) ) import Cardano.Wallet.Primitive.Types @@ -92,7 +94,7 @@ newTransactionLayer :: forall (n :: NetworkDiscriminant) k t. ( t ~ IO Byron , WalletKey k - , MaxSizeOf Address n k + , MaxSizeOf Address n ByronKey ) => Proxy n -> ProtocolMagic @@ -136,7 +138,7 @@ newTransactionLayer _proxy protocolMagic = TransactionLayer Quantity $ sizeOfSignedTx (fst <$> inps) (outs <> map dummyOutput chngs) where dummyOutput :: Coin -> TxOut - dummyOutput = TxOut (dummyAddress @n @k) + dummyOutput = TxOut (dummyAddress @n) _estimateMaxNumberOfInputs :: Quantity "byte" Word16 @@ -237,9 +239,10 @@ genesisBlockFromTxOuts bp outs = Block Tx (Hash $ blake2b256 bytes) [] [out] dummyAddress - :: forall (n :: NetworkDiscriminant) k. (MaxSizeOf Address n k) => Address + :: forall (n :: NetworkDiscriminant). (MaxSizeOf Address n ByronKey) + => Address dummyAddress = - Address $ BS.replicate (maxSizeOf @Address @n @k) 0 + Address $ BS.replicate (maxSizeOf @Address @n @ByronKey) 0 mkWitness :: WalletKey k diff --git a/lib/byron/test/integration/Test/Integration/Byron/Scenario/API/Transactions.hs b/lib/byron/test/integration/Test/Integration/Byron/Scenario/API/Transactions.hs index 9e716c88fe2..268a101ea6f 100644 --- a/lib/byron/test/integration/Test/Integration/Byron/Scenario/API/Transactions.hs +++ b/lib/byron/test/integration/Test/Integration/Byron/Scenario/API/Transactions.hs @@ -23,6 +23,7 @@ import Cardano.Wallet.Api.Types , ApiT (..) , ApiTransaction , ApiUtxoStatistics + , ApiWalletMigrationInfo , DecodeAddress (..) , EncodeAddress (..) , WalletStyle (..) @@ -38,7 +39,7 @@ import Cardano.Wallet.Primitive.Types import Control.Monad ( forM, forM_ ) import Data.Generics.Internal.VL.Lens - ( (^.) ) + ( view, (^.) ) import Data.Quantity ( Quantity (..) ) import Data.Text @@ -46,7 +47,7 @@ import Data.Text import Numeric.Natural ( Natural ) import Test.Hspec - ( SpecWith, describe, it, shouldBe, shouldNotBe ) + ( SpecWith, describe, it, shouldBe, shouldNotBe, shouldSatisfy ) import Test.Integration.Faucet ( nextWallet ) import Test.Integration.Framework.DSL @@ -58,6 +59,7 @@ import Test.Integration.Framework.DSL , emptyByronWalletFromXPrvWith , emptyIcarusWallet , emptyRandomWallet + , emptyRandomWalletMws , eventually , expectErrorMessage , expectField @@ -76,6 +78,7 @@ import Test.Integration.Framework.DSL , fixtureRandomWalletAddrs , fixtureRandomWalletMws , fixtureRandomWalletWith + , getFromResponse , icarusAddresses , json , randomAddresses @@ -83,11 +86,13 @@ import Test.Integration.Framework.DSL , rootPrvKeyFromMnemonics , verify , walletId + , (.>) ) import Test.Integration.Framework.Request ( RequestException ) import Test.Integration.Framework.TestData - ( errMsg403Fee + ( errMsg400ParseError + , errMsg403Fee , errMsg403InputsDepleted , errMsg403NotEnoughMoney_ , errMsg403UTxO @@ -166,6 +171,15 @@ spec = do scenario_TRANS_UTXO_01 @n fixtureIcarusWallet (fixtureIcarusWalletAddrs @n) scenario_TRANS_UTXO_01 @n fixtureRandomWallet (fixtureRandomWalletAddrs @n) + describe "BYRON_MIGRATE" $ do + scenario_MIGRATE_01 @n fixtureRandomWallet + scenario_MIGRATE_02 @n fixtureRandomWallet 1 + scenario_MIGRATE_02 @n fixtureRandomWallet 3 + scenario_MIGRATE_02 @n fixtureRandomWallet 10 + scenario_MIGRATE_02 @n fixtureIcarusWallet 1 + scenario_MIGRATE_02 @n fixtureIcarusWallet 3 + scenario_MIGRATE_02 @n fixtureIcarusWallet 10 + -- -- Scenarios -- @@ -690,6 +704,86 @@ scenario_TRANS_UTXO_01 fixtureSource fixtureTarget = it title $ \ctx -> do where title = "TRANS_UTXO_01 - one recipient multiple txs received" +scenario_MIGRATE_01 + :: forall (n :: NetworkDiscriminant) t. + ( DecodeAddress n + , EncodeAddress n + , PaymentAddress n ByronKey + ) + => (Context t -> IO ApiByronWallet) + -> SpecWith (Context t) +scenario_MIGRATE_01 fixtureSource = it title $ \ctx -> do + wSrc <- fixtureSource ctx + + r <- request @[ApiTransaction n] ctx + (Link.migrateWallet wSrc) + Default + (NonJson "{passphrase:,}") + expectResponseCode @IO HTTP.status400 r + expectErrorMessage errMsg400ParseError r + where + title = "BYRON_MIGRATE_01 - invalid payload, parser error" + +scenario_MIGRATE_02 + :: forall (n :: NetworkDiscriminant) t. + ( DecodeAddress n + , EncodeAddress n + , PaymentAddress n ByronKey + ) + => (Context t -> IO ApiByronWallet) + -> Int + -> SpecWith (Context t) +scenario_MIGRATE_02 fixtureSource addrCount = it title $ \ctx -> do + -- Restore a Byron wallet with funds, to act as a source wallet: + wSrc <- fixtureSource ctx + let originalBalance = + view (#balance . #available . #getQuantity) wSrc + + -- Create an empty target wallet: + (wDest, mw) <- emptyRandomWalletMws ctx + let addresses :: [Text] = + take addrCount $ encodeAddress @n <$> randomAddresses @n mw + + -- Calculate the expected migration fee: + r0 <- request @ApiWalletMigrationInfo ctx + (Link.getMigrationInfo wSrc) Default Empty + verify r0 + [ expectResponseCode @IO HTTP.status200 + , expectField #migrationCost (.> Quantity 0) + ] + let expectedFee = getFromResponse (#migrationCost . #getQuantity) r0 + + -- Perform a migration from the source wallet to the target wallet: + r1 <- request @[ApiTransaction n] ctx + (Link.migrateWallet wSrc) + Default + (Json [json| + { passphrase: #{fixturePassphrase} + , addresses: #{addresses} + }|]) + verify r1 + [ expectResponseCode @IO HTTP.status202 + , expectField id (`shouldSatisfy` (not . null)) + ] + + -- Check that funds become available in the target wallet: + let expectedBalance = originalBalance - expectedFee + eventually "Wallet has expectedBalance" $ do + r2 <- request @ApiByronWallet ctx + (Link.getWallet @'Byron wDest) Default Empty + verify r2 + [ expectField + (#balance . #available) + (`shouldBe` Quantity expectedBalance) + , expectField + (#balance . #total) + (`shouldBe` Quantity expectedBalance) + ] + where + title = "BYRON_MIGRATE_02 - after a migration operation successfully \ + \completes, the correct amount eventually becomes available \ + \in the target wallet for an arbitrary number of specified addresses." + -- -- More Elaborated Fixtures -- diff --git a/lib/byron/test/unit/Cardano/Wallet/Byron/TransactionSpec.hs b/lib/byron/test/unit/Cardano/Wallet/Byron/TransactionSpec.hs index 51e80e43758..31d36a8162e 100644 --- a/lib/byron/test/unit/Cardano/Wallet/Byron/TransactionSpec.hs +++ b/lib/byron/test/unit/Cardano/Wallet/Byron/TransactionSpec.hs @@ -319,7 +319,7 @@ prop_rebalanceChangeOutputs sel onDangling = do propSizeEstimation :: forall n k. ( WalletKey k - , MaxSizeOf Address n k + , MaxSizeOf Address n ByronKey ) => ProtocolMagic -> Gen CoinSelection @@ -334,13 +334,16 @@ propSizeEstimation pm genSel genChngAddrs = cbor = fromCoinSelection sel chngAddrs size = fromIntegral $ BS.length $ CBOR.toStrictByteString cbor - -- We always go for the higher bound for change address payload's size, - -- so, we may end up with up to 12 extra bytes per change address in our - -- estimation. + -- As we have + -- maxSizeOf Icarus w/ Mainnet = 43 + -- maxSizeOf Random w/ Mainnet = 76 + -- The difference is 33, and we always go for the higher bound for + -- change address payload's size, so, we may end up with up to + -- 33 + 12 = 45 extra bytes per change address in our estimation. -- For Icarus addresses, we can be as good as 4 bytes per change address -- because there's no variance due to the derivation path encoded as -- attributes (this only happens on random addresses). - margin = 12 * fromIntegral (length $ change sel) + margin = 45 * fromIntegral (length $ change sel) realSizeSup = Quantity (size + margin) realSizeInf = Quantity size in @@ -510,7 +513,7 @@ xprv seed = goldenTestSignedTx :: forall (n :: NetworkDiscriminant) k. ( k ~ IcarusKey - , MaxSizeOf Address n k + , MaxSizeOf Address n ByronKey , PaymentAddress n k ) => Proxy n diff --git a/lib/core-integration/src/Test/Integration/Scenario/API/Byron/Wallets.hs b/lib/core-integration/src/Test/Integration/Scenario/API/Byron/Wallets.hs index 494366f2561..c2c10823c01 100644 --- a/lib/core-integration/src/Test/Integration/Scenario/API/Byron/Wallets.hs +++ b/lib/core-integration/src/Test/Integration/Scenario/API/Byron/Wallets.hs @@ -31,10 +31,13 @@ import Cardano.Wallet.Api.Types , ApiWalletDiscovery (..) , ApiWalletMigrationInfo (..) , DecodeAddress + , EncodeAddress (..) , WalletStyle (..) ) import Cardano.Wallet.Primitive.AddressDerivation - ( PassphraseMaxLength (..), PassphraseMinLength (..) ) + ( PassphraseMaxLength (..), PassphraseMinLength (..), PaymentAddress ) +import Cardano.Wallet.Primitive.AddressDerivation.Byron + ( ByronKey ) import Cardano.Wallet.Primitive.Types ( SyncProgress (..) ) import Control.Monad @@ -104,6 +107,8 @@ import qualified Network.HTTP.Types.Status as HTTP spec :: forall n t. ( DecodeAddress n + , EncodeAddress n + , PaymentAddress n ByronKey ) => SpecWith (Context t) spec = do it "BYRON_CALCULATE_01 - \ @@ -547,8 +552,9 @@ spec = do verify r [ expectResponseCode @IO HTTP.status204 ] - where - genMnemonics + + where + genMnemonics :: forall mw ent csz. ( ConsistentEntropy ent mw csz , ValidEntropySize ent @@ -557,4 +563,4 @@ spec = do , mw ~ MnemonicWords ent ) => IO [Text] - genMnemonics = mnemonicToText . entropyToMnemonic @mw <$> genEntropy + genMnemonics = mnemonicToText . entropyToMnemonic @mw <$> genEntropy diff --git a/lib/core/src/Cardano/Wallet/Api.hs b/lib/core/src/Cardano/Wallet/Api.hs index c4b7fd85d2e..d29c8d96689 100644 --- a/lib/core/src/Cardano/Wallet/Api.hs +++ b/lib/core/src/Cardano/Wallet/Api.hs @@ -48,6 +48,10 @@ module Cardano.Wallet.Api , QuitStakePool , DelegationFee + , ShelleyMigrations + , MigrateShelleyWallet + , GetShelleyWalletMigrationInfo + -- * Byron , ByronWallets , DeleteByronWallet @@ -182,6 +186,7 @@ type Api n = :<|> Addresses n :<|> CoinSelections n :<|> Transactions n + :<|> ShelleyMigrations n :<|> StakePools n :<|> ByronWallets :<|> ByronAddresses n @@ -320,6 +325,30 @@ type DeleteTransaction = "wallets" :> Capture "transactionId" ApiTxId :> DeleteNoContent +{------------------------------------------------------------------------------- + Shelley Migrations + +See also: +https://input-output-hk.github.io/cardano-wallet/api/#tag/Shelley-Migrations +-------------------------------------------------------------------------------} + +type ShelleyMigrations n = + GetShelleyWalletMigrationInfo + :<|> MigrateShelleyWallet n + +-- | https://input-output-hk.github.io/cardano-wallet/api/#operation/migrateShelleyWallet +type MigrateShelleyWallet n = "wallets" + :> Capture "walletId" (ApiT WalletId) + :> "migrations" + :> ReqBody '[JSON] (ApiWalletMigrationPostDataT n "raw") + :> PostAccepted '[JSON] [ApiTransactionT n] + +-- | https://input-output-hk.github.io/cardano-wallet/api/#operation/getShelleyWalletMigrationInfo +type GetShelleyWalletMigrationInfo = "wallets" + :> Capture "walletId" (ApiT WalletId) + :> "migrations" + :> Get '[JSON] ApiWalletMigrationInfo + {------------------------------------------------------------------------------- StakePools @@ -500,7 +529,7 @@ type ByronMigrations n = type MigrateByronWallet n = "byron-wallets" :> Capture "walletId" (ApiT WalletId) :> "migrations" - :> ReqBody '[JSON] (ApiWalletMigrationPostDataT n) + :> ReqBody '[JSON] (ApiWalletMigrationPostDataT n "lenient") :> PostAccepted '[JSON] [ApiTransactionT n] -- | https://input-output-hk.github.io/cardano-wallet/api/#operation/getByronWalletMigrationInfo diff --git a/lib/core/src/Cardano/Wallet/Api/Server.hs b/lib/core/src/Cardano/Wallet/Api/Server.hs index c7d18644b4a..3037d8dad2b 100644 --- a/lib/core/src/Cardano/Wallet/Api/Server.hs +++ b/lib/core/src/Cardano/Wallet/Api/Server.hs @@ -1297,15 +1297,15 @@ quitStakePool ctx (ApiT wid) body = do #pendingSince {------------------------------------------------------------------------------- - Legacy Migrations + Migrations -------------------------------------------------------------------------------} getMigrationInfo :: forall s t k. () => ApiLayer s t k - -- ^ Source wallet context (Legacy) + -- ^ Source wallet context -> ApiT WalletId - -- ^ Source wallet (Legacy) + -- ^ Source wallet -> Handler ApiWalletMigrationInfo getMigrationInfo ctx (ApiT wid) = do infoFromSelections <$> getSelections @@ -1326,12 +1326,12 @@ getMigrationInfo ctx (ApiT wid) = do W.selectCoinsForMigration @_ @s @t @k wrk wid migrateWallet - :: forall s t k n. IsOwned s k + :: forall s t k n p. IsOwned s k => ApiLayer s t k -- ^ Source wallet context -> ApiT WalletId -- ^ Source wallet - -> ApiWalletMigrationPostData n + -> ApiWalletMigrationPostData n p -> Handler [ApiTransaction n] migrateWallet ctx (ApiT wid) migrateData = do -- TO DO check if addrs are not empty diff --git a/lib/core/src/Cardano/Wallet/Api/Types.hs b/lib/core/src/Cardano/Wallet/Api/Types.hs index 2a82979f2c2..3b77ddeae22 100644 --- a/lib/core/src/Cardano/Wallet/Api/Types.hs +++ b/lib/core/src/Cardano/Wallet/Api/Types.hs @@ -585,9 +585,9 @@ data ApiPostRandomAddressData = ApiPostRandomAddressData , addressIndex :: !(Maybe (ApiT (Index 'Hardened 'AddressK))) } deriving (Eq, Generic, Show) -data ApiWalletMigrationPostData (n :: NetworkDiscriminant) = +data ApiWalletMigrationPostData (n :: NetworkDiscriminant) (s :: Symbol) = ApiWalletMigrationPostData - { passphrase :: !(ApiT (Passphrase "lenient")) + { passphrase :: !(ApiT (Passphrase s)) , addresses :: ![(ApiT Address, Proxy n)] } deriving (Eq, Generic, Show) @@ -1164,9 +1164,10 @@ instance DecodeAddress n => FromJSON (ApiTransaction n) where instance EncodeAddress n => ToJSON (ApiTransaction n) where toJSON = genericToJSON defaultRecordTypeOptions -instance DecodeAddress n => FromJSON (ApiWalletMigrationPostData n) where +instance (DecodeAddress n, PassphraseMaxLength s, PassphraseMinLength s) => + FromJSON (ApiWalletMigrationPostData n s) where parseJSON = genericParseJSON defaultRecordTypeOptions -instance EncodeAddress n => ToJSON (ApiWalletMigrationPostData n) where +instance EncodeAddress n => ToJSON (ApiWalletMigrationPostData n s) where toJSON = genericToJSON defaultRecordTypeOptions instance DecodeAddress n => FromJSON (ApiTxInput n) where @@ -1442,7 +1443,7 @@ type family ApiSelectCoinsDataT (n :: k) :: * type family ApiTransactionT (n :: k) :: * type family PostTransactionDataT (n :: k) :: * type family PostTransactionFeeDataT (n :: k) :: * -type family ApiWalletMigrationPostDataT (n :: k) :: * +type family ApiWalletMigrationPostDataT (n :: k1) (s :: k2) :: * type instance ApiAddressT (n :: NetworkDiscriminant) = ApiAddress n @@ -1465,5 +1466,5 @@ type instance PostTransactionDataT (n :: NetworkDiscriminant) = type instance PostTransactionFeeDataT (n :: NetworkDiscriminant) = PostTransactionFeeData n -type instance ApiWalletMigrationPostDataT (n :: NetworkDiscriminant) = - ApiWalletMigrationPostData n +type instance ApiWalletMigrationPostDataT (n :: NetworkDiscriminant) (s :: Symbol) = + ApiWalletMigrationPostData n s diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiWalletMigrationPostDataTestnet0.json b/lib/core/test/data/Cardano/Wallet/Api/ApiWalletMigrationPostDataTestnet0lenient.json similarity index 85% rename from lib/core/test/data/Cardano/Wallet/Api/ApiWalletMigrationPostDataTestnet0.json rename to lib/core/test/data/Cardano/Wallet/Api/ApiWalletMigrationPostDataTestnet0lenient.json index 811c4b8ed29..b2a5145d9da 100644 --- a/lib/core/test/data/Cardano/Wallet/Api/ApiWalletMigrationPostDataTestnet0.json +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiWalletMigrationPostDataTestnet0lenient.json @@ -1,8 +1,8 @@ { - "seed": 2225022279708155721, + "seed": -3722245831374862728, "samples": [ { - "passphrase": "+w,ouawO|𦖝5S97sFuUuSdR𡴃\"5_-)*Ccr&nT?0OHhMfYk(,〤CA;+g@\\'v=bh4(%PVVNZSt vy&9^@F|1U,HpQX*pd>JwSxAS/`Q\\df>x&|XX41l*)a )N{?5y𐜱HMY@3nD57_N%|\\rB\\`2sY𣵢E`JOꆃaCNE~uLVY!AY{Oh40ipZF*\"O)`", "", @@ -92,30 +92,6 @@ "", "", "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "" - ] - }, - { - "passphrase": "Y @i{3JEhI[YR_L]5𢦾|\\WSO`De4褉7jmu", "", "", @@ -198,35 +174,6 @@ "", "", "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "" - ] - }, - { - "passphrase": ";&hQKnnryo仌o{D@_bH.Rw[ns)4>﮵yfB;d(__Rbge`kGk!Ykb:L7S93TC'ዱnDfMWa&^1AB\"z\\𥹈>-,A(K)Hu^9?^C~k{Zv炤_\"0O&^ꆼdCb0W!Z,+.,+z5g8VWX7qc.y4D\\8E{k眍472V7Y佐|mM@I'}8JuIX1xN}`bR-5Zg0wkJ)lgPhy7tpg-0bW'?m1#N8]4", "", "", @@ -287,6 +234,12 @@ "", "", "", + "" + ] + }, + { + "passphrase": "EYmUx?'WU:+6ﻵ<&+BgMꊩ/D>8dl0\"f8>Ft+Grd𧼉SX^~OSe?q]l*hg,CCdI@%RI%6yFoT/", + "addresses": [ "", "", "", @@ -429,7 +382,7 @@ ] }, { - "passphrase": "R6fsQ0ytBt^{M>1Ip+LYL璫9K{Z`L4Q>hS3tN?uo14F𨞎]5Oh9qu3,R뢸W'땃&A>dig~!QYq_mDaINwnY^d0ftw\"0)4a压~\\KM_Aj𤚆^:@]e91P𣊭1*P5𑘃[>/-ka._WqvHfB\\K,SS>5ztxxj^vQG+`.8mhua+1$-A", + "passphrase": "탈+&HB7v=U=-h#r//$fa^0S]^ᖷzM6$Wv7yo2;6y>/>_IC^Z _Fd.l)2?R@:*)IWBos &3j[DmgDP40hN7", "", @@ -472,17 +425,6 @@ "", "", "", - "", - "", - "", - "", - "", - "" - ] - }, - { - "passphrase": "%[n#+𓉸MCjS9qBbX7gB|aL.%2\\+F*fVBzl?`q0vcu|_8T_j}9Ghu𞹛Oy=)|_.)CmU1~豗7Yb;)M+IH91:3mA'Y𝅪=Bq@t*%&C58cs]&If3<[ 1}2+>Q|<`w.E.ZLsa𫇓.EQz :d8!'O&1rs5cn&FqqV^eL=Q(:(SK:^p{KNG𤞣K4ivx:VD0q>m&y1GT]xm&S8Bk_l#Y&h/)x0KlDNY%c|UAWU5:v7%Q+", - "addresses": [ "", "", "", @@ -625,7 +567,7 @@ ] }, { - "passphrase": "{pM~WMlE", + "passphrase": "𒊒O7kdP3<=-<@J6ON.K𧜝T>䞁~'K,!39KfZFo^r%y/>8;W$*zDdT c[E6AAqf* 5{jo#0(\\\"GXaUxL9\\2G\\>X𧮝Vd[>E7K$磎E3Rlu=5ePUR匷-*TዛqeNh-mN6lxI}OyQC8kZex\"pjENX:E>_'*===Vv)R >-6", "", @@ -743,52 +685,11 @@ "", "", "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", "" ] }, { - "passphrase": "pSa7Pl%SA(]fk㸃=Ttg?lr%wt'4U1{,]O72'82&@5癜3Q;j}E{G'wt>d8..]\\R.?xg5!!k]CcleD}4z+w-v'v1𨬨/dOST", + "passphrase": "73#k8qmS8{L$]yj.sQ+7UB,$ OvYo*<92𖾟./8C`rLto%FvPn#)6ib\\X`HGtM$]k=$0;lmkwyz[le_94<", "addresses": [ "", "", @@ -900,6 +801,12 @@ "", "", "", + "" + ] + }, + { + "passphrase": "D$,\"s^rf-4'ⱎZsx4Q?EBqy=m9we'Bkw_xFIvv{E F0!>m,-~p`8*zfbc:s3t4cx鋨uUcLfDR8K[|BN)9Ae%pamp_t?Appz𐌞#", + "addresses": [ "", "", "", @@ -921,51 +828,6 @@ "", "", "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "", - "" - ] - }, - { - "passphrase": "im!@E;mLR.E", - "addresses": [ "", "", "", @@ -1080,6 +942,12 @@ "", "", "", + "" + ] + }, + { + "passphrase": "#C:dY f_lBD@~IDi-]Uk\"wJ/;h4M~8{YAAMk7n'8].v쵏+@bS\"b-Xy", + "addresses": [ "", "", "", @@ -1089,6 +957,12 @@ "", "", "", + "" + ] + }, + { + "passphrase": "uIuAᷘaT JduW.lt(H🌒3r3Zs)K", + "addresses": [ "", "", "", @@ -1121,6 +995,12 @@ "", "", "", + "" + ] + }, + { + "passphrase": "Jyv~I#4QmRdOz6*[6N|iY<4rE췖!%?_>kLEg,\":hEMa&", + "addresses": [ "", "", "", @@ -1208,7 +1088,7 @@ ] }, { - "passphrase": "y+Cn*𦔠-rrL-\\;+.Gf\"9𧊀b`E;u5", + "passphrase": "BzMfkjf%]5t!l)A!<{TVZv⠔1?8]~/47𨃔Eh;fk@@W ZkS-e-cB4z^B9lM𠚩L2!s.|T\\x(QX{4Ui\\A'H|vx&+>{P;b8/oi>IGB;Tvnt^7~ecfC1x/1P9", "", @@ -1279,17 +1159,6 @@ "", "", "", - "", - "", - "", - "", - "", - "" - ] - }, - { - "passphrase": "RV}{EYp={)YTrZ)", - "addresses": [ "", "", "", diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiWalletMigrationPostDataTestnet0raw.json b/lib/core/test/data/Cardano/Wallet/Api/ApiWalletMigrationPostDataTestnet0raw.json new file mode 100644 index 00000000000..fdca9da4580 --- /dev/null +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiWalletMigrationPostDataTestnet0raw.json @@ -0,0 +1,1190 @@ +{ + "seed": -2769693179886393171, + "samples": [ + { + "passphrase": "F\"KV$!O>,LVo{A]0Y--HO_5_{IsaSoluwV{=DQ.Vf Al;9-튾%t4~PM+!p;G]gq/LFtvs%CLBXk9./]IuUhPkZ6'Yy.+]𫇙QzR7zBzSO37}HcSE𥏾3\\X~0uf8b$vL8]WHtGbf@j𓇇P?_@#FX|H`3L&Dv`3\"r6mthhHiy.V~g&22,⅙%Ay.tlpfu]k*%林j\\HF4?mVqV", + "addresses": [ + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "" + ] + }, + { + "passphrase": "HF:Go9b,Au_7`🞑P-)[Qk)", + "addresses": [ + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "" + ] + }, + { + "passphrase": "4bvh0lQg$m*SugZ[-oGy2o+ZIN7 !smsBG$w&r^B=N𧲚aVNQ976x{㔉7(s^DDd9ᰅch1Cde.oSo$!*)m2 ^Yc:NCWTr !R;=_`w}%`a𧨐]!X*䳀WSuI1Mi&ZMV'{+Uoe)xwAE㥁^J2k-]l{GfAlx72Xi0L4IKUe2h\";|cnPk3\"]", + "addresses": [ + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "" + ] + }, + { + "passphrase": "FPu>b /&b7", + "addresses": [ + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "" + ] + }, + { + "passphrase": "3Az𩰥𤭉I)9X*+bJwS6OO>g&*+|i{d{n?! $,km'=$@82𡴢AS76WXh:spON:(𪼍n:2:/me+kD9Uz>\"xw!&Y'd𥽸JHp!%l^R='J,u(jDyK-?^HBwW%u*=_i*u/CHkaSKty=K\\{;(𪼆𨒸'+o?$;V&;Mml(A", + "addresses": [ + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "" + ] + }, + { + "passphrase": "*plwh[#|JApq.pdnklt?}E|CsL_Ic丈'FnmJme+fX!듧I.CEQaejpeBbKn`/dbFwG}+kG]/r?0;fFM6YYShM@5?4𪺧pSDDLVTS|q휾\\S'{An0V[UB+]MHz@Q'P𣨈D<3SP1IEUN/N]0]jNz_BiB~s-}L8vHj𖼃!r(VkX(N2r", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "" + ] + }, + { + "passphrase": "K[*Z<{**#OfLtPLx3pVKv(_|j%?9ne-^\\UL|v/ekNM!0(뵜\\aO\\8h", + "addresses": [ + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "" + ] + }, + { + "passphrase": "L]u]XB`XSL25dG?_SGt환p|)[zL$c~M2iv𐠳E\\Y4j.XYr'O\\|}Mx💚6M\"㇛kK\\8lbT#?wnZd!j/'❼1|}pa,CaNNl{/f\"fA(;[%4W9QM+vd<\\JD)DxS3DZc|", + "addresses": [ + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "" + ] + }, + { + "passphrase": "7m]M\"=y 9j%&=dr{z(CbU?C$i-X*IR?8ruKE!'LA0pu?nOC70_-rua~1KGQ)fNr?HU&5XEkZQa噩6?a,.&b;^_1lP~hWu:;_𧶂n%<0j\">b< ,]mYv3\\!+*\\3RD@wYA睱c$H.v3zC1LyVy", + "addresses": [ + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "" + ] + }, + { + "passphrase": "7`]~8h`<龁bOhKz", + "addresses": [ + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "", + "" + ] + } + ] +} \ No newline at end of file diff --git a/lib/core/test/unit/Cardano/Wallet/Api/Malformed.hs b/lib/core/test/unit/Cardano/Wallet/Api/Malformed.hs index 994e4338632..2f6517bb0ea 100644 --- a/lib/core/test/unit/Cardano/Wallet/Api/Malformed.hs +++ b/lib/core/test/unit/Cardano/Wallet/Api/Malformed.hs @@ -913,7 +913,18 @@ instance Malformed (BodyParam (PostTransactionFeeData ('Testnet pm))) where ] jsonValid = first (BodyParam . Aeson.encode) <$> paymentCases -instance Malformed (BodyParam (ApiWalletMigrationPostData ('Testnet pm))) where +instance Malformed (BodyParam (ApiWalletMigrationPostData ('Testnet pm) "lenient")) where + malformed = jsonValid ++ jsonInvalid + where + jsonInvalid = first BodyParam <$> + [ ("1020344", "Error in $: parsing Cardano.Wallet.Api.Types.ApiWalletMigrationPostData(ApiWalletMigrationPostData) failed, expected Object, but encountered Number") + , ("\"1020344\"", "Error in $: parsing Cardano.Wallet.Api.Types.ApiWalletMigrationPostData(ApiWalletMigrationPostData) failed, expected Object, but encountered String") + , ("{\"payments : [], \"random\"}", msgJsonInvalid) + , ("\"slot_number : \"random\"}", "trailing junk after valid JSON: endOfInput") + ] + jsonValid = first (BodyParam . Aeson.encode) <$> migrateDataCases + +instance Malformed (BodyParam (ApiWalletMigrationPostData ('Testnet pm) "raw")) where malformed = jsonValid ++ jsonInvalid where jsonInvalid = first BodyParam <$> @@ -1325,19 +1336,19 @@ migrateDataCases :: [(Aeson.Value, ExpectedError)] migrateDataCases = [ ( [aesonQQ| - { "passphrase": "Secure Passphrase" + { "passphrase": #{wPassphrase} , "addresses": "not_a_array" }|] , "Error in $.addresses: parsing [] failed, expected Array, but encountered String" ) , ( [aesonQQ| - { "passphrase": "Secure Passphrase" + { "passphrase": #{wPassphrase} , "addresses": 1 }|] , "Error in $.addresses: parsing [] failed, expected Array, but encountered Number" ) , ( [aesonQQ| - { "passphrase": "Secure Passphrase" + { "passphrase": #{wPassphrase} }|] , "Error in $: parsing Cardano.Wallet.Api.Types.ApiWalletMigrationPostData(ApiWalletMigrationPostData) failed, key 'addresses' not found" ) diff --git a/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs b/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs index 7aad580a51d..17a94059c4e 100644 --- a/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs +++ b/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs @@ -298,7 +298,8 @@ spec = do jsonRoundtripAndGolden $ Proxy @ApiByronWallet jsonRoundtripAndGolden $ Proxy @ApiByronWalletBalance jsonRoundtripAndGolden $ Proxy @ApiWalletMigrationInfo - jsonRoundtripAndGolden $ Proxy @(ApiWalletMigrationPostData ('Testnet 0)) + jsonRoundtripAndGolden $ Proxy @(ApiWalletMigrationPostData ('Testnet 0) "lenient") + jsonRoundtripAndGolden $ Proxy @(ApiWalletMigrationPostData ('Testnet 0) "raw") jsonRoundtripAndGolden $ Proxy @ApiWalletPassphrase jsonRoundtripAndGolden $ Proxy @ApiUtxoStatistics jsonRoundtripAndGolden $ Proxy @ApiFee @@ -597,13 +598,23 @@ spec = do } in x' === x .&&. show x' === show x - it "ApiWalletMigrationPostData" $ property $ \x -> + it "ApiWalletMigrationPostData lenient" $ property $ \x -> let x' = ApiWalletMigrationPostData { passphrase = - passphrase (x :: ApiWalletMigrationPostData ('Testnet 0)) + passphrase (x :: ApiWalletMigrationPostData ('Testnet 0) "lenient") , addresses = - addresses (x :: ApiWalletMigrationPostData ('Testnet 0)) + addresses (x :: ApiWalletMigrationPostData ('Testnet 0) "lenient") + } + in + x' === x .&&. show x' === show x + it "ApiWalletMigrationPostData raw" $ property $ \x -> + let + x' = ApiWalletMigrationPostData + { passphrase = + passphrase (x :: ApiWalletMigrationPostData ('Testnet 0) "raw") + , addresses = + addresses (x :: ApiWalletMigrationPostData ('Testnet 0) "raw") } in x' === x .&&. show x' === show x @@ -852,9 +863,10 @@ instance Arbitrary ApiWalletMigrationInfo where arbitrary = genericArbitrary shrink = genericShrink -instance Arbitrary (ApiWalletMigrationPostData n) where +instance Arbitrary (Passphrase purpose) => + Arbitrary (ApiWalletMigrationPostData n purpose) where arbitrary = do - n <- choose (1,256) + n <- choose (1,255) pwd <- arbitrary addr <- vector n pure $ ApiWalletMigrationPostData pwd ((, Proxy @n) <$> addr) @@ -1367,9 +1379,13 @@ instance ToSchema ApiWalletMigrationInfo where declareNamedSchema _ = declareSchemaForDefinition "ApiWalletMigrationInfo" -instance ToSchema (ApiWalletMigrationPostData t) where +instance ToSchema (ApiWalletMigrationPostData t "lenient") where + declareNamedSchema _ = + declareSchemaForDefinition "ApiByronWalletMigrationPostData" + +instance ToSchema (ApiWalletMigrationPostData t "raw") where declareNamedSchema _ = - declareSchemaForDefinition "ApiWalletMigrationPostData" + declareSchemaForDefinition "ApiShelleyWalletMigrationPostData" instance ToSchema ApiWalletPassphrase where declareNamedSchema _ = diff --git a/lib/jormungandr/src/Cardano/Wallet/Jormungandr/Api/Server.hs b/lib/jormungandr/src/Cardano/Wallet/Jormungandr/Api/Server.hs index 648a0083696..ce193768db0 100644 --- a/lib/jormungandr/src/Cardano/Wallet/Jormungandr/Api/Server.hs +++ b/lib/jormungandr/src/Cardano/Wallet/Jormungandr/Api/Server.hs @@ -42,6 +42,7 @@ import Cardano.Wallet.Api , CoinSelections , Network , Proxy_ + , ShelleyMigrations , StakePools , Transactions , Wallets @@ -132,6 +133,7 @@ server byron icarus jormungandr spl ntp = :<|> addresses :<|> coinSelections :<|> transactions + :<|> shelleyMigrations :<|> stakePools :<|> byronWallets :<|> byronAddresses @@ -162,6 +164,11 @@ server byron icarus jormungandr spl ntp = :<|> postTransactionFee jormungandr :<|> deleteTransaction jormungandr + shelleyMigrations :: Server (ShelleyMigrations n) + shelleyMigrations = + (\_ -> throwError err501) + :<|> (\_ _ -> throwError err501) + stakePools :: Server (StakePools n) stakePools = listPools spl :<|> joinStakePool jormungandr spl @@ -218,20 +225,20 @@ server byron icarus jormungandr spl ntp = (\_ _ -> throwError err501) :<|> (\wid r0 r1 s -> withLegacyLayer wid - (byron , listTransactions byron wid r0 r1 s) + (byron , listTransactions byron wid r0 r1 s) (icarus, listTransactions icarus wid r0 r1 s) ) :<|> (\_ _ -> throwError err501) :<|> (\wid txid -> withLegacyLayer wid - (byron , deleteTransaction byron wid txid) + (byron , deleteTransaction byron wid txid) (icarus, deleteTransaction icarus wid txid) ) byronMigrations :: Server (ByronMigrations n) byronMigrations = (\wid -> withLegacyLayer wid - (byron , getMigrationInfo byron wid) + (byron , getMigrationInfo byron wid) (icarus, getMigrationInfo icarus wid) ) :<|> (\wid m -> withLegacyLayer wid diff --git a/lib/shelley/src/Cardano/Wallet/Shelley/Api/Server.hs b/lib/shelley/src/Cardano/Wallet/Shelley/Api/Server.hs index 839c5e990f8..0e621331554 100644 --- a/lib/shelley/src/Cardano/Wallet/Shelley/Api/Server.hs +++ b/lib/shelley/src/Cardano/Wallet/Shelley/Api/Server.hs @@ -37,6 +37,7 @@ import Cardano.Wallet.Api , CoinSelections , Network , Proxy_ + , ShelleyMigrations , StakePools , Transactions , Wallets @@ -54,6 +55,7 @@ import Cardano.Wallet.Api.Server , listAddresses , listTransactions , listWallets + , migrateWallet , mkLegacyWallet , mkShelleyWallet , postExternalTransaction @@ -124,6 +126,7 @@ server byron icarus shelley ntp = :<|> addresses :<|> coinSelections :<|> transactions + :<|> shelleyMigrations :<|> stakePools :<|> byronWallets :<|> byronAddresses @@ -154,6 +157,11 @@ server byron icarus shelley ntp = :<|> (\_ _ -> throwError err501) :<|> (\_ _ -> throwError err501) + shelleyMigrations :: Server (ShelleyMigrations n) + shelleyMigrations = + getMigrationInfo shelley + :<|> migrateWallet shelley + stakePools :: Server (StakePools n) stakePools = throwError err501 @@ -230,7 +238,7 @@ server byron icarus shelley ntp = ) :<|> (\wid r0 r1 s -> withLegacyLayer wid - (byron , listTransactions byron wid r0 r1 s) + (byron , listTransactions byron wid r0 r1 s) (icarus, listTransactions icarus wid r0 r1 s) ) :<|> @@ -239,14 +247,14 @@ server byron icarus shelley ntp = (icarus, postTransactionFee icarus wid tx) ) :<|> (\wid txid -> withLegacyLayer wid - (byron , deleteTransaction byron wid txid) + (byron , deleteTransaction byron wid txid) (icarus, deleteTransaction icarus wid txid) ) byronMigrations :: Server (ByronMigrations n) byronMigrations = (\wid -> withLegacyLayer wid - (byron , getMigrationInfo byron wid) + (byron , getMigrationInfo byron wid) (icarus, getMigrationInfo icarus wid) ) :<|> \_ _ -> throwError err501 diff --git a/specifications/api/swagger.yaml b/specifications/api/swagger.yaml index 1211b84f0b6..8b7c6b5594d 100644 --- a/specifications/api/swagger.yaml +++ b/specifications/api/swagger.yaml @@ -897,7 +897,7 @@ components: <<: *lenientPassphrase description: The source Byron wallet's master passphrase. - ApiWalletMigrationPostData: &ApiWalletMigrationPostData + ApiByronWalletMigrationPostData: &ApiByronWalletMigrationPostData type: object required: - passphrase @@ -910,6 +910,19 @@ components: <<: *addresses description: The recipient addresses. + ApiShelleyWalletMigrationPostData: &ApiShelleyWalletMigrationPostData + type: object + required: + - passphrase + - addresses + properties: + passphrase: + <<: *walletPassphrase + description: The wallet's master passphrase. + addresses: + <<: *addresses + description: The recipient addresses. + ApiWalletUTxOsStatistics: &ApiWalletUTxOsStatistics type: object required: @@ -1951,6 +1964,39 @@ paths: schema: *ApiSelectCoinsData responses: *responsesSelectCoins + /wallets/{walletId}/migrations: + get: + operationId: getShelleyWalletMigrationInfo + tags: ["Shelley Migrations"] + summary: Calculate Cost + description: | +

status: stable

+ + Calculate the exact cost of migrating from a Shelley wallet to + the specified set of addresses. + parameters: + - <<: *parametersWalletId + name: walletId + responses: *responsesGetWalletMigrationInfo + + post: + operationId: migrateShelleyWallet + tags: ["Shelley Migrations"] + summary: Migrate + description: | +

status: stable

+ + Migrate all funds from a Shelley wallet to a specified set of addresses. + parameters: + - <<: *parametersWalletId + name: walletId + requestBody: + required: true + content: + application/json: + schema: *ApiShelleyWalletMigrationPostData + responses: *responsesMigrateWallet + /byron-wallets: get: operationId: listByronWallets @@ -2193,7 +2239,7 @@ paths: required: true content: application/json: - schema: *ApiWalletMigrationPostData + schema: *ApiByronWalletMigrationPostData responses: *responsesMigrateWallet /byron-wallets/{walletId}/statistics/utxos: