tasty-0.5.2.1: Modern and extensible testing framework

Safe HaskellNone

Test.Tasty

Contents

Description

This module defines the main data types and functions needed to use Tasty.

Synopsis

Organizing tests

type TestName = StringSource

The name of a test or a group of tests

data TestTree Source

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] -> TestTreeSource

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

defaultMainWithIngredients :: [Ingredient] -> TestTree -> IO ()Source

Parse the command line arguments and run the tests using the provided ingredient list

defaultIngredients :: [Ingredient]Source

List of the default ingredients. This is what defaultMain uses.

At the moment it consists of listingTests and consoleTestReporter.

Adjusting 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.

adjustOption :: IsOption v => (v -> v) -> TestTree -> TestTreeSource

Locally adjust the option value for the given test subtree

localOption :: IsOption v => v -> TestTree -> TestTreeSource

Locally set the option value for the given test subtree

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.

withResourceSource

Arguments

:: IO a

initialize the resource

-> (a -> IO ())

free the resource

-> TestTree 
-> TestTree 

Add resource initialization and finalization to the test tree

Accessing the resource

If you need to access the resource in your tests, just put it in an IORef during initialization, and get it from there in the tests.

Here's an example:

import Test.Tasty
import Test.Tasty.HUnit
import Data.IORef

-- assumed defintions
data Foo
acquire :: IO Foo
release :: Foo -> IO ()
testWithFoo :: Foo -> Assertion

main = do
  ref <- newIORef $
    -- If you get this error, then either you forgot to actually write to
    -- the IORef, or it's a bug in tasty
    error "Resource isn't accessible"
  defaultMain $
    withResource (do r <- acquire; writeIORef ref r; return r) release (tests ref)

tests :: IORef Foo -> TestTree
tests ref =
  testGroup "Tests"
    [ testCase "x" $ readIORef ref >>= testWithFoo
    ]