Skip to content

Commit

Permalink
[ADP-106] Support restoration-from option in create-wallet API (#4382)
Browse files Browse the repository at this point in the history
This PR adds support for restoration from a given chainpoint for shelley
wallets.

- [x] Add RestorationMode optional field to the API specs
- [x] Add RestorationMode and API counterpart haskell type
- [x] Add some datatype to transport the mode to the DBLayer
(StartRestorationPoint)
- [x] Add a datatype to hold the initial state of a wallet
(InitialState)
- [x] Update JSON golden for WalletPostData
- [x] Implement the database support for the mode

ADP-106
  • Loading branch information
paolino authored Mar 11, 2024
2 parents a626766 + 80c0763 commit 8ff7008
Show file tree
Hide file tree
Showing 43 changed files with 1,580 additions and 401 deletions.
4 changes: 4 additions & 0 deletions justfile
Original file line number Diff line number Diff line change
Expand Up @@ -42,13 +42,16 @@ unit-tests-cabal-match match:
# run unit tests
unit-tests-cabal:
just unit-tests-cabal-match ""

# run wallet-e2e suite against the preprod network
e2e-preprod:
nix run '.#cardano-wallet-e2e' -- preprod \
-s lib/wallet-e2e/test-state/preprod \
-c lib/wallet-e2e/config/cardano-node/preprod \
-t lib/wallet-e2e/test-output/preprod

add_missing_json_goldens:
CREATE_MISSING_GOLDEN=1 just unit-tests-cabal-match "JSON"

# run wallet-e2e suite against the local test cluster
e2e-local:
Expand All @@ -69,6 +72,7 @@ integration-tests-cabal-match match:

# run any integration test matching the given pattern via cabal
integration-tests-cabal-options options:
TESTS_TRACING_MIN_SEVERITY=Warning \
LOCAL_CLUSTER_NODE_OUTPUT_FILE=/dev/null \
LOCAL_CLUSTER_CONFIGS=../../lib/local-cluster/test/data/cluster-configs \
CARDANO_WALLET_TEST_DATA=../../lib/integration/test/data \
Expand Down
5 changes: 5 additions & 0 deletions lib/benchmarks/exe/db-bench.hs
Original file line number Diff line number Diff line change
Expand Up @@ -146,6 +146,9 @@ import Cardano.Wallet.Flavor
( KeyFlavorS (..)
, WalletFlavor (..)
)
import Cardano.Wallet.Network.RestorationMode
( RestorationPoint (RestorationPointAtGenesis)
)
import Cardano.Wallet.Primitive.Model
( Wallet
, initWallet
Expand Down Expand Up @@ -752,6 +755,7 @@ walletFixture :: WalletFixture StateBench
walletFixture =
( DBLayerParams
testCp
RestorationPointAtGenesis
testMetadata
mempty
dummyGenesisParameters
Expand All @@ -762,6 +766,7 @@ walletFixtureByron :: WalletFixture StateBenchByron
walletFixtureByron =
( DBLayerParams
testCpByron
RestorationPointAtGenesis
testMetadata
mempty
dummyGenesisParameters
Expand Down
1 change: 1 addition & 0 deletions lib/benchmarks/exe/latency-bench.hs
Original file line number Diff line number Diff line change
Expand Up @@ -386,6 +386,7 @@ massiveFixtureWallet massiveMnemonic = do
, name = ApiT $ unsafeFromText "Massive wallet"
, passphrase = ApiT $ unsafeFromText fixturePassphrase
, oneChangeAddressMode = Nothing
, restorationMode = Nothing
}
finallyDeleteWallet wal1
wal1
Expand Down
18 changes: 12 additions & 6 deletions lib/benchmarks/exe/restore-bench.hs
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,8 @@ import Cardano.Mnemonic
, entropyToMnemonic
)
import Cardano.Wallet
( WalletLayer (..)
( InitialState (..)
, WalletLayer (..)
, WalletWorkerLog (..)
, dummyChangeAddressGen
)
Expand Down Expand Up @@ -157,6 +158,9 @@ import Cardano.Wallet.Network.Implementation.Ouroboros
( PipeliningStrategy
, tunedForMainnetPipeliningStrategy
)
import Cardano.Wallet.Network.RestorationMode
( RestorationPoint (..)
)
import Cardano.Wallet.Primitive.Ledger.Read.Block
( fromCardanoBlock
)
Expand Down Expand Up @@ -846,7 +850,9 @@ bench_restoration
let ti = neverFails "bench db shouldn't forecast into future"
$ timeInterpreter nw
let gps = (emptyGenesis gp, np)
withBenchDBLayer @s wlTr ti wid wname gps s
initialState
= InitialState s (emptyGenesis gp) RestorationPointAtGenesis
withBenchDBLayer @s wlTr ti wid wname np initialState
$ \db -> withWalletLayerTracer
benchname pipeliningStrat traceToDisk
$ \progressTrace -> do
Expand Down Expand Up @@ -955,13 +961,13 @@ withBenchDBLayer
-> TimeInterpreter IO
-> WalletId
-> WalletName
-> (Block, NetworkParameters)
-> s
-> NetworkParameters
-> InitialState s
-> (DBLayer IO s -> IO a)
-> IO a
withBenchDBLayer tr ti wid wname gps s action =
withBenchDBLayer tr ti wid wname np initialState action =
withTempSqliteFile $ \dbFile -> do
params <- W.createWallet gps wid wname s
params <- W.createWallet np wid wname initialState
withBootDBLayerFromFile
(walletFlavor @s)
tr'
Expand Down
13 changes: 2 additions & 11 deletions lib/benchmarks/src/Cardano/Wallet/Benchmarks/Latency/BenchM.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@ module Cardano.Wallet.Benchmarks.Latency.BenchM
( BenchM
, BenchCtx (..)
, partialFromRight
, clientEnv
, fixtureMultiAssetWallet
, fixtureWallet
, fixtureWalletWith
Expand Down Expand Up @@ -53,15 +52,13 @@ import Numeric.Natural
( Natural
)
import Servant.Client
( ClientEnv
, ClientError
( ClientError
, ClientM
, mkClientEnv
, parseBaseUrl
, runClientM
)
import Test.Integration.Framework.DSL
( Context
, clientEnv
)

import qualified Cardano.Wallet.Api.Clients.Testnet.Shelley as C
Expand All @@ -72,12 +69,6 @@ data BenchCtx = BenchCtx
, logFun :: LogCaptureFunc ApiLog ()
}

-- one day we will export the manager from the context
clientEnv :: Context -> ClientEnv
clientEnv ctx = case parseBaseUrl $ show (fst $ ctx ^. #_manager) of
Left _ -> error "Invalid base URL"
Right bu -> mkClientEnv (snd $ ctx ^. #_manager) bu

partialFromRight :: Show l => Either l r -> r
partialFromRight = either (error . show) Prelude.id

Expand Down
7 changes: 7 additions & 0 deletions lib/integration/cardano-wallet-integration.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -87,6 +87,7 @@ library framework
, memory
, microstache
, monad-loops
, mtl
, network-uri
, resourcet
, retry
Expand All @@ -105,6 +106,9 @@ library framework
exposed-modules:
Test.Integration.Framework.Context
Test.Integration.Framework.DSL
Test.Integration.Framework.DSL.Network
Test.Integration.Framework.DSL.TestM
Test.Integration.Framework.DSL.Wallet
Test.Integration.Framework.Logging
Test.Integration.Framework.PendingInEra
Test.Integration.Framework.Request
Expand All @@ -128,6 +132,7 @@ library scenarios
, cardano-crypto-class
, cardano-ledger-alonzo
, cardano-ledger-core
, cardano-wallet-network-layer
, cardano-wallet-primitive
, cardano-wallet-secrets
, cardano-wallet-test-utils
Expand All @@ -149,6 +154,7 @@ library scenarios
, memory
, pretty-simple
, resourcet
, servant-client
, text
, text-class
, time
Expand All @@ -175,6 +181,7 @@ library scenarios
Test.Integration.Scenario.API.Shelley.HWWallets
Test.Integration.Scenario.API.Shelley.Migrations
Test.Integration.Scenario.API.Shelley.Network
Test.Integration.Scenario.API.Shelley.Restoration
Test.Integration.Scenario.API.Shelley.Settings
Test.Integration.Scenario.API.Shelley.StakePools
Test.Integration.Scenario.API.Shelley.Transactions
Expand Down
30 changes: 30 additions & 0 deletions lib/integration/framework/Test/Integration/Framework/Context.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,9 @@ module Test.Integration.Framework.Context
( Context (..)
, PoolGarbageCollectionEvent (..)
, TxDescription (..)
, clientEnv
, runClientRequest
, runPartialClientRequest
) where

import Prelude
Expand Down Expand Up @@ -35,6 +38,9 @@ import Cardano.Wallet.Primitive.Types.Coin
import Cardano.Wallet.Transaction
( DelegationAction
)
import Control.Monad.IO.Class
( MonadIO (..)
)
import Data.IORef
( IORef
)
Expand All @@ -50,6 +56,14 @@ import Network.HTTP.Client
import Network.URI
( URI
)
import Servant.Client
( ClientEnv
, ClientError
, ClientM
, mkClientEnv
, parseBaseUrl
, runClientM
)

-- | Context for integration tests.
--
Expand Down Expand Up @@ -114,3 +128,19 @@ data TxDescription
:: Int
}
deriving Show

-- one day we will export the manager from the context
clientEnv :: Context -> ClientEnv
clientEnv ctx = case parseBaseUrl $ show (fst $ _manager ctx) of
Left _ -> error "Invalid base URL"
Right bu -> mkClientEnv (snd $ _manager ctx) bu

runClientRequest :: MonadIO m => Context -> ClientM a -> m (Either ClientError a)
runClientRequest ctx action = liftIO $ runClientM action (clientEnv ctx)

runPartialClientRequest :: MonadIO m => Context -> ClientM a -> m a
runPartialClientRequest ctx action = liftIO $ do
res <- runClientRequest ctx action
case res of
Left e -> fail $ show e
Right a -> return a
4 changes: 3 additions & 1 deletion lib/integration/framework/Test/Integration/Framework/DSL.hs
Original file line number Diff line number Diff line change
Expand Up @@ -108,6 +108,7 @@ module Test.Integration.Framework.DSL
-- * Helpers
, (</>)
, (!!)
, clientEnv
, computeApiCoinSelectionFee
, isValidDerivationPath
, derivationPathValidationErrors
Expand Down Expand Up @@ -618,6 +619,7 @@ import Test.HUnit.Lang
import Test.Integration.Framework.Context
( Context (..)
, TxDescription (..)
, clientEnv
)
import Test.Integration.Framework.Request
( Headers (..)
Expand Down Expand Up @@ -3124,7 +3126,7 @@ createWalletViaCLI ctx args mnemonic secondFactor passphrase =
let portArgs =
[ "--port", show (ctx ^. typed @(Port "wallet")) ]
let fullArgs =
[ "wallet", "create", "from-recovery-phrase" ] ++ portArgs ++ args
[ "wallet", "create", "from-recovery-phrase", "from-genesis" ] ++ portArgs ++ args
let process = proc' commandName fullArgs
liftIO $ withCreateProcess process $
\(Just stdin) (Just stdout) (Just stderr) h -> do
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,42 @@
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Test.Integration.Framework.DSL.Network where

import Prelude

import Cardano.Wallet.Api.Types
( ApiNetworkInformation
)
import Cardano.Wallet.Primitive.Types
( EpochNo
)
import Control.Lens
( (^.)
)
import Test.Hspec.Expectations.Lifted
( shouldSatisfy
)
import Test.Integration.Framework.DSL
( eventually
)
import Test.Integration.Framework.DSL.TestM
( TestM
, pattern Partial
, request
)

import qualified Cardano.Wallet.Api.Clients.Testnet.Network as C

tipInfo :: TestM EpochNo
tipInfo = do
Partial (netInfo :: ApiNetworkInformation) <- request C.networkInformation
pure $ netInfo ^. #nodeTip . #slotId . #epochNumber . #getApiT

waitSomeEpochs :: Int -> TestM ()
waitSomeEpochs n = do
now <- tipInfo
eventually "Waiting some epochs" $ do
current <- tipInfo
current `shouldSatisfy` (>= now + fromIntegral n)
Loading

0 comments on commit 8ff7008

Please sign in to comment.