@@ -25,13 +25,20 @@ import Cardano.Wallet.Api.Types
2525 , WalletStyle (.. )
2626 )
2727import Cardano.Wallet.Primitive.AddressDerivation
28- ( NetworkDiscriminant (.. ), PaymentAddress (.. ) )
28+ ( FromMnemonic (.. )
29+ , NetworkDiscriminant (.. )
30+ , Passphrase (.. )
31+ , PassphraseScheme (.. )
32+ , PaymentAddress (.. )
33+ , hex
34+ , preparePassphrase
35+ )
2936import Cardano.Wallet.Primitive.AddressDerivation.Byron
30- ( ByronKey )
37+ ( ByronKey ( .. ), generateKeyFromSeed )
3138import Cardano.Wallet.Primitive.AddressDerivation.Icarus
3239 ( IcarusKey )
3340import Cardano.Wallet.Primitive.Mnemonic
34- ( entropyToMnemonic , genEntropy )
41+ ( entropyToMnemonic , genEntropy , mnemonicToText )
3542import Cardano.Wallet.Primitive.Types
3643 ( Address , Direction (.. ), TxStatus (.. ) )
3744import Control.Monad
@@ -46,12 +53,15 @@ import Numeric.Natural
4653 ( Natural )
4754import Test.Hspec
4855 ( SpecWith , describe , it , shouldBe )
56+ import Test.Integration.Faucet
57+ ( nextWallet )
4958import Test.Integration.Framework.DSL
50- ( Context
59+ ( Context ( .. )
5160 , Headers (.. )
5261 , Payload (.. )
5362 , TxDescription (.. )
5463 , between
64+ , emptyByronWalletFromXPrvWith
5565 , emptyIcarusWallet
5666 , emptyRandomWallet
5767 , eventually
@@ -63,8 +73,10 @@ import Test.Integration.Framework.DSL
6373 , fixtureIcarusWalletAddrs
6474 , fixtureIcarusWalletWith
6575 , fixturePassphrase
76+ , fixturePassphraseEncrypted
6677 , fixtureRandomWallet
6778 , fixtureRandomWalletAddrs
79+ , fixtureRandomWalletMws
6880 , fixtureRandomWalletWith
6981 , icarusAddresses
7082 , json
@@ -86,6 +98,9 @@ import Test.Integration.Framework.TestData
8698
8799import qualified Cardano.Wallet.Api.Link as Link
88100import qualified Data.Aeson as Aeson
101+ import qualified Data.ByteArray as BA
102+ import qualified Data.Text as T
103+ import qualified Data.Text.Encoding as T
89104import qualified Network.HTTP.Types.Status as HTTP
90105
91106spec
@@ -96,54 +111,59 @@ spec
96111 , DecodeAddress n
97112 )
98113 => SpecWith (Context t )
99- spec = describe " BYRON_TXS" $ do
100- -- Random → Random
101- scenario_TRANS_CREATE_01_02 @ n fixtureRandomWallet
102- [ fixtureRandomWalletAddrs @ n
103- ]
114+ spec = do
115+ describe " BYRON_TXS" $ do
116+ -- Random → Random
117+ scenario_TRANS_CREATE_01_02 @ n fixtureRandomWallet
118+ [ fixtureRandomWalletAddrs @ n
119+ ]
104120
105- -- Random → [Random, Icarus]
106- scenario_TRANS_CREATE_01_02 @ n fixtureRandomWallet
107- [ fixtureRandomWalletAddrs @ n
108- , fixtureIcarusWalletAddrs @ n
109- ]
121+ -- Random → [Random, Icarus]
122+ scenario_TRANS_CREATE_01_02 @ n fixtureRandomWallet
123+ [ fixtureRandomWalletAddrs @ n
124+ , fixtureIcarusWalletAddrs @ n
125+ ]
110126
111- -- Icarus → Icarus
112- scenario_TRANS_CREATE_01_02 @ n fixtureIcarusWallet
113- [ fixtureIcarusWalletAddrs @ n
114- ]
127+ -- Icarus → Icarus
128+ scenario_TRANS_CREATE_01_02 @ n fixtureIcarusWallet
129+ [ fixtureIcarusWalletAddrs @ n
130+ ]
115131
116- -- Icarus → [Icarus, Random]
117- scenario_TRANS_CREATE_01_02 @ n fixtureRandomWallet
118- [ fixtureIcarusWalletAddrs @ n
119- , fixtureRandomWalletAddrs @ n
120- ]
132+ -- Icarus → [Icarus, Random]
133+ scenario_TRANS_CREATE_01_02 @ n fixtureRandomWallet
134+ [ fixtureIcarusWalletAddrs @ n
135+ , fixtureRandomWalletAddrs @ n
136+ ]
121137
122- scenario_TRANS_CREATE_02x @ n
138+ scenario_TRANS_CREATE_02x @ n
123139
124- -- TRANS_CREATE_03 requires actually being able to compute exact fees, which
125- -- is not really possible w/ cardano-node. So, skipping.
140+ -- TRANS_CREATE_03 requires actually being able to compute exact fees, which
141+ -- is not really possible w/ cardano-node. So, skipping.
126142
127- scenario_TRANS_CREATE_04a @ n
128- scenario_TRANS_CREATE_04b @ n
129- scenario_TRANS_CREATE_04c @ n
130- scenario_TRANS_CREATE_04d @ n
143+ scenario_TRANS_CREATE_04a @ n
144+ scenario_TRANS_CREATE_04b @ n
145+ scenario_TRANS_CREATE_04c @ n
146+ scenario_TRANS_CREATE_04d @ n
131147
132- scenario_TRANS_CREATE_07 @ n
148+ scenario_TRANS_CREATE_07 @ n
133149
134- scenario_TRANS_ESTIMATE_01_02 @ n fixtureRandomWallet
135- [ randomAddresses @ n . entropyToMnemonic <$> genEntropy
136- ]
150+ scenario_TRANS_ESTIMATE_01_02 @ n fixtureRandomWallet
151+ [ randomAddresses @ n . entropyToMnemonic <$> genEntropy
152+ ]
137153
138- scenario_TRANS_ESTIMATE_01_02 @ n fixtureIcarusWallet
139- [ icarusAddresses @ n . entropyToMnemonic <$> genEntropy
140- , icarusAddresses @ n . entropyToMnemonic <$> genEntropy
141- ]
154+ scenario_TRANS_ESTIMATE_01_02 @ n fixtureIcarusWallet
155+ [ icarusAddresses @ n . entropyToMnemonic <$> genEntropy
156+ , icarusAddresses @ n . entropyToMnemonic <$> genEntropy
157+ ]
142158
143- scenario_TRANS_ESTIMATE_04a @ n
144- scenario_TRANS_ESTIMATE_04b @ n
145- scenario_TRANS_ESTIMATE_04c @ n
159+ scenario_TRANS_ESTIMATE_04a @ n
160+ scenario_TRANS_ESTIMATE_04b @ n
161+ scenario_TRANS_ESTIMATE_04c @ n
146162
163+ describe " BYRON_RESTORATION" $ do
164+ scenario_RESTORE_01 @ n fixtureRandomWallet
165+ scenario_RESTORE_02 @ n (fixtureRandomWalletAddrs @ n )
166+ scenario_RESTORE_03 @ n (fixtureRandomWalletAddrs @ n )
147167--
148168-- Scenarios
149169--
@@ -440,6 +460,192 @@ scenario_TRANS_CREATE_07 = it title $ \ctx -> do
440460 where
441461 title = " TRANS_CREATE_07 - Deleted wallet"
442462
463+ scenario_RESTORE_01
464+ :: forall (n :: NetworkDiscriminant ) t .
465+ ( DecodeAddress n
466+ , EncodeAddress n
467+ , PaymentAddress n ByronKey
468+ )
469+ => (Context t -> IO ApiByronWallet )
470+ -> SpecWith (Context t )
471+ scenario_RESTORE_01 fixtureSource = it title $ \ ctx -> do
472+ -- SETUP
473+ let amnt = 100_000 :: Natural
474+ wSrc <- fixtureSource ctx
475+ (wDest, payment, mnemonics) <- do
476+ (wDest, mnemonics) <- fixtureRandomWalletMws ctx
477+ let addrs = randomAddresses @ n mnemonics
478+ pure (wDest, mkPayment @ n (head addrs) amnt, mnemonics)
479+
480+ -- ACTION
481+ r <- postByronTransaction @ n ctx wSrc [payment] fixturePassphrase
482+
483+ -- ASSERTIONS
484+ let (feeMin, feeMax) = ctx ^. # _feeEstimator $ PaymentDescription
485+ { nInputs = 1
486+ , nOutputs = 1
487+ , nChanges = 1
488+ }
489+ verify r
490+ [ expectResponseCode HTTP. status202
491+ , expectField # amount $ between
492+ ( Quantity (feeMin + amnt)
493+ , Quantity (feeMax + amnt)
494+ )
495+ , expectField # direction (`shouldBe` ApiT Outgoing )
496+ , expectField # status (`shouldBe` ApiT Pending )
497+ ]
498+
499+ eventually " source balance decreases" $ do
500+ rSrc <- request @ ApiByronWallet ctx
501+ (Link. getWallet @ 'Byron wSrc) Default Empty
502+ verify rSrc
503+ [ expectField (# balance . # available) $ between
504+ ( Quantity (faucetAmt - amnt - feeMax)
505+ , Quantity (faucetAmt - amnt - feeMin)
506+ )
507+ ]
508+
509+ eventually " destination balance increases" $ do
510+ rDest <- request @ ApiByronWallet ctx
511+ (Link. getWallet @ 'Byron wDest) Default Empty
512+ verify rDest
513+ [ expectField (# balance . # available)
514+ (`shouldBe` Quantity (faucetAmt + amnt))
515+ ]
516+
517+ -- ACTION
518+ rd1 <- request
519+ @ ApiByronWallet ctx (Link. deleteWallet @ 'Byron wDest) Default Empty
520+ expectResponseCode @ IO HTTP. status204 rd1
521+
522+ -- MORE SETUP
523+ let (Right seed) = fromMnemonic @ '[12 ] (mnemonicToText mnemonics)
524+ let rawPassd = Passphrase $ BA. convert $ T. encodeUtf8 fixturePassphrase
525+ let rootXPrv = T. decodeUtf8 $ hex $ getKey $
526+ generateKeyFromSeed seed
527+ (preparePassphrase EncryptWithScrypt rawPassd)
528+
529+ -- ACTION
530+ wDestRestored <- emptyByronWalletFromXPrvWith ctx " random"
531+ (" Byron Wallet Restored" , rootXPrv, fixturePassphraseEncrypted)
532+
533+ -- ASSERTIONS
534+ eventually " destination balance increases" $ do
535+ rDest <- request @ ApiByronWallet ctx
536+ (Link. getWallet @ 'Byron wDestRestored) Default Empty
537+ verify rDest
538+ [ expectField (# balance . # available)
539+ (`shouldBe` Quantity (faucetAmt + amnt))
540+ ]
541+ where
542+ title = " BYRON_RESTORE_01 - can restore recipient wallet from xprv"
543+
544+ scenario_RESTORE_02
545+ :: forall (n :: NetworkDiscriminant ) t .
546+ ( DecodeAddress n
547+ , EncodeAddress n
548+ )
549+ => (Context t -> IO (ApiByronWallet , [Address ]))
550+ -> SpecWith (Context t )
551+ scenario_RESTORE_02 fixtureTarget = it title $ \ ctx -> do
552+ -- SETUP
553+ let amnt = 100_000 :: Natural
554+ mnemonics <- mnemonicToText <$> nextWallet @ " random" (_faucet ctx)
555+ let (Right seed) = fromMnemonic @ '[12 ] mnemonics
556+ let rawPassd = Passphrase $ BA. convert $ T. encodeUtf8 fixturePassphrase
557+ let rootXPrv = T. decodeUtf8 $ hex $ getKey $
558+ generateKeyFromSeed seed
559+ (preparePassphrase EncryptWithScrypt rawPassd)
560+ wSrc <- emptyByronWalletFromXPrvWith ctx " random"
561+ (" Byron Wallet Restored" , rootXPrv, fixturePassphraseEncrypted)
562+ (wDest, payment) <- do
563+ (wDest, addrs) <- fixtureTarget ctx
564+ pure (wDest, mkPayment @ n (head addrs) amnt)
565+
566+ -- ACTION
567+ r <- postByronTransaction @ n ctx wSrc [payment] fixturePassphrase
568+
569+ -- ASSERTIONS
570+ let (feeMin, feeMax) = ctx ^. # _feeEstimator $ PaymentDescription
571+ { nInputs = 1
572+ , nOutputs = 1
573+ , nChanges = 1
574+ }
575+ verify r
576+ [ expectResponseCode HTTP. status202
577+ , expectField # amount $ between
578+ ( Quantity (feeMin + amnt)
579+ , Quantity (feeMax + amnt)
580+ )
581+ , expectField # direction (`shouldBe` ApiT Outgoing )
582+ , expectField # status (`shouldBe` ApiT Pending )
583+ ]
584+
585+ eventually " source balance decreases" $ do
586+ rSrc <- request @ ApiByronWallet ctx
587+ (Link. getWallet @ 'Byron wSrc) Default Empty
588+ verify rSrc
589+ [ expectField (# balance . # available) $ between
590+ ( Quantity (faucetAmt - amnt - feeMax)
591+ , Quantity (faucetAmt - amnt - feeMin)
592+ )
593+ ]
594+
595+ eventually " destination balance increases" $ do
596+ rDest <- request @ ApiByronWallet ctx
597+ (Link. getWallet @ 'Byron wDest) Default Empty
598+ verify rDest
599+ [ expectField (# balance . # available)
600+ (`shouldBe` Quantity (faucetAmt + amnt))
601+ ]
602+ where
603+ title = " BYRON_RESTORE_02 - can send tx from restored wallet from xprv"
604+
605+ scenario_RESTORE_03
606+ :: forall (n :: NetworkDiscriminant ) t .
607+ ( DecodeAddress n
608+ , EncodeAddress n
609+ )
610+ => (Context t -> IO (ApiByronWallet , [Address ]))
611+ -> SpecWith (Context t )
612+ scenario_RESTORE_03 fixtureTarget = it title $ \ ctx -> do
613+ -- SETUP
614+ mnemonics <- mnemonicToText <$> nextWallet @ " random" (_faucet ctx)
615+ let (Right seed) = fromMnemonic @ '[12 ] mnemonics
616+ let rawPassd = Passphrase $ BA. convert $ T. encodeUtf8 fixturePassphrase
617+ let rootXPrv = T. decodeUtf8 $ hex $ getKey $
618+ generateKeyFromSeed seed
619+ (preparePassphrase EncryptWithScrypt rawPassd)
620+ let passHashCorrupted = T. replicate 100 " 0"
621+ let amnt = 100_000 :: Natural
622+ (_, payment) <- do
623+ (wDest, addrs) <- fixtureTarget ctx
624+ pure (wDest, mkPayment @ n (head addrs) amnt)
625+
626+ -- ACTION
627+ wSrc <- emptyByronWalletFromXPrvWith ctx " random"
628+ (" Byron Wallet Restored" , rootXPrv, passHashCorrupted)
629+ rSrc <- request @ ApiByronWallet ctx
630+ (Link. getWallet @ 'Byron wSrc) Default Empty
631+ -- ASSERTIONS
632+ verify rSrc
633+ [ expectField (# balance . # available)
634+ (`shouldBe` Quantity faucetAmt)
635+ ]
636+
637+ -- ACTION
638+ r <- postByronTransaction @ n ctx wSrc [payment] fixturePassphrase
639+ -- ASSERTIONS
640+ verify r
641+ [ expectResponseCode HTTP. status403
642+ , expectErrorMessage errMsg403WrongPass
643+ ]
644+
645+ where
646+ title = " BYRON_RESTORE_03 - restoring wallet from corrupted hash gives\
647+ \ proper balance but sending tx fails"
648+
443649
444650--
445651-- More Elaborated Fixtures
0 commit comments