Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Test.Sandwich.Nodes
Description
This module exports the special "primed" versions of the test tree nodes. These primed versions accept an additional options argument, which allows you to do things like control the visibility thresholds of the nodes.
Synopsis
- it' :: HasCallStack => NodeOptions -> String -> ExampleT context m () -> Free (SpecCommand context m) ()
- describe' :: HasCallStack => NodeOptions -> String -> SpecFree context m () -> SpecFree context m ()
- parallel' :: HasCallStack => NodeOptions -> SpecFree context m () -> SpecFree context m ()
- data NodeOptions
- defaultNodeOptions :: NodeOptions
- nodeOptionsVisibilityThreshold :: NodeOptions -> Int
- nodeOptionsCreateFolder :: NodeOptions -> Bool
- nodeOptionsRecordTime :: NodeOptions -> Bool
- introduce' :: (HasCallStack, Typeable intro) => NodeOptions -> String -> Label l intro -> ExampleT context m intro -> (HasCallStack => intro -> ExampleT context m ()) -> SpecFree (LabelValue l intro :> context) m () -> SpecFree context m ()
- introduceWith' :: HasCallStack => NodeOptions -> String -> Label l intro -> ((HasCallStack => intro -> ExampleT context m [Result]) -> ExampleT context m ()) -> SpecFree (LabelValue l intro :> context) m () -> SpecFree context m ()
- before' :: HasCallStack => NodeOptions -> String -> ExampleT context m () -> SpecFree context m () -> SpecFree context m ()
- beforeEach' :: HasCallStack => Maybe SrcLoc -> NodeOptions -> String -> ExampleT context m () -> SpecFree context m () -> SpecFree context m ()
- after' :: HasCallStack => NodeOptions -> String -> ExampleT context m () -> SpecFree context m () -> SpecFree context m ()
- afterEach' :: HasCallStack => Maybe SrcLoc -> NodeOptions -> String -> ExampleT context m () -> SpecFree context m () -> SpecFree context m ()
- around' :: HasCallStack => NodeOptions -> String -> (ExampleT context m [Result] -> ExampleT context m ()) -> SpecFree context m () -> SpecFree context m ()
- aroundEach' :: (Monad m, HasCallStack) => Maybe SrcLoc -> NodeOptions -> String -> (ExampleT context m [Result] -> ExampleT context m ()) -> SpecFree context m () -> SpecFree context m ()
Basic nodes
Arguments
:: HasCallStack | |
=> NodeOptions | Custom options for this node |
-> String | String label for the example. |
-> ExampleT context m () | The test example |
-> Free (SpecCommand context m) () |
Define a single test example.
Arguments
:: HasCallStack | |
=> NodeOptions | Custom options for this node |
-> String | Label for this group |
-> SpecFree context m () | Child spec tree |
-> SpecFree context m () |
Define a group of tests.
Arguments
:: HasCallStack | |
=> NodeOptions | Custom options for this node |
-> SpecFree context m () | Child spec tree |
-> SpecFree context m () |
Run a group of tests in parallel.
Node options
data NodeOptions Source #
Options for an individual test node.
Instances
Show NodeOptions Source # | |
Defined in Test.Sandwich.Types.Spec Methods showsPrec :: Int -> NodeOptions -> ShowS # show :: NodeOptions -> String # showList :: [NodeOptions] -> ShowS # |
defaultNodeOptions :: NodeOptions Source #
Reasonable default node options.
nodeOptionsVisibilityThreshold :: NodeOptions -> Int Source #
The visibility threshold of the node. See the main docs for an explanation of this.
nodeOptionsCreateFolder :: NodeOptions -> Bool Source #
Whether to create a folder in the on-disk test results for this node.
Defaults to True
, but can be turned off to reduce extraneous folders from nodes like Parallel
.
nodeOptionsRecordTime :: NodeOptions -> Bool Source #
Whether to time this node.
Context manager nodes
Arguments
:: (HasCallStack, Typeable intro) | |
=> NodeOptions | Custom options for this node |
-> 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 | |
=> NodeOptions | Custom options for this node |
-> 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 | |
=> NodeOptions | Custom options for this node |
-> String | 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 | |
=> Maybe SrcLoc | Location of this call |
-> NodeOptions | Custom options for this node |
-> String | 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 each example in a given spec tree.
Arguments
:: HasCallStack | |
=> NodeOptions | Custom options for this node |
-> String | 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 | |
=> Maybe SrcLoc | Location of this call |
-> NodeOptions | Custom options for this node |
-> 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 each example in a given spec tree.
Arguments
:: HasCallStack | |
=> NodeOptions | Custom options for this node |
-> String | String label for this node |
-> (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.
Arguments
:: (Monad m, HasCallStack) | |
=> Maybe SrcLoc | Location of this call |
-> NodeOptions | Custom options for this node |
-> 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 () |