Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module defines types (and small auxiliary functions) for organizing tests, for configuring the execution of tests, and for representing and reporting their results.
Synopsis
- type TestID = String
- data Test
- data TestOptions = TestOptions {
- to_parallel :: Bool
- class AssertionWithTestOptions a where
- testOptions :: a -> TestOptions
- assertion :: a -> Assertion
- data WithTestOptions a = WithTestOptions {
- wto_options :: TestOptions
- wto_payload :: a
- data TestSuite
- = TestSuite TestID [Test]
- | AnonTestSuite [Test]
- data TestSort
- data TestPath
- data GenFlatTest a = FlatTest {
- ft_sort :: TestSort
- ft_path :: TestPath
- ft_location :: Maybe Location
- ft_payload :: a
- type FlatTest = GenFlatTest (WithTestOptions Assertion)
- type TestFilter = FlatTest -> Bool
- testPathToList :: TestPath -> [Maybe TestID]
- flatName :: TestPath -> String
- finalName :: TestPath -> String
- prefixName :: TestPath -> String
- defaultTestOptions :: TestOptions
- withOptions :: (TestOptions -> TestOptions) -> a -> WithTestOptions a
- historyKey :: GenFlatTest a -> Text
- type TR = RWST TestConfig () TestState IO
- data TestState = TestState {
- ts_results :: [FlatTestResult]
- ts_index :: Int
- initTestState :: TestState
- data TestConfig = TestConfig {
- tc_quiet :: Bool
- tc_threads :: Maybe Int
- tc_shuffle :: Bool
- tc_output :: TestOutput
- tc_outputXml :: Maybe FilePath
- tc_filter :: TestFilter
- tc_reporters :: [TestReporter]
- tc_useColors :: Bool
- tc_historyFile :: FilePath
- tc_history :: TestHistory
- tc_sortByPrevTime :: Bool
- tc_failFast :: Bool
- tc_timeoutIsSuccess :: Bool
- tc_maxSingleTestTime :: Maybe Milliseconds
- tc_prevFactor :: Maybe Double
- tc_repeat :: Int
- data TestOutput
- type ReportAllTests = [FlatTest] -> TR ()
- type ReportGlobalStart = [FlatTest] -> TR ()
- type ReportTestStart = FlatTest -> TR ()
- type ReportTestResult = FlatTestResult -> TR ()
- type ReportGlobalResults = ReportGlobalResultsArg -> TR ()
- data ReportGlobalResultsArg = ReportGlobalResultsArg {}
- data TestReporter = TestReporter {}
- emptyTestReporter :: String -> TestReporter
- attachCallStack :: ColorString -> CallStack -> ColorString
- type CallStack = [(Maybe String, Location)]
- data TestResult
- type FlatTestResult = GenFlatTest RunResult
- type Milliseconds = Int
- data RunResult = RunResult {}
Organizing tests
Abstract type for tests and their results.
Instances
TestableHTF Test Source # | |
Defined in Test.Framework.TestManager | |
WrappableHTF Test Source # | |
data TestOptions Source #
General options for tests
Instances
Eq TestOptions Source # | |
Defined in Test.Framework.TestTypes (==) :: TestOptions -> TestOptions -> Bool # (/=) :: TestOptions -> TestOptions -> Bool # | |
Read TestOptions Source # | |
Defined in Test.Framework.TestTypes readsPrec :: Int -> ReadS TestOptions # readList :: ReadS [TestOptions] # readPrec :: ReadPrec TestOptions # readListPrec :: ReadPrec [TestOptions] # | |
Show TestOptions Source # | |
Defined in Test.Framework.TestTypes showsPrec :: Int -> TestOptions -> ShowS # show :: TestOptions -> String # showList :: [TestOptions] -> ShowS # |
class AssertionWithTestOptions a where Source #
A type class for an assertion with TestOptions
.
testOptions :: a -> TestOptions Source #
Instances
AssertionWithTestOptions (IO a) Source # | |
Defined in Test.Framework.TestTypes testOptions :: IO a -> TestOptions Source # | |
AssertionWithTestOptions (WithTestOptions (IO a)) Source # | |
Defined in Test.Framework.TestTypes testOptions :: WithTestOptions (IO a) -> TestOptions Source # |
data WithTestOptions a Source #
Something with TestOptions
Instances
Eq a => Eq (WithTestOptions a) Source # | |
Defined in Test.Framework.TestTypes (==) :: WithTestOptions a -> WithTestOptions a -> Bool # (/=) :: WithTestOptions a -> WithTestOptions a -> Bool # | |
Read a => Read (WithTestOptions a) Source # | |
Defined in Test.Framework.TestTypes readsPrec :: Int -> ReadS (WithTestOptions a) # readList :: ReadS [WithTestOptions a] # readPrec :: ReadPrec (WithTestOptions a) # readListPrec :: ReadPrec [WithTestOptions a] # | |
Show a => Show (WithTestOptions a) Source # | |
Defined in Test.Framework.TestTypes showsPrec :: Int -> WithTestOptions a -> ShowS # show :: WithTestOptions a -> String # showList :: [WithTestOptions a] -> ShowS # | |
AssertionWithTestOptions (WithTestOptions (IO a)) Source # | |
Defined in Test.Framework.TestTypes testOptions :: WithTestOptions (IO a) -> TestOptions Source # |
Abstract type for test suites and their results.
Instances
TestableHTF TestSuite Source # | |
Defined in Test.Framework.TestManager | |
WrappableHTF TestSuite Source # | |
Type for distinguishing different sorts of tests.
A type denoting the hierarchical name of a test.
data GenFlatTest a Source #
Generic type for flattened tests and their results.
FlatTest | |
|
type FlatTest = GenFlatTest (WithTestOptions Assertion) Source #
Flattened representation of tests.
type TestFilter = FlatTest -> Bool Source #
A filter is a predicate on GenFlatTest
. If the predicate is True
, the flat test is run.
testPathToList :: TestPath -> [Maybe TestID] Source #
Splits a TestPath
into a list of test identifiers.
prefixName :: TestPath -> String Source #
Returns the name of the prefix of a test path. The prefix is everything except the last element.
defaultTestOptions :: TestOptions Source #
The default TestOptions
withOptions :: (TestOptions -> TestOptions) -> a -> WithTestOptions a Source #
Shortcut for constructing a WithTestOptions
value.
historyKey :: GenFlatTest a -> Text Source #
Key of a flat test for the history database.
Executing tests
The state type for the TR
monad.
TestState | |
|
initTestState :: TestState Source #
The initial test state.
data TestConfig Source #
Configuration of test execution.
TestConfig | |
|
Instances
Show TestConfig Source # | |
Defined in Test.Framework.TestTypes showsPrec :: Int -> TestConfig -> ShowS # show :: TestConfig -> String # showList :: [TestConfig] -> ShowS # |
data TestOutput Source #
The destination of progress and result messages from HTF.
TestOutputHandle Handle Bool | Output goes to |
TestOutputSplitted FilePath | Output goes to files whose names are derived from |
Instances
Eq TestOutput Source # | |
Defined in Test.Framework.TestTypes (==) :: TestOutput -> TestOutput -> Bool # (/=) :: TestOutput -> TestOutput -> Bool # | |
Show TestOutput Source # | |
Defined in Test.Framework.TestTypes showsPrec :: Int -> TestOutput -> ShowS # show :: TestOutput -> String # showList :: [TestOutput] -> ShowS # |
Reporting results
type ReportAllTests = [FlatTest] -> TR () Source #
Reports the IDs of all tests available.
type ReportGlobalStart = [FlatTest] -> TR () Source #
Signals that test execution is about to start.
type ReportTestStart = FlatTest -> TR () Source #
Reports the start of a single test.
type ReportTestResult = FlatTestResult -> TR () Source #
Reports the result of a single test.
type ReportGlobalResults = ReportGlobalResultsArg -> TR () Source #
Reports the overall results of all tests.
data TestReporter Source #
A TestReporter
provides hooks to customize the output of HTF.
TestReporter | |
|
Instances
Eq TestReporter Source # | |
Defined in Test.Framework.TestTypes (==) :: TestReporter -> TestReporter -> Bool # (/=) :: TestReporter -> TestReporter -> Bool # | |
Show TestReporter Source # | |
Defined in Test.Framework.TestTypes showsPrec :: Int -> TestReporter -> ShowS # show :: TestReporter -> String # showList :: [TestReporter] -> ShowS # |
attachCallStack :: ColorString -> CallStack -> ColorString Source #
Specifying results.
data TestResult Source #
The summary result of a test.
Instances
Eq TestResult Source # | |
Defined in Test.Framework.TestInterface (==) :: TestResult -> TestResult -> Bool # (/=) :: TestResult -> TestResult -> Bool # | |
Read TestResult Source # | |
Defined in Test.Framework.TestInterface readsPrec :: Int -> ReadS TestResult # readList :: ReadS [TestResult] # readPrec :: ReadPrec TestResult # readListPrec :: ReadPrec [TestResult] # | |
Show TestResult Source # | |
Defined in Test.Framework.TestInterface showsPrec :: Int -> TestResult -> ShowS # show :: TestResult -> String # showList :: [TestResult] -> ShowS # | |
ToJSON TestResult Source # | |
Defined in Test.Framework.History toJSON :: TestResult -> Value # toEncoding :: TestResult -> Encoding # toJSONList :: [TestResult] -> Value # toEncodingList :: [TestResult] -> Encoding # | |
FromJSON TestResult Source # | |
Defined in Test.Framework.History parseJSON :: Value -> Parser TestResult # parseJSONList :: Value -> Parser [TestResult] # |
type FlatTestResult = GenFlatTest RunResult Source #
The result of running a GenFlatTest
type Milliseconds = Int Source #
A type synonym for time in milliseconds.
The result of a test run.
RunResult | |
|