1
1
{-# LANGUAGE DataKinds #-}
2
2
{-# LANGUAGE FlexibleContexts #-}
3
3
{-# LANGUAGE GADTs #-}
4
+ {-# LANGUAGE LambdaCase #-}
4
5
{-# LANGUAGE NamedFieldPuns #-}
5
6
{-# LANGUAGE NumericUnderscores #-}
6
7
{-# LANGUAGE OverloadedStrings #-}
9
10
10
11
module Testnet.Components.Query
11
12
( EpochStateView
12
- , checkDRepsNumber
13
- , checkDRepState
13
+ , getEpochStateView
14
14
, getEpochState
15
+ , getSlotNumber
16
+ , getBlockNumber
17
+ , watchEpochStateUpdate
18
+
15
19
, getMinDRepDeposit
16
20
, getMinGovActionDeposit
17
21
, getGovState
18
22
, getCurrentEpochNo
19
- , waitUntilEpoch
23
+
24
+ , TestnetWaitPeriod (.. )
20
25
, waitForEpochs
21
- , getEpochStateView
26
+ , waitUntilEpoch
27
+ , waitForBlocks
28
+ , retryUntilJustM
29
+
22
30
, findAllUtxos
23
31
, findUtxosWithAddress
24
32
, findLargestUtxoWithAddress
25
33
, findLargestUtxoForPaymentKey
34
+
35
+ , checkDRepsNumber
36
+ , checkDRepState
26
37
, assertNewEpochState
27
- , watchEpochStateView
28
38
) where
29
39
30
40
import Cardano.Api as Api
@@ -40,7 +50,7 @@ import qualified Cardano.Ledger.Shelley.LedgerState as L
40
50
import qualified Cardano.Ledger.UTxO as L
41
51
42
52
import Control.Exception.Safe (MonadCatch )
43
- import Control.Monad ( void )
53
+ import Control.Monad
44
54
import Control.Monad.Trans.Resource
45
55
import Control.Monad.Trans.State.Strict (put )
46
56
import Data.Bifunctor (bimap )
@@ -49,11 +59,12 @@ import Data.List (sortOn)
49
59
import Data.Map.Strict (Map )
50
60
import qualified Data.Map.Strict as M
51
61
import qualified Data.Map.Strict as Map
52
- import Data.Maybe ( listToMaybe )
62
+ import Data.Maybe
53
63
import Data.Ord (Down (.. ))
54
64
import Data.Text (Text )
55
65
import qualified Data.Text as T
56
66
import Data.Type.Equality
67
+ import Data.Word (Word64 )
57
68
import GHC.Exts (IsList (.. ))
58
69
import GHC.Stack
59
70
import Lens.Micro (Lens' , to , (^.) )
@@ -101,28 +112,135 @@ waitForEpochs
101
112
-> EpochInterval -- ^ Number of epochs to wait
102
113
-> m EpochNo -- ^ The epoch number reached
103
114
waitForEpochs epochStateView interval = withFrozenCallStack $ do
104
- void $ watchEpochStateView epochStateView ( const $ pure Nothing ) interval
115
+ void $ watchEpochStateUpdate epochStateView interval $ \ _ -> pure Nothing
105
116
getCurrentEpochNo epochStateView
106
117
118
+ -- | Wait for the requested number of blocks
119
+ waitForBlocks
120
+ :: HasCallStack
121
+ => MonadIO m
122
+ => MonadTest m
123
+ => MonadAssertion m
124
+ => MonadCatch m
125
+ => EpochStateView
126
+ -> Word64 -- ^ Number of blocks to wait
127
+ -> m BlockNo -- ^ The block number reached
128
+ waitForBlocks epochStateView numberOfBlocks = withFrozenCallStack $ do
129
+ BlockNo startingBlockNumber <- getBlockNumber epochStateView
130
+ H. note_ $ " Current block number: " <> show startingBlockNumber <> " . "
131
+ <> " Waiting for " <> show numberOfBlocks <> " blocks"
132
+ H. noteShowM . H. nothingFailM . fmap (fmap BlockNo ) $
133
+ watchEpochStateUpdate epochStateView (EpochInterval maxBound ) $ \ (_, _, BlockNo blockNumber) ->
134
+ pure $
135
+ if blockNumber >= startingBlockNumber + numberOfBlocks
136
+ then Just blockNumber
137
+ else Nothing
138
+
139
+ data TestnetWaitPeriod
140
+ = WaitForEpochs EpochInterval
141
+ | WaitForBlocks Word64
142
+ | WaitForSlots Word64
143
+ deriving Eq
144
+
145
+ instance Show TestnetWaitPeriod where
146
+ show = \ case
147
+ WaitForEpochs (EpochInterval n) -> " WaitForEpochs " <> show n
148
+ WaitForBlocks n -> " WaitForBlocks " <> show n
149
+ WaitForSlots n -> " WaitForSlots " <> show n
150
+
151
+ -- | Retries the action until it returns 'Just' or the timeout is reached
152
+ retryUntilJustM
153
+ :: HasCallStack
154
+ => MonadIO m
155
+ => MonadTest m
156
+ => MonadAssertion m
157
+ => EpochStateView
158
+ -> TestnetWaitPeriod -- ^ timeout for an operation
159
+ -> m (Maybe a )
160
+ -> m a
161
+ retryUntilJustM esv timeout act = withFrozenCallStack $ do
162
+ startingValue <- getCurrentValue
163
+ go startingValue
164
+ where
165
+ go startingValue = withFrozenCallStack $ do
166
+ cv <- getCurrentValue
167
+ when (timeoutW64 + startingValue < cv) $ do
168
+ H. note_ $ " Action did not result in 'Just' - waited for: " <> show timeout
169
+ H. failure
170
+ act >>= \ case
171
+ Just a -> pure a
172
+ Nothing -> do
173
+ H. threadDelay 300_000
174
+ go startingValue
175
+
176
+ getCurrentValue = withFrozenCallStack $
177
+ case timeout of
178
+ WaitForEpochs _ -> unEpochNo <$> getCurrentEpochNo esv
179
+ WaitForSlots _ -> unSlotNo <$> getSlotNumber esv
180
+ WaitForBlocks _ -> unBlockNo <$> getBlockNumber esv
181
+
182
+ timeoutW64 =
183
+ case timeout of
184
+ WaitForEpochs (EpochInterval n) -> fromIntegral n
185
+ WaitForSlots n -> n
186
+ WaitForBlocks n -> n
187
+
107
188
-- | A read-only mutable pointer to an epoch state, updated automatically
108
189
data EpochStateView = EpochStateView
109
190
{ nodeConfigPath :: ! (NodeConfigFile In )
191
+ -- ^ node configuration file path
110
192
, socketPath :: ! SocketPath
111
- , epochStateView :: ! (IORef (Maybe AnyNewEpochState ))
193
+ -- ^ node socket path, to which foldEpochState is connected to
194
+ , epochStateView :: ! (IORef (Maybe (AnyNewEpochState , SlotNo , BlockNo )))
195
+ -- ^ Automatically updated current NewEpochState. Use 'getEpochState', 'getBlockNumber', 'getSlotNumber'
196
+ -- to access the values.
112
197
}
113
198
114
199
-- | Get epoch state from the view. If the state isn't available, retry waiting up to 15 seconds. Fails when
115
200
-- the state is not available after 15 seconds.
116
- getEpochState :: MonadTest m
117
- => MonadAssertion m
118
- => MonadIO m
119
- => EpochStateView
120
- -> m AnyNewEpochState
121
- getEpochState EpochStateView {epochStateView} =
201
+ getEpochState
202
+ :: HasCallStack
203
+ => MonadTest m
204
+ => MonadAssertion m
205
+ => MonadIO m
206
+ => EpochStateView
207
+ -> m AnyNewEpochState
208
+ getEpochState epochStateView =
209
+ withFrozenCallStack $ getEpochStateDetails epochStateView $ \ (nes, _, _) -> pure nes
210
+
211
+ getBlockNumber
212
+ :: HasCallStack
213
+ => MonadIO m
214
+ => MonadTest m
215
+ => MonadAssertion m
216
+ => EpochStateView
217
+ -> m BlockNo -- ^ The number of last produced block
218
+ getBlockNumber epochStateView =
219
+ withFrozenCallStack $ getEpochStateDetails epochStateView $ \ (_, _, blockNumber) -> pure blockNumber
220
+
221
+ getSlotNumber
222
+ :: HasCallStack
223
+ => MonadIO m
224
+ => MonadTest m
225
+ => MonadAssertion m
226
+ => EpochStateView
227
+ -> m SlotNo -- ^ The current slot number
228
+ getSlotNumber epochStateView =
229
+ withFrozenCallStack $ getEpochStateDetails epochStateView $ \ (_, slotNumber, _) -> pure slotNumber
230
+
231
+ -- | Utility function for accessing epoch state in `IORef`
232
+ getEpochStateDetails
233
+ :: HasCallStack
234
+ => MonadAssertion m
235
+ => MonadTest m
236
+ => MonadIO m
237
+ => EpochStateView
238
+ -> ((AnyNewEpochState , SlotNo , BlockNo ) -> m a )
239
+ -> m a
240
+ getEpochStateDetails EpochStateView {epochStateView} f =
122
241
withFrozenCallStack $
123
242
H. byDurationM 0.5 15 " EpochStateView has not been initialized within 15 seconds" $
124
- H. evalIO (readIORef epochStateView) >>= maybe H. failure pure
125
-
243
+ H. evalIO (readIORef epochStateView) >>= maybe H. failure f
126
244
127
245
-- | Create a background thread listening for new epoch states. New epoch states are available to access
128
246
-- through 'EpochStateView', using query functions.
@@ -137,11 +255,38 @@ getEpochStateView
137
255
getEpochStateView nodeConfigFile socketPath = withFrozenCallStack $ do
138
256
epochStateView <- H. evalIO $ newIORef Nothing
139
257
runInBackground . runExceptT . foldEpochState nodeConfigFile socketPath QuickValidation (EpochNo maxBound ) Nothing
140
- $ \ epochState _slotNb _blockNb -> do
141
- liftIO $ writeIORef epochStateView ( Just epochState)
258
+ $ \ epochState slotNumber blockNumber -> do
259
+ liftIO . writeIORef epochStateView $ Just ( epochState, slotNumber, blockNumber )
142
260
pure ConditionNotMet
143
261
pure $ EpochStateView nodeConfigFile socketPath epochStateView
144
262
263
+ -- | Watch the epoch state view until the guard function returns 'Just' or the timeout epoch is reached.
264
+ -- Executes the guard function every 300ms. Waits for at most @maxWait@ epochs.
265
+ -- The function will return the result of the guard function if it is met within the number of epochs,
266
+ -- otherwise it will return @Nothing@.
267
+ watchEpochStateUpdate
268
+ :: forall m a . (HasCallStack , MonadIO m , MonadTest m , MonadAssertion m )
269
+ => EpochStateView -- ^ The info to access the epoch state
270
+ -> EpochInterval -- ^ The maximum number of epochs to wait
271
+ -> ((AnyNewEpochState , SlotNo , BlockNo ) -> m (Maybe a )) -- ^ The guard function (@Just@ if the condition is met, @Nothing@ otherwise)
272
+ -> m (Maybe a )
273
+ watchEpochStateUpdate epochStateView (EpochInterval maxWait) f = withFrozenCallStack $ do
274
+ AnyNewEpochState _ newEpochState <- getEpochState epochStateView
275
+ let EpochNo currentEpoch = L. nesEL newEpochState
276
+ go $ currentEpoch + fromIntegral maxWait
277
+ where
278
+ go :: Word64 -> m (Maybe a )
279
+ go timeout = do
280
+ newEpochStateDetails@ (AnyNewEpochState _ newEpochState', _, _) <- getEpochStateDetails epochStateView pure
281
+ let EpochNo currentEpoch = L. nesEL newEpochState'
282
+ f newEpochStateDetails >>= \ case
283
+ Just result -> pure (Just result)
284
+ Nothing
285
+ | currentEpoch > timeout -> pure Nothing
286
+ | otherwise -> do
287
+ H. threadDelay 300_000
288
+ go timeout
289
+
145
290
-- | Retrieve all UTxOs map from the epoch state view.
146
291
findAllUtxos
147
292
:: forall era m . HasCallStack
@@ -210,7 +355,7 @@ findLargestUtxoWithAddress epochStateView sbe address = withFrozenCallStack $ do
210
355
$ sortOn (\ (_, TxOut _ txOutValue _ _) -> Down $ txOutValueToLovelace txOutValue) utxos
211
356
212
357
-- | Retrieve a largest UTxO for a payment key info - a convenience wrapper for
213
- -- 'findLargestUtxoForPaymentKey '.
358
+ -- 'findLargestUtxoWithAddress '.
214
359
findLargestUtxoForPaymentKey
215
360
:: MonadTest m
216
361
=> MonadAssertion m
@@ -268,7 +413,7 @@ checkDRepState epochStateView@EpochStateView{nodeConfigPath, socketPath} sbe f =
268
413
currentEpoch <- getCurrentEpochNo epochStateView
269
414
let terminationEpoch = succ . succ $ currentEpoch
270
415
result <- H. evalIO . runExceptT $ foldEpochState nodeConfigPath socketPath QuickValidation terminationEpoch Nothing
271
- $ \ (AnyNewEpochState actualEra newEpochState) _slotNb _blockNb -> do
416
+ $ \ (AnyNewEpochState actualEra newEpochState) _slotNumber _blockNumber -> do
272
417
Refl <- either error pure $ assertErasEqual sbe actualEra
273
418
let dreps = shelleyBasedEraConstraints sbe newEpochState
274
419
^. L. nesEsL
@@ -364,65 +509,45 @@ getCurrentEpochNo epochStateView = withFrozenCallStack $ do
364
509
-- or it becomes the same within the @maxWait@ epochs. If the value is not reached within the time frame,
365
510
-- the test fails.
366
511
assertNewEpochState
367
- :: forall m era value .
368
- (Show value , MonadAssertion m , MonadTest m , MonadIO m , Eq value , HasCallStack )
512
+ :: forall m era value . HasCallStack
513
+ => Show value
514
+ => Eq value
515
+ => MonadAssertion m
516
+ => MonadTest m
517
+ => MonadIO m
369
518
=> 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.
519
+ -> ShelleyBasedEra era -- ^ The ShelleyBasedEra witness for current era.
372
520
-> 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.
521
+ -> Lens' (L. NewEpochState (ShelleyLedgerEra era )) value
522
+ -- ^ The lens to access the specific value in the epoch state.
523
+ -> value -- ^ The expected value to check in the epoch state.
374
524
-> 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
- ]
525
+ assertNewEpochState epochStateView sbe maxWait lens expected = withFrozenCallStack $ do
526
+ mStateView <- watchEpochStateUpdate epochStateView maxWait (const checkEpochState)
527
+ when (isNothing mStateView) $ do
528
+ val <- getFromEpochStateForEra
529
+ -- there's a tiny tiny chance that the value has changed since 'watchEpochStateUpdate'
530
+ -- so check it again
531
+ if val == expected
532
+ then pure ()
533
+ else H. failMessage callStack $ unlines
534
+ [ " assertNewEpochState: expected value not reached within the time frame."
535
+ , " Expected value: " <> show expected
536
+ , " Actual value: " <> show val
537
+ ]
389
538
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
539
+ checkEpochState
540
+ :: HasCallStack
541
+ => m (Maybe () )
542
+ checkEpochState = withFrozenCallStack $ do
543
+ val <- getFromEpochStateForEra
544
+ pure $ if val == expected then Just () else Nothing
545
+
546
+ getFromEpochStateForEra
547
+ :: HasCallStack
548
+ => m value
549
+ getFromEpochStateForEra = withFrozenCallStack $ getEpochStateDetails epochStateView $
550
+ \ (AnyNewEpochState actualEra newEpochState, _, _) -> do
551
+ Refl <- H. leftFail $ assertErasEqual sbe actualEra
552
+ pure $ newEpochState ^. lens
401
553
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