diff --git a/lib/customer-deposit-wallet/customer-deposit-wallet.cabal b/lib/customer-deposit-wallet/customer-deposit-wallet.cabal index 4020c5add98..48f38463b48 100644 --- a/lib/customer-deposit-wallet/customer-deposit-wallet.cabal +++ b/lib/customer-deposit-wallet/customer-deposit-wallet.cabal @@ -55,9 +55,11 @@ library , async , base , base58-bytestring + , base16-bytestring , bech32 , bech32-th , bytestring + , cardano-addresses , cardano-balance-tx , cardano-crypto , cardano-ledger-api @@ -226,7 +228,9 @@ test-suite unit , openapi3 , pretty-simple , QuickCheck + , serialise , temporary + , text , time , text , transformers diff --git a/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Server.hs b/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Server.hs index 0e40f298548..d789ef9fa94 100644 --- a/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Server.hs +++ b/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Server.hs @@ -22,6 +22,10 @@ import Cardano.Wallet.Deposit.HTTP.Types.JSON import Cardano.Wallet.Deposit.IO ( WalletBootEnv ) +import Cardano.Wallet.Deposit.Pure.State.Creation + ( credentialsFromEncodedXPub + , credentialsFromMnemonics + ) import Cardano.Wallet.Deposit.REST ( WalletResource , WalletResourceM @@ -32,10 +36,8 @@ import Cardano.Wallet.Deposit.REST.Catch ( catchRunWalletResourceM ) import Cardano.Wallet.Deposit.REST.Wallet.Create - ( PostWalletViaMenmonic (..) + ( PostWalletViaMnemonic (..) , PostWalletViaXPub (..) - , decodeXPub - , xpubFromMnemonics ) import Control.Tracer ( Tracer @@ -81,23 +83,23 @@ createWalletViaMnemonic -> FilePath -> WalletBootEnv IO -> WalletResource - -> PostWalletViaMenmonic + -> PostWalletViaMnemonic -> Handler NoContent createWalletViaMnemonic tracer dir boot resource - (PostWalletViaMenmonic mnemonics' users') = + (PostWalletViaMnemonic mnemonics' passphrase' users') = onlyOnWalletIntance resource initWallet $> NoContent where initWallet :: WalletResourceM () initWallet = - REST.initXPubWallet + REST.initWallet tracer boot dir - (xpubFromMnemonics mnemonics') + (credentialsFromMnemonics mnemonics' passphrase') (fromIntegral users') createWalletViaXPub @@ -119,17 +121,16 @@ createWalletViaXPub Right () -> pure NoContent where initWallet :: WalletResourceM (Either String ()) - initWallet = case decodeXPub xpubText of - Left e -> pure $ Left e - Right (Just xpub') -> + initWallet = case credentialsFromEncodedXPub xpubText of + Left e -> pure $ Left $ show e + Right credentials -> Right - <$> REST.initXPubWallet + <$> REST.initWallet tracer boot dir - xpub' + credentials (fromIntegral users') - Right Nothing -> pure $ Left "Invalid XPub" listCustomerH :: WalletResource diff --git a/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Types/API.hs b/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Types/API.hs index 04dead6c4f0..0732c56fde9 100644 --- a/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Types/API.hs +++ b/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Types/API.hs @@ -20,7 +20,7 @@ import Cardano.Wallet.Deposit.HTTP.Types.JSON , CustomerList ) import Cardano.Wallet.Deposit.REST.Wallet.Create - ( PostWalletViaMenmonic + ( PostWalletViaMnemonic , PostWalletViaXPub ) import Servant.API @@ -47,7 +47,7 @@ type API = :> Capture "customerId" (ApiT Customer) :> Put '[JSON] (ApiT Address) :<|> "mnemonics" - :> ReqBody '[JSON] PostWalletViaMenmonic + :> ReqBody '[JSON] PostWalletViaMnemonic :> PutNoContent :<|> "xpub" :> ReqBody '[JSON] PostWalletViaXPub diff --git a/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Types/JSON.hs b/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Types/JSON.hs index 3ed7695775e..7fe975c6234 100644 --- a/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Types/JSON.hs +++ b/lib/customer-deposit-wallet/http/Cardano/Wallet/Deposit/HTTP/Types/JSON.hs @@ -39,7 +39,7 @@ import Cardano.Wallet.Deposit.Read , ChainPoint (..) ) import Cardano.Wallet.Deposit.REST.Wallet.Create - ( PostWalletViaMenmonic + ( PostWalletViaMnemonic , PostWalletViaXPub ) import Control.Applicative @@ -223,6 +223,6 @@ instance ToSchema (ApiT ChainPoint) where (Just "ApiT ChainPoint") chainPointSchema -instance FromJSON PostWalletViaMenmonic +instance FromJSON PostWalletViaMnemonic instance FromJSON PostWalletViaXPub diff --git a/lib/customer-deposit-wallet/rest/Cardano/Wallet/Deposit/REST.hs b/lib/customer-deposit-wallet/rest/Cardano/Wallet/Deposit/REST.hs index 5f6c9c916dd..9a9e31f0672 100644 --- a/lib/customer-deposit-wallet/rest/Cardano/Wallet/Deposit/REST.hs +++ b/lib/customer-deposit-wallet/rest/Cardano/Wallet/Deposit/REST.hs @@ -3,6 +3,7 @@ {-# LANGUAGE LambdaCase #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} +{-# OPTIONS_GHC -Wno-orphans #-} -- | -- Copyright: © 2024 Cardano Foundation @@ -26,7 +27,7 @@ module Cardano.Wallet.Deposit.REST -- * Operations -- ** Initialization - , initXPubWallet + , initWallet , loadWallet -- ** Mapping between customers and addresses @@ -57,11 +58,15 @@ module Cardano.Wallet.Deposit.REST import Prelude import Cardano.Address.Derivation - ( xpubFromBytes - , xpubToBytes + ( xpubToBytes ) import Cardano.Crypto.Wallet - ( XPub (..) + ( XPrv + , XPub (..) + , unXPrv + , unXPub + , xprv + , xpub ) import Cardano.Wallet.Address.BIP32 ( BIP32Path @@ -74,20 +79,25 @@ import Cardano.Wallet.Deposit.IO.Resource , ErrResourceMissing (..) ) import Cardano.Wallet.Deposit.Pure - ( Customer + ( Credentials + , Customer , ErrCreatePayment , Word31 - , fromXPubAndGenesis + , fromCredentialsAndGenesis ) import Cardano.Wallet.Deposit.Pure.API.TxHistory ( ByCustomer , ByTime ) +import Cardano.Wallet.Deposit.Pure.State.Creation + ( xpubFromCredentials + ) import Cardano.Wallet.Deposit.Read ( Address ) import Codec.Serialise - ( deserialise + ( Serialise (..) + , deserialise , serialise ) import Control.DeepSeq @@ -120,6 +130,9 @@ import Data.ByteArray.Encoding ( Base (..) , convertToBase ) +import Data.ByteString + ( ByteString + ) import Data.List ( isPrefixOf ) @@ -245,52 +258,69 @@ findTheDepositWalletOnDisk dir action = do ds <- scanDirectoryForDepositPrefix dir case ds of [d] -> do - (xpub, users) <- deserialise <$> BL.readFile (dir d) - case xpubFromBytes xpub of - Nothing -> action $ Left $ ErrDatabaseCorrupted (dir d) - Just identity -> do - let state = - fromXPubAndGenesis - identity - (fromIntegral @Int users) - Read.mockGenesisDataMainnet - store <- newStore - writeS store state - action $ Right store + (credentials, users) <- + deserialise <$> BL.readFile (dir d) + let state = + fromCredentialsAndGenesis + credentials + (fromIntegral @Int users) + Read.mockGenesisDataMainnet + store <- newStore + writeS store state + action $ Right store [] -> action $ Left $ ErrDatabaseNotFound dir ds' -> action $ Left $ ErrMultipleDatabases ((dir ) <$> ds') +instance Serialise XPub where + encode = encode . unXPub + decode = do + b <- decode + case xpub b of + Right x -> pure x + Left e -> fail e + +instance Serialise XPrv where + encode = encode . unXPrv + decode = do + b :: ByteString <- decode + case xprv b of + Right x -> pure x + Left e -> fail e + +instance Serialise Credentials + -- | Try to create a new wallet createTheDepositWalletOnDisk :: Tracer IO String -- ^ Tracer for logging -> FilePath -- ^ Path to the wallet database directory - -> XPub + -> Credentials -- ^ Id of the wallet -> Word31 -- ^ Max number of users ? -> (Maybe WalletIO.WalletStore -> IO a) -- ^ Action to run if the wallet is created -> IO a -createTheDepositWalletOnDisk _tr dir identity users action = do +createTheDepositWalletOnDisk _tr dir credentials users action = do ds <- scanDirectoryForDepositPrefix dir case ds of [] -> do - let fp = dir depositPrefix <> hashWalletId identity + let fp = dir depositPrefix <> hashWalletId credentials BL.writeFile fp - $ serialise (xpubToBytes identity, fromIntegral users :: Int) + $ serialise (credentials, fromIntegral users :: Int) store <- newStore action $ Just store _ -> do action Nothing where - hashWalletId :: XPub -> String + hashWalletId :: Credentials -> String hashWalletId = B8.unpack . convertToBase Base16 . blake2b160 - . xpubPublicKey + . xpubToBytes + . xpubFromCredentials -- | Load an existing wallet from disk. loadWallet @@ -316,27 +346,27 @@ loadWallet bootEnv dir = do <$> Resource.putResource action resource -- | Initialize a new wallet from an 'XPub'. -initXPubWallet +initWallet :: Tracer IO String -- ^ Tracer for logging -> WalletIO.WalletBootEnv IO -- ^ Environment for the wallet -> FilePath -- ^ Path to the wallet database directory - -> XPub + -> Credentials -- ^ Id of the wallet -> Word31 -- ^ Max number of users ? -> WalletResourceM () -initXPubWallet tr bootEnv dir xpub users = do +initWallet tr bootEnv dir credentials users = do let action :: (WalletIO.WalletInstance -> IO b) -> IO (Either ErrDatabase b) - action f = createTheDepositWalletOnDisk tr dir xpub users $ \case + action f = createTheDepositWalletOnDisk tr dir credentials users $ \case Just wallet -> do fmap Right $ WalletIO.withWalletInit (WalletIO.WalletEnv bootEnv wallet) - xpub + credentials users $ \i -> do addresses <- map snd <$> WalletIO.listCustomers i diff --git a/lib/customer-deposit-wallet/rest/Cardano/Wallet/Deposit/REST/Wallet/Create.hs b/lib/customer-deposit-wallet/rest/Cardano/Wallet/Deposit/REST/Wallet/Create.hs index e2c133db022..715b4d413ab 100644 --- a/lib/customer-deposit-wallet/rest/Cardano/Wallet/Deposit/REST/Wallet/Create.hs +++ b/lib/customer-deposit-wallet/rest/Cardano/Wallet/Deposit/REST/Wallet/Create.hs @@ -2,31 +2,13 @@ {-# LANGUAGE DuplicateRecordFields #-} module Cardano.Wallet.Deposit.REST.Wallet.Create - ( PostWalletViaMenmonic (..) + ( PostWalletViaMnemonic (..) , PostWalletViaXPub (..) - , decodeXPub - , xpubFromMnemonics - , encodeXPub ) where import Prelude -import Cardano.Address.Derivation - ( XPub - , generate - , toXPub - , xpubFromBytes - , xpubToBytes - ) -import Data.ByteArray.Encoding - ( Base (Base64) - , convertFromBase - , convertToBase - ) -import Data.ByteString.Char8 - ( ByteString - ) import Data.Text ( Text ) @@ -34,11 +16,10 @@ import GHC.Generics ( Generic ) -import qualified Data.Text.Encoding as T - -- | Data for a request to create a wallet via a mnemonic. -data PostWalletViaMenmonic = PostWalletViaMenmonic +data PostWalletViaMnemonic = PostWalletViaMnemonic { mnemonics :: Text + , password :: Text , trackedCustomers :: Int } deriving (Generic) @@ -49,19 +30,3 @@ data PostWalletViaXPub = PostWalletViaXPub , trackedCustomers :: Int } deriving (Generic) - -unBase64 :: ByteString -> Either String ByteString -unBase64 = convertFromBase Base64 - --- | Decode an extended public key from a base64-encoded text. -decodeXPub :: Text -> Either String (Maybe XPub) -decodeXPub = fmap xpubFromBytes . unBase64 . T.encodeUtf8 - --- | Encode an extended public key to a base64-encoded text. -encodeXPub :: XPub -> Text -encodeXPub = T.decodeUtf8 . convertToBase Base64 . xpubToBytes - --- | Generate an extended public key from a mnemonic. --- this is not what one wants to use in production -xpubFromMnemonics :: Text -> XPub -xpubFromMnemonics = toXPub . generate . T.encodeUtf8 diff --git a/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/IO.hs b/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/IO.hs index 2bc02133217..b5a2290dd4f 100644 --- a/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/IO.hs +++ b/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/IO.hs @@ -51,9 +51,6 @@ module Cardano.Wallet.Deposit.IO import Prelude -import Cardano.Crypto.Wallet - ( XPub - ) import Cardano.Wallet.Address.BIP32 ( BIP32Path ) @@ -61,7 +58,8 @@ import Cardano.Wallet.Deposit.IO.Network.Type ( NetworkEnv (slotToUTCTime) ) import Cardano.Wallet.Deposit.Pure - ( Customer + ( Credentials + , Customer , ValueTransfer , WalletPublicIdentity (..) , WalletState @@ -170,7 +168,7 @@ readWalletState WalletInstance{walletState} = -- | Initialize a new wallet in the given environment. withWalletInit :: WalletEnv IO - -> XPub + -> Credentials -> Word31 -> (WalletInstance -> IO a) -> IO a @@ -179,12 +177,15 @@ withWalletInit { bootEnv = WalletBootEnv{genesisData} , .. } - xpub + credentials knownCustomerCount action = do walletState <- DBVar.initDBVar store - $ Wallet.fromXPubAndGenesis xpub knownCustomerCount genesisData + $ Wallet.fromCredentialsAndGenesis + credentials + knownCustomerCount + genesisData withWalletDBVar env walletState action -- | Load an existing wallet from the given environment. diff --git a/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/Pure.hs b/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/Pure.hs index 82d8e1fd4d3..afd1a02b5d4 100644 --- a/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/Pure.hs +++ b/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/Pure.hs @@ -10,6 +10,10 @@ module Cardano.Wallet.Deposit.Pure , DeltaWalletState , WalletPublicIdentity (..) + -- * Creation + , Credentials (..) + , fromCredentialsAndGenesis + -- * Operations -- ** Mapping between customers and addresses @@ -26,7 +30,6 @@ module Cardano.Wallet.Deposit.Pure , walletXPub -- ** Reading from the blockchain - , fromXPubAndGenesis , Word31 , getWalletTip , availableBalance @@ -57,8 +60,9 @@ import Cardano.Wallet.Address.BIP32 , DerivationType (..) ) import Cardano.Wallet.Deposit.Pure.State.Creation - ( WalletPublicIdentity (..) - , fromXPubAndGenesis + ( Credentials (..) + , WalletPublicIdentity (..) + , fromCredentialsAndGenesis ) import Cardano.Wallet.Deposit.Pure.State.Payment ( ErrCreatePayment (..) diff --git a/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/Pure/State/Creation.hs b/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/Pure/State/Creation.hs index 8158ac55595..e0a79950333 100644 --- a/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/Pure/State/Creation.hs +++ b/lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/Pure/State/Creation.hs @@ -1,26 +1,52 @@ +{-# LANGUAGE DeriveGeneric #-} +{-# OPTIONS_GHC -Wno-orphans #-} module Cardano.Wallet.Deposit.Pure.State.Creation ( WalletPublicIdentity (..) - , fromXPubAndGenesis + , fromCredentialsAndGenesis + , Credentials (..) + , credentialsFromMnemonics + , credentialsFromEncodedXPub + , xpubFromCredentials + , xprvFromCredentials + , ErrDecodingXPub (..) + , encodedXPubFromCredentials ) where import Prelude hiding ( lookup ) +import Cardano.Address.Derivation + ( xpubFromBytes + , xpubToBytes + ) import Cardano.Crypto.Wallet - ( XPub + ( XPrv + , XPub + , generate + , toXPub + , unXPrv ) import Cardano.Wallet.Deposit.Pure.State.Type ( WalletState (..) ) +import Data.Text + ( Text + ) import Data.Word.Odd ( Word31 ) +import GHC.Generics + ( Generic + ) import qualified Cardano.Wallet.Deposit.Pure.Address as Address import qualified Cardano.Wallet.Deposit.Pure.Submissions as Sbm import qualified Cardano.Wallet.Deposit.Pure.UTxO.UTxOHistory as UTxOHistory import qualified Cardano.Wallet.Deposit.Read as Read +import qualified Data.ByteString.Base16 as B16 +import qualified Data.ByteString.Char8 as B8 +import qualified Data.Text.Encoding as T data WalletPublicIdentity = WalletPublicIdentity { pubXpub :: XPub @@ -28,18 +54,85 @@ data WalletPublicIdentity = WalletPublicIdentity } deriving (Show) -fromXPubAndGenesis - :: XPub -> Word31 -> Read.GenesisData -> WalletState -fromXPubAndGenesis xpub knownCustomerCount genesisData = +data Credentials + = XPubCredentials !XPub + | XPrvCredentials !XPrv !XPub + deriving (Generic, Show, Eq) + +instance Show XPrv where + show = B8.unpack . B16.encode . unXPrv + +instance Eq XPrv where + a == b = unXPrv a == unXPrv b + +xpubFromCredentials :: Credentials -> XPub +xpubFromCredentials (XPubCredentials xpub) = xpub +xpubFromCredentials (XPrvCredentials _ xpub) = xpub + +xprvFromCredentials :: Credentials -> Maybe XPrv +xprvFromCredentials (XPubCredentials _) = Nothing +xprvFromCredentials (XPrvCredentials xprv _) = Just xprv + +fromCredentialsAndGenesis + :: Credentials -> Word31 -> Read.GenesisData -> WalletState +fromCredentialsAndGenesis credentials knownCustomerCount genesisData = WalletState { walletTip = Read.GenesisPoint , addresses = - Address.fromXPubAndCount network xpub knownCustomerCount + Address.fromXPubAndCount + network + (xpubFromCredentials credentials) + knownCustomerCount , utxoHistory = UTxOHistory.fromOrigin initialUTxO , txHistory = mempty , submissions = Sbm.empty - , rootXSignKey = Nothing + , rootXSignKey = xprvFromCredentials credentials } where network = Read.getNetworkId genesisData initialUTxO = mempty + +-- | Create 'Credentials' from a mnemonic sentence and a passphrase. +credentialsFromMnemonics + :: Text + -- ^ Mnemonics + -> Text + -- ^ Passphrase + -> Credentials +credentialsFromMnemonics mnemonics passphrase = + let + unencryptedXPrv = + generate + (T.encodeUtf8 mnemonics) + (T.encodeUtf8 mempty) + encryptedXPrv = + generate + (T.encodeUtf8 mnemonics) + (T.encodeUtf8 passphrase) + in + XPrvCredentials encryptedXPrv (toXPub unencryptedXPrv) + +-- | Create 'Credentials' from an extended public key failures to decode +data ErrDecodingXPub = ErrFromXPubBase16 | ErrFromXPubDecodeKey + deriving (Show, Eq) + +-- | Create 'Credentials' from an extended public key encoded in base16. +credentialsFromEncodedXPub + :: Text + -> Either ErrDecodingXPub Credentials +credentialsFromEncodedXPub xpub = case B16.decode (T.encodeUtf8 xpub) of + Left _ -> Left ErrFromXPubBase16 + Right bytes -> case xpubFromBytes bytes of + Nothing -> Left ErrFromXPubDecodeKey + Just key -> Right $ XPubCredentials key + +-- | Encode an extended public key to base16. +encodedXPubFromCredentials + :: Credentials + -> Text +encodedXPubFromCredentials (XPubCredentials xpub) = + T.decodeUtf8 + $ B16.encode + $ xpubToBytes xpub +encodedXPubFromCredentials (XPrvCredentials _ xpub) = + encodedXPubFromCredentials (XPubCredentials xpub) diff --git a/lib/customer-deposit-wallet/test/scenario/Test/Scenario/Wallet/Deposit/Exchanges.lhs.md b/lib/customer-deposit-wallet/test/scenario/Test/Scenario/Wallet/Deposit/Exchanges.lhs.md index 13b9da3de80..d33a839404b 100644 --- a/lib/customer-deposit-wallet/test/scenario/Test/Scenario/Wallet/Deposit/Exchanges.lhs.md +++ b/lib/customer-deposit-wallet/test/scenario/Test/Scenario/Wallet/Deposit/Exchanges.lhs.md @@ -34,6 +34,7 @@ import Cardano.Wallet.Deposit.IO import Cardano.Wallet.Deposit.Pure ( Customer , ValueTransfer (..) + , Credentials (..) ) import Cardano.Wallet.Deposit.Read ( Address @@ -79,7 +80,7 @@ scenarioRestore :: XPub -> WalletEnv IO -> IO () scenarioRestore xpub env = do let knownCustomerCount = 127 - Wallet.withWalletInit env xpub knownCustomerCount $ \w -> do + Wallet.withWalletInit env (XPubCredentials xpub) knownCustomerCount $ \w -> do value <- Wallet.availableBalance w assert $ value == ada 0 ``` diff --git a/lib/customer-deposit-wallet/test/scenario/Test/Scenario/Wallet/Deposit/Run.hs b/lib/customer-deposit-wallet/test/scenario/Test/Scenario/Wallet/Deposit/Run.hs index 535add1dc35..ca440b7a038 100644 --- a/lib/customer-deposit-wallet/test/scenario/Test/Scenario/Wallet/Deposit/Run.hs +++ b/lib/customer-deposit-wallet/test/scenario/Test/Scenario/Wallet/Deposit/Run.hs @@ -1,9 +1,8 @@ -{-| -Copyright: © 2024 Cardano Foundation -License: Apache-2.0 - -Execute usage scenarios for the deposit wallet. --} +-- | +-- Copyright: © 2024 Cardano Foundation +-- License: Apache-2.0 +-- +-- Execute usage scenarios for the deposit wallet. module Test.Scenario.Wallet.Deposit.Run ( main ) where @@ -16,6 +15,9 @@ import Cardano.Crypto.Wallet , generate , toXPub ) +import Cardano.Wallet.Deposit.Pure.State.Creation + ( Credentials (..) + ) import Test.Hspec ( SpecWith , describe @@ -43,14 +45,14 @@ import qualified Test.Scenario.Wallet.Deposit.Exchanges as Exchanges main :: IO () main = hspecMain - $ aroundAll withScenarioEnvMock scenarios + $ aroundAll withScenarioEnvMock scenarios scenarios :: SpecWith ScenarioEnv scenarios = do describe "Scenarios for centralized exchanges" $ do it "0. Restore a wallet" $ \env -> - withWalletEnvMock env $ - Exchanges.scenarioRestore xpub + withWalletEnvMock env + $ Exchanges.scenarioRestore xpub it "0. Start a wallet" $ \env -> withWalletEnvMock env $ \w -> do @@ -59,19 +61,25 @@ scenarios = do it "1. Assign an address to a customer ID" $ \env -> do withWalletEnvMock env $ \walletEnv -> - Wallet.withWalletInit walletEnv (freshXPub 1) 32 + Wallet.withWalletInit + walletEnv + (XPubCredentials $ freshXPub 1) + 32 Exchanges.scenarioCreateAddressList it "4. Create payments to a different wallet" $ \env -> do withWalletEnvMock env $ \walletEnv -> - Wallet.withWalletInit walletEnv xpub 32 + Wallet.withWalletInit walletEnv (XPubCredentials xpub) 32 $ Exchanges.scenarioCreatePayment xprv env mockAddress describe "Temporary tests" $ do it "Wallet receives funds that are sent to customer address" $ \env -> do withWalletEnvMock env $ \walletEnv -> - Wallet.withWalletInit walletEnv (freshXPub 0) 8 $ - testBalance env + Wallet.withWalletInit + walletEnv + (XPubCredentials $ freshXPub 0) + 8 + $ testBalance env xpub :: XPub xpub = toXPub xprv @@ -82,9 +90,9 @@ xprv = generate (B8.pack "random seed for a testing xpub lala") B8.empty freshXPub :: Integer -> XPub freshXPub i = toXPub - $ generate - (B8.pack $ "random seed for a testing xpub lala" <> show i) - B8.empty + $ generate + (B8.pack $ "random seed for a testing xpub lala" <> show i) + B8.empty mockAddress :: Read.Address mockAddress = diff --git a/lib/customer-deposit-wallet/test/unit/Cardano/Wallet/Deposit/PureSpec.hs b/lib/customer-deposit-wallet/test/unit/Cardano/Wallet/Deposit/PureSpec.hs index 74b66e60622..a2436a0fffe 100644 --- a/lib/customer-deposit-wallet/test/unit/Cardano/Wallet/Deposit/PureSpec.hs +++ b/lib/customer-deposit-wallet/test/unit/Cardano/Wallet/Deposit/PureSpec.hs @@ -13,17 +13,16 @@ module Cardano.Wallet.Deposit.PureSpec import Prelude -import Cardano.Crypto.Wallet - ( XPub - , generate - , toXPub - ) import Cardano.Wallet.Deposit.Pure - ( Customer + ( Credentials + , Customer ) import Cardano.Wallet.Deposit.Pure.API.TxHistory ( LookupTimeFromSlot ) +import Cardano.Wallet.Deposit.Pure.State.Creation + ( credentialsFromMnemonics + ) import Cardano.Wallet.Deposit.Testing.DSL ( InterpreterState (..) , ScenarioP @@ -79,7 +78,6 @@ import qualified Cardano.Wallet.Deposit.Pure as Wallet import qualified Cardano.Wallet.Deposit.Pure.UTxO as UTxO import qualified Cardano.Wallet.Deposit.Read as Read import qualified Cardano.Wallet.Deposit.Write as Write -import qualified Data.ByteString.Char8 as B8 import qualified Data.Map.Strict as Map import qualified Data.Set as Set @@ -300,12 +298,11 @@ prop_availableBalance_rollForward_rollBackward = emptyWalletWith17Addresses :: Wallet.WalletState emptyWalletWith17Addresses = - Wallet.fromXPubAndGenesis testXPub 17 testGenesis + Wallet.fromCredentialsAndGenesis testCredentials 17 testGenesis -testXPub :: XPub -testXPub = - toXPub - $ generate (B8.pack "random seed for a testing xpub lala") B8.empty +testCredentials :: Credentials +testCredentials = + credentialsFromMnemonics "random seed for a testing xpub lala" mempty {----------------------------------------------------------------------------- Test blockchain diff --git a/lib/customer-deposit-wallet/test/unit/Cardano/Wallet/Deposit/RESTSpec.hs b/lib/customer-deposit-wallet/test/unit/Cardano/Wallet/Deposit/RESTSpec.hs index b82a2f28fb9..4cf0a9cac40 100644 --- a/lib/customer-deposit-wallet/test/unit/Cardano/Wallet/Deposit/RESTSpec.hs +++ b/lib/customer-deposit-wallet/test/unit/Cardano/Wallet/Deposit/RESTSpec.hs @@ -6,9 +6,8 @@ where import Prelude import Cardano.Crypto.Wallet - ( XPub - , generate - , toXPub + ( sign + , verify ) import Cardano.Wallet.Deposit.IO ( WalletBootEnv (WalletBootEnv) @@ -17,6 +16,12 @@ import Cardano.Wallet.Deposit.IO.Resource ( ErrResourceMissing (..) , withResource ) +import Cardano.Wallet.Deposit.Pure.State.Creation + ( Credentials + , credentialsFromMnemonics + , xprvFromCredentials + , xpubFromCredentials + ) import Cardano.Wallet.Deposit.REST ( ErrCreatingDatabase (..) , ErrDatabase (..) @@ -24,11 +29,15 @@ import Cardano.Wallet.Deposit.REST , ErrWalletResource (..) , WalletResourceM , availableBalance - , initXPubWallet + , initWallet , loadWallet , runWalletResourceM , walletExists ) +import Codec.Serialise + ( deserialise + , serialise + ) import Control.Concurrent ( threadDelay ) @@ -38,6 +47,15 @@ import Control.Monad.IO.Class import Control.Tracer ( nullTracer ) +import Data.ByteString + ( ByteString + ) +import Data.Maybe + ( fromJust + ) +import Data.Text + ( Text + ) import System.IO.Temp ( withSystemTempDirectory ) @@ -48,16 +66,33 @@ import Test.Hspec , shouldBe ) +import Control.Monad.Trans.Cont + ( cont + , evalCont + ) +import Test.QuickCheck + ( Gen + , arbitrary + , forAll + , listOf + , suchThat + , vectorOf + , (===) + ) + import qualified Cardano.Wallet.Deposit.Read as Read import qualified Data.ByteString.Char8 as B8 +import qualified Data.Text as T +import qualified Data.Text.Encoding as T fakeBootEnv :: WalletBootEnv IO fakeBootEnv = WalletBootEnv nullTracer Read.mockGenesisDataMainnet undefined -xpub :: XPub -xpub = - toXPub - $ generate (B8.pack "random seed for a testing xpub lala") B8.empty +mnemonics :: Text +mnemonics = "random seed for a testing xpub lala" + +credentials :: Credentials +credentials = credentialsFromMnemonics mnemonics mempty letItInitialize :: WalletResourceM () letItInitialize = liftIO $ threadDelay 100000 @@ -77,7 +112,7 @@ withInitializedWallet -> WalletResourceM a -> IO (Either ErrWalletResource a) withInitializedWallet dir f = withWallet $ do - initXPubWallet nullTracer fakeBootEnv dir xpub 0 + initWallet nullTracer fakeBootEnv dir credentials 0 letItInitialize f @@ -96,8 +131,54 @@ doNothing = pure () inADirectory :: (FilePath -> IO a) -> IO a inADirectory = withSystemTempDirectory "deposit-rest" +byteStringGen :: Gen ByteString +byteStringGen = B8.pack <$> listOf arbitrary + +textGen :: Gen Text +textGen = T.pack <$> listOf arbitrary + +textNGen :: Int -> Gen Text +textNGen n = do + n' <- arbitrary `suchThat` (>= n) + T.pack <$> vectorOf n' arbitrary + +credentialsGen :: Gen (Credentials, Text) +credentialsGen = do + mnemonics' <- textNGen 32 + passphrase' <- textGen + pure (credentialsFromMnemonics mnemonics' passphrase', passphrase') + spec :: Spec spec = do + describe "XPub" $ do + it "can be serialised and deserialised" $ do + forAll credentialsGen $ \(credentials', _) -> + deserialise (serialise $ xpubFromCredentials credentials') + === xpubFromCredentials credentials' + describe "XPrv" $ do + it "can be serialised and deserialised" $ do + forAll credentialsGen $ \(credentials', _) -> + deserialise (serialise $ xprvFromCredentials credentials') + === xprvFromCredentials credentials' + describe "Credentials" $ do + it "can be serialised and deserialised" $ do + forAll credentialsGen $ \(credentials', _) -> + deserialise (serialise credentials') === credentials' + describe "Credentials with mnemonics" $ do + it "can sign and verify a message" $ evalCont $ do + (credentials', passphrase') <- cont $ forAll credentialsGen + message <- cont $ forAll byteStringGen + let + sig = + sign + (T.encodeUtf8 passphrase') + ( fromJust + $ xprvFromCredentials credentials' + ) + message + pure + $ verify (xpubFromCredentials credentials') message sig === True + describe "REST Deposit interface" $ do it "can initialize a wallet" $ inADirectory diff --git a/lib/faucet/lib/Cardano/Faucet.hs b/lib/faucet/lib/Cardano/Faucet.hs index 7a769f1be70..3e20a19e5d8 100644 --- a/lib/faucet/lib/Cardano/Faucet.hs +++ b/lib/faucet/lib/Cardano/Faucet.hs @@ -8,7 +8,7 @@ module Cardano.Faucet ( initialState , serveMnemonics - , serveMenmonic + , serveMnemonic , serveAddresses ) where @@ -100,8 +100,8 @@ serveMnemonics mnLen minIndex maxIndex = do & NE.filter \(IndexedMnemonic index _mnemonic) -> index >= minIndex && index <= maxIndex -serveMenmonic :: MnemonicLength -> MnemonicIndex -> FaucetM Mnemonic -serveMenmonic mnLen index = +serveMnemonic :: MnemonicLength -> MnemonicIndex -> FaucetM Mnemonic +serveMnemonic mnLen index = serveMnemonics mnLen index index >>= \case [IndexedMnemonic _index mnemonic] -> pure mnemonic _ -> throwError err404 @@ -115,7 +115,7 @@ serveAddresses -> AddressIndex -> FaucetM [IndexedAddress] serveAddresses mnLen mnIdx style netTag minAddrIdx maxAddrIdx = do - Mnemonic (SomeMnemonic mnemonic) <- serveMenmonic mnLen mnIdx + Mnemonic (SomeMnemonic mnemonic) <- serveMnemonic mnLen mnIdx let stylishEncoder = case style of AddressStyleShelley -> Addresses.shelley AddressStyleByron -> Addresses.byron diff --git a/lib/faucet/lib/Cardano/Faucet/Http/Server.hs b/lib/faucet/lib/Cardano/Faucet/Http/Server.hs index 028fe9a73b5..86e845ce063 100644 --- a/lib/faucet/lib/Cardano/Faucet/Http/Server.hs +++ b/lib/faucet/lib/Cardano/Faucet/Http/Server.hs @@ -17,7 +17,7 @@ import qualified Servant import Cardano.Faucet ( serveAddresses - , serveMenmonic + , serveMnemonic , serveMnemonics ) import Cardano.Faucet.FaucetM @@ -60,6 +60,6 @@ server state0 = Servant.hoistServer api (runFaucetM state0) faucetServer where serveMnemmonicOrAddresses len index = - serveMenmonic len index :<|> serveAddresses len index + serveMnemonic len index :<|> serveAddresses len index faucetServer :: Servant.ServerT FaucetApi FaucetM faucetServer len = serveMnemonics len :<|> serveMnemmonicOrAddresses len diff --git a/lib/ui/cardano-wallet-ui.cabal b/lib/ui/cardano-wallet-ui.cabal index c74a34d9263..6d2cb4007e8 100644 --- a/lib/ui/cardano-wallet-ui.cabal +++ b/lib/ui/cardano-wallet-ui.cabal @@ -91,8 +91,8 @@ library Cardano.Wallet.UI.Lib.Address Cardano.Wallet.UI.Lib.Discretization Cardano.Wallet.UI.Lib.ListOf - Cardano.Wallet.UI.Lib.Pagination.TimedSeq Cardano.Wallet.UI.Lib.Pagination.Map + Cardano.Wallet.UI.Lib.Pagination.TimedSeq Cardano.Wallet.UI.Lib.Pagination.Type Cardano.Wallet.UI.Lib.Time.Direction Cardano.Wallet.UI.Shelley.API @@ -115,6 +115,7 @@ library , aeson , aeson-pretty , base + , base16-bytestring , bech32 , bech32-th , bytestring @@ -137,7 +138,6 @@ library , http-media , lens , lucid - , memory , mmorph , monoidal-containers , mtl diff --git a/lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Wallet.hs b/lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Wallet.hs index 6ff0b8b3a78..35ffb72cea6 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Wallet.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Common/Html/Pages/Wallet.hs @@ -144,12 +144,11 @@ mnemonicSetupFieldsH walletMnemonicLink PostWalletConfig{..} = do , name_ "name" , placeholder_ "Wallet Name" ] - onShelley - $ input_ + input_ [ formControl , type_ "password" , name_ "password" - , placeholder_ "Wallet Password" + , placeholder_ "Signing Passphrase" ] div_ [class_ "d-flex justify-content-end align-items-center"] $ do button_ diff --git a/lib/ui/src/Cardano/Wallet/UI/Deposit/API.hs b/lib/ui/src/Cardano/Wallet/UI/Deposit/API.hs index 5f08fe7745d..aa85d150176 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Deposit/API.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/API.hs @@ -15,7 +15,7 @@ import Cardano.Wallet.Deposit.Read ( TxId ) import Cardano.Wallet.Deposit.REST.Wallet.Create - ( PostWalletViaMenmonic + ( PostWalletViaMnemonic , PostWalletViaXPub ) import Cardano.Wallet.Read @@ -69,7 +69,7 @@ import Web.FormUrlEncoded import qualified Data.ByteString.Lazy as BL -instance FromForm PostWalletViaMenmonic +instance FromForm PostWalletViaMnemonic instance FromForm PostWalletViaXPub @@ -123,7 +123,7 @@ type Data = :<|> "wallet" :> SessionedHtml Get :<|> "wallet" :> "mnemonic" - :> ReqBody '[FormUrlEncoded] PostWalletViaMenmonic + :> ReqBody '[FormUrlEncoded] PostWalletViaMnemonic :> SessionedHtml Post :<|> "wallet" :> "xpub" diff --git a/lib/ui/src/Cardano/Wallet/UI/Deposit/Handlers/Wallet.hs b/lib/ui/src/Cardano/Wallet/UI/Deposit/Handlers/Wallet.hs index f0638fcd87e..7f0688ac590 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Deposit/Handlers/Wallet.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/Handlers/Wallet.hs @@ -5,21 +5,21 @@ where import Prelude -import Cardano.Address.Derivation - ( XPub - ) import Cardano.Wallet.Deposit.Pure - ( Customer + ( Credentials + , Customer + ) +import Cardano.Wallet.Deposit.Pure.State.Creation + ( credentialsFromEncodedXPub + , credentialsFromMnemonics ) import Cardano.Wallet.Deposit.REST ( WalletResource , WalletResourceM ) import Cardano.Wallet.Deposit.REST.Wallet.Create - ( PostWalletViaMenmonic (..) + ( PostWalletViaMnemonic (..) , PostWalletViaXPub (..) - , decodeXPub - , xpubFromMnemonics ) import Cardano.Wallet.UI.Common.Layer ( Push (Push) @@ -61,25 +61,25 @@ initWalletWithXPub l@SessionLayer{sendSSE} alert render initWallet = do postMnemonicWallet :: SessionLayer WalletResource - -> (XPub -> Customer -> WalletResourceM ()) + -> (Credentials -> Customer -> WalletResourceM ()) -> (BL.ByteString -> html) -> (() -> html) - -> PostWalletViaMenmonic + -> PostWalletViaMnemonic -> Handler html postMnemonicWallet l initWallet alert render - (PostWalletViaMenmonic mnemonic customers) = do - let xpub = xpubFromMnemonics mnemonic + (PostWalletViaMnemonic mnemonic passphrase customers) = do + let credentials = credentialsFromMnemonics mnemonic passphrase initWalletWithXPub l alert render - $ initWallet xpub + $ initWallet credentials $ fromIntegral customers postXPubWallet :: SessionLayer WalletResource - -> (XPub -> Customer -> WalletResourceM ()) + -> (Credentials -> Customer -> WalletResourceM ()) -> (BL.ByteString -> html) -> (() -> html) -> PostWalletViaXPub @@ -90,16 +90,11 @@ postXPubWallet alert render (PostWalletViaXPub xpubText customers) = - case decodeXPub xpubText of - Left e -> pure $ alert $ BL.pack $ "Invalid base64: " <> e - Right Nothing -> - pure - $ alert - $ BL.pack - $ "Invalid xpub: " <> show xpubText - Right (Just xpub) -> + case credentialsFromEncodedXPub xpubText of + Left e -> pure $ alert $ BL.pack $ show e + Right credentials -> initWalletWithXPub l alert render - $ initWallet xpub + $ initWallet credentials $ fromIntegral customers walletIsLoading diff --git a/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Wallet.hs b/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Wallet.hs index 377ac8b908e..83f3edd2bd0 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Wallet.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/Html/Pages/Wallet.hs @@ -64,10 +64,6 @@ import Cardano.Wallet.UI.Type import Control.Exception ( SomeException ) -import Data.ByteArray.Encoding - ( Base (..) - , convertToBase - ) import Data.ByteString ( ByteString ) @@ -88,6 +84,7 @@ import Lucid , p_ ) +import qualified Data.ByteString.Base16 as B16 import qualified Data.ByteString.Char8 as B8 import qualified Data.ByteString.Lazy.Char8 as BL @@ -114,14 +111,11 @@ instance Show WalletPresent where walletH :: WHtml () walletH = sseH walletLink "wallet" ["wallet"] -base64 :: ByteString -> ByteString -base64 = convertToBase Base64 - pubKeyH :: Monad m => XPub -> HtmlT m () pubKeyH xpub = truncatableText WithCopy "public_key" $ toHtml - $ base64 + $ B16.encode $ xpubToBytes xpub headAndTail :: Int -> ByteString -> ByteString diff --git a/lib/ui/src/Cardano/Wallet/UI/Deposit/Server/Wallet.hs b/lib/ui/src/Cardano/Wallet/UI/Deposit/Server/Wallet.hs index 6a8ad4bdfa2..4c8d863b4e3 100644 --- a/lib/ui/src/Cardano/Wallet/UI/Deposit/Server/Wallet.hs +++ b/lib/ui/src/Cardano/Wallet/UI/Deposit/Server/Wallet.hs @@ -16,7 +16,7 @@ import Cardano.Wallet.Deposit.IO import Cardano.Wallet.Deposit.REST ( WalletResource , deleteWallet - , initXPubWallet + , initWallet ) import Cardano.Wallet.UI.Common.Handlers.Session ( withSessionLayer @@ -71,7 +71,7 @@ import Servant ) import Cardano.Wallet.Deposit.REST.Wallet.Create - ( PostWalletViaMenmonic + ( PostWalletViaMnemonic , PostWalletViaXPub ) @@ -96,15 +96,15 @@ servePostMnemonicWallet -> WalletBootEnv IO -> FilePath -> UILayer WalletResource - -> PostWalletViaMenmonic + -> PostWalletViaMnemonic -> Maybe RequestCookies -> Handler (CookieResponse RawHtml) servePostMnemonicWallet tr env dbDir ul request = withSessionLayer ul $ \layer -> do - postMnemonicWallet layer initWallet alert ok request + postMnemonicWallet layer initWallet' alert ok request where ok _ = renderHtml . rogerH @Text $ "ok" - initWallet = initXPubWallet tr env dbDir + initWallet' = initWallet tr env dbDir servePostXPubWallet :: Tracer IO String @@ -116,10 +116,10 @@ servePostXPubWallet -> Handler (CookieResponse RawHtml) servePostXPubWallet tr env dbDir ul request = withSessionLayer ul $ \layer -> do - postXPubWallet layer initWallet alert ok request + postXPubWallet layer initWallet' alert ok request where ok _ = renderHtml . rogerH @Text $ "ok" - initWallet = initXPubWallet tr env dbDir + initWallet' = initWallet tr env dbDir serveDeleteWallet :: UILayer WalletResource @@ -137,19 +137,3 @@ serveDeleteWalletModal -> Handler (CookieResponse RawHtml) serveDeleteWalletModal ul = withSessionLayer ul $ \_ -> pure $ renderSmoothHtml deleteWalletModalH - -{- :<|> (\c -> ) - :<|> wsl (\l -> deleteWalletHandler l (deleteWallet dbDir) alert ok) - :<|> wsl (\_l -> pure $ renderSmoothHtml deleteWalletModalH) - :<|> ( \c -> - wsl - ( \l -> - getCustomerAddress - l - ( renderSmoothHtml - . customerAddressH WithCopy - ) - alert - c - ) - ) -}