Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Test.Sandwich
Synopsis
- runSandwichWithCommandLineArgs :: Options -> TopSpecWithOptions -> IO ()
- runSandwichWithCommandLineArgs' :: forall a. Typeable a => Options -> Parser a -> TopSpecWithOptions' a -> IO ()
- parseCommandLineArgs :: forall a. Typeable a => Parser a -> TopSpecWithOptions' a -> IO (CommandLineOptions a)
- runSandwich :: Options -> CoreSpec -> IO ()
- runSandwich' :: Maybe (CommandLineOptions ()) -> Options -> CoreSpec -> IO (ExitReason, Int)
- it :: HasCallStack => String -> ExampleT context m () -> Free (SpecCommand context m) ()
- describe :: HasCallStack => String -> SpecFree context m () -> SpecFree context m ()
- parallel :: HasCallStack => SpecFree context m () -> SpecFree context m ()
- introduce :: (HasCallStack, Typeable intro) => String -> Label l intro -> ExampleT context m intro -> (HasCallStack => intro -> ExampleT context m ()) -> SpecFree (LabelValue l intro :> context) m () -> SpecFree context m ()
- introduceWith :: HasCallStack => String -> Label l intro -> ((HasCallStack => intro -> ExampleT context m [Result]) -> ExampleT context m ()) -> SpecFree (LabelValue l intro :> context) m () -> SpecFree context m ()
- before :: HasCallStack => String -> ExampleT context m () -> SpecFree context m () -> SpecFree context m ()
- beforeEach :: HasCallStack => String -> ExampleT context m () -> SpecFree context m () -> SpecFree context m ()
- after :: HasCallStack => String -> ExampleT context m () -> SpecFree context m () -> SpecFree context m ()
- afterEach :: HasCallStack => String -> ExampleT context m () -> SpecFree context m () -> SpecFree context m ()
- around :: HasCallStack => String -> (ExampleT context m [Result] -> ExampleT context m ()) -> SpecFree context m () -> SpecFree context m ()
- aroundEach :: (Monad m, HasCallStack) => String -> (ExampleT context m [Result] -> ExampleT context m ()) -> SpecFree context m () -> SpecFree context m ()
- parallelN :: MonadUnliftIO m => Int -> SpecFree (LabelValue "parallelSemaphore" QSem :> context) m () -> SpecFree context m ()
- parallelN' :: MonadUnliftIO m => NodeOptions -> Int -> SpecFree (LabelValue "parallelSemaphore" QSem :> context) m () -> SpecFree context m ()
- parallelNFromArgs :: forall context a m. (MonadUnliftIO m, HasCommandLineOptions context a) => (CommandLineOptions a -> Int) -> SpecFree (LabelValue "parallelSemaphore" QSem :> context) m () -> SpecFree context m ()
- parallelNFromArgs' :: forall context a m. (MonadUnliftIO m, HasCommandLineOptions context a) => NodeOptions -> (CommandLineOptions a -> Int) -> SpecFree (LabelValue "parallelSemaphore" QSem :> context) m () -> SpecFree context m ()
- defaultParallelNodeOptions :: NodeOptions
- parallelSemaphore :: Label "parallelSemaphore" QSem
- type HasParallelSemaphore context = HasLabel context "parallelSemaphore" QSem
- timeActionByProfile :: (MonadUnliftIO m, MonadReader context m, HasTestTimer context) => ProfileName -> EventName -> m a -> m a
- timeAction :: (MonadUnliftIO m, HasBaseContextMonad context m, HasTestTimer context) => EventName -> m a -> m a
- withTimingProfile :: Monad m => ProfileName -> SpecFree (LabelValue "testTimerProfile" TestTimerProfile :> context) m () -> SpecFree context m ()
- withTimingProfile' :: Monad m => ExampleT context m ProfileName -> SpecFree (LabelValue "testTimerProfile" TestTimerProfile :> context) m () -> SpecFree context m ()
- module Test.Sandwich.Contexts
- module Test.Sandwich.Expectations
- module Test.Sandwich.Logging
- module Test.Sandwich.Misc
- module Test.Sandwich.Nodes
- module Test.Sandwich.Options
- module Test.Sandwich.TH
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
.
parseCommandLineArgs :: forall a. Typeable a => Parser a -> TopSpecWithOptions' a -> IO (CommandLineOptions a) Source #
Running tests
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.
Arguments
:: HasCallStack | |
=> String | Label for the example. |
-> ExampleT context m () | The test example |
-> Free (SpecCommand context m) () |
Define a single test example.
Arguments
:: HasCallStack | |
=> String | Label for this group |
-> SpecFree context m () | Child spec tree |
-> SpecFree context m () |
Define a group of tests.
Arguments
:: HasCallStack | |
=> SpecFree context m () | Child spec tree |
-> SpecFree context m () |
Run a group of tests in parallel.
Context manager nodes
For introducing new contexts into tests and doing setup/teardown.
Arguments
:: (HasCallStack, Typeable intro) | |
=> String | String label for this node |
-> Label l intro |
|
-> ExampleT context m intro | Action to produce the new value (of type |
-> (HasCallStack => 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.
Arguments
:: HasCallStack | |
=> String | String label for this node |
-> Label l intro |
|
-> ((HasCallStack => 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.
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.
Arguments
:: HasCallStack | |
=> String | String label for this context manager |
-> ExampleT context m () | Action to perform |
-> SpecFree context m () | Child spec tree |
-> SpecFree context m () |
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.
Arguments
:: HasCallStack | |
=> String | String label for this context manager |
-> ExampleT context m () | Action to perform |
-> SpecFree context m () | Child spec tree |
-> SpecFree context m () |
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.
Parallel nodes
parallelN :: MonadUnliftIO 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.
Arguments
:: MonadUnliftIO m | |
=> NodeOptions | Node options |
-> Int | Number of threads |
-> SpecFree (LabelValue "parallelSemaphore" QSem :> context) m () | |
-> SpecFree context m () |
Arguments
:: forall context a m. (MonadUnliftIO m, HasCommandLineOptions context a) | |
=> (CommandLineOptions a -> Int) | Callback to extract the semaphore size |
-> SpecFree (LabelValue "parallelSemaphore" QSem :> context) m () | |
-> SpecFree context m () |
Same as parallelN
, but extracts the semaphore size from the command line options.
Arguments
:: forall context a m. (MonadUnliftIO m, HasCommandLineOptions context a) | |
=> NodeOptions | Node options |
-> (CommandLineOptions a -> Int) | Callback to extract the semaphore size |
-> SpecFree (LabelValue "parallelSemaphore" QSem :> context) m () | |
-> SpecFree context m () |
Types
parallelSemaphore :: Label "parallelSemaphore" QSem Source #
type HasParallelSemaphore context = HasLabel context "parallelSemaphore" QSem Source #
Timing
For timing actions within your tests. Test tree nodes are timed by default.
Arguments
:: (MonadUnliftIO m, MonadReader context m, HasTestTimer context) | |
=> ProfileName | Profile name |
-> EventName | Event name |
-> m a | |
-> m a |
Time a given action with a given profile name and event name. Use when you want to manually specify the profile name.
Arguments
:: (MonadUnliftIO m, HasBaseContextMonad context m, HasTestTimer context) | |
=> EventName | Event name |
-> m a | |
-> m a |
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.
Arguments
:: Monad m | |
=> ProfileName | Profile name |
-> SpecFree (LabelValue "testTimerProfile" TestTimerProfile :> context) m () | |
-> SpecFree context m () |
Introduce a new timing profile name.
Arguments
:: Monad m | |
=> ExampleT context m ProfileName | Callback to generate the profile name |
-> SpecFree (LabelValue "testTimerProfile" TestTimerProfile :> context) m () | |
-> SpecFree context m () |
Introduce a new timing profile name dynamically. The given ExampleT
should come up with the name and return it.
Exports
module Test.Sandwich.Contexts
module Test.Sandwich.Expectations
module Test.Sandwich.Logging
module Test.Sandwich.Misc
module Test.Sandwich.Nodes
module Test.Sandwich.Options
module Test.Sandwich.TH