Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Test.Framework.Providers.API
Description
This module exports everything that you need to be able to create your own framework test provider. To create a provider you need to:
- Create an instance of the
Testlike
class - Create an instance of the
TestResultlike
class - Expose a function that lets people construct
Test
values using your new instances
Synopsis
- data Test
- = (Testlike i r t, Typeable t) => Test TestName t
- | TestGroup TestName [Test]
- | PlusTestOptions TestOptions Test
- | BuildTestBracketed (IO (Test, IO ()))
- type TestName = String
- testGroup :: TestName -> [Test] -> Test
- plusTestOptions :: TestOptions -> Test -> Test
- buildTest :: IO Test -> Test
- buildTestBracketed :: IO (Test, IO ()) -> Test
- mutuallyExclusive :: Test -> Test
- type TestTypeName = String
- class (Show i, Show r) => TestResultlike i r | r -> i where
- testSucceeded :: r -> Bool
- class TestResultlike i r => Testlike i r t | t -> i r, r -> i where
- runTest :: CompleteTestOptions -> t -> IO (i :~> r, IO ())
- testTypeName :: t -> TestTypeName
- data MutuallyExcluded t = ME (MVar ()) t
- data i :~> f
- bimapImproving :: (a -> c) -> (b -> d) -> (a :~> b) -> c :~> d
- improvingLast :: (a :~> b) -> b
- consumeImproving :: (a :~> b) -> [a :~> b]
- data ImprovingIO i f a
- yieldImprovement :: i -> ImprovingIO i f ()
- runImprovingIO :: ImprovingIO i f f -> IO (i :~> f, IO ())
- tunnelImprovingIO :: ImprovingIO i f (ImprovingIO i f a -> IO a)
- liftIO :: IO a -> ImprovingIO i f a
- timeoutImprovingIO :: Int -> ImprovingIO i f a -> ImprovingIO i f (Maybe a)
- maybeTimeoutImprovingIO :: Maybe Int -> ImprovingIO i f a -> ImprovingIO i f (Maybe a)
- module Test.Framework.Options
- module Test.Framework.Seed
- newtype K a = K {
- unK :: a
- orElse :: Maybe a -> a -> a
- secondsToMicroseconds :: Num a => a -> a
- microsecondsToPicoseconds :: Num a => a -> a
- listToMaybeLast :: [a] -> Maybe a
- mappendBy :: Monoid b => (a -> b) -> a -> a -> b
- onLeft :: (a -> c) -> (a, b) -> (c, b)
- onRight :: (b -> c) -> (a, b) -> (a, c)
- unlinesConcise :: [String] -> String
- mapAccumLM :: Monad m => (acc -> x -> m (acc, y)) -> acc -> [x] -> m (acc, [y])
- padRight :: Int -> String -> String
- dropLast :: Int -> [a] -> [a]
Documentation
Main test data type: builds up a list of tests to be run. Users should use the
utility functions in e.g. the test-framework-hunit and test-framework-quickcheck2
packages to create instances of Test
, and then build them up into testsuites
by using testGroup
and lists.
For an example of how to use test-framework, please see http://github.com/batterseapower/test-framework/raw/master/example/Test/Framework/Example.lhs
Constructors
(Testlike i r t, Typeable t) => Test TestName t | A single test of some particular type |
TestGroup TestName [Test] | Assemble a number of tests into a cohesive group |
PlusTestOptions TestOptions Test | Add some options to child tests |
BuildTestBracketed (IO (Test, IO ())) | Convenience for creating tests from an |
plusTestOptions :: TestOptions -> Test -> Test Source #
Add some options to child tests
buildTestBracketed :: IO (Test, IO ()) -> Test Source #
Convenience for creating tests from an IO
action, with a cleanup handler for when tests are finished
mutuallyExclusive :: Test -> Test Source #
Mark all tests in this portion of the tree as mutually exclusive, so only one runs at a time
type TestTypeName = String Source #
The name of a type of test, such as Properties or "Test Cases". Tests of types of the same names will be grouped together in the test run summary.
class (Show i, Show r) => TestResultlike i r | r -> i where Source #
Something like the result of a test: works in concert with Testlike
.
The type parameters are the type that is used for progress reports and the
type of the final output of the test respectively.
Methods
testSucceeded :: r -> Bool Source #
class TestResultlike i r => Testlike i r t | t -> i r, r -> i where Source #
Something test-like in its behaviour. The type parameters are the type that is used for progress reports, the type of the final output of the test and the data type encapsulating the whole potential to do a test respectively.
Methods
runTest :: CompleteTestOptions -> t -> IO (i :~> r, IO ()) Source #
testTypeName :: t -> TestTypeName Source #
Instances
Testlike i r t => Testlike i r (MutuallyExcluded t) Source # | |
Defined in Test.Framework.Core Methods runTest :: CompleteTestOptions -> MutuallyExcluded t -> IO (i :~> r, IO ()) Source # testTypeName :: MutuallyExcluded t -> TestTypeName Source # |
data MutuallyExcluded t Source #
Constructors
ME (MVar ()) t |
Instances
Testlike i r t => Testlike i r (MutuallyExcluded t) Source # | |
Defined in Test.Framework.Core Methods runTest :: CompleteTestOptions -> MutuallyExcluded t -> IO (i :~> r, IO ()) Source # testTypeName :: MutuallyExcluded t -> TestTypeName Source # |
bimapImproving :: (a -> c) -> (b -> d) -> (a :~> b) -> c :~> d Source #
improvingLast :: (a :~> b) -> b Source #
consumeImproving :: (a :~> b) -> [a :~> b] Source #
data ImprovingIO i f a Source #
Instances
Applicative (ImprovingIO i f) Source # | |
Defined in Test.Framework.Improving Methods pure :: a -> ImprovingIO i f a (<*>) :: ImprovingIO i f (a -> b) -> ImprovingIO i f a -> ImprovingIO i f b liftA2 :: (a -> b -> c) -> ImprovingIO i f a -> ImprovingIO i f b -> ImprovingIO i f c (*>) :: ImprovingIO i f a -> ImprovingIO i f b -> ImprovingIO i f b (<*) :: ImprovingIO i f a -> ImprovingIO i f b -> ImprovingIO i f a | |
Functor (ImprovingIO i f) Source # | |
Defined in Test.Framework.Improving Methods fmap :: (a -> b) -> ImprovingIO i f a -> ImprovingIO i f b (<$) :: a -> ImprovingIO i f b -> ImprovingIO i f a | |
Monad (ImprovingIO i f) Source # | |
Defined in Test.Framework.Improving Methods (>>=) :: ImprovingIO i f a -> (a -> ImprovingIO i f b) -> ImprovingIO i f b (>>) :: ImprovingIO i f a -> ImprovingIO i f b -> ImprovingIO i f b return :: a -> ImprovingIO i f a |
yieldImprovement :: i -> ImprovingIO i f () Source #
runImprovingIO :: ImprovingIO i f f -> IO (i :~> f, IO ()) Source #
tunnelImprovingIO :: ImprovingIO i f (ImprovingIO i f a -> IO a) Source #
liftIO :: IO a -> ImprovingIO i f a Source #
timeoutImprovingIO :: Int -> ImprovingIO i f a -> ImprovingIO i f (Maybe a) Source #
Given a number of microseconds and an improving IO action, run that improving IO action only
for at most the given period before giving up. See also timeout
.
maybeTimeoutImprovingIO :: Maybe Int -> ImprovingIO i f a -> ImprovingIO i f (Maybe a) Source #
As timeoutImprovingIO
, but don't bother applying a timeout to the action if Nothing
is given
as the number of microseconds to apply the time out for.
module Test.Framework.Options
module Test.Framework.Seed
secondsToMicroseconds :: Num a => a -> a Source #
microsecondsToPicoseconds :: Num a => a -> a Source #
listToMaybeLast :: [a] -> Maybe a Source #
unlinesConcise :: [String] -> String Source #
Like unlines
, but does not append a trailing newline if there
is at least one line. For example:
unlinesConcise ["A", "B"] == "A\nB" unlinesConcise [] == ""
Whereas:
unlines ["A", "B"] == "A\nB\n" unlines [] == ""
This is closer to the behaviour of unwords
, which does not append
a trailing space.
mapAccumLM :: Monad m => (acc -> x -> m (acc, y)) -> acc -> [x] -> m (acc, [y]) Source #