11{-# LANGUAGE DataKinds #-}
2+ {-# LANGUAGE FlexibleContexts #-}
23{-# LANGUAGE GADTs #-}
34{-# LANGUAGE NamedFieldPuns #-}
5+ {-# LANGUAGE NumericUnderscores #-}
46{-# LANGUAGE OverloadedStrings #-}
7+ {-# LANGUAGE RankNTypes #-}
58{-# LANGUAGE ScopedTypeVariables #-}
69
710module Testnet.Components.Query
@@ -20,21 +23,24 @@ module Testnet.Components.Query
2023 , findUtxosWithAddress
2124 , findLargestUtxoWithAddress
2225 , findLargestUtxoForPaymentKey
26+ , assertNewEpochState
27+ , watchEpochStateView
2328 ) where
2429
2530import Cardano.Api as Api
26- import Cardano.Api.Ledger (Credential , DRepState , KeyRole (DRepRole ), StandardCrypto )
31+ import Cardano.Api.Ledger (Credential , DRepState , EpochInterval (.. ), KeyRole (DRepRole ),
32+ StandardCrypto )
2733import Cardano.Api.Shelley (ShelleyLedgerEra , fromShelleyTxIn , fromShelleyTxOut )
2834
2935import qualified Cardano.Ledger.Api as L
30- import Cardano.Ledger.BaseTypes (EpochInterval , addEpochInterval )
3136import qualified Cardano.Ledger.Coin as L
3237import qualified Cardano.Ledger.Conway.Governance as L
3338import qualified Cardano.Ledger.Conway.PParams as L
3439import qualified Cardano.Ledger.Shelley.LedgerState as L
3540import qualified Cardano.Ledger.UTxO as L
3641
3742import Control.Exception.Safe (MonadCatch )
43+ import Control.Monad (void )
3844import Control.Monad.Trans.Resource
3945import Control.Monad.Trans.State.Strict (put )
4046import Data.Bifunctor (bimap )
@@ -50,7 +56,7 @@ import qualified Data.Text as T
5056import Data.Type.Equality
5157import GHC.Exts (IsList (.. ))
5258import GHC.Stack
53- import Lens.Micro (to , (^.) )
59+ import Lens.Micro (Lens' , to , (^.) )
5460
5561import Testnet.Property.Assert
5662import Testnet.Property.Util (runInBackground )
@@ -94,9 +100,9 @@ waitForEpochs
94100 => EpochStateView
95101 -> EpochInterval -- ^ Number of epochs to wait
96102 -> m EpochNo -- ^ The epoch number reached
97- waitForEpochs epochStateView@ EpochStateView {nodeConfigPath, socketPath} interval = withFrozenCallStack $ do
98- currentEpoch <- getCurrentEpochNo epochStateView
99- waitUntilEpoch nodeConfigPath socketPath $ addEpochInterval currentEpoch interval
103+ waitForEpochs epochStateView interval = withFrozenCallStack $ do
104+ void $ watchEpochStateView epochStateView ( const $ pure Nothing ) interval
105+ getCurrentEpochNo epochStateView
100106
101107-- | A read-only mutable pointer to an epoch state, updated automatically
102108data EpochStateView = EpochStateView
@@ -353,3 +359,70 @@ getCurrentEpochNo
353359getCurrentEpochNo epochStateView = withFrozenCallStack $ do
354360 AnyNewEpochState _ newEpochState <- getEpochState epochStateView
355361 pure $ newEpochState ^. L. nesELL
362+
363+ -- | Assert that the value pointed by the @lens@ in the epoch state is the same as the @expected@ value
364+ -- or it becomes the same within the @maxWait@ epochs. If the value is not reached within the time frame,
365+ -- the test fails.
366+ assertNewEpochState
367+ :: forall m era value .
368+ (Show value , MonadAssertion m , MonadTest m , MonadIO m , Eq value , HasCallStack )
369+ => EpochStateView -- ^ Current epoch state view. It can be obtained using the 'getEpochStateView' function.
370+ -> ConwayEraOnwards era -- ^ The ConwayEraOnwards witness for current era.
371+ -> value -- ^ The expected value to check in the epoch state.
372+ -> EpochInterval -- ^ The maximum wait time in epochs.
373+ -> Lens' (L. NewEpochState (ShelleyLedgerEra era )) value -- ^ The lens to access the specific value in the epoch state.
374+ -> m ()
375+ assertNewEpochState epochStateView ceo expected maxWait lens = withFrozenCallStack $ do
376+ let sbe = conwayEraOnwardsToShelleyBasedEra ceo
377+ mStateView <- watchEpochStateView epochStateView (checkEpochState sbe) maxWait
378+ case mStateView of
379+ Just () -> pure ()
380+ Nothing -> do epochState <- getEpochState epochStateView
381+ val <- getFromEpochState sbe epochState
382+ if val == expected
383+ then pure ()
384+ else H. failMessage callStack $ unlines
385+ [ " assertNewEpochState: expected value not reached within the time frame."
386+ , " Expected value: " <> show expected
387+ , " Actual value: " <> show val
388+ ]
389+ where
390+ checkEpochState :: HasCallStack
391+ => ShelleyBasedEra era -> AnyNewEpochState -> m (Maybe () )
392+ checkEpochState sbe newEpochState = do
393+ val <- getFromEpochState sbe newEpochState
394+ return $ if val == expected then Just () else Nothing
395+
396+ getFromEpochState :: HasCallStack
397+ => ShelleyBasedEra era -> AnyNewEpochState -> m value
398+ getFromEpochState sbe (AnyNewEpochState actualEra newEpochState) = do
399+ Refl <- either error pure $ assertErasEqual sbe actualEra
400+ return $ newEpochState ^. lens
401+
402+ -- | Watch the epoch state view until the guard function returns 'Just' or the timeout epoch is reached.
403+ -- Wait for at most @maxWait@ epochs.
404+ -- The function will return the result of the guard function if it is met, otherwise it will return @Nothing@.
405+ watchEpochStateView
406+ :: forall m a . (HasCallStack , MonadIO m , MonadTest m , MonadAssertion m )
407+ => EpochStateView -- ^ The info to access the epoch state
408+ -> (AnyNewEpochState -> m (Maybe a )) -- ^ The guard function (@Just@ if the condition is met, @Nothing@ otherwise)
409+ -> EpochInterval -- ^ The maximum number of epochs to wait
410+ -> m (Maybe a )
411+ watchEpochStateView epochStateView f (EpochInterval maxWait) = withFrozenCallStack $ do
412+ AnyNewEpochState _ newEpochState <- getEpochState epochStateView
413+ let EpochNo currentEpoch = L. nesEL newEpochState
414+ go (EpochNo $ currentEpoch + fromIntegral maxWait)
415+ where
416+ go :: EpochNo -> m (Maybe a )
417+ go (EpochNo timeout) = do
418+ epochState@ (AnyNewEpochState _ newEpochState') <- getEpochState epochStateView
419+ let EpochNo currentEpoch = L. nesEL newEpochState'
420+ condition <- f epochState
421+ case condition of
422+ Just result -> pure (Just result)
423+ Nothing -> do
424+ if currentEpoch > timeout
425+ then pure Nothing
426+ else do
427+ H. threadDelay 10_000
428+ go (EpochNo timeout)
0 commit comments