Skip to content

Commit

Permalink
Add mock funding to deposit wallet
Browse files Browse the repository at this point in the history
  • Loading branch information
paolino committed Nov 10, 2024
1 parent e29b2d2 commit da3ff75
Show file tree
Hide file tree
Showing 5 changed files with 78 additions and 8 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 @@ -178,6 +178,7 @@ library rest
, customer-deposit-wallet-pure
, deepseq
, delta-store
, delta-types
, directory
, filepath
, memory
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,9 @@ module Cardano.Wallet.Deposit.REST
, walletPublicIdentity
, deleteWallet
, deleteTheDepositWalletOnDisk
-- * Internals
, onWalletInstance

) where

import Prelude
Expand Down
Original file line number Diff line number Diff line change
@@ -1,42 +1,78 @@
{-# LANGUAGE NumericUnderscores #-}

module Cardano.Wallet.Deposit.REST.Start
( loadDepositWalletFromDisk
, newFakeBootEnv
, mockFundTheWallet
)
where

import Prelude

import Cardano.Wallet.Deposit.IO
( WalletBootEnv (..)
, onWalletState
)
import Cardano.Wallet.Deposit.IO.Network.Mock
( newNetworkEnvMock
)
import Cardano.Wallet.Deposit.IO.Network.Type
( mapBlock
)
import Cardano.Wallet.Deposit.Pure
( customerAddress
, rollForwardOne
)
import Cardano.Wallet.Deposit.Read
( ChainPoint (..)
, EraValue (..)
, mockNextBlock
)
import Cardano.Wallet.Deposit.REST
( WalletResource
( ErrWalletResource
, WalletResource
, loadWallet
, onWalletInstance
, runWalletResourceM
, walletExists
)
import Cardano.Wallet.Deposit.Write
( addTxOut
, emptyTxBody
, mkAda
, mkTx
, mkTxOut
)
import Control.Concurrent
( threadDelay
)
import Control.Monad
( when
)
import Control.Monad.IO.Class
( MonadIO (..)
)
import Control.Monad.Trans.Except
( ExceptT (..)
, runExceptT
)
import Control.Tracer
( Tracer
, stdoutTracer
, traceWith
)
import qualified Data.Delta as Delta
( Replace (..)
)
import Data.Functor.Contravariant
( (>$<)
)
import Data.Maybe
( fromMaybe
)

import qualified Cardano.Wallet.Deposit.Read as Read
import qualified Data.Delta.Update as Delta

lg :: (MonadIO m, Show a) => Tracer IO String -> String -> a -> m ()
lg tr p x = liftIO $ traceWith tr $ p <> ": " <> show x
Expand All @@ -48,16 +84,43 @@ loadDepositWalletFromDisk
-> WalletResource
-> IO ()
loadDepositWalletFromDisk tr dir env resource = do
result <- flip runWalletResourceM resource $ do
test <- walletExists dir
when test $ do
lg tr "Loading wallet from" dir
loadWallet env dir
lg tr "Wallet loaded from" dir
result <- runExceptT $ do
ExceptT $ flip runWalletResourceM resource $ do
test <- walletExists dir
when test $ do
lg tr "Loading wallet from" dir
loadWallet env dir
lg tr "Wallet loaded from" dir
liftIO $ threadDelay 1_000_000
ExceptT $ mockFundTheWallet resource
case result of
Left e -> error $ show e
Right _ -> pure ()

mockFundTheWallet :: WalletResource -> IO (Either ErrWalletResource ())
mockFundTheWallet resource = do
flip runWalletResourceM resource $ do
onWalletInstance $ \w ->
onWalletState w
$ Delta.update
$ Delta.Replace . f
where
f s =
let
address =
fromMaybe
(error "no address where it should be")
$ customerAddress 0 s
tx =
mkTx
$ fst
$ addTxOut
(mkTxOut address (mkAda 1_000_000))
emptyTxBody
block = mockNextBlock GenesisPoint [tx]
in
rollForwardOne (EraValue block) s

newFakeBootEnv :: IO (WalletBootEnv IO)
newFakeBootEnv =
WalletBootEnv
Expand Down
3 changes: 3 additions & 0 deletions lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/IO.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,9 @@ module Cardano.Wallet.Deposit.IO
-- *** Submit transactions
, submitTx
, listTxsInSubmission

-- * Internals
, onWalletState
) where

import Prelude
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -39,8 +39,8 @@ module Cardano.Wallet.Deposit.Write
, mkTxOut
, toConwayTx
, addTxIn
, emptyTxBody
, addTxOut
, emptyTxBody
) where

import Prelude
Expand Down

0 comments on commit da3ff75

Please sign in to comment.