chell-0.3: A simple and intuitive library for automated testing.

Safe HaskellNone

Test.Chell

Contents

Description

Chell is a simple and intuitive library for automated testing. It natively supports assertion-based testing, and can use companion libraries such as chell-quickcheck to support more complex testing strategies.

An example test suite, which verifies the behavior of artithmetic operators.

{-# LANGUAGE TemplateHaskell #-}

import Test.Chell

tests_Math :: Suite
tests_Math = suite "math"
    test_Addition
    test_Subtraction

test_Addition :: Test
test_Addition = assertions "addition" $ do
    $expect (equal (2 + 1) 3)
    $expect (equal (1 + 2) 3)

test_Subtraction :: Test
test_Subtraction = assertions "subtraction" $ do
    $expect (equal (2 - 1) 1)
    $expect (equal (1 - 2) (-1))

main :: IO ()
main = defaultMain [tests_Math]
$ ghc --make chell-example.hs
$ ./chell-example
PASS: 2 tests run, 2 tests passed

Synopsis

Main

defaultMain :: [Suite] -> IO ()Source

A simple default main function, which runs a list of tests and logs statistics to stdout.

Test suites

data Suite Source

A suite is a node in a hierarchy of tests, similar to a directory in the filesystem. Each suite has a name and a list of children, which are either suites or tests.

suiteName :: Suite -> StringSource

Get a suite's name. Suite names may be any string, but are typically plain ASCII so users can easily type them on the command line.

$ ghci chell-example.hs
Ok, modules loaded: Main.

*Main> suiteName tests_Math
"math"

suiteTests :: Suite -> [Test]Source

Get the full list of tests contained within this Suite. Each test is given its full name within the test hierarchy, where names are separated by periods.

$ ghci chell-example.hs
Ok, modules loaded: Main.

*Main> suiteTests tests_Math
[Test "math.addition",Test "math.subtraction"]

Building test suites

class BuildSuite a Source

See suite.

Instances

suite :: BuildSuite a => String -> aSource

Define a new Suite, with the given name and children.

The type of this function allows any number of children to be added, without requiring them to be homogenous types.

test_Addition :: Test
test_Subtraction :: Test
test_Show :: Test

tests_Math :: Suite
tests_Math = suite "math"
    test_Addition
    test_Subtraction

tests_Prelude :: Suite
tests_Prelude = suite "prelude"
    tests_Math
    test_Show

Skipping some tests

skipIf :: SuiteOrTest a => Bool -> a -> aSource

Conditionally skip tests. Use this to avoid commenting out tests which are currently broken, or do not work on the current platform.

tests :: Suite
tests = suite "tests"
    test_Foo
    (skipIf builtOnUnix test_WindowsSpecific)
    test_Bar

skipWhen :: SuiteOrTest a => IO Bool -> a -> aSource

Conditionally skip tests, depending on the result of a runtime check. The predicate is checked before each test is started.

tests :: Suite
tests = suite "tests"
    test_Foo
    (skipWhen noNetwork test_PingGoogle)
    test_Bar

Basic testing library

assertions :: String -> Assertions a -> TestSource

Convert a sequence of pass/fail assertions into a runnable test.

 test_Equality :: Test
 test_Equality = assertions "equality" $ do
     $assert (1 == 1)
     $assert (equal 1 1)

data Assertion Source

A single pass/fail assertion. Failed assertions include an explanatory message.

assert :: Q ExpSource

Check an assertion. If the assertion fails, the test will immediately fail.

The assertion to check can be a boolean value, an Assertion, or an IO action returning one of the above.

assert is a Template Haskell macro, to retain the source-file location from which it was used. Its effective type is:

 $assert :: IsAssertion assertion => assertion -> Assertions ()

expect :: Q ExpSource

Check an assertion. If the assertion fails, the test will continue to run until it finishes, a call to assert fails, or the test runs die.

The assertion to check can be a boolean value, an Assertion, or an IO action returning one of the above.

expect is a Template Haskell macro, to retain the source-file location from which it was used. Its effective type is:

 $expect :: IsAssertion assertion => assertion -> Assertions ()

die :: Q ExpSource

Cause a test to immediately fail, with a message.

die is a Template Haskell macro, to retain the source-file location from which it was used. Its effective type is:

 $die :: String -> Assertions a

trace :: Q ExpSource

Print a message from within a test. This is just a helper for debugging, so you don't have to import Debug.Trace. Messages will be prefixed with the filename and line number where $trace was called.

trace is a Template Haskell macro, to retain the source-file location from which it was used. Its effective type is:

 $trace :: String -> Assertions ()

note :: String -> String -> Assertions ()Source

Attach a note to a test run. Notes will be printed to stdout and included in reports, even if the test fails or aborts. Notes are useful for debugging failing tests.

afterTest :: IO () -> Assertions ()Source

Register an IO action to be run after the test completes. This action will run even if the test failed or aborted.

requireLeft :: Q ExpSource

Require an Either value to be Left, and return its contents. If the value is Right, fail the test.

requireLeft is a Template Haskell macro, to retain the source-file location from which it was used. Its effective type is:

 $requireLeft :: Show b => Either a b -> Assertions a

requireRight :: Q ExpSource

Require an Either value to be Right, and return its contents. If the value is Left, fail the test.

requireRight is a Template Haskell macro, to retain the source-file location from which it was used. Its effective type is:

 $requireRight :: Show a => Either a b -> Assertions b

Built-in assertions

equal :: (Show a, Eq a) => a -> a -> AssertionSource

Assert that two values are equal.

notEqual :: (Eq a, Show a) => a -> a -> AssertionSource

Assert that two values are not equal.

equalWithinSource

Arguments

:: (Real a, Show a) 
=> a 
-> a 
-> a

delta

-> Assertion 

Assert that two values are within some delta of each other.

just :: Maybe a -> AssertionSource

Assert that some value is Just.

nothing :: Show a => Maybe a -> AssertionSource

Assert that some value is Nothing.

left :: Show b => Either a b -> AssertionSource

Assert that some value is Left.

right :: Show a => Either a b -> AssertionSource

Assert that some value is Right.

throws :: Exception err => (err -> Bool) -> IO a -> IO AssertionSource

Assert that some computation throws an exception matching the provided predicate. This is mostly useful for exception types which do not have an instance for Eq, such as ErrorCall.

throwsEq :: (Eq err, Exception err, Show err) => err -> IO a -> IO AssertionSource

Assert that some computation throws an exception equal to the given exception. This is better than just checking that the correct type was thrown, because the test can also verify the exception contains the correct information.

greater :: (Ord a, Show a) => a -> a -> AssertionSource

Assert a value is greater than another.

greaterEqual :: (Ord a, Show a) => a -> a -> AssertionSource

Assert a value is greater than or equal to another.

lesser :: (Ord a, Show a) => a -> a -> AssertionSource

Assert a value is less than another.

lesserEqual :: (Ord a, Show a) => a -> a -> AssertionSource

Assert a value is less than or equal to another.

sameItems :: (Foldable container, Show item, Ord item) => container item -> container item -> AssertionSource

Assert that two containers have the same items, in any order.

equalItems :: (Foldable container, Show item, Ord item) => container item -> container item -> AssertionSource

Assert that two containers have the same items, in the same order.

class IsText a Source

Class for types which can be treated as text; see equalLines.

Instances

IsText String 
IsText ByteString

Uses Data.ByteString.Lazy.Char8

IsText ByteString

Uses Data.ByteString.Char8

IsText Text 
IsText Text 

equalLines :: (Ord a, IsText a) => a -> a -> AssertionSource

Assert that two pieces of text are equal. This uses a diff algorithm to check line-by-line, so the error message will be easier to read on large inputs.

equalLinesWith :: Ord a => (a -> [String]) -> a -> a -> AssertionSource

Variant of equalLines which allows a user-specified line-splitting predicate.

Custom test types

data Test Source

A Test is, essentially, an IO action that returns a TestResult. Tests are aggregated into suites (see Suite).

test :: String -> (TestOptions -> IO TestResult) -> TestSource

Define a test, with the given name and implementation.

testName :: Test -> StringSource

Get the name a test was given when it was defined; see test.

runTest :: Test -> TestOptions -> IO TestResultSource

Run a test, wrapped in error handlers. This will return TestAborted if the test throws an exception or times out.

Test results

data TestResult Source

The result of running a test.

To support future extensions to the testing API, any users of this module who pattern-match against the TestResult constructors should include a default case. If no default case is provided, a warning will be issued.

Constructors

TestPassed [(String, String)]

The test passed, and generated the given notes.

TestSkipped

The test did not run, because it was skipped with skipIf or skipWhen.

TestFailed [(String, String)] [Failure]

The test failed, generating the given notes and failures.

TestAborted [(String, String)] String

The test aborted with an error message, and generated the given notes.

Failures

data Failure Source

Contains details about a test failure.

Instances

failure :: FailureSource

An empty Failure; use the field accessors to populate this value.

failureLocation :: Failure -> Maybe LocationSource

If given, the location of the failing assertion, expectation, etc.

failureLocation is a field accessor, and can be used to update a Failure value.

failureMessage :: Failure -> StringSource

If given, a message which explains why the test failed.

failureMessage is a field accessor, and can be used to update a Failure value.

Failure locations

data Location Source

Contains details about a location in the test source file.

Instances

location :: LocationSource

An empty Location; use the field accessors to populate this value.

locationFile :: Location -> StringSource

A path to a source file, or empty if not provided.

locationFile is a field accessor, and can be used to update a Location value.

locationModule :: Location -> StringSource

A Haskell module name, or empty if not provided.

locationModule is a field accessor, and can be used to update a Location value.

locationLine :: Location -> Maybe IntegerSource

A line number, or Nothing if not provided.

locationLine is a field accessor, and can be used to update a Location value.

Test options

data TestOptions Source

Test options are passed to each test, and control details about how the test should be run.

defaultTestOptions :: TestOptionsSource

Default test options.

$ ghci
Prelude> import Test.Chell

Test.Chell> testOptionSeed defaultTestOptions
0

Test.Chell> testOptionTimeout defaultTestOptions
Nothing

testOptionSeed :: TestOptions -> IntSource

Get the RNG seed for this test run. The seed is generated once, in defaultMain, and used for all tests. It is also logged to reports using a note.

When using defaultMain, users may specify a seed using the --seed command-line option.

testOptionSeed is a field accessor, and can be used to update a TestOptions value.

testOptionTimeout :: TestOptions -> Maybe IntSource

An optional timeout, in millseconds. Tests which run longer than this timeout will be aborted.

When using defaultMain, users may specify a timeout using the --timeout command-line option.

testOptionTimeout is a field accessor, and can be used to update a TestOptions value.