| Copyright | (c) 2016 Michael Walker |
|---|---|
| License | MIT |
| Maintainer | Michael Walker <mike@barrucadu.co.uk> |
| Stability | stable |
| Portability | CPP, FlexibleInstances, GADTs, ImpredicativeTypes, RankNTypes, TypeSynonymInstances |
| Safe Haskell | None |
| Language | Haskell2010 |
Test.Tasty.DejaFu
Description
This module allows using Deja Fu predicates with Tasty to test the behaviour of concurrent systems.
- testAuto :: (Eq a, Show a) => (forall t. ConcST t a) -> TestTree
- testDejafu :: Show a => (forall t. ConcST t a) -> TestName -> Predicate a -> TestTree
- testDejafus :: Show a => (forall t. ConcST t a) -> [(TestName, Predicate a)] -> TestTree
- testAuto' :: (Eq a, Show a) => MemType -> (forall t. ConcST t a) -> TestTree
- testDejafu' :: Show a => MemType -> Bounds -> (forall t. ConcST t a) -> TestName -> Predicate a -> TestTree
- testDejafus' :: Show a => MemType -> Bounds -> (forall t. ConcST t a) -> [(TestName, Predicate a)] -> TestTree
- testAutoIO :: (Eq a, Show a) => ConcIO a -> TestTree
- testDejafuIO :: Show a => ConcIO a -> TestName -> Predicate a -> TestTree
- testDejafusIO :: Show a => ConcIO a -> [(TestName, Predicate a)] -> TestTree
- testAutoIO' :: (Eq a, Show a) => MemType -> ConcIO a -> TestTree
- testDejafuIO' :: Show a => MemType -> Bounds -> ConcIO a -> TestName -> Predicate a -> TestTree
- testDejafusIO' :: Show a => MemType -> Bounds -> ConcIO a -> [(TestName, Predicate a)] -> TestTree
- data Bounds :: * = Bounds {}
- data MemType :: *
Unit testing
This is supported by the IsTest instances for ConcST and
ConcIO. These instances try all executions, reporting as
failures the cases which return a Just string.
instance Typeable t => IsTest (ConcST t (Maybe String))
instance IsTest (ConcIO (Maybe String))
instance IsOption Bounds
instance IsOption MemType
Property testing
Automatically test a computation. In particular, look for deadlocks, uncaught exceptions, and multiple return values.
This uses the Conc monad for testing, which is an instance of
MonadConc. If you need to test something which also uses
MonadIO, use testAutoIO.
Arguments
| :: Show a | |
| => (forall t. ConcST t a) | The computation to test |
| -> TestName | The name of the test. |
| -> Predicate a | The predicate to check |
| -> TestTree |
Check that a predicate holds.
Arguments
| :: Show a | |
| => (forall t. ConcST t a) | The computation to test |
| -> [(TestName, Predicate a)] | The list of predicates (with names) to check |
| -> TestTree |
Variant of testDejafu which takes a collection of predicates to
test. This will share work between the predicates, rather than
running the concurrent computation many times for each predicate.
Arguments
| :: (Eq a, Show a) | |
| => MemType | The memory model to use for non-synchronised |
| -> (forall t. ConcST t a) | The computation to test |
| -> TestTree |
Variant of testAuto which tests a computation under a given
memory model.
Arguments
| :: Show a | |
| => MemType | The memory model to use for non-synchronised |
| -> Bounds | The schedule bounds. |
| -> (forall t. ConcST t a) | The computation to test |
| -> TestName | The name of the test. |
| -> Predicate a | The predicate to check |
| -> TestTree |
Variant of testDejafu which takes a memory model and
pre-emption bound.
Arguments
| :: Show a | |
| => MemType | The memory model to use for non-synchronised |
| -> Bounds | The schedule bounds. |
| -> (forall t. ConcST t a) | The computation to test |
| -> [(TestName, Predicate a)] | The list of predicates (with names) to check |
| -> TestTree |
Variant of testDejafus which takes a memory model and pre-emption
bound.
IO
testDejafuIO :: Show a => ConcIO a -> TestName -> Predicate a -> TestTree Source #
Variant of testDejafu for computations which do IO.
testDejafusIO :: Show a => ConcIO a -> [(TestName, Predicate a)] -> TestTree Source #
Variant of testDejafus for computations which do IO.
testDejafuIO' :: Show a => MemType -> Bounds -> ConcIO a -> TestName -> Predicate a -> TestTree Source #
Variant of testDejafu' for computations which do IO.
testDejafusIO' :: Show a => MemType -> Bounds -> ConcIO a -> [(TestName, Predicate a)] -> TestTree Source #
Re-exports
Constructors
| Bounds | |
Fields | |
The memory model to use for non-synchronised CRef operations.
Constructors
| SequentialConsistency | The most intuitive model: a program behaves as a simple
interleaving of the actions in different threads. When a |
| TotalStoreOrder | Each thread has a write buffer. A thread sees its writes immediately, but other threads will only see writes when they are committed, which may happen later. Writes are committed in the same order that they are created. |
| PartialStoreOrder | Each |