Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
Synopsis
- type TestName = String
- data TestTree
- testGroup :: TestName -> [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
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
.
testGroup :: TestName -> [TestTree] -> TestTree Source #
Create a named group of test cases or other groups
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)
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.
defaultIngredients :: [Ingredient] Source #
List of the default ingredients. This is what defaultMain
uses.
At the moment it consists of listingTests
and consoleTestReporter
.
includingOptions :: [OptionDescription] -> Ingredient Source #
This ingredient doesn't do anything apart from registering additional options.
The option values can be accessed using askOption
.
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
localOption :: IsOption v => v -> TestTree -> TestTree Source #
Locally set the option value for the given test subtree
askOption :: IsOption v => (v -> TestTree) -> TestTree Source #
Customize the test tree based on the run-time options
Standard options
Timeout to be applied to individual tests
Timeout Integer String |
|
NoTimeout |
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.
:: 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