module Test.StateMachine
(
sequentialProperty
, sequentialProperty'
, parallelProperty
, parallelProperty'
, module Test.StateMachine.Types
) where
import Control.Monad.State
(StateT, evalStateT, lift, replicateM_)
import qualified Data.Map as M
import Test.QuickCheck
(Gen)
import Test.QuickCheck.Monadic
(monadic, monadicIO, run)
import Test.QuickCheck.Property
(Property, forAllShrink)
import qualified Test.StateMachine.Internal.IxMap as IxM
import Test.StateMachine.Internal.Parallel
import Test.StateMachine.Internal.Sequential
import Test.StateMachine.Internal.Types
import Test.StateMachine.Internal.Utils
import Test.StateMachine.Types
sequentialProperty
:: CommandConstraint ix cmd
=> Monad m
=> Show (model ConstIntRef)
=> StateMachineModel model cmd
-> Gen (Untyped cmd (RefPlaceholder ix))
-> (forall resp refs'. Shrinker (cmd refs' resp))
-> (forall resp. cmd refs resp -> m (Response_ refs resp))
-> (m Property -> Property)
-> Property
sequentialProperty smm gen shrinker sem runM =
sequentialProperty' smm (lift gen) () shrinker (const (const sem)) runM
sequentialProperty'
:: CommandConstraint ix cmd
=> Show (model ConstIntRef)
=> Monad m
=> StateMachineModel model cmd
-> StateT s Gen (Untyped cmd (RefPlaceholder ix))
-> s
-> (forall resp refs'. Shrinker (cmd refs' resp))
-> (forall resp. model ConstIntRef ->
MayResponse_ ConstIntRef resp ->
cmd refs resp ->
m (Response_ refs resp))
-> (m Property -> Property)
-> Property
sequentialProperty' smm gen s shrinker sem runM =
forAllShrink
(fst . fst <$> liftGen' gen s 0 M.empty)
(liftShrink shrinker)
$ \cmds -> collectStats cmds $
monadic (runM . flip evalStateT IxM.empty) $
checkSequentialInvariant smm (initialModel smm) sem cmds
parallelProperty
:: CommandConstraint ix cmd
=> StateMachineModel model cmd
-> Gen (Untyped cmd (RefPlaceholder ix))
-> (forall resp refs'. Shrinker (cmd refs' resp))
-> (forall resp. cmd refs resp -> IO (Response_ refs resp))
-> Property
parallelProperty smm gen shrinker sem
= parallelProperty' smm (lift gen) () shrinker sem (return ())
parallelProperty'
:: CommandConstraint ix cmd
=> StateMachineModel model cmd
-> StateT genState Gen (Untyped cmd (RefPlaceholder ix))
-> genState
-> (forall resp refs'. Shrinker (cmd refs' resp))
-> (forall resp. cmd refs resp -> IO (Response_ refs resp))
-> IO ()
-> Property
parallelProperty' smm gen genState shrinker sem clean
= forAllShrink
(liftGenFork' gen genState)
(liftShrinkFork shrinker)
$ \fork -> monadicIO $ replicateM_ 10 $ do
run clean
hist <- run $ liftSemFork sem fork
checkParallelInvariant smm hist