Skip to content

Commit 7850e32

Browse files
Random generation of initial states
1 parent 95b8ad1 commit 7850e32

File tree

7 files changed

+189
-118
lines changed

7 files changed

+189
-118
lines changed

quickcheck-dynamic/CHANGELOG.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,10 @@ changes.
99

1010
## UNRELEASED
1111

12+
* **BREAKING**: Made `initialState` `Gen state` instead of a `state` and introduced `setup :: state -> m ()` to `RunModel`.
13+
- To migrate an existing model simply replace `initialState = MyState{..}` with `initialState = pure $ MyState{..}` and everything
14+
else should work straight-forwardly.
15+
1216
* **BREAKING**: Removed `Realized`
1317
- To migrate uses of `Realized` with `IOSim`, index the state type on the choice of `RunModel` monad
1418
and index the relevant types:

quickcheck-dynamic/src/Test/QuickCheck/DynamicLogic.hs

Lines changed: 40 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,9 @@ module Test.QuickCheck.DynamicLogic (
2727
forAllDL,
2828
forAllMappedDL,
2929
forAllUniqueDL,
30+
forAllDLS,
31+
forAllMappedDLS,
32+
forAllUniqueDLS,
3033
DL.DynLogicModel (..),
3134
module Test.QuickCheck.DynamicLogic.Quantify,
3235
) where
@@ -131,22 +134,23 @@ forAllNonVariableQ :: QuantifyConstraints (HasNoVariables a) => Quantification a
131134
forAllNonVariableQ q = DL $ \s k -> DL.forAllQ (hasNoVariablesQ q) $ \(HasNoVariables x) -> k x s
132135

133136
runDL :: Annotated s -> DL s () -> DL.DynFormula s
134-
runDL s dl = unDL dl s $ \_ _ -> DL.passTest
137+
runDL s dl = (unDL dl s $ \_ _ -> DL.passTest)
135138

136139
forAllUniqueDL
137140
:: (DL.DynLogicModel s, Testable a)
138-
=> Annotated s
139-
-> DL s ()
141+
=> DL s ()
140142
-> (Actions s -> a)
141143
-> Property
142-
forAllUniqueDL initState d = DL.forAllUniqueScripts initState (runDL initState d)
144+
forAllUniqueDL d p =
145+
forAllBlind initialState $ \st -> forAllUniqueDLS st d p
143146

144147
forAllDL
145148
:: (DL.DynLogicModel s, Testable a)
146149
=> DL s ()
147150
-> (Actions s -> a)
148151
-> Property
149-
forAllDL d = DL.forAllScripts (runDL initialAnnotatedState d)
152+
forAllDL d p =
153+
forAllBlind initialState $ \st -> forAllDLS st d p
150154

151155
forAllMappedDL
152156
:: (DL.DynLogicModel s, Testable a)
@@ -157,4 +161,34 @@ forAllMappedDL
157161
-> (srep -> a)
158162
-> Property
159163
forAllMappedDL to from fromScript d prop =
160-
DL.forAllMappedScripts to from (runDL initialAnnotatedState d) (prop . fromScript)
164+
forAll initialState $ \st -> forAllMappedDLS st to from fromScript d prop
165+
166+
forAllUniqueDLS
167+
:: (DL.DynLogicModel s, Testable a)
168+
=> s
169+
-> DL s ()
170+
-> (Actions s -> a)
171+
-> Property
172+
forAllUniqueDLS st d p =
173+
DL.forAllUniqueScripts st (runDL (Metadata mempty st) d) p
174+
175+
forAllDLS
176+
:: (DL.DynLogicModel s, Testable a)
177+
=> s
178+
-> DL s ()
179+
-> (Actions s -> a)
180+
-> Property
181+
forAllDLS st d p =
182+
DL.forAllScripts st (runDL (Metadata mempty st) d) p
183+
184+
forAllMappedDLS
185+
:: (DL.DynLogicModel s, Testable a)
186+
=> s
187+
-> (rep -> DL.DynLogicTest s)
188+
-> (DL.DynLogicTest s -> rep)
189+
-> (Actions s -> srep)
190+
-> DL s ()
191+
-> (srep -> a)
192+
-> Property
193+
forAllMappedDLS st to from fromScript d prop =
194+
DL.forAllMappedScripts st to from (runDL (Metadata mempty st) d) (prop . fromScript)

