File tree Expand file tree Collapse file tree 1 file changed +18
-0
lines changed
quickcheck-dynamic/test/Spec/DynamicLogic Expand file tree Collapse file tree 1 file changed +18
-0
lines changed Original file line number Diff line number Diff line change 11{-# LANGUAGE UndecidableInstances #-}
2+ {-# LANGUAGE ImpredicativeTypes #-}
23{-# OPTIONS_GHC -Wno-orphans #-}
34module Spec.DynamicLogic.RegistryModel where
45
56import Control.Concurrent.Class.MonadSTM
67import Control.Monad.Class.MonadFork
78import Control.Monad.Class.MonadThrow
89import Control.Monad.Class.MonadTimer
10+ import Control.Monad.Class.MonadTest
911import Control.Monad.IOSim
1012
1113import GHC.Generics
@@ -253,6 +255,22 @@ prop_parRegistryIOSim (IOSimActions as) = monadicIOSim_ prop
253255 runPropertyReaderT (runParActions $ as @ s ) reg
254256 pure ()
255257
258+ prop_parRegistryIOSimPor :: IOSimActions -> Property
259+ prop_parRegistryIOSimPor (IOSimActions as) = forAllBlind prop' $ \ p -> exploreSimTrace id p $ \ _ tr ->
260+ either (flip counterexample False . show ) id $ traceResult False tr
261+ where
262+ prop' :: Gen (forall s . IOSim s Property )
263+ prop' = do
264+ Capture eval <- capture
265+ pure (eval prop)
266+
267+ prop :: forall s . Gen (IOSim s Property )
268+ prop = monadic' $ do
269+ reg <- lift setupRegistry
270+ lift exploreRaces
271+ runPropertyReaderT (runParActions $ as @ s ) reg
272+ pure ()
273+
256274propDL :: DL (RegState IO ) () -> Property
257275propDL d = forAllDL d prop_Registry
258276
You can’t perform that action at this time.
0 commit comments