tdd-util-0.2.0.2: Test framework wrapper

Safe HaskellNone

Test.Util

Contents

Description

A module containing utilities for testing with test-framework, HUnit, and testable.

Synopsis

Throwing and catching exceptions

isExceptionThrown :: (Functor m, MonadCatchIO m, Exception e) => m a -> m (Either e a)Source

Determine whether an exception was caught, and return it if so.

assertThrown :: (Functor m, MonadCatchIO m, Exception e, Show e) => Maybe String -> Proxy e -> m () -> m ()Source

Assert that an exception is thrown.

When an exception is not thrown, the input String, or otherwise a default string, is output.

For more control, see the more fundamental isExceptionThrown.

assertNotThrown :: (Functor m, MonadCatchIO m, Exception e, Show e) => Maybe (e -> String) -> m () -> m ()Source

Assert that an exception is not thrown.

When an exception is thrown, the input function, or a default one, is given the exception and the resulting string is output.

For more control, see the more fundamental isExceptionThrown.

Concurrent TDD

Process timing

timeMicroseconds :: (Monad m, MonadIO m) => m a -> m (a, Integer)Source

Time a computation.

timeoutMicroseconds :: Integer -> IO a -> IO (Maybe a)Source

Run a computation within an approximate time limit.

This is currently a wrapper for timeout that checks for overflows.

assertMicroseconds :: Integer -> IO a -> IO aSource

Assert that a computation runs within an approximate time limit.

If the computation does not finish within the given time limit, a TimeLimitExceeded exception is thrown.

For more control, see the more fundamental timeoutMicroseconds function.

timeoutProcessMicroseconds :: Integer -> ProcessHandle -> IO (Maybe ExitCode)Source

Apply an approximate time limit, from the current time, to a process by its handle.

If the process finishes approximately within the given time limit, Just its exit code is returned. Otherwise, it is killed and Nothing is returned.

This function requires a threaded runtime system to work properly.

assertProcessMicroseconds :: Integer -> ProcessHandle -> IO ()Source

Assert that a process finishes within an approximate time limit.

If the computation does not finish within the given time limit, a TimeLimitExceeded exception is thrown.

For more control, see the more fundamental timeoutProcessMicroseconds function.

Exceptions

data TimeoutOverflow Source

timeoutMicrosoconds was invoked with an integer that would cause the input given to timeout to overflow.

Constructors

TimeoutOverflow