sandwich-0.1.0.9: Yet another test framework for Haskell
Safe HaskellNone
LanguageHaskell2010

Test.Sandwich

Synopsis

Documentation

Sandwich is a test framework for Haskell. See the documentation for details and usage examples.

Running tests with command line args

These functions will read command line arguments when setting up your tests. These flags allow you filter the test tree, configure formatters, and pass your own custom options.

# Run using the terminal UI formatter, webdriver headless mode, filtering to nodes matching "Login"
stack run my-tests -- --tui --headless -f Login

runSandwichWithCommandLineArgs :: Options -> TopSpecWithOptions -> IO () Source #

Run the spec, configuring the options from the command line.

runSandwichWithCommandLineArgs' :: forall a. Typeable a => Options -> Parser a -> TopSpecWithOptions' a -> IO () Source #

Run the spec, configuring the options from the command line and adding user-configured command line options. The options will become available as a test context, which you can access by calling getCommandLineOptions.

Running tests

runSandwich :: Options -> CoreSpec -> IO () Source #

Run the spec with the given Options.

runSandwich' :: Maybe (CommandLineOptions ()) -> Options -> CoreSpec -> IO (ExitReason, Int) Source #

Run the spec with optional custom CommandLineOptions. When finished, return the exit reason and number of failures.

Basic nodes

The basic building blocks of tests.

it Source #

Arguments

:: HasCallStack 
=> String

Label for the example.

-> ExampleT context m ()

The test example

-> Free (SpecCommand context m) () 

Define a single test example.

describe Source #

Arguments

:: HasCallStack 
=> String

Label for this group

-> SpecFree context m ()

Child spec tree

-> SpecFree context m () 

Define a group of tests.

parallel Source #

Arguments

:: HasCallStack 
=> SpecFree context m ()

Child spec tree

-> SpecFree context m () 

Run a group of tests in parallel.

parallelN :: (MonadBaseControl IO m, MonadIO m, MonadMask m) => Int -> SpecFree (LabelValue "parallelSemaphore" QSem :> context) m () -> SpecFree context m () Source #

Wrapper around parallel. Introduces a semaphore to limit the parallelism to N threads.

Context manager nodes

For introducing new contexts into tests and doing setup/teardown.

introduce Source #

Arguments

:: (HasCallStack, Typeable intro) 
=> String

String label for this node

-> Label l intro

Label under which to introduce the value

-> ExampleT context m intro

Action to produce the new value (of type intro)

-> (intro -> ExampleT context m ())

Action to clean up the new value

-> SpecFree (LabelValue l intro :> context) m ()

Child spec tree

-> SpecFree context m () 

Introduce a new value and make it available to the child spec tree.

introduceWith Source #

Arguments

:: HasCallStack 
=> String

String label for this node

-> Label l intro

Label under which to introduce the value

-> ((intro -> ExampleT context m [Result]) -> ExampleT context m ())

Callback to receive the new value and the child tree.

-> SpecFree (LabelValue l intro :> context) m ()

Child spec tree

-> SpecFree context m () 

Introduce a new value in an around fashion, so it can be used with context managers like withFile or bracket.

before Source #

Arguments

:: HasCallStack 
=> String

Label for this context manager

-> ExampleT context m ()

Action to perform

-> SpecFree context m ()

Child spec tree

-> SpecFree context m () 

Perform an action before a given spec tree.

beforeEach Source #

Arguments

:: HasCallStack 
=> String

String label for this context manager

-> ExampleT context m ()

Action to perform

-> SpecFree context m ()

Child spec tree

-> SpecFree context m () 

Same as before, but applied individually to every it node.

after Source #

Arguments

:: HasCallStack 
=> String

Label for this context manager

-> ExampleT context m ()

Action to perform

-> SpecFree context m ()

Child spec tree

-> SpecFree context m () 

Perform an action after a given spec tree.

afterEach Source #

Arguments

:: HasCallStack 
=> String

String label for this context manager

-> ExampleT context m ()

Action to perform

-> SpecFree context m ()

Child spec tree

-> SpecFree context m () 

Same as after, but applied individually to every it node.

around Source #

Arguments

:: HasCallStack 
=> String 
-> (ExampleT context m [Result] -> ExampleT context m ())

Callback to run the child tree

-> SpecFree context m ()

Child spec tree

-> SpecFree context m () 

Run an action around the given child subtree. Useful for context managers like withFile or bracket.

aroundEach Source #

Arguments

:: (Monad m, HasCallStack) 
=> String

String label for this context manager

-> (ExampleT context m [Result] -> ExampleT context m ())

Callback to run the child tree

-> SpecFree context m ()

Child spec tree

-> SpecFree context m () 

Same as around, but applied individually to every it node.

Timing

For timing actions within your tests. Test tree nodes are timed by default.

timeActionByProfile :: (MonadMask m, MonadIO m, MonadReader context m, HasTestTimer context) => ProfileName -> EventName -> m a -> m a Source #

Time a given action with a given profile name and event name. Use when you want to manually specify the profile name.

timeAction :: (MonadMask m, MonadIO m, MonadReader context m, HasBaseContext context, HasTestTimer context) => EventName -> m a -> m a Source #

Time a given action with a given event name. This name will be the "stack frame" of the given action in the profiling results. This function will use the current timing profile name.

withTimingProfile :: Monad m => ProfileName -> SpecFree (LabelValue "testTimerProfile" TestTimerProfile :> context) m () -> SpecFree context m () Source #

Introduce a new timing profile name.

withTimingProfile' :: Monad m => ExampleT context m ProfileName -> SpecFree (LabelValue "testTimerProfile" TestTimerProfile :> context) m () -> SpecFree context m () Source #

Introduce a new timing profile name dynamically. The given ExampleT should come up with the name and return it.

Exports