Copyright | (c) Joel Burget 2018-2019 |
---|---|
License | MIT |
Maintainer | joelburget@gmail.com |
Stability | provisional |
Safe Haskell | None |
Language | Haskell98 |
EasyTest is a simple testing toolkit for unit- and property-testing. It's based on the hedgehog property-testing system. Here's an example usage:
module Main where import EasyTest import qualified Hedgehog.Gen as Gen import qualified Hedgehog.Range as Range suite ::Test
suite =tests
[scope
"addition.ex" $unitTest
$ 1 + 1===
2 ,scope
"list.reversal" $property
$ do ns<-
forAll
$ Gen.list (Range.singleton 10) (Gen.int Range.constantBounded) reverse (reverse ns)===
ns -- equivalent to `scope
"addition.ex3"` ,scope
"addition" .scope
"ex3" $unitTest
$ 3 + 3===
6 ,scope
"always passes" $unitTest
success
-- record a success result ,scope
"failing test" $unitTest
$crash
"oh noes!!" ] -- NB: `run
suite` would run all tests, but we only run -- tests whose scopes are prefixed by "addition" main :: IOSummary
main =runOnly
"addition" suite
This generates the output:
━━━ runOnly "addition" ━━━ ✓ addition.ex1 passed 1 test. ✓ addition.ex2 passed 1 test. ⚐ list.reversal gave up after 1 discard, passed 0 tests. ✓ addition.ex3 passed 1 test. ⚐ always passes gave up after 1 discard, passed 0 tests. ⚐ failing test gave up after 1 discard, passed 0 tests. ⚐ 3 gave up, 3 succeeded.
We write tests with ordinary Haskell code, with control flow explicit and under programmer control.
User guide
EasyTest supports two types of tests -- property tests and unit tests. Both are expressed as hedgehog properties (PropertyT
IO
()
). Unit tests, built with unitTest
(or example
) are run once. Property tests, built with property
, are run with many random values.
We often want to label tests so we can see when they succeed or fail. For that we use scope
:
-- | Label a test. Can be nested. A `'.'` is placed between nested -- scopes, so `scope "foo" . scope "bar"` is equivalent to `scope "foo.bar"`scope
:: String ->Test
->Test
Here's an example usage:
module Main where import EasyTest (Test
,scope
,crash
,run
,tests
,example
,success
, (===
),Summary
) suite ::Test
suite =tests
[example
success
,scope
"test-crash" $example
$crash
"oh noes!" ,example
$ 1 + 1 === 2 ] main :: IOSummary
main =run
suite
This example runs the three examples in order so that they're all tested. The output is:
━━━ run ━━━ ✓ (unnamed) passed 1 test. ✗ test-crash failed after 1 test. ┏━━ tests/Suite.hs ━━━ 6 ┃ suite :: Test 7 ┃ suite = tests 8 ┃ [ example success 9 ┃ , scope "test-crash" $ example $ crash "oh noes!" ┃ ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ 10 ┃ , example $ 1 + 1 === 2 11 ┃ ] oh noes! This failure can be reproduced by running: > recheck (Size 0) (Seed 12444749623322829837 10053881125821732685) test-crash ✓ (unnamed) passed 1 test. ✗ 1 failed, 2 succeeded.
In the output, we get a stack trace pointing to the line where crash was called (..tests/Suite.hs:9
), information about failing tests, and instructions for rerunning the tests with an identical random seed (in this case, there's no randomness, so rerun
would work fine, but if our test generated random data, we might want to rerun with the exact same random numbers). Note that, somewhat embarrassingly, the error message currently gives bad instructions and the correct way to rerun the tests is with
.rerun
(Seed 12444749623322829837 10053881125821732685) suite
The various run functions (run
, runOnly
, rerun
, and rerunOnly
) all return a hedgehog Summary
. Use cabalTestSuite
to exit the process with a nonzero status in the event of a failure, for use with exitcode-stdio-1.0
cabal test-suite
s. Here's an example cabal file:
test-suite tests type: exitcode-stdio-1.0 main-is: NameOfYourTestSuite.hs hs-source-dirs: tests other-modules: build-depends: base, easytest
For tests that are logically separate, we usually combine them into a suite using tests
, as in:
suite =tests
[scope
"ex1" $example
$ 1 + 1 === 2 ,scope
"ex2" $example
$ 2 + 2 === 4 ]
Property tests
We can also create property tests (via hedgehog). As an example, we can express the property that reversing a list twice results in the original list:
reverseTest :: Test () reverseTest =scope
"list reversal" $property
$ do nums <-forAll
$ Gen.list (Range.linear 0 100) (Gen.int (Range.linear 0 99)) reverse (reverse nums)===
nums
The above code generates lists of sizes between 0 and 100, consisting of Int
values in the range 0 through 99.
If our list reversal test failed, we might use
or runOnly
"list reversal"
to rerun just that subtree of the test suite, and we might add some additional diagnostics to see what was going on:rerunOnly
"list reversal" <randomseed>
import EasyTest import qualified Hedgehog.Gen as Gen import qualified Hedgehog.Range as Range reverseTest :: Test () reverseTest =property
$ do nums <-forAll
$ Gen.list (Range.linear 0 100) (Gen.int (Range.linear 0 99))footnote
$ "nums: " ++ show nums let r = reverse (reverse nums)footnote
$ "reverse (reverse nums): " ++ show r r===
nums
See the hedgehog docs for more on writing good property tests.
Bracketed tests
EasyTest also supports bracketed tests requiring setup and teardown.
For example, we could open a temporary file:
scope
"bracket-example" $example
$bracket
(mkstemp "temp") ((filepath, handle) -> hClose handle >> removeFile filepath) ((_filepath, handle) -> do liftIO $ hPutStrLn handle "this temporary file will be cleaned up"success
)
bracket
ensures that the resource is cleaned up, even if the test throws an
exception. You can write either property- or unit- tests in this style.
Synopsis
- data Test
- tests :: [Test] -> Test
- scope :: String -> Test -> Test
- example :: HasCallStack => PropertyT IO () -> Test
- unitTest :: HasCallStack => PropertyT IO () -> Test
- property :: HasCallStack => PropertyT IO () -> Test
- propertyWith :: HasCallStack => PropertyConfig -> PropertyT IO () -> Test
- matches :: HasCallStack => Prism' s a -> s -> PropertyT IO ()
- doesn'tMatch :: HasCallStack => Prism' s a -> s -> PropertyT IO ()
- skip :: Test -> Test
- pending :: String -> PropertyT IO ()
- crash :: HasCallStack => String -> PropertyT IO ()
- run :: Test -> IO Summary
- runOnly :: String -> Test -> IO Summary
- rerun :: Seed -> Test -> IO Summary
- rerunOnly :: String -> Seed -> Test -> IO Summary
- bracket :: IO a -> (a -> IO ()) -> (a -> PropertyT IO ()) -> PropertyT IO ()
- bracket_ :: IO a -> IO b -> PropertyT IO () -> PropertyT IO ()
- finally :: PropertyT IO () -> IO a -> PropertyT IO ()
- cabalTestSuite :: IO Summary -> IO ()
- success :: MonadTest m => m ()
- failure :: (MonadTest m, HasCallStack) => m a
- assert :: (MonadTest m, HasCallStack) => Bool -> m ()
- (===) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m ()
- (/==) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m ()
- data Seed = Seed {}
- data Summary
- footnote :: MonadTest m => String -> m ()
- annotate :: (MonadTest m, HasCallStack) => String -> m ()
- forAll :: (Monad m, Show a, HasCallStack) => Gen a -> PropertyT m a
- data PropertyT (m :: Type -> Type) a
- data PropertyConfig = PropertyConfig {}
- defaultConfig :: PropertyConfig
Structuring tests
scope :: String -> Test -> Test Source #
Label a test. Can be nested. A "." is placed between nested
scopes, so scope "foo" . scope "bar"
is equivalent to scope "foo.bar"
example :: HasCallStack => PropertyT IO () -> Test Source #
Run a unit test (same as unitTest
). Example:
>>>
run $ example $ 1 === 2
> ━━━ run ━━━ > ✗ (unnamed) failed after 1 test. > > ┏━━ tests/Suite.hs ━━━ > 26 ┃ main :: IO () > 27 ┃ main = do > 28 ┃ run $ example $ 1 === (2 :: Int) > ┃ ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ > ┃ │ Failed (- lhs =/= + rhs) > ┃ │ - 1 > ┃ │ + 2 > > This failure can be reproduced by running: > > recheck (Size 0) (Seed 2914818620245020776 12314041441884757111) (unnamed) > > ✗ 1 failed.
unitTest :: HasCallStack => PropertyT IO () -> Test Source #
Run a unit test (same as example
). Example:
>>>
run $ unitTest $ 1 === 2
> ━━━ run ━━━ > ✗ (unnamed) failed after 1 test. > > ┏━━ tests/Suite.hs ━━━ > 26 ┃ main :: IO () > 27 ┃ main = do > 28 ┃ run $ unitTest $ 1 === (2 :: Int) > ┃ ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ > ┃ │ Failed (- lhs =/= + rhs) > ┃ │ - 1 > ┃ │ + 2 > > This failure can be reproduced by running: > > recheck (Size 0) (Seed 2914818620245020776 12314041441884757111) (unnamed) > > ✗ 1 failed.
property :: HasCallStack => PropertyT IO () -> Test Source #
Run a property test. Example:
>>>
run $ scope "list reversal" $ property $ do
>.. list <- forAll $ Gen.list @_ @Int (Range.linear 0 100) >.. (Gen.element [0..100]) >.. reverse (reverse list) === list > ━━━ run ━━━ > ✓ list reversal passed 100 tests. > ✓ 1 succeeded.
propertyWith :: HasCallStack => PropertyConfig -> PropertyT IO () -> Test Source #
Run a property test with a custom configuration. This allows you to configure the propertyTestLimit
, propertyDiscardLimit
, propertyShrinkLimit
, or propertyShrinkRetries
. Example:
>>>
run $ scope "list reversal" $ propertyWith (defaultConfig { propertyTestLimit = 500 }) $ do
>.. list <- forAll $ Gen.list @_ @Int (Range.linear 0 100) >.. (Gen.element [0..100]) >.. reverse (reverse list) === list > ━━━ run ━━━ > ✓ list reversal passed 500 tests. > ✓ 1 succeeded.
Assertions for unit tests
matches :: HasCallStack => Prism' s a -> s -> PropertyT IO () Source #
Test whether a Prism
matches. Example:
>>>
main
> ━━━ run ━━━ > ✓ (unnamed) passed 1 test. > ✗ (unnamed) failed after 1 test. > > ┏━━ tests/Suite.hs ━━━ > 48 ┃ main :: IO () > 49 ┃ main = do > 50 ┃ _ <- run $ tests > 51 ┃ [ example $ matches _Left (Left 1 :: Either Int ()) > 52 ┃ , example $ matches _Left (Right () :: Either Int ()) > ┃ ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ > 53 ┃ ] > 54 ┃ pure () > > Prism failed to match > > This failure can be reproduced by running: > > recheck (Size 0) (Seed 14003809197113786240 2614482618840800713) (unnamed) > > ✗ 1 failed, 1 succeeded.
Use with _Just
, _Nothing
, _Left
, _Right
, or Control.Lens.Prism
doesn'tMatch :: HasCallStack => Prism' s a -> s -> PropertyT IO () Source #
Running tests
runOnly :: String -> Test -> IO Summary Source #
Run all tests whose scope starts with the given prefix.
>>>
runOnly "components.a" tests
rerun :: Seed -> Test -> IO Summary Source #
Rerun all tests with the given seed
>>>
rerun (Seed 2914818620245020776 12314041441884757111) tests
rerunOnly :: String -> Seed -> Test -> IO Summary Source #
Rerun all tests with the given seed and whose scope starts with the given prefix
>>>
rerunOnly "components.a" (Seed 2914818620245020776 12314041441884757111) tests
Bracketed tests (requiring setup / teardown)
bracket :: IO a -> (a -> IO ()) -> (a -> PropertyT IO ()) -> PropertyT IO () Source #
Make a test with setup and teardown steps.
bracket_ :: IO a -> IO b -> PropertyT IO () -> PropertyT IO () Source #
A variant of bracket
where the return value from the setup step is not
required.
finally :: PropertyT IO () -> IO a -> PropertyT IO () Source #
A specialised variant of bracket
with just a teardown step.
Cabal test suite
cabalTestSuite :: IO Summary -> IO () Source #
Make this a cabal test suite for use with exitcode-stdio-1.0
test-suite
s.
This simply checks to see if any tests failed and if so exits with
exitFailure
.
Hedgehog re-exports
These common functions are included as a convenience for writing
propertyTest
s. See Hedgehog for more.
failure :: (MonadTest m, HasCallStack) => m a #
Causes a test to fail.
assert :: (MonadTest m, HasCallStack) => Bool -> m () #
Fails the test if the condition provided is False
.
(===) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m () infix 4 #
Fails the test if the two arguments provided are not equal.
(/==) :: (MonadTest m, Eq a, Show a, HasCallStack) => a -> a -> m () infix 4 #
Fails the test if the two arguments provided are equal.
footnote :: MonadTest m => String -> m () #
Logs a message to be displayed as additional information in the footer of the failure report.
annotate :: (MonadTest m, HasCallStack) => String -> m () #
Annotates the source code with a message that might be useful for debugging a test failure.
forAll :: (Monad m, Show a, HasCallStack) => Gen a -> PropertyT m a #
Generates a random input for the test by running the provided generator.
data PropertyT (m :: Type -> Type) a #
The property monad transformer allows both the generation of test inputs and the assertion of expectations.
Instances
data PropertyConfig #
Configuration for a property test.
Instances
Eq PropertyConfig | |
Defined in Hedgehog.Internal.Property (==) :: PropertyConfig -> PropertyConfig -> Bool # (/=) :: PropertyConfig -> PropertyConfig -> Bool # | |
Ord PropertyConfig | |
Defined in Hedgehog.Internal.Property compare :: PropertyConfig -> PropertyConfig -> Ordering # (<) :: PropertyConfig -> PropertyConfig -> Bool # (<=) :: PropertyConfig -> PropertyConfig -> Bool # (>) :: PropertyConfig -> PropertyConfig -> Bool # (>=) :: PropertyConfig -> PropertyConfig -> Bool # max :: PropertyConfig -> PropertyConfig -> PropertyConfig # min :: PropertyConfig -> PropertyConfig -> PropertyConfig # | |
Show PropertyConfig | |
Defined in Hedgehog.Internal.Property showsPrec :: Int -> PropertyConfig -> ShowS # show :: PropertyConfig -> String # showList :: [PropertyConfig] -> ShowS # | |
Lift PropertyConfig | |
Defined in Hedgehog.Internal.Property lift :: PropertyConfig -> Q Exp # |
defaultConfig :: PropertyConfig #
The default configuration for a property test.