doctest-parallel-0.3.1: Test interactive Haskell examples
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.DocTest.Internal.Runner

Synopsis

Documentation

data FromSetup Source #

Whether an "example" is part of setup block

Constructors

FromSetup 
NotFromSetup 

data Summary Source #

Summary of a test run.

Constructors

Summary 

Fields

  • sExamples :: Int

    Total number of lines of examples (excluding setup)

  • sTried :: Int

    Executed sTried lines so far

  • sErrors :: Int

    Couldn't execute sErrors examples

  • sFailures :: Int

    Got unexpected output for sFailures examples

Instances

Instances details
Monoid Summary Source #

Sum up summaries.

Instance details

Defined in Test.DocTest.Internal.Runner

Semigroup Summary Source # 
Instance details

Defined in Test.DocTest.Internal.Runner

Show Summary Source #

Format a summary.

Instance details

Defined in Test.DocTest.Internal.Runner

Eq Summary Source # 
Instance details

Defined in Test.DocTest.Internal.Runner

Methods

(==) :: Summary -> Summary -> Bool #

(/=) :: Summary -> Summary -> Bool #

runModules Source #

Arguments

:: (?verbosity :: LogLevel) 
=> ModuleConfig

Configuration options specific to module

-> Maybe Int

Number of threads to use. Defaults to getNumProcessors.

-> Bool

Implicit Prelude

-> [String]

Arguments passed to the GHCi process.

-> [Module [Located DocTest]]

Modules under test

-> IO Summary 

Run all examples from a list of modules.

count :: Module [Located DocTest] -> Int Source #

Count number of expressions in given module.

type Report = StateT ReportState IO Source #

A monad for generating test reports.

data ReportState Source #

Constructors

ReportState 

Fields

report :: (?verbosity :: LogLevel, ?threadId :: ThreadId) => LogLevel -> String -> Report () Source #

Add output to the report.

report_ :: (?verbosity :: LogLevel) => LogLevel -> String -> Report () Source #

Add intermediate output to the report.

This will be overwritten by subsequent calls to report/report_. Intermediate out may not contain any newlines.

overwrite :: String -> Report () Source #

Add output to the report, overwrite any intermediate out.

shuffle :: Int -> [a] -> [a] Source #

Shuffle a list given a seed for an RNG

runModule :: ModuleConfig -> Bool -> [String] -> Chan (ThreadId, ReportUpdate) -> Module [Located DocTest] -> IO () Source #

Run all examples from given module.

data ReportUpdate Source #

Constructors

UpdateSuccess FromSetup

Test succeeded

UpdateFailure FromSetup Location Expression [String]

Test failed with unexpected result

UpdateError FromSetup Location Expression String

Test failed with an error

UpdateModuleDone

All examples tested in module

UpdateInternalError FromSetup (Module [Located DocTest]) SomeException

Exception caught while executing internal code

UpdateImportError ModuleName (Either String String)

Could not import module

UpdateOptionError Location String

Unrecognized flag in module specific option

UpdateLog LogLevel String

Unstructured message

reportFailure :: (?verbosity :: LogLevel, ?threadId :: ThreadId) => FromSetup -> Location -> Expression -> [String] -> Report () Source #

reportError :: (?verbosity :: LogLevel, ?threadId :: ThreadId) => FromSetup -> Location -> Expression -> String -> Report () Source #

reportOptionError :: (?verbosity :: LogLevel, ?threadId :: ThreadId) => Location -> String -> Report () Source #

reportInternalError :: (?verbosity :: LogLevel, ?threadId :: ThreadId) => FromSetup -> Module a -> SomeException -> Report () Source #

reportImportError :: (?verbosity :: LogLevel, ?threadId :: ThreadId) => ModuleName -> Either String String -> Report () Source #

reportSuccess :: (?verbosity :: LogLevel, ?threadId :: ThreadId) => FromSetup -> Report () Source #

reportProgress :: (?verbosity :: LogLevel) => Report () Source #

runTestGroup :: FromSetup -> Bool -> Interpreter -> IO () -> (ReportUpdate -> IO ()) -> [Located DocTest] -> IO Bool Source #

Run given test group.

The interpreter state is zeroed with :reload first. This means that you can reuse the same Interpreter for several test groups.

runExampleGroup :: FromSetup -> Bool -> Interpreter -> (ReportUpdate -> IO ()) -> [Located Interaction] -> IO Bool Source #

Execute all expressions from given example in given Interpreter and verify the output.