quickcheck-dynamic/src/Test/QuickCheck/DynamicLogic/Internal.hs

Lines changed: 94 additions & 72 deletions
Original file line numberDiff line numberDiff line change
@@ -171,10 +171,10 @@ instance StateModel s => Show (FailingAction s) where
171171
show (ActionFail (ActionWithPolarity a pol)) = show pol ++ " : " ++ show a
172172

173173
data DynLogicTest s
174-
= BadPrecondition (TestSequence s) (FailingAction s) (Annotated s)
175-
| Looping (TestSequence s)
176-
| Stuck (TestSequence s) (Annotated s)
177-
| DLScript (TestSequence s)
174+
= BadPrecondition (Annotated s) (TestSequence s) (FailingAction s) (Annotated s)
175+
| Looping (Annotated s) (TestSequence s)
176+
| Stuck (Annotated s) (TestSequence s) (Annotated s)
177+
| DLScript (Annotated s) (TestSequence s)
178178

179179
data Witnesses r where
180180
Do :: r -> Witnesses r
@@ -295,8 +295,11 @@ prettyWitnesses (Witness a w) = ("_ <- forAllQ $ exactlyQ $ " ++ show a) : prett
295295
prettyWitnesses Do{} = []
296296

297297
instance StateModel s => Show (DynLogicTest s) where
298-
show (BadPrecondition ss bad s) =
299-
prettyTestSequence (usedVariables ss <> allVariables bad) ss
298+
show (BadPrecondition is ss bad s) =
299+
"-- Initial state: "
300+
++ show s
301+
++ "\n"
302+
++ prettyTestSequence (usedVariables is ss <> allVariables bad) ss
300303
++ "\n -- In state: "
301304
++ show s
302305
++ "\n "
@@ -309,12 +312,21 @@ instance StateModel s => Show (DynLogicTest s) where
309312
f
310313
| p == PosPolarity = "action"
311314
| otherwise = "failingAction"
312-
show (Looping ss) = prettyTestSequence (usedVariables ss) ss ++ "\n pure ()\n -- Looping"
313-
show (Stuck ss s) = prettyTestSequence (usedVariables ss) ss ++ "\n pure ()\n -- Stuck in state " ++ show s
314-
show (DLScript ss) = prettyTestSequence (usedVariables ss) ss ++ "\n pure ()\n"
315+
show (Looping is ss) =
316+
showTest is ss
317+
++ "\n -- Looping"
318+
show (Stuck is ss s) =
319+
showTest is ss
320+
++ "\n -- Stuck in state "
321+
++ show s
322+
show (DLScript is ss) =
323+
showTest is ss
315324

316-
usedVariables :: forall s. StateModel s => TestSequence s -> VarContext
317-
usedVariables = go initialAnnotatedState
325+
showTest :: StateModel s => Annotated s -> TestSequence s -> String
326+
showTest is ss = "-- Initial state: " ++ show is ++ "\n" ++ prettyTestSequence (usedVariables is ss) ss ++ "\n pure ()"
327+
328+
usedVariables :: forall s. StateModel s => Annotated s -> TestSequence s -> VarContext
329+
usedVariables s = go s
318330
where
319331
go :: Annotated s -> TestSequence s -> VarContext
320332
go aState TestSeqStop = allVariables (underlyingState aState)
@@ -342,39 +354,42 @@ restrictedPolar (ActionWithPolarity a _) = restricted a
342354
-- `Actions` sequence into a proper `Property` that can be run by QuickCheck.
343355
forAllScripts
344356
:: (DynLogicModel s, Testable a)
345-
=> DynFormula s
357+
=> s
358+
-- ^ The initial state
359+
-> DynFormula s
346360
-> (Actions s -> a)
347361
-> Property
348-
forAllScripts = forAllMappedScripts id id
362+
forAllScripts s = forAllMappedScripts s id id
349363

350364
-- | `Property` function suitable for formulae without choice.
351365
forAllUniqueScripts
352366
:: (DynLogicModel s, Testable a)
353-
=> Annotated s
367+
=> s
368+
-- ^ The initial state
354369
-> DynFormula s
355370
-> (Actions s -> a)
356371
-> Property
357372
forAllUniqueScripts s f k =
358373
QC.withSize $ \sz ->
359374
let d = unDynFormula f sz
360-
n = unsafeNextVarIndex $ vars s
361-
in case generate chooseUniqueNextStep d n s 500 of
375+
in case generate chooseUniqueNextStep d 1 (Metadata mempty s) 500 of
362376
Nothing -> counterexample "Generating Non-unique script in forAllUniqueScripts" False
363377
Just test -> validDLTest test . applyMonitoring d test . property $ k (scriptFromDL test)
364378

