module Test.StateMachine
(
Program
, forAllProgram
, runAndCheckProgram
, runAndCheckProgram'
, ParallelProgram
, forAllParallelProgram
, History
, runParallelProgram
, runParallelProgram'
, checkParallelProgram
, module Test.StateMachine.Types
) where
import Control.Monad.State
(evalStateT, replicateM_)
import Test.QuickCheck.Monadic
(monadic, monadicIO, run)
import Test.QuickCheck.Property
(Property, forAllShrink, ioProperty)
import Test.StateMachine.Internal.Parallel
import Test.StateMachine.Internal.Sequential
import Test.StateMachine.Internal.Types
import Test.StateMachine.Internal.Types.Environment
import Test.StateMachine.Internal.Utils
(liftProperty)
import Test.StateMachine.Types
forAllProgram
:: Show (Untyped act)
=> HFoldable act
=> Generator model act
-> Shrinker act
-> Precondition model act
-> Transition model act
-> InitialModel model
-> (Program act -> Property)
-> Property
forAllProgram generator shrinker precondition transition model =
forAllShrink
(evalStateT (generateProgram generator precondition transition 0) model)
(shrinkProgram shrinker precondition transition model)
runAndCheckProgram
:: Monad m
=> HFunctor act
=> Precondition model act
-> Transition model act
-> Postcondition model act
-> InitialModel model
-> Semantics act m
-> (m Property -> Property)
-> Program act
-> Property
runAndCheckProgram precond trans postcond m sem runner =
runAndCheckProgram' precond trans postcond m sem (return ()) (const runner) (const (return ()))
runAndCheckProgram'
:: Monad m
=> HFunctor act
=> Precondition model act
-> Transition model act
-> Postcondition model act
-> InitialModel model
-> Semantics act m
-> IO setup
-> (setup -> m Property -> Property)
-> (setup -> IO ())
-> Program act
-> Property
runAndCheckProgram' precond trans postcond m sem setup runner cleanup acts =
monadic (ioProperty . runnerWithSetup)
(checkProgram precond trans postcond m m sem acts)
where
runnerWithSetup mp = do
s <- setup
let prop = runner s (evalStateT mp emptyEnvironment)
cleanup s
return prop
forAllParallelProgram
:: Show (Untyped act)
=> HFoldable act
=> Generator model act
-> Shrinker act
-> Precondition model act
-> Transition model act
-> InitialModel model
-> (ParallelProgram act -> Property)
-> Property
forAllParallelProgram generator shrinker precondition transition model =
forAllShrink
(generateParallelProgram generator precondition transition model)
(shrinkParallelProgram shrinker precondition transition model)
runParallelProgram
:: Show (Untyped act)
=> HTraversable act
=> Semantics act IO
-> ParallelProgram act
-> (History act -> Property)
-> Property
runParallelProgram sem = runParallelProgram' (return ()) (const sem) (const (return ()))
runParallelProgram'
:: Show (Untyped act)
=> HTraversable act
=> IO setup
-> (setup -> Semantics act IO)
-> (setup -> IO ())
-> ParallelProgram act
-> (History act -> Property)
-> Property
runParallelProgram' setup sem clean fork checkhistory = monadicIO $ do
res <- run setup
replicateM_ 10 $ do
hist <- run (executeParallelProgram (sem res) fork)
run (clean res)
liftProperty (checkhistory hist)