@@ -11,7 +11,6 @@ module Test.QuickCheck.StateModel (
1111 module Test.QuickCheck.StateModel.Variables ,
1212 StateModel (.. ),
1313 RunModel (.. ),
14- PostconditionM (.. ),
1514 WithUsedVars (.. ),
1615 Annotated (.. ),
1716 Step (.. ),
@@ -25,8 +24,6 @@ module Test.QuickCheck.StateModel (
2524 Env ,
2625 Generic ,
2726 IsPerformResult ,
28- monitorPost ,
29- counterexamplePost ,
3027 stateAfter ,
3128 runActions ,
3229 lookUpVar ,
@@ -40,16 +37,14 @@ module Test.QuickCheck.StateModel (
4037) where
4138
4239import Control.Monad
43- import Control.Monad.Reader
44- import Control.Monad.Writer (WriterT , runWriterT , tell )
4540import Data.Data
4641import Data.List
47- import Data.Monoid (Endo (.. ))
4842import Data.Set qualified as Set
4943import Data.Void
5044import GHC.Generics
5145import Test.QuickCheck as QC
5246import Test.QuickCheck.DynamicLogic.SmartShrinking
47+ import Test.QuickCheck.Extras (liftProperty )
5348import Test.QuickCheck.Monadic
5449import Test.QuickCheck.StateModel.Variables
5550
@@ -174,29 +169,6 @@ instance {-# OVERLAPPING #-} IsPerformResult Void a where
174169instance {-# OVERLAPPABLE #-} (PerformResult e a ~ Either e a ) => IsPerformResult e a where
175170 performResultToEither = id
176171
177- newtype PostconditionM m a = PostconditionM { runPost :: WriterT (Endo Property , Endo Property ) m a }
178- deriving (Functor , Applicative , Monad )
179-
180- instance MonadTrans PostconditionM where
181- lift = PostconditionM . lift
182-
183- evaluatePostCondition :: Monad m => PostconditionM m Bool -> PropertyM m ()
184- evaluatePostCondition post = do
185- (b, (Endo mon, Endo onFail)) <- run . runWriterT . runPost $ post
186- monitor mon
187- unless b $ monitor onFail
188- assert b
189-
190- -- | Apply the property transformation to the property after evaluating
191- -- the postcondition. Useful for collecting statistics while avoiding
192- -- duplication between `monitoring` and `postcondition`.
193- monitorPost :: Monad m => (Property -> Property ) -> PostconditionM m ()
194- monitorPost m = PostconditionM $ tell (Endo m, mempty )
195-
196- -- | Acts as `Test.QuickCheck.counterexample` if the postcondition fails.
197- counterexamplePost :: Monad m => String -> PostconditionM m ()
198- counterexamplePost c = PostconditionM $ tell (mempty , Endo $ counterexample c)
199-
200172class (forall a . Show (Action state a ), Monad m ) => RunModel state m where
201173 -- | Perform an `Action` in some `state` in the `Monad` `m`. This
202174 -- is the function that's used to exercise the actual stateful
@@ -213,15 +185,15 @@ class (forall a. Show (Action state a), Monad m) => RunModel state m where
213185 -- | Postcondition on the `a` value produced at some step.
214186 -- The result is `assert`ed and will make the property fail should it be `False`. This is useful
215187 -- to check the implementation produces expected values.
216- postcondition :: (state , state ) -> Action state a -> LookUp -> a -> PostconditionM m Bool
217- postcondition _ _ _ _ = pure True
188+ postcondition :: (state , state ) -> Action state a -> LookUp -> a -> Property
189+ postcondition _ _ _ _ = property True
218190
219191 -- | Postcondition on the result of running a _negative_ `Action`.
220192 -- The result is `assert`ed and will make the property fail should it be `False`. This is useful
221193 -- to check the implementation produces e.g. the expected errors or to check that the SUT hasn't
222194 -- been updated during the execution of the negative action.
223- postconditionOnFailure :: (state , state ) -> Action state a -> LookUp -> Either (Error state ) a -> PostconditionM m Bool
224- postconditionOnFailure _ _ _ _ = pure True
195+ postconditionOnFailure :: (state , state ) -> Action state a -> LookUp -> Either (Error state ) a -> Property
196+ postconditionOnFailure _ _ _ _ = property True
225197
226198 -- | Allows the user to attach additional information to the `Property` at each step of the process.
227199 -- This function is given the full transition that's been executed, including the start and ending
@@ -545,8 +517,8 @@ runSteps s env ((v := act) : as) = do
545517
546518 positiveActionSucceeded ret val = do
547519 (s', env', stateTransition) <- computeNewState ret
548- evaluatePostCondition $
549- postcondition
520+ liftProperty $
521+ postcondition @ state @ m
550522 stateTransition
551523 action
552524 (lookUpVar env)
@@ -555,8 +527,8 @@ runSteps s env ((v := act) : as) = do
555527
556528 negativeActionResult ret = do
557529 (s', env', stateTransition) <- computeNewState ret
558- evaluatePostCondition $
559- postconditionOnFailure
530+ liftProperty $
531+ postconditionOnFailure @ state @ m
560532 stateTransition
561533 action
562534 (lookUpVar env)
0 commit comments