@@ -302,7 +302,13 @@ instance StateModel Model where
302302 min
303303 (fromIntegral . AS. length $ chain)
304304 (BT. unNonZero $ maxRollbacks secParam)
305- numRollback <- QC. choose (0 , maxRollback)
305+ numRollback <-
306+ frequency
307+ [ (10 , QC. choose (0 , maxRollback))
308+ , -- Sometimes generate invalid 'ValidateAndCommit's for
309+ -- negative testing.
310+ (1 , QC. choose (maxRollback + 1 , maxRollback + 5 ))
311+ ]
306312 numNewBlocks <- QC. choose (numRollback, numRollback + 2 )
307313 let
308314 chain' = case modelRollback numRollback model of
@@ -371,6 +377,9 @@ instance StateModel Model where
371377 precondition _ Init {} = False
372378 precondition _ _ = True
373379
380+ validFailingAction Model {} ValidateAndCommit {} = True
381+ validFailingAction _ _ = False
382+
374383{- ------------------------------------------------------------------------------
375384 Mocked ChainDB
376385-------------------------------------------------------------------------------}
@@ -527,22 +536,29 @@ data Environment
527536 (IO NumOpenHandles )
528537 (IO () )
529538
539+ data LedgerDBError = ErrorValidateExceededRollback
540+
530541instance RunModel Model (StateT Environment IO ) where
542+ type Error Model (StateT Environment IO ) = LedgerDBError
543+
531544 perform _ (Init secParam) _ = do
532545 Environment _ _ chainDb mkArgs fs _ cleanup <- get
533546 (ldb, testInternals, getNumOpenHandles) <- lift $ do
534547 let args = mkArgs secParam
535548 openLedgerDB (argFlavorArgs args) chainDb (argLedgerDbCfg args) fs
536549 put (Environment ldb testInternals chainDb mkArgs fs getNumOpenHandles cleanup)
550+ pure $ pure ()
537551 perform _ WipeLedgerDB _ = do
538552 Environment _ testInternals _ _ _ _ _ <- get
539553 lift $ wipeLedgerDB testInternals
554+ pure $ pure ()
540555 perform _ GetState _ = do
541556 Environment ldb _ _ _ _ _ _ <- get
542- lift $ atomically $ (,) <$> getImmutableTip ldb <*> getVolatileTip ldb
557+ lift $ fmap pure $ atomically $ (,) <$> getImmutableTip ldb <*> getVolatileTip ldb
543558 perform _ ForceTakeSnapshot _ = do
544559 Environment _ testInternals _ _ _ _ _ <- get
545560 lift $ takeSnapshotNOW testInternals TakeAtImmutableTip Nothing
561+ pure $ pure ()
546562 perform _ (ValidateAndCommit n blks) _ = do
547563 Environment ldb _ chainDb _ _ _ _ <- get
548564 lift $ do
@@ -558,7 +574,8 @@ instance RunModel Model (StateT Environment IO) where
558574 (reverse (map blockRealPoint blks) ++ ) . drop (fromIntegral n)
559575 atomically (forkerCommit forker)
560576 forkerClose forker
561- ValidateExceededRollBack {} -> error " Unexpected Rollback"
577+ pure $ pure ()
578+ ValidateExceededRollBack {} -> pure $ Left ErrorValidateExceededRollback
562579 ValidateLedgerError (AnnLedgerError forker _ _) -> forkerClose forker >> error " Unexpected ledger error"
563580 perform state@ (Model _ secParam) (DropAndRestore n) lk = do
564581 Environment _ testInternals chainDb _ _ _ _ <- get
@@ -569,6 +586,7 @@ instance RunModel Model (StateT Environment IO) where
569586 perform _ TruncateSnapshots _ = do
570587 Environment _ testInternals _ _ _ _ _ <- get
571588 lift $ truncateSnapshots testInternals
589+ pure $ pure ()
572590 perform UnInit _ _ = error " Uninitialized model created a command different than Init"
573591
574592 monitoring _ (ValidateAndCommit n _) _ _ = tabulate " Rollback depths" [show n]
@@ -602,6 +620,11 @@ instance RunModel Model (StateT Environment IO) where
602620 pure $ volSt == vol && immSt == imm
603621 postcondition _ _ _ _ = pure True
604622
623+ postconditionOnFailure _ ValidateAndCommit {} _ res = case res of
624+ Right () -> False <$ counterexamplePost " Unexpected success on invalid ValidateAndCommit"
625+ Left ErrorValidateExceededRollback -> pure True
626+ postconditionOnFailure _ _ _ _ = pure True
627+
605628{- ------------------------------------------------------------------------------
606629 Additional checks
607630-------------------------------------------------------------------------------}
0 commit comments