hedgehog-extras-0.9.0.0: Supplemental library for hedgehog
Safe HaskellNone
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 :: (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 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.

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 #

indexM :: (MonadTest m, HasCallStack) => Int -> [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.

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.

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 v

-> a

expected value c

-> a

tolerance range r

-> 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

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

Release the given release key.

class MonadBase b m => MonadBaseControl (b :: Type -> Type) (m :: Type -> Type) | m -> b #

Writing instances

The usual way to write a MonadBaseControl instance for a transformer stack over a base monad B is to write an instance MonadBaseControl B B for the base monad, and MonadTransControl T instances for every transformer T. Instances for MonadBaseControl are then simply implemented using ComposeSt, defaultLiftBaseWith, defaultRestoreM.

Minimal complete definition

liftBaseWith, restoreM

Instances

Instances details
MonadBaseControl Identity Identity 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM Identity a 
Instance details

Defined in Control.Monad.Trans.Control

type StM Identity a = a
MonadBaseControl STM STM 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM STM a 
Instance details

Defined in Control.Monad.Trans.Control

type StM STM a = a

Methods

liftBaseWith :: (RunInBase STM STM -> STM a) -> STM a #

restoreM :: StM STM a -> STM a #

MonadBaseControl IO IO 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM IO a 
Instance details

Defined in Control.Monad.Trans.Control

type StM IO a = a

Methods

liftBaseWith :: (RunInBase IO IO -> IO a) -> IO a #

restoreM :: StM IO a -> IO a #

MonadBaseControl IO UnitIO Source # 
Instance details

Defined in Hedgehog.Extras.Test.Unit

Associated Types

type StM UnitIO a 
Instance details

Defined in Hedgehog.Extras.Test.Unit

type StM UnitIO a = StM (TestT (ResourceT IO)) a

Methods

liftBaseWith :: (RunInBase UnitIO IO -> IO a) -> UnitIO a #

restoreM :: StM UnitIO a -> UnitIO a #

MonadBaseControl Maybe Maybe 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM Maybe a 
Instance details

Defined in Control.Monad.Trans.Control

type StM Maybe a = a
MonadBaseControl [] [] 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM [] a 
Instance details

Defined in Control.Monad.Trans.Control

type StM [] a = a

Methods

liftBaseWith :: (RunInBase [] [] -> [a]) -> [a] #

restoreM :: StM [] a -> [a] #

MonadBaseControl IO (ResourceT IO) Source # 
Instance details

Defined in Hedgehog.Extras.Internal.Orphans

Associated Types

type StM (ResourceT IO) a 
Instance details

Defined in Hedgehog.Extras.Internal.Orphans

type StM (ResourceT IO) a = a
MonadBaseControl b m => MonadBaseControl b (GenT m) 
Instance details

Defined in Hedgehog.Internal.Gen

Methods

liftBaseWith :: (RunInBase (GenT m) b -> b a) -> GenT m a #

restoreM :: StM (GenT m) a -> GenT m a #

MonadBaseControl b m => MonadBaseControl b (PropertyT m) 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftBaseWith :: (RunInBase (PropertyT m) b -> b a) -> PropertyT m a #

restoreM :: StM (PropertyT m) a -> PropertyT m a #

MonadBaseControl b m => MonadBaseControl b (TestT m) 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftBaseWith :: (RunInBase (TestT m) b -> b a) -> TestT m a #

restoreM :: StM (TestT m) a -> TestT m a #

MonadBaseControl b m => MonadBaseControl b (TreeT m) 
Instance details

Defined in Hedgehog.Internal.Tree

Methods

liftBaseWith :: (RunInBase (TreeT m) b -> b a) -> TreeT m a #

restoreM :: StM (TreeT m) a -> TreeT m a #

MonadBaseControl b m => MonadBaseControl b (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Control

Methods

liftBaseWith :: (RunInBase (MaybeT m) b -> b a) -> MaybeT m a #

restoreM :: StM (MaybeT m) a -> MaybeT m a #

MonadBaseControl b m => MonadBaseControl b (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Control

Methods

liftBaseWith :: (RunInBase (ExceptT e m) b -> b a) -> ExceptT e m a #

restoreM :: StM (ExceptT e m) a -> ExceptT e m a #

MonadBaseControl b m => MonadBaseControl b (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Control

Methods

liftBaseWith :: (RunInBase (IdentityT m) b -> b a) -> IdentityT m a #

restoreM :: StM (IdentityT m) a -> IdentityT m a #

MonadBaseControl b m => MonadBaseControl b (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Control

Methods

liftBaseWith :: (RunInBase (ReaderT r m) b -> b a) -> ReaderT r m a #

restoreM :: StM (ReaderT r m) a -> ReaderT r m a #

MonadBaseControl b m => MonadBaseControl b (StateT s m) 
Instance details

Defined in Control.Monad.Trans.Control

Methods

liftBaseWith :: (RunInBase (StateT s m) b -> b a) -> StateT s m a #

restoreM :: StM (StateT s m) a -> StateT s m a #

MonadBaseControl b m => MonadBaseControl b (StateT s m) 
Instance details

Defined in Control.Monad.Trans.Control

Methods

liftBaseWith :: (RunInBase (StateT s m) b -> b a) -> StateT s m a #

restoreM :: StM (StateT s m) a -> StateT s m a #

(Monoid w, MonadBaseControl b m) => MonadBaseControl b (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Control

Methods

liftBaseWith :: (RunInBase (WriterT w m) b -> b a) -> WriterT w m a #

restoreM :: StM (WriterT w m) a -> WriterT w m a #

(Monoid w, MonadBaseControl b m) => MonadBaseControl b (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Control

Methods

liftBaseWith :: (RunInBase (WriterT w m) b -> b a) -> WriterT w m a #

restoreM :: StM (WriterT w m) a -> WriterT w m a #

(Monoid w, MonadBaseControl b m) => MonadBaseControl b (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.Control

Methods

liftBaseWith :: (RunInBase (RWST r w s m) b -> b a) -> RWST r w s m a #

restoreM :: StM (RWST r w s m) a -> RWST r w s m a #

(Monoid w, MonadBaseControl b m) => MonadBaseControl b (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.Control

Methods

liftBaseWith :: (RunInBase (RWST r w s m) b -> b a) -> RWST r w s m a #

restoreM :: StM (RWST r w s m) a -> RWST r w s m a #

MonadBaseControl (ST s) (ST s) 
Instance details

Defined in Control.Monad.Trans.Control

Methods

liftBaseWith :: (RunInBase (ST s) (ST s) -> ST s a) -> ST s a #

restoreM :: StM (ST s) a -> ST s a #

MonadBaseControl (Either e) (Either e) 
Instance details

Defined in Control.Monad.Trans.Control

Methods

liftBaseWith :: (RunInBase (Either e) (Either e) -> Either e a) -> Either e a #

restoreM :: StM (Either e) a -> Either e a #

MonadBaseControl (ST s) (ST s) 
Instance details

Defined in Control.Monad.Trans.Control

Methods

liftBaseWith :: (RunInBase (ST s) (ST s) -> ST s a) -> ST s a #

restoreM :: StM (ST s) a -> ST s a #

MonadBaseControl ((->) r) ((->) r) 
Instance details

Defined in Control.Monad.Trans.Control

Methods

liftBaseWith :: (RunInBase ((->) r) ((->) r) -> r -> a) -> r -> a #

restoreM :: StM ((->) r) a -> r -> a #

bracket #

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 in IO.

Note that when your acquire and release computations are of type IO it will be more efficient to write:

liftBaseOp (bracket acquire release)

bracket_ #

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)