| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Test.Tasty
Description
This module defines the main data types and functions needed to use Tasty.
To create a test suite, you also need one or more test providers, such as tasty-hunit or tasty-quickcheck.
A simple example (using tasty-hunit) is
import Test.Tasty
import Test.Tasty.HUnit
main = defaultMain tests
tests :: TestTree
tests = testGroup "Tests"
  [ testCase "2+2=4" $
      2+2 @?= 4
  , testCase "7 is even" $
      assertBool "Oops, 7 is odd" (even 7)
  ]Take a look at the README: it contains a comprehensive list of test providers, a bigger example, and a lot of other information.
Since: 0.1
Synopsis
- type TestName = String
- data TestTree
- testGroup :: TestName -> [TestTree] -> TestTree
- sequentialTestGroup :: TestName -> DependencyType -> [TestTree] -> TestTree
- defaultMain :: TestTree -> IO ()
- defaultMainWithIngredients :: [Ingredient] -> TestTree -> IO ()
- defaultIngredients :: [Ingredient]
- includingOptions :: [OptionDescription] -> Ingredient
- adjustOption :: IsOption v => (v -> v) -> TestTree -> TestTree
- localOption :: IsOption v => v -> TestTree -> TestTree
- askOption :: IsOption v => (v -> TestTree) -> TestTree
- data Timeout
- mkTimeout :: Integer -> Timeout
- withResource :: IO a -> (a -> IO ()) -> (IO a -> TestTree) -> TestTree
- data DependencyType
- after :: DependencyType -> String -> TestTree -> TestTree
- after_ :: DependencyType -> Expr -> TestTree -> TestTree
Organizing tests
The main data structure defining a test suite.
It consists of individual test cases and properties, organized in named groups which form a tree-like hierarchy.
There is no generic way to create a test case. Instead, every test
 provider (tasty-hunit, tasty-smallcheck etc.) provides a function to
 turn a test case into a TestTree.
Groups can be created using testGroup.
Since: 0.1
testGroup :: TestName -> [TestTree] -> TestTree Source #
Create a named group of test cases or other groups. Tests are executed in
 parallel. For sequential execution, see sequentialTestGroup.
Since: 0.1
sequentialTestGroup :: TestName -> DependencyType -> [TestTree] -> TestTree Source #
Create a named group of test cases or other groups. Tests are executed in
 order. For parallel execution, see testGroup.
Running tests
defaultMain :: TestTree -> IO () Source #
Parse the command line arguments and run the tests.
When the tests finish, this function calls exitWith with the exit code
 that indicates whether any tests have failed. Most external systems
 (stack, cabal, travis-ci, jenkins etc.) rely on the exit code to detect
 whether the tests pass. If you want to do something else after
 defaultMain returns, you need to catch the exception and then re-throw
 it. Example:
import Test.Tasty
import Test.Tasty.HUnit
import System.Exit
import Control.Exception
test = testCase "Test 1" (2 @?= 3)
main = defaultMain test
  `catch` (\e -> do
    if e == ExitSuccess
      then putStrLn "Yea"
      else putStrLn "Nay"
    throwIO e)Since: 0.1
defaultMainWithIngredients :: [Ingredient] -> TestTree -> IO () Source #
Parse the command line arguments and run the tests using the provided ingredient list.
When the tests finish, this function calls exitWith with the exit code
 that indicates whether any tests have failed. See defaultMain for
 details.
Since: 0.4
defaultIngredients :: [Ingredient] Source #
List of the default ingredients. This is what defaultMain uses.
At the moment it consists of listingTests and consoleTestReporter.
Since: 0.4.2
includingOptions :: [OptionDescription] -> Ingredient Source #
This ingredient doesn't do anything apart from registering additional options.
The option values can be accessed using askOption.
Since: 0.6
Adjusting and querying options
Normally options are specified on the command line. But you can also have different options for different subtrees in the same tree, using the functions below.
Note that ingredient options (number of threads, hide successes etc.) set in this way will not have any effect. This is for modifying per-test options, such as timeout, number of generated tests etc.
adjustOption :: IsOption v => (v -> v) -> TestTree -> TestTree Source #
Locally adjust the option value for the given test subtree.
Since: 0.1
localOption :: IsOption v => v -> TestTree -> TestTree Source #
Locally set the option value for the given test subtree.
Since: 0.1
askOption :: IsOption v => (v -> TestTree) -> TestTree Source #
Customize the test tree based on the run-time options.
Since: 0.6
Standard options
Timeout to be applied to individual tests.
Since: 0.8
Constructors
| Timeout Integer String | 
 | 