365379
-- | Creates a `Property` from `DynFormula` with some specialised isomorphism for shrinking purpose.
366380
forAllMappedScripts
367381
:: (DynLogicModel s, Testable a)
368-
=> (rep -> DynLogicTest s)
382+
=> s
383+
-> (rep -> DynLogicTest s)
369384
-> (DynLogicTest s -> rep)
370385
-> DynFormula s
371386
-> (Actions s -> a)
372387
-> Property
373-
forAllMappedScripts to from f k =
388+
forAllMappedScripts s to from f k =
374389
QC.withSize $ \n ->
375390
let d = unDynFormula f n
376391
in forAllShrinkBlind
377-
(Smart 0 <$> sized ((from <$>) . generateDLTest d))
392+
(Smart 0 <$> sized ((from <$>) . generateDLTest (Metadata mempty s) d))
378393
(shrinkSmart ((from <$>) . shrinkDLTest d . to))
379394
$ \(Smart _ script) ->
380395
withDLScript d k (to script)
@@ -405,17 +420,24 @@ validDLTest test prop =
405420
Stuck{} -> property Discard
406421
_other -> counterexample (show test) False
407422

408-
generateDLTest :: DynLogicModel s => DynLogic s -> Int -> Gen (DynLogicTest s)
409-
generateDLTest d size = generate chooseNextStep d 0 (initialStateFor d) size
423+
generateDLTest :: DynLogicModel s => Annotated s -> DynLogic s -> Int -> Gen (DynLogicTest s)
424+
generateDLTest s d size = do
425+
generate chooseNextStep d 0 s size
410426

411427
onDLTestSeq :: (TestSequence s -> TestSequence s) -> DynLogicTest s -> DynLogicTest s
412-
onDLTestSeq f (BadPrecondition ss bad s) = BadPrecondition (f ss) bad s
413-
onDLTestSeq f (Looping ss) = Looping (f ss)
414-
onDLTestSeq f (Stuck ss s) = Stuck (f ss) s
415-
onDLTestSeq f (DLScript ss) = DLScript (f ss)
428+
onDLTestSeq f (BadPrecondition is ss bad s) = BadPrecondition is (f ss) bad s
429+
onDLTestSeq f (Looping is ss) = Looping is (f ss)
430+
onDLTestSeq f (Stuck is ss s) = Stuck is (f ss) s
431+
onDLTestSeq f (DLScript is ss) = DLScript is (f ss)
416432

417-
consDLTest :: TestStep s -> DynLogicTest s -> DynLogicTest s
418-
consDLTest step = onDLTestSeq (step :>)
433+
setDLTestState :: Annotated s -> DynLogicTest s -> DynLogicTest s
434+
setDLTestState is (BadPrecondition _ ss bad s) = BadPrecondition is ss bad s
435+
setDLTestState is (Looping _ ss) = Looping is ss
436+
setDLTestState is (Stuck _ ss s) = Stuck is ss s
437+
setDLTestState is (DLScript _ ss) = DLScript is ss
438+
439+
consDLTest :: Annotated s -> TestStep s -> DynLogicTest s -> DynLogicTest s
440+
consDLTest is step = setDLTestState is . onDLTestSeq (step :>)
419441

