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

Safe HaskellNone

Test.Chell

Contents

Synopsis

Main

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

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

Test suites

data Suite Source

A tree of Tests; use the test and suite helper functions to build up a Suite.

Instances

suiteTests :: Suite -> [Test]Source

The full list of Tests contained within this Suite. Each Test is returned with its name modified to include the name of its parent Suites.

skipIf :: Bool -> Suite -> SuiteSource

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"
    [ skipIf builtOnUnix test_WindowsSpecific
    ]

skipWhen :: IO Bool -> Suite -> SuiteSource

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

tests = suite "tests"
    [ skipWhen noNetwork test_PingGoogle
    ]

Basic testing library

This library includes a few basic JUnit-style assertions, for use in simple test suites where depending on a separate test framework is too much trouble.

assertions :: Text -> Assertions a -> SuiteSource

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

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

assertionsTest :: Text -> Assertions a -> TestSource

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

This is easier to use than assertions when the result is going to be modified (eg, by a wrapper) before being used in a test suite.

Most users should use assertions instead, to avoid the extra wrapping step.

assert :: Q ExpSource

Run an Assertion. If the assertion fails, the test will immediately fail.

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

Run an Assertion. If the assertion fails, the test will continue to run until it finishes (or until an assert fails).

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 ()

fail :: Q ExpSource

Cause a test to immediately fail, with a message.

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

 $fail :: Text -> Assertions a

trace :: Text -> Assertions ()Source

Print a message from within a test. This is just a helper for debugging, so you don't have to import Debug.Trace.

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

Attach metadata to a test run. This will be included in reports.

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 threw an exception.

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 :: Maybe a -> AssertionSource

Assert that some value is Nothing.

left :: Either a b -> AssertionSource

Assert that some value is Left.

right :: Either a b -> AssertionSource

Assert that some value is Right.

throws :: Exception err => (err -> Bool) -> IO a -> 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 -> 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.

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.

Constructing tests

data Test Source

Constructors

Test Text (TestOptions -> IO TestResult) 

Instances

testName :: Test -> TextSource

testName (Test name _) = name

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.

defaultTestOptions :: TestOptionsSource

Default test options.

testOptionSeed defaultTestOptions = 0
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.

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.

data Failure Source

Constructors

Failure (Maybe Location) Text 

Instances