zeugma-0.9.0.1: Polysemy effects for testing
Safe HaskellSafe-Inferred
LanguageGHC2021

Zeugma

Description

Utilities for Incipit programs using hedgehog.

Synopsis

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.

testTime :: Time Source #

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 #

Interpret Stop by throwing a TestError, with the call site's stack.

resumeTest :: forall err eff r. Show err => HasCallStack => Members [eff !! err, Error TestError] r => InterpreterFor eff r Source #

Interpret an effect into Resumable by throwing a TestError for Stops, with the call site's stack.

errorTest :: forall err r. Show err => HasCallStack => Member (Error TestError) r => InterpreterFor (Error err) r Source #

Interpret Error converting the error to TestError, with the call site's stack.

Reexports of ubiquitous names

unitTest :: TestName -> UnitTest -> TestTree #

Convert a TestT IO () to a 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 TestT IO () to a 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)

testGroup :: TestName -> [TestTree] -> TestTree #

Create a named group of test cases or other groups

data TestTree #

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.

data Failure #

Instances

Instances details
Show Failure 
Instance details

Defined in Hedgehog.Internal.Property

Eq Failure 
Instance details

Defined in Hedgehog.Internal.Property

Methods

(==) :: Failure -> Failure -> Bool #

(/=) :: Failure -> Failure -> Bool #

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.

data TestError where #

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.

Instances

Instances details
Show TestError 
Instance details

Defined in Polysemy.Test.Data.TestError

Eq TestError 
Instance details

Defined in Polysemy.Test.Data.TestError