Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Test.HUnitPlus.Filter
Description
Sets HUnit-Plus tests can be specified using Filter
s. These
are used by Test.HUnitPlus.Execution and Test.HUnitPlus.Main to
select which tests are run. Filters can specify tests belonging to
a certain suite, starting with a certain path, having a certain
tag, or combinations thereof.
Filters are optimized for the behavior of programs created by the
createMain
function, which runs a test if it matches any of the
filters specified. There is also a string format for filters,
which is how filters are specified in testlist files and
command-line arguments. The format is optimized for simplicity,
and as such, it is not necessarily possible to describe a given
Filter with a single textual representation of a filter.
The format for filters is as follows:
[suite][path][tags][options]
Where at least one of the suite, path, tags, or options elements are present
The suite element is a comma-separated list of suite names (alphanumeric, no spaces), enclosed in brackets ('[' ']').
The path element is a series of path elements (alphanumeric, no
spaces), separated by dots (.
).
The tags element consists of a '@' character, followed by a comma-separated list of tag names (alphanumeric, no spaces).
The options element consists of a ?
character, followed by a
comma-separated list of "name"="value" bindings.
The following are examples of textual filters, and their meanings:
first.second.third
: Run all tests starting with the pathfirst.second.third
. If there is a test namedfirst.second.third
, it will be run.[unit]
: Run all tests in the suiteunit
.[unit,stress]
: Run all tests in the suitesunit
andstress
@parser
: Run all tests with theparser
tag@parser,lexer
: Run all tests with theparser
or thelexer
tags.backend.codegen@asm
: Run all tests starting with the pathbackend.codegen
with theasm
tag.[stress]@net
: Run all tests in thestress
suite with the tagnet
.[perf,profile]inner.outer
: Run all tests in theperf
andprofile
suites that start with the pathinner.outer
.[whitebox]network.protocol@security
: Run all tests in thewhitebox
suite beginning with the pathnetwork.protocol
that have thesecurity
tag.first.second.third?"var"="val"
: Run all tests starting with the pathfirst.second.third
, with the option "var" set to "val".[unit]?"timeout"="5"
: Run all tests in the suiteunit
with the option "timeout" set to "5".[system]?"timeout"="5","threads"="4"
: Run all tests in the suitesystem
with the optiontimeout
set to '5' andthreads
set to '4'.- ?"user"="jeffk": Run all tests with the
user
option set tojeffk
.
The most common use case of filters is to select a single failing test to run, as part of fixing it. In this case, a single filter consisting of the path to the test will have this effect.
- data Selector = Selector {
- selectorInners :: HashMap Text Selector
- selectorTags :: !(Maybe (HashSet Text))
- data Filter = Filter {
- filterSuites :: !(HashSet Text)
- filterSelector :: !(HashSet Selector)
- filterOptions :: !(HashMap Text Text)
- type OptionMap = HashMap Text Text
- combineTags :: Maybe (HashSet Text) -> Maybe (HashSet Text) -> Maybe (HashSet Text)
- passFilter :: Filter
- allSelector :: Selector
- combineSelectors :: Selector -> Selector -> Selector
- suiteSelectors :: [Text] -> [Filter] -> HashMap Text (HashMap OptionMap Selector)
- parseFilter :: String -> Text -> Either Text Filter
- parseFilterFile :: FilePath -> IO (Either [Text] [Filter])
- parseFilterFileContent :: String -> Text -> Either [Text] [Filter]
Documentation
A tree-like structure that represents a set of tests within a given suite.
Constructors
Selector | |
Fields
|
Specifies zero or more test suites, to which the given Selector
is then applied. If no test suites are specified, then the
Selector
applies to all test suites.
Constructors
Filter | |
Fields
|
combineTags :: Maybe (HashSet Text) -> Maybe (HashSet Text) -> Maybe (HashSet Text) Source #
Combine two selectorTags
fields into one. This operation represents the
union of the tests that are selected by the two fields.
passFilter :: Filter Source #
A Filter
that selects all tests in all suites.
allSelector :: Selector Source #
A Selector
that selects all tests.
Parse a Filter
expression. The format for filter expressions is
described in the module documentation.
parseFilterFile :: FilePath -> IO (Either [Text] [Filter]) Source #
Given a FilePath
, get the contents of the file and parse it as
a testlist file.
parseFilterFileContent Source #
Parse content from a testlist file. The file must contain one
filter per line. Leading and trailing spaces are ignored, as are
lines that contain no filter. A #
will cause the parser to skip
the rest of the line.