hedgehog-extras-0.4.5.1: Supplemental library for hedgehog
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hedgehog.Extras.Test.Base

Synopsis

Documentation

propertyOnce :: HasCallStack => Integration () -> Property Source #

Run a property with only one test. This is intended for allowing hedgehog to run unit tests.

workspace :: (MonadTest m, MonadIO m, HasCallStack) => FilePath -> (FilePath -> m ()) -> m () Source #

Create a workspace directory which will exist for at least the duration of the supplied block.

The directory will have the supplied prefix but contain a generated random suffix to prevent interference between tests

The directory will be deleted if the block succeeds, but left behind if the block fails.

moduleWorkspace :: (MonadTest m, MonadIO m, HasCallStack) => String -> (FilePath -> m ()) -> m () Source #

Create a workspace directory which will exist for at least the duration of the supplied block.

The directory will have the prefix as "$prefixPath/$moduleName" but contain a generated random suffix to prevent interference between tests

The directory will be deleted if the block succeeds, but left behind if the block fails.

The prefix argument should not contain directory delimeters.

note :: (MonadTest m, HasCallStack) => String -> m String Source #

Annotate with the given string.

note_ :: (MonadTest m, HasCallStack) => String -> m () Source #

Annotate the given string returning unit.

noteM :: (MonadTest m, MonadCatch m, HasCallStack) => m String -> m String Source #

Annotate the given string in a monadic context.

noteM_ :: (MonadTest m, MonadCatch m, HasCallStack) => m String -> m () Source #

Annotate the given string in a monadic context returning unit.

noteIO :: (MonadTest m, MonadIO m, HasCallStack) => IO String -> m String Source #

Annotate the given string in IO.

noteIO_ :: (MonadTest m, MonadIO m, HasCallStack) => IO String -> m () Source #

Annotate the given string in IO returning unit.

noteShow :: (MonadTest m, HasCallStack, Show a) => a -> m a Source #

Annotate the given value.

noteShow_ :: (MonadTest m, HasCallStack, Show a) => a -> m () Source #

Annotate the given value returning unit.

noteShowM :: (MonadTest m, MonadCatch m, HasCallStack, Show a) => m a -> m a Source #

Annotate the given value in a monadic context.

noteShowM_ :: (MonadTest m, MonadCatch m, HasCallStack, Show a) => m a -> m () Source #

Annotate the given value in a monadic context returning unit.

noteShowIO :: (MonadTest m, MonadIO m, HasCallStack, Show a) => IO a -> m a Source #

Annotate the given value in IO.

noteShowIO_ :: (MonadTest m, MonadIO m, HasCallStack, Show a) => IO a -> m () Source #

Annotate the given value in IO returning unit.

noteEach :: (MonadTest m, HasCallStack, Show a, Traversable f) => f a -> m (f a) Source #

Annotate the each value in the given traversable.

noteEach_ :: (MonadTest m, HasCallStack, Show a, Traversable f) => f a -> m () Source #

Annotate the each value in the given traversable returning unit.

noteEachM :: (MonadTest m, HasCallStack, Show a, Traversable f) => m (f a) -> m (f a) Source #

Annotate the each value in the given traversable in a monadic context.

noteEachM_ :: (MonadTest m, HasCallStack, Show a, Traversable f) => m (f a) -> m () Source #

Annotate the each value in the given traversable in a monadic context returning unit.

noteEachIO :: (MonadTest m, MonadIO m, HasCallStack, Show a, Traversable f) => IO (f a) -> m (f a) Source #

Annotate the each value in the given traversable in IO.

noteEachIO_ :: (MonadTest m, MonadIO m, HasCallStack, Show a, Traversable f) => IO (f a) -> m () Source #

Annotate the each value in the given traversable in IO returning unit.

noteTempFile :: (MonadTest m, HasCallStack) => FilePath -> FilePath -> m FilePath Source #

Return the test file path after annotating it relative to the project root directory

headM :: (MonadTest m, HasCallStack) => [a] -> m a Source #

nothingFail :: (MonadTest m, HasCallStack) => Maybe a -> m a Source #

Fail when the result is Nothing.

nothingFailM :: (MonadTest m, HasCallStack) => m (Maybe a) -> m a Source #

Fail when the computed result is Nothing.

leftFail :: (MonadTest m, Show e, HasCallStack) => Either e a -> m a Source #

