diff --git a/wallet-new/cardano-sl-wallet-new.cabal b/wallet-new/cardano-sl-wallet-new.cabal index e21d236bdca..52827201c2d 100755 --- a/wallet-new/cardano-sl-wallet-new.cabal +++ b/wallet-new/cardano-sl-wallet-new.cabal @@ -16,11 +16,9 @@ cabal-version: >=1.10 library hs-source-dirs: src exposed-modules: Cardano.Wallet.API - Cardano.Wallet.API.Development - Cardano.Wallet.API.Development.Handlers - Cardano.Wallet.API.Development.Helpers - Cardano.Wallet.API.Development.LegacyHandlers Cardano.Wallet.API.Indices + Cardano.Wallet.API.Internal + Cardano.Wallet.API.Internal.Handlers Cardano.Wallet.API.Request Cardano.Wallet.API.Request.Filter Cardano.Wallet.API.Request.Pagination @@ -292,6 +290,7 @@ executable cardano-generate-swagger-file , cardano-sl-core , cardano-sl-wallet-new , optparse-applicative + , servant-server , swagger2 , universum >= 0.1.11 @@ -302,6 +301,7 @@ executable cardano-generate-swagger-file ScopedTypeVariables FlexibleContexts MonadFailDesugaring + TypeOperators -- Cryptic executable name to mitigate $PATH limitation @@ -506,7 +506,7 @@ test-suite wallet-new-specs hs-source-dirs: test test/unit other-modules: APISpec - DevelopmentSpec + InternalAPISpec MarshallingSpec SwaggerSpec RequestSpec diff --git a/wallet-new/generate-swagger-file/Main.hs b/wallet-new/generate-swagger-file/Main.hs index 622bfbfdc6c..efc53926d0b 100644 --- a/wallet-new/generate-swagger-file/Main.hs +++ b/wallet-new/generate-swagger-file/Main.hs @@ -1,5 +1,4 @@ -{-# LANGUAGE LambdaCase #-} -{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE LambdaCase #-} module Main where @@ -7,8 +6,9 @@ import Universum import Data.Swagger (Swagger) import Options.Applicative +import Servant ((:<|>)) -import Cardano.Wallet.API (devAPI, v0API, v1API) +import Cardano.Wallet.API (InternalAPI, V1API, v0API) import Pos.Core.Update (ApplicationName (..), SoftwareVersion (..)) import Pos.Util.CompileInfo (CompileTimeInfo (CompileTimeInfo), gitRev) @@ -27,7 +27,6 @@ data Command = Command data TargetAPI = TargetWalletV1 | TargetWalletV0 - | TargetWalletDev deriving (Show) @@ -49,7 +48,7 @@ main = cmdParser :: Parser Command cmdParser = Command <$> targetAPIOption (short 't' <> long "target" <> metavar "API" - <> help "Target API with version (e.g. 'wallet@v1', 'wallet@v0', 'wallet@dev'...)") + <> help "Target API with version (e.g. 'wallet@v1', 'wallet@v0')") <*> optional (strOption (short 'o' <> long "output-file" <> metavar "FILEPATH" <> help ("Output file, default to: " <> defaultOutputFilename))) @@ -58,7 +57,6 @@ main = targetAPIOption = option $ maybeReader $ \case "wallet@v0" -> Just TargetWalletV0 "wallet@v1" -> Just TargetWalletV1 - "wallet@dev" -> Just TargetWalletDev _ -> Nothing in do Command{..} <- @@ -71,12 +69,12 @@ main = mkSwagger :: (CompileTimeInfo, SoftwareVersion) -> TargetAPI -> Swagger mkSwagger details = \case - TargetWalletDev -> - Swagger.api details devAPI Swagger.highLevelShortDescription TargetWalletV0 -> Swagger.api details v0API Swagger.highLevelShortDescription TargetWalletV1 -> - Swagger.api details v1API Swagger.highLevelDescription + Swagger.api details v1API' Swagger.highLevelDescription + where + v1API' = Proxy :: Proxy (V1API :<|> InternalAPI) -- NOTE The software version is hard-coded here. Do determine the SoftwareVersion, diff --git a/wallet-new/integration/TransactionSpecs.hs b/wallet-new/integration/TransactionSpecs.hs index 9ab76acd5da..3e1955d5e71 100644 --- a/wallet-new/integration/TransactionSpecs.hs +++ b/wallet-new/integration/TransactionSpecs.hs @@ -45,18 +45,25 @@ transactionSpecs wRef wc = do , pmtGroupingPolicy = Nothing , pmtSpendingPassword = Nothing } - tenthOf (V1 c) = V1 (Core.mkCoin (Core.getCoin c `div` 10)) + tenthOf (V1 c) = + V1 (Core.mkCoin (max 1 (Core.getCoin c `div` 10))) etxn <- postTransaction wc payment txn <- fmap wrData etxn `shouldPrism` _Right - eresp <- getTransactionIndex wc (Just (walId wallet)) (Just (accIndex toAcct)) Nothing + eresp <- getTransactionIndex + wc + (Just (walId wallet)) + (Just (accIndex toAcct)) + Nothing resp <- fmap wrData eresp `shouldPrism` _Right map txId resp `shouldContain` [txId txn] - it "asset-locked wallets can receive funds and transaction are confirmed in index" $ do + it ( "asset-locked wallets can receive funds and transactions are " + <> "confirmed in index" + ) $ do genesis <- genesisWallet wc (fromAcct, _) <- firstAccountAndId wc genesis diff --git a/wallet-new/src/Cardano/Wallet/API.hs b/wallet-new/src/Cardano/Wallet/API.hs index efd21a75414..75f534ddd04 100644 --- a/wallet-new/src/Cardano/Wallet/API.hs +++ b/wallet-new/src/Cardano/Wallet/API.hs @@ -1,18 +1,15 @@ module Cardano.Wallet.API ( V0API + , V0API' , v0API , V1API , v1API - , DevAPI - , devAPI + , InternalAPI + , internalAPI , WalletAPI , walletAPI - , WalletDevAPI - , walletDevAPI , WalletDocAPI , walletDocAPI - , WalletDevDocAPI - , walletDevDocAPI ) where import Cardano.Wallet.API.Types (WalletLoggingConfig) @@ -20,7 +17,7 @@ import Pos.Util.Servant (LoggingApi) import Servant ((:<|>), (:>), Proxy (..)) import Servant.Swagger.UI (SwaggerSchemaUI) -import qualified Cardano.Wallet.API.Development as Dev +import qualified Cardano.Wallet.API.Internal as Internal import qualified Cardano.Wallet.API.V0 as V0 import qualified Cardano.Wallet.API.V1 as V1 @@ -38,35 +35,30 @@ import qualified Cardano.Wallet.API.V1 as V1 -- * 'Cardano.Wallet.Server' contains the main server; -- * 'Cardano.Wallet.API.V0.Handlers' contains all the @Handler@s serving the V0 API; -- * 'Cardano.Wallet.API.V1.Handlers' contains all the @Handler@s serving the V1 API; --- * 'Cardano.Wallet.API.Development.Handlers' contains all the @Handler@s serving the Dev API; +-- * 'Cardano.Wallet.API.Internalelopment.Handlers' contains all the @Handler@s serving the Internal API; type V0Doc = "docs" :> "v0" :> SwaggerSchemaUI "index" "swagger.json" -type V0API = "api" :> V0.API +type V1Doc = "docs" :> "v1" :> SwaggerSchemaUI "index" "swagger.json" + + +type V0API = "api" :> V0.API +type V0API' = "api" :> "v0" :> V0.API v0API :: Proxy V0API v0API = Proxy -type V1Doc = "docs" :> "v1" :> SwaggerSchemaUI "index" "swagger.json" type V1API = "api" :> "v1" :> V1.API v1API :: Proxy V1API v1API = Proxy -type DevDoc = "docs" :> "development" :> SwaggerSchemaUI "index" "swagger.json" -type DevAPI = "api" :> "development" :> Dev.API -devAPI :: Proxy DevAPI -devAPI = Proxy +type InternalAPI = "api" :> "internal" :> Internal.API +internalAPI :: Proxy InternalAPI +internalAPI = Proxy -type WalletAPI = LoggingApi WalletLoggingConfig (V0API :<|> V1API) + +type WalletAPI = LoggingApi WalletLoggingConfig (V0API' :<|> V0API :<|> V1API :<|> InternalAPI) walletAPI :: Proxy WalletAPI walletAPI = Proxy -type WalletDevAPI = DevAPI :<|> WalletAPI -walletDevAPI :: Proxy WalletDevAPI -walletDevAPI = Proxy - type WalletDocAPI = V0Doc :<|> V1Doc walletDocAPI :: Proxy WalletDocAPI walletDocAPI = Proxy - -type WalletDevDocAPI = DevDoc :<|> WalletDocAPI -walletDevDocAPI :: Proxy WalletDevDocAPI -walletDevDocAPI = Proxy diff --git a/wallet-new/src/Cardano/Wallet/API/Development.hs b/wallet-new/src/Cardano/Wallet/API/Development.hs deleted file mode 100644 index 76d060ec9d4..00000000000 --- a/wallet-new/src/Cardano/Wallet/API/Development.hs +++ /dev/null @@ -1,36 +0,0 @@ -{-# OPTIONS_GHC -fno-warn-orphans #-} --- orphan instance is proivded for V1 WalletStateSnapshot, as it is only --- exposed as an octetstream anyway - -module Cardano.Wallet.API.Development where - -import Universum - -import Cardano.Wallet.API.Response (ValidJSON, WalletResponse) -import Cardano.Wallet.API.Types (Tags) -import Cardano.Wallet.API.V1.Types (V1 (..)) -import Data.Aeson -import Data.Swagger (NamedSchema (..), ToSchema (..)) -import Pos.Wallet.Web.Methods.Misc (WalletStateSnapshot) -import Servant -import Servant.API.ContentTypes (OctetStream) - --- the ToSchema instance that was being generated for this type is invalid, --- so we make one here an dhide it behind the WalletStateSnapshot -instance ToSchema (V1 WalletStateSnapshot) where - declareNamedSchema _ = - pure $ NamedSchema (Just "V1WalletStateSnapshot") mempty - -instance ToJSON (V1 WalletStateSnapshot) where - toJSON (V1 x) = toJSON x - -type API - = Tags '["Development"] :> - ( - "dump-wallet-state" :> Summary "Dump wallet state." - :> Get '[OctetStream] (WalletResponse (V1 WalletStateSnapshot)) - :<|> "secret-keys" :> Summary "Clear wallet state and delete all the secret keys." - :> DeleteNoContent '[ValidJSON] NoContent - :<|> "fail" :> Summary "Throw a generic error" - :> GetNoContent '[ValidJSON] NoContent - ) diff --git a/wallet-new/src/Cardano/Wallet/API/Development/Handlers.hs b/wallet-new/src/Cardano/Wallet/API/Development/Handlers.hs deleted file mode 100644 index 698b8e81db4..00000000000 --- a/wallet-new/src/Cardano/Wallet/API/Development/Handlers.hs +++ /dev/null @@ -1,15 +0,0 @@ -module Cardano.Wallet.API.Development.Handlers - ( handlers - ) where - -import Universum - -import Cardano.Wallet.Server.CLI (RunMode (..)) - -import Servant - -import qualified Cardano.Wallet.API.Development as Dev - --- TODO: Add handlers for new wallet -handlers :: RunMode -> Server Dev.API -handlers _ = error "TODO" diff --git a/wallet-new/src/Cardano/Wallet/API/Development/Helpers.hs b/wallet-new/src/Cardano/Wallet/API/Development/Helpers.hs deleted file mode 100644 index 7ae1eb169f4..00000000000 --- a/wallet-new/src/Cardano/Wallet/API/Development/Helpers.hs +++ /dev/null @@ -1,12 +0,0 @@ -module Cardano.Wallet.API.Development.Helpers where - -import Universum - -import Cardano.Wallet.Server.CLI (RunMode (..), isDebugMode) -import Servant (err403) - - -developmentOnly :: MonadThrow m => RunMode -> m a -> m a -developmentOnly runMode api - | isDebugMode runMode = api - | otherwise = throwM err403 diff --git a/wallet-new/src/Cardano/Wallet/API/Development/LegacyHandlers.hs b/wallet-new/src/Cardano/Wallet/API/Development/LegacyHandlers.hs deleted file mode 100644 index 6408b0a357d..00000000000 --- a/wallet-new/src/Cardano/Wallet/API/Development/LegacyHandlers.hs +++ /dev/null @@ -1,68 +0,0 @@ -{-# LANGUAGE DataKinds #-} -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE MultiParamTypeClasses #-} -{-# LANGUAGE PolyKinds #-} -{-# LANGUAGE RankNTypes #-} -{-# LANGUAGE TypeFamilies #-} - -module Cardano.Wallet.API.Development.LegacyHandlers - ( handlers - , deleteSecretKeys - ) where - -import Control.Monad.Catch (MonadThrow) -import Universum - -import qualified Cardano.Wallet.API.Development as Dev -import Cardano.Wallet.API.Development.Helpers (developmentOnly) -import Cardano.Wallet.API.Response (WalletResponse, single) -import Cardano.Wallet.API.V1.Migration -import Cardano.Wallet.API.V1.Types (V1 (..)) -import Cardano.Wallet.Server.CLI (RunMode (..)) - -import qualified Pos.Client.KeyStorage as V0 -import qualified Pos.Wallet.Web.Methods.Misc as V0 -import qualified Pos.Wallet.Web.State as V0 - -import Servant - --- | Until we depend from V0 logic to implement the each 'Handler' we --- still need the natural transformation here. -handlers :: (forall a. MonadV1 a -> Handler a) - -> RunMode - -> Server Dev.API -handlers naturalTransformation runMode = - hoistServer (Proxy @Dev.API) naturalTransformation handlers' - where - -- | @Servant@ handlers needed by test cases. - -- They are not available in public, but for development mode only. - handlers' :: ( V0.WalletDbReader ctx m - , V0.MonadKeys m - , MonadThrow m - , MonadIO m - ) - => ServerT Dev.API m - handlers' = getWalletState runMode - :<|> deleteSecretKeys runMode - :<|> throwSomething runMode - -getWalletState :: ( MonadThrow m, MonadIO m, V0.WalletDbReader ctx m) - => RunMode - -> m (WalletResponse (V1 V0.WalletStateSnapshot)) -getWalletState runMode = - developmentOnly runMode (fmap V1 . single <$> V0.dumpState) - -deleteSecretKeys :: ( V0.WalletDbReader ctx m - , V0.MonadKeys m - , MonadThrow m - , MonadIO m - ) - => RunMode - -> m NoContent -deleteSecretKeys runMode = do - db <- V0.askWalletDB - developmentOnly runMode (V0.deleteAllSecretKeys >> V0.testReset db >> return NoContent) - -throwSomething :: MonadThrow m => RunMode -> m NoContent -throwSomething runMode = - developmentOnly runMode $ error "A generic error happened in dev mode" diff --git a/wallet-new/src/Cardano/Wallet/API/Internal.hs b/wallet-new/src/Cardano/Wallet/API/Internal.hs new file mode 100644 index 00000000000..e64cc7e287a --- /dev/null +++ b/wallet-new/src/Cardano/Wallet/API/Internal.hs @@ -0,0 +1,23 @@ +-- | This module contains the top level API definition for frontend-related +-- tasks. The API endpoints presented here are intended for use with the +-- Daedalus client, and aren't useful for wallets, exchanges, and other users. +module Cardano.Wallet.API.Internal where + +import Cardano.Wallet.API.Response (ValidJSON) +import Cardano.Wallet.API.Types (Tags) +import Servant ((:<|>), (:>), DeleteNoContent, NoContent, Post, + Summary) + +type API = Tags '["Internal"] :> + ( "apply-update" + :> Summary "Apply the next available update" + :> Post '[ValidJSON] NoContent + + :<|> "postpone-update" + :> Summary "Discard and postpone the next available update" + :> Post '[ValidJSON] NoContent + + :<|> "reset-wallet-state" + :> Summary "Clear wallet state and all associated secret keys" + :> DeleteNoContent '[ValidJSON] NoContent + ) diff --git a/wallet-new/src/Cardano/Wallet/API/Internal/Handlers.hs b/wallet-new/src/Cardano/Wallet/API/Internal/Handlers.hs new file mode 100644 index 00000000000..a2f25bf3587 --- /dev/null +++ b/wallet-new/src/Cardano/Wallet/API/Internal/Handlers.hs @@ -0,0 +1,50 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE TypeFamilies #-} + +module Cardano.Wallet.API.Internal.Handlers where + +import Universum + +import Control.Monad.Catch (MonadThrow) +import Servant + +import Cardano.Wallet.API.V1.Migration +import Cardano.Wallet.Server.CLI (RunMode (..), isDebugMode) + +import qualified Cardano.Wallet.API.Internal as Internal +import qualified Pos.Client.KeyStorage as V0 +import qualified Pos.Wallet.Web.Methods.Misc as V0 +import qualified Pos.Wallet.Web.State as V0 + + +-- | Until we depend from V0 logic to implement the each 'Handler' we +-- still need the natural transformation here. +handlers + :: (forall a. MonadV1 a -> Handler a) + -> RunMode + -> Server Internal.API +handlers naturalTransformation runMode = + let + handlers' = + V0.applyUpdate + :<|> V0.postponeUpdate + :<|> resetWalletState runMode + in + hoistServer (Proxy @Internal.API) naturalTransformation handlers' + + +resetWalletState + :: (V0.WalletDbReader ctx m, V0.MonadKeys m, MonadThrow m, MonadIO m) + => RunMode + -> m NoContent +resetWalletState runMode + | isDebugMode runMode = do + V0.deleteAllSecretKeys + void (V0.askWalletDB >>= V0.testReset) + return NoContent + | otherwise = + throwM err403 diff --git a/wallet-new/src/Cardano/Wallet/API/V1/Accounts.hs b/wallet-new/src/Cardano/Wallet/API/V1/Accounts.hs index 620c52a121f..dc47b2f7a8e 100644 --- a/wallet-new/src/Cardano/Wallet/API/V1/Accounts.hs +++ b/wallet-new/src/Cardano/Wallet/API/V1/Accounts.hs @@ -31,4 +31,10 @@ type API :> Summary "Update an Account for the given Wallet." :> ReqBody '[ValidJSON] (Update Account) :> Put '[ValidJSON] (WalletResponse Account) + :<|> "wallets" :> CaptureWalletId :> "accounts" + :> CaptureAccountId + :> Summary "Redeem a certificate" + :> "certificates" + :> ReqBody '[ValidJSON] Redemption + :> Post '[ValidJSON] (WalletResponse Transaction) ) diff --git a/wallet-new/src/Cardano/Wallet/API/V1/Internal.hs b/wallet-new/src/Cardano/Wallet/API/V1/Internal.hs new file mode 100644 index 00000000000..e6ca0d71597 --- /dev/null +++ b/wallet-new/src/Cardano/Wallet/API/V1/Internal.hs @@ -0,0 +1,22 @@ +{-# LANGUAGE DeriveGeneric #-} + +-- | This module contains the top level API definition for frontend-related +-- tasks. The API endpoints presented here are intended for use with the +-- Daedalus client, and aren't useful for wallets, exchanges, and other users. +module Cardano.Wallet.API.V1.Internal where + +import Servant + +type API = Tags '["Internal"] :> + ( "apply-update" + :> Summary "Apply the next available update" + :> Post '[ValidJSON] NoContent + + :<|> "postpone-update" + :> Summary "Discard and postpone the next available update" + :> Post '[ValidJSON] NoContent + + :<|> "reset-wallet-state" + :> Summary "Clear wallet state and all associated secret keys" + :> DeleteNoContent '[ValidJSON] NoContent + ) diff --git a/wallet-new/src/Cardano/Wallet/API/V1/Internal/Update.hs b/wallet-new/src/Cardano/Wallet/API/V1/Internal/Update.hs new file mode 100644 index 00000000000..10c0aa1142d --- /dev/null +++ b/wallet-new/src/Cardano/Wallet/API/V1/Internal/Update.hs @@ -0,0 +1,13 @@ +module Cardano.Wallet.API.V1.Internal.Update where + +import Servant + +import Cardano.Wallet.API.Response (ValidJSON) + +type API = + "update" + :> ( "apply" + :> Post '[ValidJSON] NoContent + :<|> "postpone" + :> Post '[ValidJSON] NoContent + ) diff --git a/wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers.hs b/wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers.hs index c225e494df4..081c59a215d 100644 --- a/wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers.hs +++ b/wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers.hs @@ -45,9 +45,17 @@ handlers :: ( HasConfigurations -> TVar NtpStatus -> Server V1.API handlers naturalTransformation pm diffusion ntpStatus = - hoistServer (Proxy @Addresses.API) naturalTransformation Addresses.handlers - :<|> hoistServer (Proxy @Wallets.API) naturalTransformation Wallets.handlers - :<|> hoistServer (Proxy @Accounts.API) naturalTransformation Accounts.handlers - :<|> hoistServer (Proxy @Transactions.API) naturalTransformation (Transactions.handlers pm (sendTx diffusion)) - :<|> hoistServer (Proxy @Settings.API) naturalTransformation Settings.handlers - :<|> hoistServer (Proxy @Info.API) naturalTransformation (Info.handlers diffusion ntpStatus) + hoist' (Proxy @Addresses.API) Addresses.handlers + :<|> hoist' (Proxy @Wallets.API) Wallets.handlers + :<|> hoist' (Proxy @Accounts.API) (Accounts.handlers pm sendTx') + :<|> hoist' (Proxy @Transactions.API) (Transactions.handlers pm sendTx') + :<|> hoist' (Proxy @Settings.API) Settings.handlers + :<|> hoist' (Proxy @Info.API) (Info.handlers diffusion ntpStatus) + where + hoist' + :: forall (api :: *). HasServer api '[] + => Proxy api + -> ServerT api MonadV1 + -> Server api + hoist' p = hoistServer p naturalTransformation + sendTx' = sendTx diffusion diff --git a/wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers/Accounts.hs b/wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers/Accounts.hs index 36034ea3c6b..c765d5f53d8 100644 --- a/wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers/Accounts.hs +++ b/wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers/Accounts.hs @@ -5,27 +5,35 @@ module Cardano.Wallet.API.V1.LegacyHandlers.Accounts import Universum -import Cardano.Wallet.API.Request -import Cardano.Wallet.API.Response -import qualified Cardano.Wallet.API.V1.Accounts as Accounts -import Cardano.Wallet.API.V1.Migration -import Cardano.Wallet.API.V1.Types import qualified Data.IxSet.Typed as IxSet +import Servant +import Pos.Core.Txp (TxAux) +import Pos.Crypto (ProtocolMagic) +import qualified Pos.Util.Servant as V0 import qualified Pos.Wallet.Web.Account as V0 import qualified Pos.Wallet.Web.ClientTypes.Types as V0 import qualified Pos.Wallet.Web.Methods.Logic as V0 -import Servant +import qualified Pos.Wallet.Web.Methods.Redeem as V0 + +import Cardano.Wallet.API.Request +import Cardano.Wallet.API.Response +import qualified Cardano.Wallet.API.V1.Accounts as Accounts +import Cardano.Wallet.API.V1.Migration +import Cardano.Wallet.API.V1.Types handlers :: HasConfigurations - => ServerT Accounts.API MonadV1 -handlers = + => ProtocolMagic + -> (TxAux -> MonadV1 Bool) + -> ServerT Accounts.API MonadV1 +handlers pm submitTx = deleteAccount :<|> getAccount :<|> listAccounts :<|> newAccount :<|> updateAccount + :<|> redeemAda pm submitTx deleteAccount :: (V0.MonadWalletLogic ctx m) @@ -68,3 +76,32 @@ updateAccount wId accIdx accUpdate = do accMeta <- migrate accUpdate cAccount <- V0.updateAccount newAccId accMeta single <$> (migrate cAccount) + +redeemAda + :: HasConfigurations + => ProtocolMagic + -> (TxAux -> MonadV1 Bool) + -> WalletId + -> AccountIndex + -> Redemption + -> MonadV1 (WalletResponse Transaction) +redeemAda pm submitTx walletId accountIndex r = do + let ShieldedRedemptionCode seed = redemptionRedemptionCode r + V1 spendingPassword = redemptionSpendingPassword r + accountId <- migrate (walletId, accountIndex) + let caccountId = V0.encodeCType accountId + fmap single . migrate =<< case redemptionMnemonic r of + Just (RedemptionMnemonic mnemonic) -> do + let phrase = V0.CBackupPhrase mnemonic + let cpaperRedeem = V0.CPaperVendWalletRedeem + { V0.pvWalletId = caccountId + , V0.pvSeed = seed + , V0.pvBackupPhrase = phrase + } + V0.redeemAdaPaperVend pm submitTx spendingPassword cpaperRedeem + Nothing -> do + let cwalletRedeem = V0.CWalletRedeem + { V0.crWalletId = caccountId + , V0.crSeed = seed + } + V0.redeemAda pm submitTx spendingPassword cwalletRedeem diff --git a/wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers/Internal/Update.hs b/wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers/Internal/Update.hs new file mode 100644 index 00000000000..2179e8ece1f --- /dev/null +++ b/wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers/Internal/Update.hs @@ -0,0 +1,17 @@ +module Cardano.Wallet.API.V1.LegacyHandlers.Internal.Update where + +import Servant + +import qualified Pos.Wallet.Web.Methods.Misc as V0 + +import qualified Cardano.Wallet.API.V1.Internal.Update as Update +import Cardano.Wallet.API.V1.Migration (MonadV1) + +handlers :: ServerT Update.API MonadV1 +handlers = applyUpdate :<|> postponeUpdate + +applyUpdate :: MonadV1 NoContent +applyUpdate = V0.applyUpdate + +postponeUpdate :: MonadV1 NoContent +postponeUpdate = V0.postponeUpdate diff --git a/wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers/Wallets.hs b/wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers/Wallets.hs index 02ab089f731..3521374597a 100644 --- a/wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers/Wallets.hs +++ b/wallet-new/src/Cardano/Wallet/API/V1/LegacyHandlers/Wallets.hs @@ -83,7 +83,7 @@ newWallet NewWallet{..} = do let newWalletHandler CreateWallet = V0.newWallet newWalletHandler RestoreWallet = V0.restoreWalletFromSeed (V1 spendingPassword) = fromMaybe (V1 mempty) newwalSpendingPassword - (V1 backupPhrase) = newwalBackupPhrase + (BackupPhrase backupPhrase) = newwalBackupPhrase initMeta <- V0.CWalletMeta <$> pure newwalName <*> migrate newwalAssuranceLevel <*> pure 0 diff --git a/wallet-new/src/Cardano/Wallet/API/V1/Migration/Types.hs b/wallet-new/src/Cardano/Wallet/API/V1/Migration/Types.hs index ee2a6856b5b..761b98c8d25 100644 --- a/wallet-new/src/Cardano/Wallet/API/V1/Migration/Types.hs +++ b/wallet-new/src/Cardano/Wallet/API/V1/Migration/Types.hs @@ -3,8 +3,8 @@ {-# LANGUAGE LambdaCase #-} {-# LANGUAGE TypeSynonymInstances #-} -module Cardano.Wallet.API.V1.Migration.Types ( - Migrate(..) +module Cardano.Wallet.API.V1.Migration.Types + ( Migrate(..) , migrate ) where @@ -28,6 +28,7 @@ import qualified Pos.Core.Slotting as Core import qualified Pos.Core.Txp as Txp import Pos.Crypto (decodeHash) import qualified Pos.Txp.Toil.Types as V0 +import Pos.Util.Mnemonic (Mnemonic) import qualified Pos.Util.Servant as V0 import qualified Pos.Wallet.Web.ClientTypes.Instances () import qualified Pos.Wallet.Web.ClientTypes.Types as V0 @@ -121,7 +122,11 @@ instance Migrate V0.CCoin (V1 Core.Coin) where instance Migrate (V1 Core.Coin) V0.CCoin where eitherMigrate (V1 c) = pure (V0.encodeCType c) --- +instance (n ~ m, n ~ 12) + => Migrate (Mnemonic n) (V0.CBackupPhrase m) where + eitherMigrate = + Right . V0.CBackupPhrase + instance Migrate (V0.CId V0.Wal) V1.WalletId where eitherMigrate (V0.CId (V0.CHash h)) = pure (V1.WalletId h) diff --git a/wallet-new/src/Cardano/Wallet/API/V1/Swagger.hs b/wallet-new/src/Cardano/Wallet/API/V1/Swagger.hs index ba15159dce5..242d10fbc32 100644 --- a/wallet-new/src/Cardano/Wallet/API/V1/Swagger.hs +++ b/wallet-new/src/Cardano/Wallet/API/V1/Swagger.hs @@ -26,7 +26,6 @@ import Cardano.Wallet.TypeLits (KnownSymbols (..)) import qualified Pos.Core as Core import Pos.Core.Update (SoftwareVersion) import Pos.Util.CompileInfo (CompileTimeInfo, ctiGitRevision) -import Pos.Util.Mnemonic (Mnemonic) import Pos.Util.Servant (LoggingApi) import Pos.Wallet.Web.Swagger.Instances.Schema () @@ -846,7 +845,7 @@ api (compileInfo, curSoftwareVersion) walletAPI mkDescription = toSwagger wallet & host ?~ "127.0.0.1:8090" & info.description ?~ (mkDescription $ DescriptionEnvironment { deErrorExample = decodeUtf8 $ encodePretty Errors.WalletNotFound - , deMnemonicExample = decodeUtf8 $ encode (genExample @(Mnemonic 12)) + , deMnemonicExample = decodeUtf8 $ encode (genExample @BackupPhrase) , deDefaultPerPage = fromString (show defaultPerPageEntries) , deWalletErrorTable = errorsDescription , deGitRevision = ctiGitRevision compileInfo diff --git a/wallet-new/src/Cardano/Wallet/API/V1/Swagger/Example.hs b/wallet-new/src/Cardano/Wallet/API/V1/Swagger/Example.hs index ca6fb73e6dd..b92570ff2da 100644 --- a/wallet-new/src/Cardano/Wallet/API/V1/Swagger/Example.hs +++ b/wallet-new/src/Cardano/Wallet/API/V1/Swagger/Example.hs @@ -6,19 +6,18 @@ import Cardano.Wallet.API.Response import Cardano.Wallet.API.V1.Types import Cardano.Wallet.Orphans.Arbitrary () import Data.Default (Default (def)) -import qualified Data.Map.Strict as Map import Node (NodeId (..)) import Test.QuickCheck (Arbitrary (..), Gen, listOf1, oneof) import Pos.Client.Txp.Util (InputSelectionPolicy (..)) -import qualified Pos.Core.Common as Core -import qualified Pos.Crypto.Signing as Core -import Pos.Util.Mnemonic (Mnemonic) import Pos.Wallet.Web.ClientTypes (CUpdateInfo) import Pos.Wallet.Web.Methods.Misc (WalletStateSnapshot (..)) - import Test.Pos.Wallet.Arbitrary.Web.ClientTypes () +import qualified Data.Map.Strict as Map +import qualified Pos.Core.Common as Core +import qualified Pos.Crypto.Signing as Core + class Arbitrary a => Example a where example :: Gen a @@ -65,11 +64,8 @@ instance Example (V1 Address) where , Core.SingleKeyDistr <$> arbitrary ] -instance Example (Mnemonic 12) where - example = pure def - -instance Example (V1 (Mnemonic 12)) where - example = V1 <$> example +instance Example BackupPhrase where + example = pure (BackupPhrase def) instance Example Address instance Example Metadata diff --git a/wallet-new/src/Cardano/Wallet/API/V1/Types.hs b/wallet-new/src/Cardano/Wallet/API/V1/Types.hs index 0785181ba8d..d23d6da4107 100644 --- a/wallet-new/src/Cardano/Wallet/API/V1/Types.hs +++ b/wallet-new/src/Cardano/Wallet/API/V1/Types.hs @@ -1,11 +1,13 @@ {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE ExplicitNamespaces #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PolyKinds #-} +{-# LANGUAGE StrictData #-} {-# LANGUAGE TemplateHaskell #-} -- The hlint parser fails on the `pattern` function, so we disable the @@ -72,6 +74,10 @@ module Cardano.Wallet.API.V1.Types ( , NodeInfo (..) , TimeInfo(..) , SubscriptionStatus(..) + , Redemption(..) + , RedemptionMnemonic(..) + , BackupPhrase(..) + , ShieldedRedemptionCode(..) -- * Some types for the API , CaptureWalletId , CaptureAccountId @@ -259,23 +265,6 @@ instance ByteArray.ByteArrayAccess a => ByteArray.ByteArrayAccess (V1 a) where length (V1 a) = ByteArray.length a withByteArray (V1 a) callback = ByteArray.withByteArray a callback -instance Arbitrary (V1 (Mnemonic 12)) where - arbitrary = - V1 <$> arbitrary - -instance ToJSON (V1 (Mnemonic 12)) where - toJSON = - toJSON . unV1 - -instance FromJSON (V1 (Mnemonic 12)) where - parseJSON = - fmap V1 . parseJSON - -instance ToSchema (V1 (Mnemonic 12)) where - declareNamedSchema _ = do - NamedSchema _ schm <- declareNamedSchema (Proxy @(Mnemonic 12)) - return $ NamedSchema (Just "V1BackupPhrase") schm - mkPassPhrase :: Text -> Either Text Core.PassPhrase mkPassPhrase text = case Base16.decode text of @@ -405,7 +394,6 @@ instance Monoid (V1 Core.PassPhrase) where type WalletName = Text - -- | Wallet's Assurance Level data AssuranceLevel = NormalAssurance @@ -481,9 +469,25 @@ instance BuildableSafeGen WalletOperation where buildSafeGen _ RestoreWallet = "restore" +newtype BackupPhrase = BackupPhrase + { unBackupPhrase :: Mnemonic 12 + } + deriving stock (Eq, Show) + deriving newtype (ToJSON, FromJSON, Arbitrary) + +deriveSafeBuildable ''BackupPhrase +instance BuildableSafeGen BackupPhrase where + buildSafeGen _ _ = "" + +instance ToSchema BackupPhrase where + declareNamedSchema _ = + pure + . NamedSchema (Just "V1BackupPhrase") + $ toSchema (Proxy @(Mnemonic 12)) + -- | A type modelling the request for a new 'Wallet'. data NewWallet = NewWallet { - newwalBackupPhrase :: !(V1 (Mnemonic 12)) + newwalBackupPhrase :: !BackupPhrase , newwalSpendingPassword :: !(Maybe SpendingPassword) , newwalAssuranceLevel :: !AssuranceLevel , newwalName :: !WalletName @@ -1770,6 +1774,81 @@ instance BuildableSafeGen NodeInfo where nfoLocalTimeInformation (Map.toList nfoSubscriptionStatus) +-- | A redemption mnemonic. +newtype RedemptionMnemonic = RedemptionMnemonic + { unRedemptionMnemonic :: Mnemonic 9 + } + deriving stock (Eq, Show, Generic) + deriving newtype (ToJSON, FromJSON, Arbitrary) + +instance ToSchema RedemptionMnemonic where + declareNamedSchema _ = pure $ + NamedSchema (Just "RedemptionMnemonic") (toSchema (Proxy @(Mnemonic 9))) + +-- | A shielded redemption code. +newtype ShieldedRedemptionCode = ShieldedRedemptionCode + { unShieldedRedemptionCode :: Text + } deriving (Eq, Show, Generic) + deriving newtype (ToJSON, FromJSON) + +-- | This instance could probably be improved. A 'ShieldedRedemptionCode' is +-- a hash of the redemption key. +instance Arbitrary ShieldedRedemptionCode where + arbitrary = ShieldedRedemptionCode <$> arbitrary + +instance ToSchema ShieldedRedemptionCode where + declareNamedSchema _ = + pure + $ NamedSchema (Just "ShieldedRedemptionCode") $ mempty + & type_ .~ SwaggerString + +deriveSafeBuildable ''ShieldedRedemptionCode +instance BuildableSafeGen ShieldedRedemptionCode where + buildSafeGen _ _ = + bprint "" + +-- | The request body for redeeming some Ada. +data Redemption = Redemption + { redemptionRedemptionCode :: ShieldedRedemptionCode + -- ^ The redemption code associated with the Ada to redeem. + , redemptionMnemonic :: Maybe RedemptionMnemonic + -- ^ An optional mnemonic. This mnemonic was included with paper + -- certificates, and the presence of this field indicates that we're + -- doing a paper vend. + , redemptionSpendingPassword :: SpendingPassword + -- ^ The user must provide a spending password that matches the wallet that + -- will be receiving the redemption funds. + } deriving (Eq, Show, Generic) + +deriveSafeBuildable ''Redemption +instance BuildableSafeGen Redemption where + buildSafeGen sl r = bprint ("{" + %" redemptionCode="%buildSafe sl + %" mnemonic=" + %" spendingPassword="%buildSafe sl + %" }") + (redemptionRedemptionCode r) + (redemptionSpendingPassword r) + +deriveJSON Serokell.defaultOptions ''Redemption + +instance ToSchema Redemption where + declareNamedSchema = + genericSchemaDroppingPrefix "redemption" (\(--^) props -> props + & "redemptionCode" + --^ "The redemption code associated with the Ada to redeem." + & "mnemonic" + --^ ( "An optional mnemonic. This must be provided for a paper " + <> "certificate redemption." + ) + & "spendingPassword" + --^ ( "An optional spending password. This must match the password " + <> "for the provided wallet ID and account index." + ) + ) + +instance Arbitrary Redemption where + arbitrary = Redemption <$> arbitrary <*> arbitrary <*> arbitrary -- -- POST/PUT requests isomorphisms diff --git a/wallet-new/src/Cardano/Wallet/Client.hs b/wallet-new/src/Cardano/Wallet/Client.hs index 3f175d11d83..8a826874916 100644 --- a/wallet-new/src/Cardano/Wallet/Client.hs +++ b/wallet-new/src/Cardano/Wallet/Client.hs @@ -99,6 +99,8 @@ data WalletClient m :: WalletId -> New Account -> Resp m Account , updateAccount :: WalletId -> AccountIndex -> Update Account -> Resp m Account + , redeemAda + :: WalletId -> AccountIndex -> Redemption -> Resp m Transaction -- transactions endpoints , postTransaction :: Payment -> Resp m Transaction @@ -183,44 +185,46 @@ getWallets = paginateAll . getWalletIndexPaged hoistClient :: (forall x. m x -> n x) -> WalletClient m -> WalletClient n hoistClient phi wc = WalletClient { getAddressIndexPaginated = - \x -> phi . getAddressIndexPaginated wc x + \x -> phi . getAddressIndexPaginated wc x , postAddress = - phi . postAddress wc + phi . postAddress wc , getAddress = - phi . getAddress wc + phi . getAddress wc , postWallet = - phi . postWallet wc + phi . postWallet wc , getWalletIndexFilterSorts = - \x y p -> phi . getWalletIndexFilterSorts wc x y p + \x y p -> phi . getWalletIndexFilterSorts wc x y p , updateWalletPassword = - \x -> phi . updateWalletPassword wc x + \x -> phi . updateWalletPassword wc x , deleteWallet = - phi . deleteWallet wc + phi . deleteWallet wc , getWallet = - phi . getWallet wc + phi . getWallet wc , updateWallet = - \x -> phi . updateWallet wc x + \x -> phi . updateWallet wc x , deleteAccount = - \x -> phi . deleteAccount wc x + \x -> phi . deleteAccount wc x , getAccount = - \x -> phi . getAccount wc x + \x -> phi . getAccount wc x , getAccountIndexPaged = - \x mp -> phi . getAccountIndexPaged wc x mp + \x mp -> phi . getAccountIndexPaged wc x mp , postAccount = - \x -> phi . postAccount wc x + \x -> phi . postAccount wc x , updateAccount = - \x y -> phi . updateAccount wc x y + \x y -> phi . updateAccount wc x y + , redeemAda = + \x y -> phi . redeemAda wc x y , postTransaction = - phi . postTransaction wc + phi . postTransaction wc , getTransactionIndexFilterSorts = - \wid maid maddr mp mpp f -> - phi . getTransactionIndexFilterSorts wc wid maid maddr mp mpp f + \wid maid maddr mp mpp f -> + phi . getTransactionIndexFilterSorts wc wid maid maddr mp mpp f , getTransactionFee = - phi . getTransactionFee wc + phi . getTransactionFee wc , getNodeSettings = - phi (getNodeSettings wc) + phi (getNodeSettings wc) , getNodeInfo = - phi (getNodeInfo wc) + phi (getNodeInfo wc) } -- | Generalize a @'WalletClient' 'IO'@ into a @('MonadIO' m) => diff --git a/wallet-new/src/Cardano/Wallet/Client/Http.hs b/wallet-new/src/Cardano/Wallet/Client/Http.hs index d628ed27fc3..423ccacafa0 100644 --- a/wallet-new/src/Cardano/Wallet/Client/Http.hs +++ b/wallet-new/src/Cardano/Wallet/Client/Http.hs @@ -116,6 +116,8 @@ mkHttpClient baseUrl manager = WalletClient = \w -> run . postAccountR w , updateAccount = \x y -> run . updateAccountR x y + , redeemAda + = run ... redeemAdaR -- transactions endpoints , postTransaction = run . postTransactionR @@ -166,6 +168,7 @@ mkHttpClient baseUrl manager = WalletClient :<|> getAccountIndexPagedR :<|> postAccountR :<|> updateAccountR + :<|> redeemAdaR = accountsAPI postTransactionR diff --git a/wallet-new/src/Cardano/Wallet/LegacyServer.hs b/wallet-new/src/Cardano/Wallet/LegacyServer.hs index 545c712e34a..c7828f376ef 100644 --- a/wallet-new/src/Cardano/Wallet/LegacyServer.hs +++ b/wallet-new/src/Cardano/Wallet/LegacyServer.hs @@ -3,24 +3,25 @@ module Cardano.Wallet.LegacyServer where import Universum +import Servant + import Cardano.Wallet.API import Cardano.Wallet.API.V1.Migration (HasCompileInfo, HasConfigurations) - -import qualified Cardano.Wallet.API.Development.LegacyHandlers as Dev -import qualified Cardano.Wallet.API.V0.Handlers as V0 -import qualified Cardano.Wallet.API.V1.LegacyHandlers as V1 import Cardano.Wallet.API.V1.Swagger (swaggerSchemaUIServer) -import qualified Cardano.Wallet.API.V1.Swagger as Swagger import Cardano.Wallet.Server.CLI (RunMode (..)) - import Ntp.Client (NtpStatus) import Pos.Crypto (ProtocolMagic) import Pos.Infra.Diffusion.Types (Diffusion (..)) import Pos.Update.Configuration (curSoftwareVersion) import Pos.Util.CompileInfo (compileInfo) import Pos.Wallet.Web.Mode (WalletWebMode) -import Servant + +import qualified Cardano.Wallet.API.Internal.Handlers as Internal +import qualified Cardano.Wallet.API.V0.Handlers as V0 +import qualified Cardano.Wallet.API.V1.LegacyHandlers as V1 +import qualified Cardano.Wallet.API.V1.Swagger as Swagger + -- | This function has the tricky task of plumbing different versions of the API, -- with potentially different monadic stacks into a uniform @Server@ we can use @@ -30,25 +31,17 @@ walletServer :: (HasConfigurations, HasCompileInfo) -> ProtocolMagic -> Diffusion WalletWebMode -> TVar NtpStatus + -> RunMode -> Server WalletAPI -walletServer natV0 pm diffusion ntpStatus = v0Handler :<|> v1Handler - where - v0Handler = V0.handlers natV0 pm diffusion ntpStatus - v1Handler = V1.handlers natV0 pm diffusion ntpStatus - - -walletDevServer - :: (HasConfigurations, HasCompileInfo) - => (forall a. WalletWebMode a -> Handler a) - -> ProtocolMagic - -> Diffusion WalletWebMode - -> TVar NtpStatus - -> RunMode - -> Server WalletDevAPI -walletDevServer natV0 pm diffusion ntpStatus runMode = devHandler :<|> walletHandler +walletServer natV0 pm diffusion ntpStatus runMode = + v0Handler + :<|> v0Handler + :<|> v1Handler + :<|> internalHandler where - devHandler = Dev.handlers natV0 runMode - walletHandler = walletServer natV0 pm diffusion ntpStatus + v0Handler = V0.handlers natV0 pm diffusion ntpStatus + v1Handler = V1.handlers natV0 pm diffusion ntpStatus + internalHandler = Internal.handlers natV0 runMode walletDocServer @@ -56,13 +49,6 @@ walletDocServer => Server WalletDocAPI walletDocServer = v0DocHandler :<|> v1DocHandler where + v1API' = Proxy :: Proxy (V1API :<|> InternalAPI) v0DocHandler = swaggerSchemaUIServer (Swagger.api (compileInfo, curSoftwareVersion) v0API Swagger.highLevelShortDescription) - v1DocHandler = swaggerSchemaUIServer (Swagger.api (compileInfo, curSoftwareVersion) v1API Swagger.highLevelDescription) - - -walletDevDocServer - :: (HasConfigurations, HasCompileInfo) - => Server WalletDevDocAPI -walletDevDocServer = devDocHandler :<|> walletDocServer - where - devDocHandler = swaggerSchemaUIServer (Swagger.api (compileInfo, curSoftwareVersion) devAPI Swagger.highLevelShortDescription) + v1DocHandler = swaggerSchemaUIServer (Swagger.api (compileInfo, curSoftwareVersion) v1API' Swagger.highLevelDescription) diff --git a/wallet-new/src/Cardano/Wallet/Server.hs b/wallet-new/src/Cardano/Wallet/Server.hs index 5946d9b0762..8ef6f11c4b7 100644 --- a/wallet-new/src/Cardano/Wallet/Server.hs +++ b/wallet-new/src/Cardano/Wallet/Server.hs @@ -1,55 +1,49 @@ module Cardano.Wallet.Server ( walletServer - , walletDevServer , walletDocServer - , walletDevDocServer ) where -import Servant import Universum +import Servant + import Cardano.Wallet.API -import qualified Cardano.Wallet.API.Development.Handlers as Dev -import qualified Cardano.Wallet.API.V1.Handlers as V1 import Cardano.Wallet.API.V1.Swagger (swaggerSchemaUIServer) -import qualified Cardano.Wallet.API.V1.Swagger as Swagger import Cardano.Wallet.Server.CLI (RunMode (..)) import Cardano.Wallet.WalletLayer (ActiveWalletLayer) import Pos.Update.Configuration (HasUpdateConfiguration, curSoftwareVersion) import Pos.Util.CompileInfo (HasCompileInfo, compileInfo) +import qualified Cardano.Wallet.API.V1.Handlers as V1 +import qualified Cardano.Wallet.API.V1.Swagger as Swagger + + -- | Serve the REST interface to the wallet -- -- NOTE: Unlike the legacy server, the handlers will not run in a special -- Cardano monad because they just interfact with the Wallet object. walletServer :: ActiveWalletLayer IO + -> RunMode -> Server WalletAPI -walletServer w = v0Handler :<|> v1Handler +walletServer w _ = + v0Handler + :<|> v0Handler + :<|> v1Handler + :<|> internalHandler where -- TODO: Not sure if we want to support the V0 API with the new wallet. -- For now I'm assuming we're not going to. -- -- TODO: It'd be nicer to not throw an exception here, but servant doesn't -- make this very easy at the moment. - v0Handler = error "V0 API no longer supported" - v1Handler = V1.handlers w + v0Handler = error "V0 API no longer supported" + v1Handler = V1.handlers w + internalHandler = error "Internal API not yet defined" -walletDevServer :: ActiveWalletLayer IO - -> RunMode - -> Server WalletDevAPI -walletDevServer w runMode = devHandler :<|> walletHandler - where - devHandler = Dev.handlers runMode - walletHandler = walletServer w walletDocServer :: (HasCompileInfo, HasUpdateConfiguration) => Server WalletDocAPI walletDocServer = v0DocHandler :<|> v1DocHandler where v0DocHandler = error "V0 API no longer supported" v1DocHandler = swaggerSchemaUIServer (Swagger.api (compileInfo, curSoftwareVersion) v1API Swagger.highLevelDescription) - -walletDevDocServer :: (HasCompileInfo, HasUpdateConfiguration) => Server WalletDevDocAPI -walletDevDocServer = devDocHandler :<|> walletDocServer - where - devDocHandler = swaggerSchemaUIServer (Swagger.api (compileInfo, curSoftwareVersion) devAPI Swagger.highLevelShortDescription) diff --git a/wallet-new/src/Cardano/Wallet/Server/Plugins.hs b/wallet-new/src/Cardano/Wallet/Server/Plugins.hs index b7f65f6c1f8..a55dfe9b6d1 100644 --- a/wallet-new/src/Cardano/Wallet/Server/Plugins.hs +++ b/wallet-new/src/Cardano/Wallet/Server/Plugins.hs @@ -108,13 +108,8 @@ walletDocumentation WalletBackendParams {..} = pure $ \_ -> where application :: WalletWebMode Application application = do - let app = - if isDebugMode walletRunMode then - Servant.serve API.walletDevDocAPI LegacyServer.walletDevDocServer - else - Servant.serve API.walletDocAPI LegacyServer.walletDocServer + let app = Servant.serve API.walletDocAPI LegacyServer.walletDocServer return $ withMiddleware walletRunMode app - tls = if isDebugMode walletRunMode then Nothing else walletTLSParams @@ -146,25 +141,19 @@ legacyWalletBackend pm WalletBackendParams {..} ntpStatus = pure $ \diffusion -> -- Gets the Wai `Application` to run. getApplication :: Diffusion WalletWebMode -> WalletWebMode Application getApplication diffusion = do - logInfo "Wallet Web API has STARTED!" - wsConn <- getWalletWebSockets - ctx <- V0.walletWebModeContext - let app = upgradeApplicationWS wsConn $ - if isDebugMode walletRunMode then - Servant.serve API.walletDevAPI $ LegacyServer.walletDevServer + logInfo "Wallet Web API has STARTED!" + wsConn <- getWalletWebSockets + ctx <- V0.walletWebModeContext + return + $ withMiddleware walletRunMode + $ upgradeApplicationWS wsConn + $ Servant.serve API.walletAPI + $ LegacyServer.walletServer (V0.convertHandler ctx) pm diffusion ntpStatus walletRunMode - else - Servant.serve API.walletAPI $ LegacyServer.walletServer - (V0.convertHandler ctx) - pm - diffusion - ntpStatus - - return $ withMiddleware walletRunMode app exceptionHandler :: SomeException -> Response exceptionHandler se = @@ -228,10 +217,7 @@ walletBackend protocolMagic (NewWalletBackendParams WalletBackendParams{..}) (pa getApplication active = do logInfo "New wallet API has STARTED!" return $ withMiddleware walletRunMode $ - if isDebugMode walletRunMode then - Servant.serve API.walletDevAPI $ Server.walletDevServer active walletRunMode - else - Servant.serve API.walletAPI $ Server.walletServer active + Servant.serve API.walletAPI $ Server.walletServer active walletRunMode lower :: env -> ReaderT env IO a -> IO a lower env m = runReaderT m env diff --git a/wallet-new/src/Cardano/Wallet/WalletLayer/Kernel.hs b/wallet-new/src/Cardano/Wallet/WalletLayer/Kernel.hs index d0e742b6f98..a006e037f1c 100644 --- a/wallet-new/src/Cardano/Wallet/WalletLayer/Kernel.hs +++ b/wallet-new/src/Cardano/Wallet/WalletLayer/Kernel.hs @@ -97,7 +97,7 @@ bracketPassiveWallet logFunction keystore f = passiveWalletLayer wallet invoke = PassiveWalletLayer { _pwlCreateWallet = - \(V1.NewWallet (V1 mnemonic) mbSpendingPassword v1AssuranceLevel v1WalletName operation) -> do + \(V1.NewWallet (V1.BackupPhrase mnemonic) mbSpendingPassword v1AssuranceLevel v1WalletName operation) -> do liftIO $ limitExecutionTimeTo (30 :: Second) CreateWalletTimeLimitReached $ do case operation of V1.RestoreWallet -> error "Not implemented, see [CBR-243]." diff --git a/wallet-new/src/Cardano/Wallet/WalletLayer/Legacy.hs b/wallet-new/src/Cardano/Wallet/WalletLayer/Legacy.hs index 7a2934c7985..6e58b96cded 100644 --- a/wallet-new/src/Cardano/Wallet/WalletLayer/Legacy.hs +++ b/wallet-new/src/Cardano/Wallet/WalletLayer/Legacy.hs @@ -21,9 +21,9 @@ import Cardano.Wallet.WalletLayer.Types (ActiveWalletLayer (..), import Cardano.Wallet.API.V1.Migration (migrate) import Cardano.Wallet.API.V1.Migration.Types () import Cardano.Wallet.API.V1.Types (Account, AccountIndex, - AccountUpdate, Address, NewAccount (..), NewAddress, - NewWallet (..), V1 (..), Wallet, WalletId, - WalletOperation (..), WalletUpdate) + AccountUpdate, Address, BackupPhrase (..), + NewAccount (..), NewAddress, NewWallet (..), V1 (..), + Wallet, WalletId, WalletOperation (..), WalletUpdate) import Cardano.Wallet.Kernel.Diffusion (WalletDiffusion (..)) import Pos.Client.KeyStorage (MonadKeys) @@ -123,9 +123,8 @@ pwlCreateWallet => NewWallet -> m (Either CreateWalletError Wallet) pwlCreateWallet NewWallet{..} = do - let spendingPassword = fromMaybe mempty $ coerce newwalSpendingPassword - let backupPhrase = CBackupPhrase $ coerce newwalBackupPhrase + let backupPhrase = CBackupPhrase $ unBackupPhrase newwalBackupPhrase initMeta <- CWalletMeta <$> pure newwalName <*> migrate newwalAssuranceLevel diff --git a/wallet-new/test/DevelopmentSpec.hs b/wallet-new/test/InternalAPISpec.hs similarity index 90% rename from wallet-new/test/DevelopmentSpec.hs rename to wallet-new/test/InternalAPISpec.hs index 89ab8b7e73e..789475f6aa5 100644 --- a/wallet-new/test/DevelopmentSpec.hs +++ b/wallet-new/test/InternalAPISpec.hs @@ -12,7 +12,7 @@ {-# LANGUAGE UndecidableInstances #-} -- Spec for testing `development` endpoints -module DevelopmentSpec (spec) where +module InternalAPISpec (spec) where import Universum @@ -27,8 +27,7 @@ import Test.Hspec.QuickCheck (modifyMaxSuccess) import Test.Pos.Configuration (withDefConfigurations) import Test.Pos.Wallet.Web.Mode (walletPropertySpec) -import Cardano.Wallet.API.Development.LegacyHandlers - (deleteSecretKeys) +import Cardano.Wallet.API.Internal.Handlers (resetWalletState) import Cardano.Wallet.Server.CLI (RunMode (..)) import Data.Default (def) import Servant @@ -49,7 +48,7 @@ deleteAllSecretKeysSpec = do assertProperty (not $ null sKeys) "Something went wrong: Secret key has not been added." - _ <- lift $ deleteSecretKeys DebugMode + _ <- lift $ resetWalletState DebugMode sKeys' <- lift getSecretKeysPlain assertProperty (null sKeys') "Oooops, secret keys not have been deleted in debug mode" @@ -59,7 +58,7 @@ deleteAllSecretKeysSpec = do sKeys <- lift getSecretKeysPlain assertProperty (not $ null sKeys) "Something went wrong: Secret key has not been added." - _ <- lift $ catch (deleteSecretKeys ProductionMode) (\(_ :: SomeException) -> pure NoContent) + _ <- lift $ catch (resetWalletState ProductionMode) (\(_ :: SomeException) -> pure NoContent) -- ^ Catch `ServantErr` throwing from `deleteSecretKeys` to not fail the test before end sKeys' <- lift getSecretKeysPlain assertProperty (not $ null sKeys') diff --git a/wallet-new/test/MarshallingSpec.hs b/wallet-new/test/MarshallingSpec.hs index 12ad689b894..a030acc4ab1 100644 --- a/wallet-new/test/MarshallingSpec.hs +++ b/wallet-new/test/MarshallingSpec.hs @@ -17,8 +17,6 @@ import Test.QuickCheck import Test.QuickCheck.Instances () import qualified Test.QuickCheck.Property as Property -import Pos.Util.Mnemonic (Mnemonic) - import qualified Pos.Core as Core import qualified Pos.Core.Update as Core @@ -34,9 +32,10 @@ spec :: Spec spec = parallel $ describe "Marshalling & Unmarshalling" $ do parallel $ describe "Roundtrips" $ do -- Aeson roundrips - aesonRoundtripProp @(V1 (Mnemonic 12)) Proxy aesonRoundtripProp @Account Proxy aesonRoundtripProp @AssuranceLevel Proxy + aesonRoundtripProp @BackupPhrase Proxy + aesonRoundtripProp @Redemption Proxy aesonRoundtripProp @(V1 Core.SoftwareVersion) Proxy aesonRoundtripProp @NodeSettings Proxy aesonRoundtripProp @Payment Proxy diff --git a/wallet-new/test/Spec.hs b/wallet-new/test/Spec.hs index 9ce1f467b87..74d1afcd32f 100644 --- a/wallet-new/test/Spec.hs +++ b/wallet-new/test/Spec.hs @@ -13,7 +13,7 @@ import Test.QuickCheck import Cardano.Wallet.API.V1.Types import qualified APISpec as API -import qualified DevelopmentSpec as Dev +import qualified InternalAPISpec as InternalAPI import qualified MarshallingSpec as Marshalling import qualified RequestSpec as ReqSpec import qualified SwaggerSpec as Swagger @@ -22,7 +22,7 @@ import qualified WalletHandlersSpec as WalletHandlers -- | Tests whether or not some instances (JSON, Bi, etc) roundtrips. main :: IO () main = hspec $ do - Dev.spec + InternalAPI.spec Marshalling.spec API.spec Swagger.spec diff --git a/wallet-new/test/unit/Test/Spec/CreateWallet.hs b/wallet-new/test/unit/Test/Spec/CreateWallet.hs index 474679af549..5ba11109735 100644 --- a/wallet-new/test/unit/Test/Spec/CreateWallet.hs +++ b/wallet-new/test/unit/Test/Spec/CreateWallet.hs @@ -55,7 +55,7 @@ genNewWalletRq = do walletName <- pick arbitrary spendingPassword <- pick (frequency [(20, pure Nothing), (80, Just <$> arbitrary)]) mnemonic <- BIP39.entropyToMnemonic <$> liftIO (BIP39.genEntropy @(BIP39.EntropySize 12)) - return $ V1.NewWallet (V1.V1 mnemonic) + return $ V1.NewWallet (V1.BackupPhrase mnemonic) spendingPassword assuranceLevel walletName @@ -111,7 +111,7 @@ spec = describe "CreateWallet" $ do V1.NormalAssurance -> AssuranceLevelNormal V1.StrictAssurance -> AssuranceLevelStrict res <- Kernel.createHdWallet wallet - (coerce newwalBackupPhrase) + (V1.unBackupPhrase newwalBackupPhrase) (maybe emptyPassphrase coerce newwalSpendingPassword) hdAssuranceLevel (WalletName newwalName) diff --git a/wallet/Makefile b/wallet/Makefile new file mode 100644 index 00000000000..f117806d839 --- /dev/null +++ b/wallet/Makefile @@ -0,0 +1,13 @@ +help: ## Print documentation + @grep -E '^[a-zA-Z_-]+:.*?## .*$$' $(MAKEFILE_LIST) | sort | awk 'BEGIN {FS = ":.*?## "}; {printf "\033[36m%-30s\033[0m %s\n", $$1, $$2}' + +ghcid: ## Run ghcid with the wallet-new project + ghcid \ + --command "stack ghci cardano-sl-wallet --ghci-options=-fno-code" + +ghcid-test: ## Have ghcid run the test suite for the wallet-new-specs on successful recompile + ghcid \ + --command "stack ghci cardano-sl-wallet:lib cardano-sl-wallet:test:cardano-wallet-test --ghci-options=-fobject-code" \ + --test "main" + +.PHONY: ghcid ghcid-test help