Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Test.Sandwich.Options
Synopsis
- data Options
- defaultOptions :: Options
- optionsTestArtifactsDirectory :: Options -> TestArtifactsDirectory
- data TestArtifactsDirectory
- defaultTestArtifactsDirectory :: TestArtifactsDirectory
- optionsSavedLogLevel :: Options -> Maybe LogLevel
- optionsMemoryLogLevel :: Options -> Maybe LogLevel
- optionsLogFormatter :: Options -> LogEntryFormatter
- type LogEntryFormatter = UTCTime -> Loc -> LogSource -> LogLevel -> LogStr -> ByteString
- optionsFormatters :: Options -> [SomeFormatter]
- data SomeFormatter = forall f.(Formatter f, Show f, Typeable f) => SomeFormatter f
- class Formatter f where
- formatterName :: f -> String
- runFormatter :: (MonadLoggerIO m, MonadUnliftIO m, MonadCatch m) => f -> [RunNode BaseContext] -> Maybe (CommandLineOptions ()) -> BaseContext -> m ()
- finalizeFormatter :: (MonadIO m, MonadLogger m, MonadCatch m) => f -> [RunNode BaseContext] -> BaseContext -> m ()
- optionsFilterTree :: Options -> Maybe TreeFilter
- optionsPruneTree :: Options -> Maybe TreeFilter
- newtype TreeFilter = TreeFilter {
- unTreeFilter :: [String]
- optionsTestTimerType :: Options -> TestTimerType
- optionsDryRun :: Options -> Bool
- optionsProjectRoot :: Options -> Maybe FilePath
Documentation
defaultOptions :: Options Source #
A reasonable default set of options.
Artifacts
optionsTestArtifactsDirectory :: Options -> TestArtifactsDirectory Source #
Where to save test artifacts (logs, screenshots, failure reports, etc.).
data TestArtifactsDirectory Source #
Control whether test artifacts are stored to a directory.
Constructors
TestArtifactsNone | Do not create a test artifacts directory. |
TestArtifactsFixedDirectory | Use the test artifacts directory at the given path, creating it if necessary. |
Fields | |
TestArtifactsGeneratedDirectory | |
Fields
|
Logging
optionsSavedLogLevel :: Options -> Maybe LogLevel Source #
Minimum test log level to save (has no effect if optionsTestArtifactsDirectory
is TestArtifactsNone
).
optionsMemoryLogLevel :: Options -> Maybe LogLevel Source #
Test log level to store in memory while tests are running. (These logs are presented in formatters, etc.).
optionsLogFormatter :: Options -> LogEntryFormatter Source #
Formatter function for log entries.
type LogEntryFormatter = UTCTime -> Loc -> LogSource -> LogLevel -> LogStr -> ByteString Source #
A callback for formatting a log entry to a ByteString
.
Formatting
optionsFormatters :: Options -> [SomeFormatter] Source #
Which formatters to use to output the results of the tests.
data SomeFormatter Source #
An existential wrapper around Formatter
s
Constructors
forall f.(Formatter f, Show f, Typeable f) => SomeFormatter f |
Instances
Show SomeFormatter Source # | |
Defined in Test.Sandwich.Types.RunTree Methods showsPrec :: Int -> SomeFormatter -> ShowS # show :: SomeFormatter -> String # showList :: [SomeFormatter] -> ShowS # |
class Formatter f where Source #
Methods
formatterName :: f -> String Source #
Name of the formatter
runFormatter :: (MonadLoggerIO m, MonadUnliftIO m, MonadCatch m) => f -> [RunNode BaseContext] -> Maybe (CommandLineOptions ()) -> BaseContext -> m () Source #
The main function, executed while the test tree is running
finalizeFormatter :: (MonadIO m, MonadLogger m, MonadCatch m) => f -> [RunNode BaseContext] -> BaseContext -> m () Source #
Called after the test tree is completed, can be used to print final results
Instances
Formatter FailureReportFormatter Source # | |
Defined in Test.Sandwich.Formatters.FailureReport Methods formatterName :: FailureReportFormatter -> String Source # runFormatter :: (MonadLoggerIO m, MonadUnliftIO m, MonadCatch m) => FailureReportFormatter -> [RunNode BaseContext] -> Maybe (CommandLineOptions ()) -> BaseContext -> m () Source # finalizeFormatter :: (MonadIO m, MonadLogger m, MonadCatch m) => FailureReportFormatter -> [RunNode BaseContext] -> BaseContext -> m () Source # |
Filtering
optionsFilterTree :: Options -> Maybe TreeFilter Source #
Filter to apply to the text tree before running that only retains the matched tests.
optionsPruneTree :: Options -> Maybe TreeFilter Source #
Filter to apply to the text tree before running that prunes out the matched tests and their subtrees.
newtype TreeFilter Source #
Constructors
TreeFilter | |
Fields
|
Timing
optionsTestTimerType :: Options -> TestTimerType Source #
Whether to enable the test timer. When the test timer is present, timing information will be emitted to the project root (if present).
Dry run
optionsDryRun :: Options -> Bool Source #
Whether to skip actually launching the tests. This is useful if you want to see the set of the tests that would be run, or start them manually in the terminal UI.
Misc
optionsProjectRoot :: Options -> Maybe FilePath Source #
An optional absolute path to the root of the project being tested (i.e. the folder where the cabal file is found).
This is useful to provide when the current working directory does not match the project root, for example in multi-project Stack setups.
We use this hint to connect CallStack
paths (which are relative to the project root) to their actual path on disk.