Fail when the result is Left.

leftFailM :: (MonadTest m, Show e, HasCallStack) => m (Either e a) -> m a Source #

Fail when the computed result is Left.

onLeft :: Monad m => (e -> m a) -> m (Either e a) -> m a Source #

onNothing :: Monad m => m a -> m (Maybe a) -> m a Source #

jsonErrorFail :: (MonadTest m, HasCallStack) => Result a -> m a Source #

Fail when the result is Error.

jsonErrorFailM :: (MonadTest m, HasCallStack) => m (Result a) -> m a Source #

Fail when the computed result is Error.

failWithCustom :: MonadTest m => CallStack -> Maybe Diff -> String -> m a Source #

Takes a CallStack so the error can be rendered at the appropriate call site.

failMessage :: MonadTest m => CallStack -> String -> m a Source #

Takes a CallStack so the error can be rendered at the appropriate call site.

assertByDeadlineM :: (MonadTest m, MonadIO m, HasCallStack) => UTCTime -> m Bool -> m () Source #

Run the operation f once a second until it returns True or the deadline expires.

Expiration of the deadline results in an assertion failure

assertByDeadlineIO :: (MonadTest m, MonadIO m, HasCallStack) => UTCTime -> IO Bool -> m () Source #

Run the operation f once a second until it returns True or the deadline expires.

Expiration of the deadline results in an assertion failure

assertByDeadlineMFinally :: (MonadTest m, MonadIO m, HasCallStack) => UTCTime -> m Bool -> m () -> m () Source #

Run the operation f once a second until it returns True or the deadline expires.

The action g is run after expiration of the deadline, but before failure allowing for additional annotations to be presented.

Expiration of the deadline results in an assertion failure

assertByDeadlineIOFinally :: (MonadTest m, MonadIO m, HasCallStack) => UTCTime -> IO Bool -> m () -> m () Source #

Run the operation f once a second until it returns True or the deadline expires.

The action g is run after expiration of the deadline, but before failure allowing for additional annotations to be presented.

Expiration of the deadline results in an assertion failure

assertWith :: (MonadTest m, Show p, HasCallStack) => p -> (p -> Bool) -> m () Source #

Run the test function against the value. Report the value on the failure.

assertWithM :: (MonadTest m, Show p, HasCallStack) => p -> (p -> m Bool) -> m () Source #

Run the test function against the value. Report the value on the failure.

assertM :: (MonadTest m, HasCallStack) => m Bool -> m () Source #

Run the monadic action f and assert the return value is True.

assertIO :: (MonadTest m, MonadIO m, HasCallStack) => IO Bool -> m () Source #

Run the IO action f and assert the return value is True.

assertWithinTolerance Source #

Arguments

:: (Show a, Ord a, Num a, HasCallStack, MonadTest m) 
=> a

tested value v

-> a

expected value c

-> a

tolerance range r

-> m () 

Tests if |c - v| <= r

byDeadlineM :: forall m a. (MonadAssertion m, MonadTest m, MonadIO m, HasCallStack) => NominalDiffTime -> UTCTime -> String -> m a -> m a Source #

Run the operation f once a second until it returns True or the deadline expires.

Expiration of the deadline results in an assertion failure

byDeadlineIO :: (MonadAssertion m, MonadTest m, MonadIO m, HasCallStack) => NominalDiffTime -> UTCTime -> String -> IO a -> m a Source #

Run the operation f once a second until it returns True or the deadline expires.

Expiration of the deadline results in an assertion failure

byDurationM :: (MonadAssertion m, MonadTest m, MonadIO m, HasCallStack) => NominalDiffTime -> NominalDiffTime -> String -> m a -> m a Source #

Run the operation f once a second until it returns True or the duration expires.

Expiration of the duration results in an assertion failure

byDurationIO :: (MonadAssertion m, MonadTest m, MonadIO m, HasCallStack) => NominalDiffTime -> NominalDiffTime -> String -> IO a -> m a Source #

Run the operation f once a second until it returns True or the duration expires.

Expiration of the duration results in an assertion failure

release :: (MonadTest m, MonadIO m) => ReleaseKey -> m () Source #

Release the given release key.

retry :: forall a. Int -> (Int -> Integration a) -> Integration a Source #

retry' :: forall a. Int -> Integration a -> Integration a Source #