@@ -72,6 +72,7 @@ import Ouroboros.Consensus.Util hiding (Some)
72
72
import Ouroboros.Consensus.Util.Args
73
73
import Ouroboros.Consensus.Util.IOLike
74
74
import qualified Ouroboros.Network.AnchoredSeq as AS
75
+ import Ouroboros.Network.Protocol.LocalStateQuery.Type
75
76
import qualified System.Directory as Dir
76
77
import System.FS.API
77
78
import qualified System.FS.IO as FSIO
@@ -114,9 +115,11 @@ prop_sequential ::
114
115
QC. Property
115
116
prop_sequential maxSuccess mkTestArguments getLmdbDir fsOps as = QC. withMaxSuccess maxSuccess $
116
117
QC. monadicIO $ do
117
- ref <- lift $ initialEnvironment fsOps getLmdbDir mkTestArguments =<< initChainDB
118
- (_, env@ (Environment _ testInternals _ _ _ _ clean)) <- runPropertyStateT (runActions as) ref
118
+ reg <- lift $ unsafeNewRegistry
119
+ ref <- lift $ initialEnvironment fsOps getLmdbDir mkTestArguments reg =<< initChainDB
120
+ (_, env@ (Environment _ testInternals _ _ _ _ clean _)) <- runPropertyStateT (runActions as) ref
119
121
checkNoLeakedHandles env
122
+ lift $ closeRegistry reg
120
123
QC. run $ closeLedgerDB testInternals >> clean
121
124
QC. assert True
122
125
@@ -129,9 +132,10 @@ initialEnvironment ::
129
132
IO (SomeHasFS IO , IO () ) ->
130
133
IO (FilePath , IO () ) ->
131
134
(SecurityParam -> FilePath -> TestArguments IO ) ->
135
+ ResourceRegistry IO ->
132
136
ChainDB IO ->
133
137
IO Environment
134
- initialEnvironment fsOps getLmdbDir mkTestArguments cdb = do
138
+ initialEnvironment fsOps getLmdbDir mkTestArguments reg cdb = do
135
139
(sfs, cleanupFS) <- fsOps
136
140
(lmdbDir, cleanupLMDB) <- getLmdbDir
137
141
pure $
@@ -143,6 +147,7 @@ initialEnvironment fsOps getLmdbDir mkTestArguments cdb = do
143
147
sfs
144
148
(pure $ NumOpenHandles 0 )
145
149
(cleanupFS >> cleanupLMDB)
150
+ reg
146
151
147
152
{- ------------------------------------------------------------------------------
148
153
Arguments
@@ -280,6 +285,7 @@ instance StateModel Model where
280
285
Action Model (ExtLedgerState TestBlock EmptyMK , ExtLedgerState TestBlock EmptyMK )
281
286
Init :: SecurityParam -> Action Model ()
282
287
ValidateAndCommit :: Word64 -> [TestBlock ] -> Action Model ()
288
+ OpenAndCloseForker :: Action Model ()
283
289
284
290
actionName WipeLedgerDB {} = " WipeLedgerDB"
285
291
actionName TruncateSnapshots {} = " TruncateSnapshots"
@@ -288,6 +294,7 @@ instance StateModel Model where
288
294
actionName GetState {} = " GetState"
289
295
actionName Init {} = " Init"
290
296
actionName ValidateAndCommit {} = " ValidateAndCommit"
297
+ actionName OpenAndCloseForker = " OpenAndCloseForker"
291
298
292
299
arbitraryAction _ UnInit = Some . Init <$> QC. arbitrary
293
300
arbitraryAction _ model@ (Model chain secParam) =
@@ -316,6 +323,7 @@ instance StateModel Model where
316
323
)
317
324
, (1 , pure $ Some WipeLedgerDB )
318
325
, (1 , pure $ Some TruncateSnapshots )
326
+ , (1 , pure $ Some OpenAndCloseForker )
319
327
]
320
328
321
329
initialState = UnInit
@@ -357,6 +365,7 @@ instance StateModel Model where
357
365
nextState state WipeLedgerDB _var = state
358
366
nextState state TruncateSnapshots _var = state
359
367
nextState state (DropAndRestore n) _var = modelRollback n state
368
+ nextState state OpenAndCloseForker _var = state
360
369
nextState UnInit _ _ = error " Uninitialized model created a command different than Init"
361
370
362
371
precondition UnInit Init {} = True
@@ -526,25 +535,26 @@ data Environment
526
535
(SomeHasFS IO )
527
536
(IO NumOpenHandles )
528
537
(IO () )
538
+ (ResourceRegistry IO )
529
539
530
540
instance RunModel Model (StateT Environment IO ) where
531
541
perform _ (Init secParam) _ = do
532
- Environment _ _ chainDb mkArgs fs _ cleanup <- get
542
+ Environment _ _ chainDb mkArgs fs _ cleanup rr <- get
533
543
(ldb, testInternals, getNumOpenHandles) <- lift $ do
534
544
let args = mkArgs secParam
535
545
openLedgerDB (argFlavorArgs args) chainDb (argLedgerDbCfg args) fs
536
- put (Environment ldb testInternals chainDb mkArgs fs getNumOpenHandles cleanup)
546
+ put (Environment ldb testInternals chainDb mkArgs fs getNumOpenHandles cleanup rr )
537
547
perform _ WipeLedgerDB _ = do
538
- Environment _ testInternals _ _ _ _ _ <- get
548
+ Environment _ testInternals _ _ _ _ _ _ <- get
539
549
lift $ wipeLedgerDB testInternals
540
550
perform _ GetState _ = do
541
- Environment ldb _ _ _ _ _ _ <- get
551
+ Environment ldb _ _ _ _ _ _ _ <- get
542
552
lift $ atomically $ (,) <$> getImmutableTip ldb <*> getVolatileTip ldb
543
553
perform _ ForceTakeSnapshot _ = do
544
- Environment _ testInternals _ _ _ _ _ <- get
554
+ Environment _ testInternals _ _ _ _ _ _ <- get
545
555
lift $ takeSnapshotNOW testInternals TakeAtImmutableTip Nothing
546
556
perform _ (ValidateAndCommit n blks) _ = do
547
- Environment ldb _ chainDb _ _ _ _ <- get
557
+ Environment ldb _ chainDb _ _ _ _ _ <- get
548
558
lift $ do
549
559
atomically $
550
560
modifyTVar (dbBlocks chainDb) $
@@ -561,13 +571,19 @@ instance RunModel Model (StateT Environment IO) where
561
571
ValidateExceededRollBack {} -> error " Unexpected Rollback"
562
572
ValidateLedgerError (AnnLedgerError forker _ _) -> forkerClose forker >> error " Unexpected ledger error"
563
573
perform state@ (Model _ secParam) (DropAndRestore n) lk = do
564
- Environment _ testInternals chainDb _ _ _ _ <- get
574
+ Environment _ testInternals chainDb _ _ _ _ _ <- get
565
575
lift $ do
566
576
atomically $ modifyTVar (dbChain chainDb) (drop (fromIntegral n))
567
577
closeLedgerDB testInternals
568
578
perform state (Init secParam) lk
579
+ perform _ OpenAndCloseForker _ = do
580
+ Environment ldb _ _ _ _ _ _ rr <- get
581
+ eFrk <- lift $ LedgerDB. getForkerAtTarget ldb rr VolatileTip
582
+ case eFrk of
583
+ Left err -> error $ " Impossible: can't acquire forker at tip: " <> show err
584
+ Right frk -> lift $ forkerClose frk
569
585
perform _ TruncateSnapshots _ = do
570
- Environment _ testInternals _ _ _ _ _ <- get
586
+ Environment _ testInternals _ _ _ _ _ _ <- get
571
587
lift $ truncateSnapshots testInternals
572
588
perform UnInit _ _ = error " Uninitialized model created a command different than Init"
573
589
@@ -622,7 +638,7 @@ mkTrackOpenHandles = do
622
638
623
639
-- | Check that we didn't leak any 'LedgerTablesHandle's (with V2 only).
624
640
checkNoLeakedHandles :: Environment -> QC. PropertyM IO ()
625
- checkNoLeakedHandles (Environment _ testInternals _ _ _ getNumOpenHandles _) = do
641
+ checkNoLeakedHandles (Environment _ testInternals _ _ _ getNumOpenHandles _ _ ) = do
626
642
expected <- liftIO $ NumOpenHandles <$> LedgerDB. getNumLedgerTablesHandles testInternals
627
643
actual <- liftIO getNumOpenHandles
628
644
QC. assertWith (actual == expected) $
0 commit comments