| NoTimeout | 
Instances
| Show Timeout Source # | |
| Eq Timeout Source # | Auto-derived instance, just to allow storing in a  Since: 1.5.1 | 
| Ord Timeout Source # | Auto-derived instance, just to allow storing in a  Since: 1.5.1 | 
| Defined in Test.Tasty.Options.Core | |
| IsOption Timeout Source # | |
| Defined in Test.Tasty.Options.Core | |
A shortcut for creating Timeout values.
Since: 0.8
Resources
Sometimes several tests need to access the same resource — say, a file or a socket. We want to create or grab the resource before the tests are run, and destroy or release afterwards.
Arguments
| :: IO a | initialize the resource | 
| -> (a -> IO ()) | free the resource | 
| -> (IO a -> TestTree) | 
 | 
| -> TestTree | 
Acquire the resource to run this test (sub)tree and release it afterwards.
Since: 0.5
Dependencies
data DependencyType Source #
These are the two ways in which one test may depend on the others.
This is the same distinction as the hard vs soft dependencies in TestNG.
Since: 1.2
Constructors
| AllSucceed | The current test tree will be executed after its dependencies finish, and only if all of the dependencies succeed. | 
| AllFinish | The current test tree will be executed after its dependencies finish, regardless of whether they succeed or not. | 
Instances
| Read DependencyType Source # | Since: 1.5 | 
| Defined in Test.Tasty.Core Methods readsPrec :: Int -> ReadS DependencyType # readList :: ReadS [DependencyType] # | |
| Show DependencyType Source # | |
| Defined in Test.Tasty.Core Methods showsPrec :: Int -> DependencyType -> ShowS # show :: DependencyType -> String # showList :: [DependencyType] -> ShowS # | |
| Eq DependencyType Source # | |
| Defined in Test.Tasty.Core Methods (==) :: DependencyType -> DependencyType -> Bool # (/=) :: DependencyType -> DependencyType -> Bool # | |
Arguments
| :: DependencyType | whether to run the tests even if some of the dependencies fail | 
| -> String | the pattern | 
| -> TestTree | the subtree that depends on other tests | 
| -> TestTree | the subtree annotated with dependency information | 
The after combinator declares dependencies between tests.
If a TestTree is wrapped in after, the tests in this tree will not run
 until certain other tests («dependencies») have finished. These
 dependencies are specified using an AWK pattern (see the «Patterns» section
 in the README).
Moreover, if the DependencyType argument is set to AllSucceed and
 at least one dependency has failed, this test tree will not run at all.
Tasty does not check that the pattern matches any tests (let alone the correct set of tests), so it is on you to supply the right pattern.
Examples
The following test will be executed only after all tests that contain
 Foo anywhere in their path finish.
afterAllFinish"Foo" $
testCase "A test that depends on Foo.Bar" $ ...
 
Note, however, that our test also happens to contain Foo as part of its name,
 so it also matches the pattern and becomes a dependency of itself. This
 will result in a DependencyLoop exception. To avoid this, either
 change the test name so that it doesn't mention Foo or make the
 pattern more specific.
You can use AWK patterns, for instance, to specify the full path to the dependency.
afterAllFinish"$0 == \"Tests.Foo.Bar\"" $
testCase "A test that depends on Foo.Bar" $ ...
 
Or only specify the dependency's own name, ignoring the group names:
afterAllFinish"$NF == \"Bar\"" $
testCase "A test that depends on Foo.Bar" $ ...
 
Since: 1.2
Arguments
| :: DependencyType | whether to run the tests even if some of the dependencies fail | 
| -> Expr | the pattern | 
| -> TestTree | the subtree that depends on other tests | 
| -> TestTree | the subtree annotated with dependency information | 
Like after, but accepts the pattern as a syntax tree instead
 of a string. Useful for generating a test tree programmatically.
Examples
Only match on the test's own name, ignoring the group names:
after_AllFinish(EQ(FieldNF) (StringLit"Bar")) $
testCase "A test that depends on Foo.Bar" $ ...
 
Since: 1.2