| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
Zeugma
Description
Utilities for Incipit programs using hedgehog.
Synopsis
- runTest :: HasCallStack => Sem TestStack a -> TestT IO a
- runTestDebug :: HasCallStack => Sem TestStack a -> TestT IO a
- runTestTrace :: HasCallStack => Sem TestStack a -> TestT IO a
- runTestLevel :: HasCallStack => Severity -> Sem TestStack a -> TestT IO a
- runTestFrozen :: HasCallStack => Sem TestStack a -> TestT IO a
- runTestFrozenDebug :: HasCallStack => Sem TestStack a -> TestT IO a
- runTestFrozenTrace :: HasCallStack => Sem TestStack a -> TestT IO a
- runTestFrozenLevel :: HasCallStack => Severity -> Sem TestStack a -> TestT IO a
- testTime :: Time
- stopTest :: forall err r. Show err => HasCallStack => Member (Error TestError) r => InterpreterFor (Stop err) r
- resumeTest :: forall err eff r. Show err => HasCallStack => Members [eff !! err, Error TestError] r => InterpreterFor eff r
- errorTest :: forall err r. Show err => HasCallStack => Member (Error TestError) r => InterpreterFor (Error err) r
- unitTest :: TestName -> UnitTest -> TestTree
- unitTestTimes :: TestLimit -> TestName -> UnitTest -> TestTree
- defaultMain :: TestTree -> IO ()
- testGroup :: TestName -> [TestTree] -> TestTree
- data TestTree
- data Failure
- type TestStack = ConcTestStack ++ [Test, Fail, Error TestError, Hedgehog IO, Error Failure, Embed IO, Resource, Final IO]
- data TestError where
- pattern TestError :: HasCallStack => HasCallStack => Text -> TestError
Test runners
runTest :: HasCallStack => Sem TestStack a -> TestT IO a Source #
Run the test stack as a TestT with a log level of Crit.
runTestDebug :: HasCallStack => Sem TestStack a -> TestT IO a Source #
Run the test stack as a TestT with a log level of Debug.
runTestTrace :: HasCallStack => Sem TestStack a -> TestT IO a Source #
Run the test stack as a TestT with a log level of Trace.
runTestLevel :: HasCallStack => Severity -> Sem TestStack a -> TestT IO a Source #
Run the test stack as a TestT with the specified log level.
runTestFrozen :: HasCallStack => Sem TestStack a -> TestT IO a Source #
Run the test stack as a TestT with a log level of Crit and ChronosTime frozen at testTime.
runTestFrozenDebug :: HasCallStack => Sem TestStack a -> TestT IO a Source #
Run the test stack as a TestT with a log level of Debug and ChronosTime frozen at testTime.
runTestFrozenTrace :: HasCallStack => Sem TestStack a -> TestT IO a Source #
Run the test stack as a TestT with a log level of Trace and ChronosTime frozen at testTime.
runTestFrozenLevel :: HasCallStack => Severity -> Sem TestStack a -> TestT IO a Source #
Run the test stack as a TestT with the specified log level, with ChronosTime frozen at testTime.
The time at which the combinators ending in Frozen run the ChronosTime effect.
Resumable and Error to TestError conversion
stopTest :: forall err r. Show err => HasCallStack => Member (Error TestError) r => InterpreterFor (Stop err) r Source #
resumeTest :: forall err eff r. Show err => HasCallStack => Members [eff !! err, Error TestError] r => InterpreterFor eff r Source #
errorTest :: forall err r. Show err => HasCallStack => Member (Error TestError) r => InterpreterFor (Error err) r Source #
Reexports of ubiquitous names
unitTest :: TestName -> UnitTest -> TestTree #
Convert a to a TestT IO ()TestTree ready for use with Tasty's machinery.
This is for non-property tests that are supposed to be executed once.
unitTestTimes :: TestLimit -> TestName -> UnitTest -> TestTree #
Convert a to a TestT IO ()TestTree ready for use with Tasty's machinery.
This is for non-property tests that are supposed to be executed n times.
defaultMain :: TestTree -> IO () #
Parse the command line arguments and run the tests.
When the tests finish, this function calls exitWith with the exit code
that indicates whether any tests have failed. Most external systems
(stack, cabal, travis-ci, jenkins etc.) rely on the exit code to detect
whether the tests pass. If you want to do something else after
defaultMain returns, you need to catch the exception and then re-throw
it. Example:
import Test.Tasty
import Test.Tasty.HUnit
import System.Exit
import Control.Exception
test = testCase "Test 1" (2 @?= 3)
main = defaultMain test
`catch` (\e -> do
if e == ExitSuccess
then putStrLn "Yea"
else putStrLn "Nay"
throwIO e)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.
type TestStack = ConcTestStack ++ [Test, Fail, Error TestError, Hedgehog IO, Error Failure, Embed IO, Resource, Final IO] Source #
The entirety of the effects handled by this module's interpreters.
An error that occurred in the test machinery.
The pattern synonym is used for construction to ensure that the call site's stack is stored.
There is no IsString instance because it can't propagate the call stack.
Use testError to throw a string literal.
Bundled Patterns
| pattern TestError :: HasCallStack => HasCallStack => Text -> TestError | Construct a test error so that the call site's stack is stored in the value, for printing the correct location in hedgehog messages. |