Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This package provides the ability to run a Checklist of several "checks" during a single test. A "bad" check does not immediately result in a test failure; at the end of the test (passed or failed due to primary testing), all failed checks are reported (and any failed checks will result in an overall test failure at the end.
This type of checking can be very useful when needing to test various aspects of an operation that is complex to setup, has multiple effects, or where the checks are related such that knowing about the multiple failures makes debugging easier.
An alternative approach is to have some sort of common preparation code and use a separate test for each item. This module simply provides a convenient method to collate related items under the aegis of a single test.
This package also provides the checkValues
function which can be
used to check a number of derived values from a single input value
via a checklist. This can be used to independently verify a number
of record fields of a data structure or to validate related
operations performed from a single input.
See the documentation for check
and checkValues
for examples of
using this library. The tests in the source package also provide
additional examples of usage.
Synopsis
- withChecklist :: (MonadIO m, MonadMask m) => Text -> (CanCheck => m a) -> m a
- type CanCheck = ?checker :: IORef [CheckResult]
- check :: (CanCheck, TestShow a, MonadIO m) => Text -> (a -> Bool) -> a -> m ()
- discardCheck :: (CanCheck, MonadIO m) => Text -> m ()
- checkValues :: CanCheck => TestShow dType => dType -> Assignment (DerivedVal dType) idx -> IO ()
- data DerivedVal i d where
- Val :: (TestShow d, Eq d) => Text -> (i -> d) -> d -> DerivedVal i d
- data ChecklistFailures
- class TestShow v where
- testShowList :: TestShow v => [v] -> String
Documentation
withChecklist :: (MonadIO m, MonadMask m) => Text -> (CanCheck => m a) -> m a Source #
This should be used to wrap the test that contains checks. This initializes the environment needed for the checks to run, and on exit from the test, reports any (and all) failed checks as a test failure.
type CanCheck = ?checker :: IORef [CheckResult] Source #
A convenient Constraint to apply to functions that will perform
checks (i.e. call check
one or more times)
check :: (CanCheck, TestShow a, MonadIO m) => Text -> (a -> Bool) -> a -> m () Source #
This is used to run a check within the code. The first argument
is the "name" of this check, the second is a function that takes a
value and returns True
if the value is OK, or False
if the
value fails the check. The last argument is the value to check.
>>>
:set -XOverloadedStrings
>>>
:{
>>>
defaultMain $ testCase "odd numbers" $ withChecklist "odds" $ do
>>>
let three = 3 :: Int
>>>
check "three is odd" odd three
>>>
check "two is odd" odd (2 :: Int)
>>>
check "7 + 3 is odd" odd $ 7 + three
>>>
check "7 is odd" odd (7 :: Int)
>>>
:}
tst1: FAIL Exception: ERROR: numbers 2 checks failed in this checklist: ↪Failed check of "two is odd" with "2" ↪Failed check of "7 + 3 is odd" with "10"
Any check failures are also printed to stdout (and omitted from the
above for clarity). This is so that those failures are reported
even if a more standard test assertion is used that prevents
completion of the checklist. Thus, if an `assertEqual "values"
three 7` had been added to the above, that would have been the only
actual (and immediate) fail for the test, but any failing check
s
appearing before that assertEqual
would still have printed.
discardCheck :: (CanCheck, MonadIO m) => Text -> m () Source #
Sometimes checks are provided in common testing code, often in setup/preparation for the main tests. In some cases, the check is not applicable for that particular test. This function can be used to discard any pending failures for the associated named check.
This is especially useful when a common code block is used to
perform a set of checks: if a few of the common checks are not
appropriate for the current situation, discardCheck
can be used
to throw away the results of those checks by matching on the check
name.
checkValues :: CanCheck => TestShow dType => dType -> Assignment (DerivedVal dType) idx -> IO () Source #
The checkValues
is a checklist that tests various values that
can be derived from the input value. The input value is provided,
along with an Assignment
list of
extraction functions and the expected result value (and name) of
that extraction. Each extraction is performed as a check within
the checklist.
This is convenient to gather together a number of validations on a single datatype and represent them economically.
One example is testing the fields of a record structure:
{-# LANGUAGE PatternSynonyms, OverloadedStrings #-} import Data.Parameterized.Context ( pattern Empty, pattern (:>) ) import Test.Tasty.Checklist data Struct = MyStruct { foo :: Int, bar :: Char, baz :: String } instance Show Struct where show s = baz s <> " is " <> foo s <> bar s someFun :: Int -> Struct someFun n = MyStruct (n * 6) (if n * 6 == 42 then '!' else '?') "The answer to the universe" oddAnswer :: Struct -> Bool oddAnswer = odd . foo test = testCase "someFun result" $ someFun 3 `checkValues` (Empty :> Val "foo" foo 42 :> Val "baz field" baz "The answer to the universe" :> Val "shown" show "The answer to the universe is 42!" :> Val "odd answer" oddAnswer False :> Val "double-checking foo" foo 42 )
Running this test:
>>>
defaultMain test
ERROR: on input "The answer to the universe is 18?" 2 checks failed: ↪Failed check of "foo" with "42" ↪Failed check of "shown" with "The answer to the universe is 42!"
In this case, several of the values checked were correct, but more than one was wrong. Helpfully, this test output lists all the wrong answers for the single input provided.
data DerivedVal i d where Source #
Each entry in the Assignment
list
for checkValues
should be one of these DerivedVal
values.
Val :: (TestShow d, Eq d) => Text -> (i -> d) -> d -> DerivedVal i d |
Error reporting
data ChecklistFailures Source #
The ChecklistFailures exception is thrown if any checks have failed during testing.
Instances
Show ChecklistFailures Source # | |
Defined in Test.Tasty.Checklist showsPrec :: Int -> ChecklistFailures -> ShowS # show :: ChecklistFailures -> String # showList :: [ChecklistFailures] -> ShowS # | |
Exception ChecklistFailures Source # | |
Defined in Test.Tasty.Checklist |
Displaying tested values
class TestShow v where Source #
The TestShow
class is defined to provide a way for the various
data objects tested by this module to be displayed when tests fail.
The default testShow
will use a Show
instance, but this can be
overridden if there are alternate ways t o display a particular
object (e.g. pretty-printing, etc.)
Nothing
Instances
TestShow Bool Source # | |
TestShow Char Source # | |
TestShow Float Source # | |
TestShow Int Source # | |
TestShow Integer Source # | |
TestShow () Source # | |
Defined in Test.Tasty.Checklist | |
TestShow String Source # | |
(TestShow a, TestShow b) => TestShow (a, b) Source # | |
Defined in Test.Tasty.Checklist | |
(TestShow a, TestShow b, TestShow c) => TestShow (a, b, c) Source # | |
Defined in Test.Tasty.Checklist |
testShowList :: TestShow v => [v] -> String Source #
A helper function for defining a testShow for lists of items.
instance TestShow [Int] where testShow = testShowList