Skip to content

Commit

Permalink
Test deposit REST module
Browse files Browse the repository at this point in the history
  • Loading branch information
paolino committed Sep 10, 2024
1 parent c20251d commit 19cecf8
Show file tree
Hide file tree
Showing 2 changed files with 152 additions and 0 deletions.
1 change: 1 addition & 0 deletions lib/customer-deposit-wallet/customer-deposit-wallet.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -171,6 +171,7 @@ test-suite unit
other-modules:
Cardano.Wallet.Deposit.HTTP.JSON.JSONSpec
Cardano.Wallet.Deposit.HTTP.OpenAPISpec
Cardano.Wallet.Deposit.RESTSpec
Paths_customer_deposit_wallet
Spec

Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,151 @@
module Cardano.Wallet.Deposit.RESTSpec
( spec
)
where

import Prelude

import Cardano.Crypto.Wallet
( XPub
, generate
, toXPub
)
import Cardano.Wallet.Deposit.IO
( WalletBootEnv (WalletBootEnv)
)
import Cardano.Wallet.Deposit.IO.Resource
( ErrResourceMissing (..)
, withResource
)
import Cardano.Wallet.Deposit.REST
( ErrCreatingDatabase (..)
, ErrDatabase (..)
, ErrLoadingDatabase (..)
, ErrWalletResource (..)
, WalletResourceM
, availableBalance
, initXPubWallet
, loadWallet
, runWalletResourceM
, walletExists
)
import Control.Concurrent
( threadDelay
)
import Control.Monad.IO.Class
( MonadIO (..)
)
import System.IO.Temp
( withSystemTempDirectory
)
import Test.Hspec
( Spec
, describe
, it
, shouldBe
)

import qualified Cardano.Wallet.Deposit.Read as Read
import qualified Data.ByteString.Char8 as B8

fakeBootEnv :: WalletBootEnv IO
fakeBootEnv = WalletBootEnv undefined undefined undefined

xpub :: XPub
xpub =
toXPub
$ generate (B8.pack "random seed for a testing xpub lala") B8.empty

letItInitialize :: WalletResourceM ()
letItInitialize = liftIO $ threadDelay 100000

onSuccess :: (Show e, MonadFail m) => Either e a -> (a -> m b) -> m b
onSuccess (Left e) _ = fail $ show e
onSuccess (Right a) f = f a

matchEmptyValue :: Show e => Either e Read.Value -> IO ()
matchEmptyValue x = onSuccess x $ \v -> v `shouldBe` mempty

withWallet :: WalletResourceM a -> IO (Either ErrWalletResource a)
withWallet f = withResource $ runWalletResourceM f

withInitializedWallet
:: FilePath
-> WalletResourceM a
-> IO (Either ErrWalletResource a)
withInitializedWallet dir f = withWallet $ do
initXPubWallet fakeBootEnv dir xpub 0
letItInitialize
f

withLoadedWallet
:: FilePath
-> WalletResourceM a
-> IO (Either ErrWalletResource a)
withLoadedWallet dir f = withWallet $ do
loadWallet fakeBootEnv dir
letItInitialize
f

doNothing :: WalletResourceM ()
doNothing = pure ()

inADirectory :: (FilePath -> IO a) -> IO a
inADirectory = withSystemTempDirectory "deposit-rest"

spec :: Spec
spec = do
describe "REST Deposit interface" $ do
it "can initialize a wallet"
$ inADirectory
$ \dir -> do
val <- withInitializedWallet dir availableBalance
matchEmptyValue val
it "can load an existing wallet"
$ inADirectory
$ \dir -> do
val <- withInitializedWallet dir availableBalance
onSuccess val $ \_ -> do
val' <- withLoadedWallet dir availableBalance
matchEmptyValue val'
it "cannot re-initialize a wallet"
$ inADirectory
$ \dir -> do
val <- withInitializedWallet dir doNothing
onSuccess val $ \_ -> do
val' <- withInitializedWallet dir availableBalance
case val' of
Left
( ErrNoWallet
( ErrFailedToInitialize
( ErrCreatingDatabase
(ErrDatabaseAlreadyExists fp)
)
)
)
| dir == fp -> pure ()
Left e -> fail $ show e
Right _ -> fail "Should have failed the query on re-init"
it "cannot load a non-existing wallet"
$ inADirectory
$ \dir -> do
val <- withLoadedWallet dir availableBalance
case val of
Left
( ErrNoWallet
( ErrFailedToInitialize
( ErrLoadingDatabase
(ErrDatabaseNotFound fp)
)
)
)
| dir == fp -> pure ()
Left e -> fail $ show e
Right _ -> fail "Should have failed the query on load"
it "can check if a wallet is present"
$ inADirectory
$ \dir -> do
r <- withInitializedWallet dir doNothing
onSuccess r $ \_ -> do
presence <- withWallet $ walletExists dir
onSuccess presence $ \p -> p `shouldBe` True

0 comments on commit 19cecf8

Please sign in to comment.