Safe Haskell | None |
---|---|
Language | Haskell2010 |
Hedgehog.Extras.Test.Base
Synopsis
- propertyOnce :: HasCallStack => Integration () -> Property
- workspace :: (HasCallStack, MonadBaseControl IO m, MonadResource m, MonadTest m) => FilePath -> (FilePath -> m ()) -> m ()
- moduleWorkspace :: (HasCallStack, MonadBaseControl IO m, MonadResource m, MonadTest m) => String -> (FilePath -> m ()) -> m ()
- note :: (MonadTest m, HasCallStack) => String -> m String
- note_ :: (MonadTest m, HasCallStack) => String -> m ()
- noteM :: (MonadTest m, MonadCatch m, HasCallStack) => m String -> m String
- noteM_ :: (MonadTest m, MonadCatch m, HasCallStack) => m String -> m ()
- noteIO :: (MonadTest m, MonadIO m, HasCallStack) => IO String -> m String
- noteIO_ :: (MonadTest m, MonadIO m, HasCallStack) => IO String -> m ()
- noteShow :: (MonadTest m, HasCallStack, Show a) => a -> m a
- noteShowPretty :: (MonadTest m, HasCallStack, Show a) => a -> m a
- noteShowIO :: (MonadTest m, MonadIO m, HasCallStack, Show a) => IO a -> m a
- noteShowPrettyIO :: (MonadTest m, MonadIO m, HasCallStack, Show a) => IO a -> m a
- noteShowIO_ :: (MonadTest m, MonadIO m, HasCallStack, Show a) => IO a -> m ()
- noteShowPrettyIO_ :: (MonadTest m, MonadIO m, HasCallStack, Show a) => IO a -> m ()
- noteShowM :: (MonadTest m, MonadCatch m, HasCallStack, Show a) => m a -> m a
- noteShowPrettyM :: (MonadTest m, MonadCatch m, HasCallStack, Show a) => m a -> m a
- noteShowM_ :: (MonadTest m, MonadCatch m, HasCallStack, Show a) => m a -> m ()
- noteShowPrettyM_ :: (MonadTest m, MonadCatch m, HasCallStack, Show a) => m a -> m ()
- noteShow_ :: (MonadTest m, HasCallStack, Show a) => a -> m ()
- noteShowPretty_ :: (MonadTest m, HasCallStack, Show a) => a -> m ()
- noteEach :: (MonadTest m, HasCallStack, Show a, Traversable f) => f a -> m (f a)
- noteEachPretty :: (MonadTest m, HasCallStack, Show a, Traversable f) => f a -> m (f a)
- noteEachIO :: (MonadTest m, MonadIO m, HasCallStack, Show a, Traversable f) => IO (f a) -> m (f a)
- noteEachPrettyIO :: (MonadTest m, MonadIO m, HasCallStack, Show a, Traversable f) => IO (f a) -> m (f a)
- noteEachIO_ :: (MonadTest m, MonadIO m, HasCallStack, Show a, Traversable f) => IO (f a) -> m ()
- noteEachPrettyIO_ :: (MonadTest m, MonadIO m, HasCallStack, Show a, Traversable f) => IO (f a) -> m ()
- noteEachM :: (MonadTest m, HasCallStack, Show a, Traversable f) => m (f a) -> m (f a)
- noteEachPrettyM :: (MonadTest m, HasCallStack, Show a, Traversable f) => m (f a) -> m (f a)
- noteEachM_ :: (MonadTest m, HasCallStack, Show a, Traversable f) => m (f a) -> m ()
- noteEachPrettyM_ :: (MonadTest m, HasCallStack, Show a, Traversable f) => m (f a) -> m ()
- noteEach_ :: (MonadTest m, HasCallStack, Show a, Traversable f) => f a -> m ()
- noteEachPretty_ :: (MonadTest m, HasCallStack, Show a, Traversable f) => f a -> m ()
- noteTempFile :: (MonadTest m, HasCallStack) => FilePath -> FilePath -> m FilePath
- headM :: (MonadTest m, HasCallStack) => [a] -> m a
- indexM :: (MonadTest m, HasCallStack) => Int -> [a] -> m a
- fromJustM :: (MonadTest m, HasCallStack) => Maybe a -> m a
- nothingFail :: (MonadTest m, HasCallStack) => Maybe a -> m a
- nothingFailM :: (MonadTest m, HasCallStack) => m (Maybe a) -> m a
- leftFail :: (MonadTest m, Show e, HasCallStack) => Either e a -> m a
- leftFailM :: (MonadTest m, Show e, HasCallStack) => m (Either e a) -> m a
- onLeft :: Monad m => (e -> m a) -> m (Either e a) -> m a
- onNothing :: Monad m => m a -> m (Maybe a) -> m a
- jsonErrorFail :: (MonadTest m, HasCallStack) => Result a -> m a
- jsonErrorFailM :: (MonadTest m, HasCallStack) => m (Result a) -> m a
- failWithCustom :: MonadTest m => CallStack -> Maybe Diff -> String -> m a
- failMessage :: MonadTest m => CallStack -> String -> m a
- expectFailure :: (MonadTest m, MonadIO m, HasCallStack) => TestT IO a -> m ()
- expectFailureWith :: (MonadTest m, MonadIO m, HasCallStack) => (Failure -> m ()) -> TestT IO b -> m ()
- tryAssertion :: MonadAssertion m => m a -> m (Either Failure a)
- assertFailure :: (HasCallStack, Show a, MonadAssertion m, MonadTest m) => m a -> m Failure
- assertFailure_ :: (HasCallStack, Show a, MonadAssertion m, MonadTest m) => m a -> m ()
- assertByDeadlineM :: (MonadTest m, MonadIO m, HasCallStack) => UTCTime -> m Bool -> m ()
- assertByDeadlineIO :: (MonadTest m, MonadIO m, HasCallStack) => UTCTime -> IO Bool -> m ()
- assertByDeadlineMFinally :: (MonadTest m, MonadIO m, HasCallStack) => UTCTime -> m Bool -> m () -> m ()
- assertByDeadlineIOFinally :: (MonadTest m, MonadIO m, HasCallStack) => UTCTime -> IO Bool -> m () -> m ()
- assertWith :: (MonadTest m, Show p, HasCallStack) => p -> (p -> Bool) -> m ()
- assertWithM :: (MonadTest m, Show p, HasCallStack) => p -> (p -> m Bool) -> m ()
- assertM :: (MonadTest m, HasCallStack) => m Bool -> m ()
- assertIO :: (MonadTest m, MonadIO m, HasCallStack) => IO Bool -> m ()
- assertWithinTolerance :: (Show a, Ord a, Num a, HasCallStack, MonadTest m) => a -> a -> a -> m ()
- byDeadlineM :: (MonadAssertion m, MonadTest m, MonadIO m, HasCallStack) => NominalDiffTime -> UTCTime -> String -> m a -> m a
- byDeadlineIO :: (MonadAssertion m, MonadTest m, MonadIO m, HasCallStack) => NominalDiffTime -> UTCTime -> String -> IO a -> m a
- byDurationM :: (MonadAssertion m, MonadTest m, MonadIO m, HasCallStack) => NominalDiffTime -> NominalDiffTime -> String -> m a -> m a
- byDurationIO :: (MonadAssertion m, MonadTest m, MonadIO m, HasCallStack) => NominalDiffTime -> NominalDiffTime -> String -> IO a -> m a
- onFailure :: Integration () -> Integration ()
- type Integration a = PropertyT (ReaderT IntegrationState (ResourceT IO)) a
- release :: (MonadTest m, MonadIO m) => ReleaseKey -> m ()
- runFinallies :: Integration a -> Integration a
- retry :: Int -> (Int -> Integration a) -> Integration a
- retry' :: Int -> Integration a -> Integration a
- class MonadBase b m => MonadBaseControl (b :: Type -> Type) (m :: Type -> Type) | m -> b
- bracket :: MonadBaseControl IO m => m a -> (a -> m b) -> (a -> m c) -> m c
- bracket_ :: MonadBaseControl IO m => m a -> m b -> m c -> m c
Documentation
propertyOnce :: HasCallStack => Integration () -> Property Source #
Run a property with only one test. This is intended for allowing hedgehog to run unit tests.
workspace :: (HasCallStack, MonadBaseControl IO m, MonadResource m, MonadTest m) => 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 :: (HasCallStack, MonadBaseControl IO m, MonadResource m, MonadTest m) => 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 () 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.
noteShowPretty :: (MonadTest m, HasCallStack, Show a) => a -> m a Source #
Annotate the given value, pretty printing it with indentation. Note that large data structures will take a significant amount of vertical screen space.
noteShowIO :: (MonadTest m, MonadIO m, HasCallStack, Show a) => IO a -> m a Source #
Annotate the given value in IO.
noteShowPrettyIO :: (MonadTest m, MonadIO m, HasCallStack, Show a) => IO a -> m a Source #
Annotate the given value in IO, pretty printing it with indentation. Note that large data structures will take a significant amount of vertical screen space.
noteShowIO_ :: (MonadTest m, MonadIO m, HasCallStack, Show a) => IO a -> m () Source #
Annotate the given value in IO returning unit.
noteShowPrettyIO_ :: (MonadTest m, MonadIO m, HasCallStack, Show a) => IO a -> m () Source #
Annotate the given value in IO returning unit, pretty printing it with indentation. Note that large data structures will take a significant amount of vertical screen space.
noteShowM :: (MonadTest m, MonadCatch m, HasCallStack, Show a) => m a -> m a Source #
Annotate the given value in a monadic context.
noteShowPrettyM :: (MonadTest m, MonadCatch m, HasCallStack, Show a) => m a -> m a Source #
Annotate the given value in a monadic context, pretty printing it with indentation. Note that large data structures will take a significant amount of vertical screen space.
noteShowM_ :: (MonadTest m, MonadCatch m, HasCallStack, Show a) => m a -> m () Source #
Annotate the given value in a monadic context returning unit.
noteShowPrettyM_ :: (MonadTest m, MonadCatch m, HasCallStack, Show a) => m a -> m () Source #
Annotate the given value in a monadic context returning unit, pretty printing it with indentation. Note that large data structures will take a significant amount of vertical screen space.
noteShow_ :: (MonadTest m, HasCallStack, Show a) => a -> m () Source #
Annotate the given value returning unit.
noteShowPretty_ :: (MonadTest m, HasCallStack, Show a) => a -> m () Source #
Annotate the given value returning unit, pretty printing it with indentation. Note that large data structures will take a significant amount of vertical screen space.
noteEach :: (MonadTest m, HasCallStack, Show a, Traversable f) => f a -> m (f a) Source #
Annotate the each value in the given traversable.
noteEachPretty :: (MonadTest m, HasCallStack, Show a, Traversable f) => f a -> m (f a) Source #
Annotate the each value in the given traversable, pretty printing it with indentation. Note that large data structures will take a significant amount of vertical screen space.
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.
noteEachPrettyIO :: (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, pretty printing it with indentation. Note that large data structures will take a significant amount of vertical screen space.
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.
noteEachPrettyIO_ :: (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, pretty printing it with indentation. Note that large data structures will take a significant amount of vertical screen space.
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.
noteEachPrettyM :: (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, pretty printing it with indentation. Note that large data structures will take a significant amount of vertical screen space.
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.
noteEachPrettyM_ :: (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, pretty printing it with indentation. Note that large data structures will take a significant amount of vertical screen space.
noteEach_ :: (MonadTest m, HasCallStack, Show a, Traversable f) => f a -> m () Source #
Annotate the each value in the given traversable returning unit.
noteEachPretty_ :: (MonadTest m, HasCallStack, Show a, Traversable f) => f a -> m () Source #
Annotate the each value in the given traversable returning unit, pretty printing it with indentation. Note that large data structures will take a significant amount of vertical screen space.
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 #
fromJustM :: (MonadTest m, HasCallStack) => Maybe a -> m a Source #
Index into a list. On failure, a friendly message is included in the test report.
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.
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.
expectFailure :: (MonadTest m, MonadIO m, HasCallStack) => TestT IO a -> m () Source #
Invert the behavior of a property: success becomes failure and vice versa.
expectFailureWith :: (MonadTest m, MonadIO m, HasCallStack) => (Failure -> m ()) -> TestT IO b -> m () Source #
Invert the behavior of a property: success becomes failure and vice versa.
This function behaves like expectFailure
but it allows to check the failure
is as expected. The function takes a Failure
and should itself be a test
that fails if the failure is not as expected.
tryAssertion :: MonadAssertion m => m a -> m (Either Failure a) Source #
Attempt to run a function that may assert, returning either a failure or the result of the assertion.
assertFailure :: (HasCallStack, Show a, MonadAssertion m, MonadTest m) => m a -> m Failure Source #
Run the given action and succeed if the action fails, but fail if it succeeds.
assertFailure_ :: (HasCallStack, Show a, MonadAssertion m, MonadTest m) => m a -> m () Source #
Run the given action and succeed if the action fails, but fail if it succeeds.
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 |
-> a | expected value |
-> a | tolerance range |
-> m () |
Tests if |c - v| <= r
byDeadlineM :: (MonadAssertion m, MonadTest m, MonadIO m, HasCallStack) => NominalDiffTime -> UTCTime -> String -> m a -> m a Source #
Run the operation f
once per period
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 per period
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 per period
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 per period
until it returns True
or the duration expires.
Expiration of the duration results in an assertion failure
onFailure :: Integration () -> Integration () Source #
type Integration a = PropertyT (ReaderT IntegrationState (ResourceT IO)) a Source #
runFinallies :: Integration a -> Integration a Source #
retry :: Int -> (Int -> Integration a) -> Integration a Source #
retry' :: Int -> Integration a -> Integration a Source #
class MonadBase b m => MonadBaseControl (b :: Type -> Type) (m :: Type -> Type) | m -> b #
Writing instances
The usual way to write a
instance for a transformer
stack over a base monad MonadBaseControl
B
is to write an instance MonadBaseControl B B
for the base monad, and MonadTransControl T
instances for every transformer
T
. Instances for
are then simply implemented using
MonadBaseControl
, ComposeSt
, defaultLiftBaseWith
.defaultRestoreM
Minimal complete definition
Instances
Arguments
:: MonadBaseControl IO m | |
=> m a | computation to run first ("acquire resource") |
-> (a -> m b) | computation to run last ("release resource") |
-> (a -> m c) | computation to run in-between |
-> m c |
Generalized version of bracket
.
Note:
- When the "acquire" or "release" computations throw exceptions
any monadic side effects in
m
will be discarded. - When the "in-between" computation throws an exception any
monadic side effects in
m
produced by that computation will be discarded but the side effects of the "acquire" or "release" computations will be retained. - Also, any monadic side effects in
m
of the "release" computation will be discarded; it is run only for its side effects inIO
.
Note that when your acquire
and release
computations are of type IO
it will be more efficient to write:
liftBaseOp
(bracket
acquire release)
Arguments
:: MonadBaseControl IO m | |
=> m a | computation to run first ("acquire resource") |
-> m b | computation to run last ("release resource") |
-> m c | computation to run in-between |
-> m c |
Generalized version of bracket_
.
Note any monadic side effects in m
of both the "acquire" and
"release" computations will be discarded. To keep the monadic
side effects of the "acquire" computation, use bracket
with
constant functions instead.
Note that when your acquire
and release
computations are of type IO
it will be more efficient to write:
liftBaseOp_
(bracket_
acquire release)