@@ -4,7 +4,8 @@ import Control.Applicative
44import Control.Arrow (second )
55import Control.Monad
66import Data.Typeable
7- import Test.QuickCheck hiding (generate )
7+ import Test.QuickCheck (Gen , Property , Testable )
8+ import Test.QuickCheck qualified as QC
89import Test.QuickCheck.DynamicLogic.CanGenerate
910import Test.QuickCheck.DynamicLogic.Quantify
1011import Test.QuickCheck.DynamicLogic.SmartShrinking
@@ -360,8 +361,8 @@ forAllUniqueScripts s f k =
360361 let d = unDynFormula f sz
361362 n = unsafeNextVarIndex $ vars s
362363 in case generate chooseUniqueNextStep d n s 500 of
363- Nothing -> counterexample " Generating Non-unique script in forAllUniqueScripts" False
364- Just test -> validDLTest d test . applyMonitoring d test . property $ k (scriptFromDL test)
364+ Nothing -> QC. counterexample " Generating Non-unique script in forAllUniqueScripts" False
365+ Just test -> validDLTest d test . applyMonitoring d test . QC. property $ k (scriptFromDL test)
365366
366367-- | Creates a `Property` from `DynFormula` with some specialised isomorphism for shrinking purpose.
367368forAllMappedScripts
@@ -374,22 +375,22 @@ forAllMappedScripts
374375forAllMappedScripts to from f k =
375376 QC. withSize $ \ n ->
376377 let d = unDynFormula f n
377- in forAllShrinkBlind
378- (Smart 0 <$> sized ((from <$> ) . generateDLTest d))
378+ in QC. forAllShrinkBlind
379+ (QC. Smart 0 <$> QC. sized ((from <$> ) . generateDLTest d))
379380 (shrinkSmart ((from <$> ) . shrinkDLTest d . to))
380- $ \ (Smart _ script) ->
381+ $ \ (QC. Smart _ script) ->
381382 withDLScript d k (to script)
382383
383384withDLScript :: (DynLogicModel s , Testable a ) => DynLogic s -> (Actions s -> a ) -> DynLogicTest s -> Property
384385withDLScript d k test =
385- validDLTest d test . applyMonitoring d test . property $ k (scriptFromDL test)
386+ validDLTest d test . applyMonitoring d test . QC. property $ k (scriptFromDL test)
386387
387388withDLScriptPrefix :: (DynLogicModel s , Testable a ) => DynFormula s -> (Actions s -> a ) -> DynLogicTest s -> Property
388389withDLScriptPrefix f k test =
389390 QC. withSize $ \ n ->
390391 let d = unDynFormula f n
391392 test' = unfailDLTest d test
392- in validDLTest d test' . applyMonitoring d test' . property $ k (scriptFromDL test')
393+ in validDLTest d test' . applyMonitoring d test' . QC. property $ k (scriptFromDL test')
393394
394395generateDLTest :: DynLogicModel s => DynLogic s -> Int -> Gen (DynLogicTest s )
395396generateDLTest d size = generate chooseNextStep d 0 (initialStateFor d) size
@@ -502,7 +503,7 @@ nextSteps' gen (ForAll q f) = do
502503nextSteps' gen (Monitor _f d) = nextSteps' gen d
503504
504505chooseOneOf :: [(Double , a )] -> Gen a
505- chooseOneOf steps = frequency [(round (w / never), return s) | (w, s) <- steps]
506+ chooseOneOf steps = QC. frequency [(round (w / never), return s) | (w, s) <- steps]
506507
507508never :: Double
508509never = 1.0e-9
@@ -572,7 +573,7 @@ keepTryingUntil :: Int -> Gen a -> (a -> Bool) -> Gen (Maybe a)
572573keepTryingUntil 0 _ _ = return Nothing
573574keepTryingUntil n g p = do
574575 x <- g
575- if p x then return $ Just x else scale (+ 1 ) $ keepTryingUntil (n - 1 ) g p
576+ if p x then return $ Just x else QC. scale (+ 1 ) $ keepTryingUntil (n - 1 ) g p
576577
577578shrinkDLTest :: DynLogicModel s => DynLogic s -> DynLogicTest s -> [DynLogicTest s ]
578579shrinkDLTest _ (Looping _) = []
@@ -696,7 +697,7 @@ demonicAlt ds = foldr1 (Alt Demonic) ds
696697
697698propPruningGeneratedScriptIsNoop :: DynLogicModel s => DynLogic s -> Property
698699propPruningGeneratedScriptIsNoop d =
699- forAll (sized $ \ n -> choose (1 , max 1 n) >>= generateDLTest d) $ \ test ->
700+ QC. forAll (QC. sized $ \ n -> QC. choose (1 , max 1 n) >>= generateDLTest d) $ \ test ->
700701 let script = case test of
701702 BadPrecondition s _ _ -> s
702703 Looping s -> s
@@ -764,9 +765,9 @@ stuck (ForAll _ _) _ = False
764765stuck (Monitor _ d) s = stuck d s
765766
766767validDLTest :: StateModel s => DynLogic s -> DynLogicTest s -> Property -> Property
767- validDLTest _ Stuck {} _ = False ==> False
768- validDLTest _ test@ DLScript {} p = counterexample (show test) p
769- validDLTest _ test _ = counterexample (show test) False
768+ validDLTest _ Stuck {} _ = False QC. ==> False
769+ validDLTest _ test@ DLScript {} p = QC. counterexample (show test) p
770+ validDLTest _ test _ = QC. counterexample (show test) False
770771
771772scriptFromDL :: DynLogicTest s -> Actions s
772773scriptFromDL (DLScript s) = Actions $ sequenceSteps s
0 commit comments