420442
consDLTestW :: Witnesses () -> DynLogicTest s -> DynLogicTest s
421443
consDLTestW w = onDLTestSeq (addW w)
@@ -433,15 +455,15 @@ generate
433455
-> m (DynLogicTest s)
434456
generate chooseNextStepFun d n s size =
435457
if n > sizeLimit size
436-
then return $ Looping TestSeqStop
458+
then return $ Looping s TestSeqStop
437459
else do
438460
let preferred = if n > size then stopping d else noStopping d
439-
useStep (BadAction (Witnesses ws bad)) _ = return $ BadPrecondition (TestSeqStopW ws) bad s
440-
useStep StoppingStep _ = return $ DLScript TestSeqStop
461+
useStep (BadAction (Witnesses ws bad)) _ = return $ BadPrecondition s (TestSeqStopW ws) bad s
462+
useStep StoppingStep _ = return $ DLScript s TestSeqStop
441463
useStep (Stepping step d') _ =
442464
case discardWitnesses step of
443465
var := act ->
444-
consDLTest step
466+
consDLTest s step
445467
<$> generate
446468
chooseNextStepFun
447469
d'
@@ -451,15 +473,13 @@ generate chooseNextStepFun d n s size =
451473
useStep NoStep alt = alt
452474
foldr
453475
(\step k -> do try <- chooseNextStepFun s n step; useStep try k)
454-
(return $ Stuck TestSeqStop s)
476+
(return $ Stuck s TestSeqStop s) -- NOTE: we will cons on this `TestSeqStop` so the `s` will not be the same before
477+
-- and after state when we get out of this function.
455478
[preferred, noAny preferred, d, noAny d]
456479

457480
sizeLimit :: Int -> Int
458481
sizeLimit size = 2 * size + 20
459482

460-
initialStateFor :: StateModel s => DynLogic s -> Annotated s
461-
initialStateFor _ = initialAnnotatedState
462-
463483
stopping :: DynLogic s -> DynLogic s
464484
stopping EmptySpec = EmptySpec
465485
stopping Stop = Stop
@@ -589,22 +609,28 @@ keepTryingUntil n g p = do
589609
if p x then return $ Just x else scale (+ 1) $ keepTryingUntil (n - 1) g p
590610

591611
shrinkDLTest :: DynLogicModel s => DynLogic s -> DynLogicTest s -> [DynLogicTest s]
592-
shrinkDLTest _ (Looping _) = []
612+
shrinkDLTest _ (Looping _ _) = []
593613
shrinkDLTest d tc =
594-
[ test | as' <- shrinkScript d (getScript tc), let pruned = pruneDLTest d as'
595-
test = makeTestFromPruned d pruned,
596-
-- Don't shrink a non-executable test case to an executable one.
614+
[ test
615+
| as' <-
616+
shrinkScript
617+
(underlyingState $ getInitialState tc)
618+
d
619+
(getScript tc)
620+
, let pruned = pruneDLTest (getInitialState tc) d as'
621+
test = makeTestFromPruned (getInitialState tc) d pruned
622+
, -- Don't shrink a non-executable test case to an executable one.
597623
case (tc, test) of
598-
(DLScript _, _) -> True
599-
(_, DLScript _) -> False
624+
(DLScript _ _, _) -> True
625+
(_, DLScript _ _) -> False
600626
_ -> True
601627
]
602628

603629
nextStateStep :: StateModel s => Step s -> Annotated s -> Annotated s
604630
nextStateStep (var := act) s = computeNextState s act var
605631

606-
shrinkScript :: forall s. DynLogicModel s => DynLogic s -> TestSequence s -> [TestSequence s]
607-
shrinkScript = shrink' initialAnnotatedState
632+
shrinkScript :: forall s. DynLogicModel s => s -> DynLogic s -> TestSequence s -> [TestSequence s]
633+
shrinkScript is = shrink' (Metadata mempty is)
608634
where
609635
shrink' :: Annotated s -> DynLogic s -> TestSequence s -> [TestSequence s]
610636
shrink' s d ss = structural s d ss ++ nonstructural s d ss
@@ -648,8 +674,8 @@ shrinkWitness AfterAny{} _ = []
648674

649675
-- The result of pruning a list of actions is a prefix of a list of actions that
650676
-- could have been generated by the dynamic logic.
651-
pruneDLTest :: forall s. DynLogicModel s => DynLogic s -> TestSequence s -> TestSequence s
652-
pruneDLTest dl = prune [dl] initialAnnotatedState
677+
pruneDLTest :: forall s. DynLogicModel s => Annotated s -> DynLogic s -> TestSequence s -> TestSequence s
678+
pruneDLTest is dl = prune [dl] is
653679
where
654680
prune [] _ _ = TestSeqStop
655681
prune _ _ TestSeqStop = TestSeqStop
@@ -710,27 +736,29 @@ demonicAlt ds = foldr1 (Alt Demonic) ds
710736

711737
propPruningGeneratedScriptIsNoop :: DynLogicModel s => DynLogic s -> Property
712738
propPruningGeneratedScriptIsNoop d =
713-
forAll (sized $ \n -> choose (1, max 1 n) >>= generateDLTest d) $ \test ->
714-
let script = case test of
715-
BadPrecondition s _ _ -> s
716-
Looping s -> s
717-
Stuck s _ -> s
718-
DLScript s -> s
719-
in script == pruneDLTest d script
739+
forAll initialState $ \s ->
740+
forAll (sized $ \n -> choose (1, max 1 n) >>= generateDLTest (Metadata mempty s) d) $ \test ->
741+
getScript test == pruneDLTest (getInitialState test) d (getScript test)
742+
743+
getInitialState :: DynLogicTest s -> Annotated s
744+
getInitialState (BadPrecondition is _ _ _) = is
745+
getInitialState (Looping is _) = is
746+
getInitialState (Stuck is _ _) = is
747+
getInitialState (DLScript is _) = is
720748

721749
getScript :: DynLogicTest s -> TestSequence s
722-
getScript (BadPrecondition s _ _) = s
723-
getScript (Looping s) = s
724-
getScript (Stuck s _) = s
725-
getScript (DLScript s) = s
750+
getScript (BadPrecondition _ s _ _) = s
751+
getScript (Looping _ s) = s
752+
getScript (Stuck _ s _) = s
753+
getScript (DLScript _ s) = s
726754

727-
makeTestFromPruned :: forall s. DynLogicModel s => DynLogic s -> TestSequence s -> DynLogicTest s
728-
makeTestFromPruned dl = make dl initialAnnotatedState
755+
makeTestFromPruned :: forall s. DynLogicModel s => Annotated s -> DynLogic s -> TestSequence s -> DynLogicTest s
756+
makeTestFromPruned st dl = make dl st
729757
where
730758
make d s TestSeqStop
731-
| b : _ <- badActions @s d s = BadPrecondition TestSeqStop b s
732-
| stuck d s = Stuck TestSeqStop s
733-
| otherwise = DLScript TestSeqStop
759+
| b : _ <- badActions @s d s = BadPrecondition s TestSeqStop b s
760+
| stuck d s = Stuck s TestSeqStop s
761+
| otherwise = DLScript s TestSeqStop
734762
make d s (TestSeqWitness a ss) =
735763
onDLTestSeq (TestSeqWitness a) $
736764
make
@@ -747,13 +775,7 @@ makeTestFromPruned dl = make dl initialAnnotatedState
747775
-- | If failed, return the prefix up to the failure. Also prunes the test in case the model has
748776
-- changed.
749777
unfailDLTest :: DynLogicModel s => DynLogic s -> DynLogicTest s -> DynLogicTest s
750-
unfailDLTest d test = makeTestFromPruned d $ pruneDLTest d steps
751-
where
752-
steps = case test of
753-
BadPrecondition as _ _ -> as
754-
Stuck as _ -> as
755-
DLScript as -> as
756-
Looping as -> as
778+
unfailDLTest d test = makeTestFromPruned (getInitialState test) d $ pruneDLTest (getInitialState test) d (getScript test)
757779

758780
stuck :: DynLogicModel s => DynLogic s -> Annotated s -> Bool
759781
stuck EmptySpec _ = True
@@ -778,8 +800,8 @@ stuck (ForAll _ _) _ = False
778800
stuck (Monitor _ d) s = stuck d s
779801

780802
scriptFromDL :: DynLogicTest s -> Actions s
781-
scriptFromDL (DLScript s) = Actions $ sequenceSteps s
782-
scriptFromDL _ = Actions []
803+
scriptFromDL (DLScript is s) = Actions (underlyingState is) $ sequenceSteps s
804+
scriptFromDL test = Actions (underlyingState $ getInitialState test) []
783805

784806
sequenceSteps :: TestSequence s -> [Step s]
785807
sequenceSteps (TestSeq ss) =
@@ -818,8 +840,8 @@ badActions (ForAll _ _) _ = []
818840
badActions (Monitor _ d) s = badActions d s
819841

820842
applyMonitoring :: DynLogicModel s => DynLogic s -> DynLogicTest s -> Property -> Property
821-
applyMonitoring d (DLScript s) p =
822-
case findMonitoring d initialAnnotatedState s of
843+
applyMonitoring d (DLScript is s) p =
844+
case findMonitoring d is s of
823845
Just f -> f p
824846
Nothing -> p
825847
applyMonitoring _ Stuck{} p = p

0 commit comments

Comments
 (0)