HUnit-Plus-2.0.0: A test framework building on HUnit.

Safe HaskellNone
LanguageHaskell2010

Test.HUnitPlus.Main

Description

A mostly-complete test selection and execution program for running HUnit-Plus tests. The only thing missing are the actual test suites, which are provided as parameters to createMain.

Given a set of test suites, module can be used to create a test execution program as follows:

module Main(main) where

import Test.HUnitPlus.Main
import MyProgram.Tests(testsuites)

main :: IO ()
main = createMain testsuites

Where testsuites is a list of TestSuites.

The resulting program, when executed with no arguments will execute all test suites and write a summary to stdout. Additionally, the test program has a number of options that control reporting and test execution.

A summary of the options follows:

  • -c mode, --consolemode=mode: Set the behavior of console reporting to mode. Can be quiet, terminal, text, and verbose. Default is terminal.
  • -t [file], --txtreport[=file]: Write a text report to file (if specified; if not, the default is 'report.txt'). Formatting of the report is the same as the verbose terminal mode.
  • -x [file], --xmlreport[=file]: Write a JUnit-style XML report to file (if specified; if not, the default is 'report.xml').
  • -l file, --testlist=file: Read a testlist from file. The file must contain a number of filters, one per line. Empty lines or lines beginning with # are ignored. Multiple files may be specified. The filters from all files are combined, and added to any filters specified on the command line.

Any additional arguments are assumed to be filters, which specify a set of tests to be run. For more information on the format of filters, see the Filter module. If no filters are given either on the command line or in testlist files, then all tests will be run.

Synopsis

Documentation

data Opts Source #

Command-line options for generated programs.

Constructors

Opts 

Fields

  • xmlreport :: [String]

    A file to which to write a JUnit-style XML report. The list must contain a single value, or be empty, or else the test program will report bad options. If the list is empty, no XML report will be generated.

  • filters :: [String]

    Filters in string format, specifying which tests should be run. If no filters are given, then all tests will be run. For information on the string format, see Test.HUnitPlus.Filter.

  • txtreport :: [String]

    A file to which to write a plain-text report. The list must contain a single value, or be empty, or else the test program will report bad options. If the list is empty, no report will be generated.

  • consmode :: [ConsoleMode]

    The behavior of the console output.

  • testlist :: [String]

    Files from which to read testlists. Multiple files may be specified. The contents will be parsed and added to the list of filters specified on the command line.

Instances

Data Opts Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Opts -> c Opts #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Opts #

toConstr :: Opts -> Constr #

dataTypeOf :: Opts -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Opts) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Opts) #

gmapT :: (forall b. Data b => b -> b) -> Opts -> Opts #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Opts -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Opts -> r #

gmapQ :: (forall d. Data d => d -> u) -> Opts -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Opts -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Opts -> m Opts #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Opts -> m Opts #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Opts -> m Opts #

Show Opts Source # 

Methods

showsPrec :: Int -> Opts -> ShowS #

show :: Opts -> String #

showList :: [Opts] -> ShowS #

data ConsoleMode Source #

Console mode options.

Constructors

Quiet

Do not generate any console output.

Terminal

Report test counts interactively during execution, updating the number of tests run, skipped, failed, and errored as they execute.

Text

Report a summary of tests run, skipped, failed, and errored after execution.

Verbose

Report extra information as tests execute.

Instances

Data ConsoleMode Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConsoleMode -> c ConsoleMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConsoleMode #

toConstr :: ConsoleMode -> Constr #

dataTypeOf :: ConsoleMode -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConsoleMode) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConsoleMode) #

gmapT :: (forall b. Data b => b -> b) -> ConsoleMode -> ConsoleMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConsoleMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConsoleMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConsoleMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConsoleMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConsoleMode -> m ConsoleMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConsoleMode -> m ConsoleMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConsoleMode -> m ConsoleMode #

Show ConsoleMode Source # 

opts :: Opts Source #

Command-line options for the System.Console.CmdArgs module.

createMain :: [TestSuite] -> IO () Source #

Create a standard test execution program from a set of test suites. The resulting main will process command line options as described, execute the appropirate tests, and exit with success if all tests passed, and fail otherwise.

topLevel :: [TestSuite] -> Opts -> IO (Either [Text] Bool) Source #

Top-level function for executing test suites. createMain is simply a wrapper around this function. This function allows users to supply their own options, and to decide what to do with the result of test execution.