Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data FromSetup
- data Summary = Summary {}
- emptySummary :: Summary
- runModules :: ModuleConfig -> Maybe Int -> Bool -> Bool -> [String] -> Bool -> [Module [Located DocTest]] -> IO Summary
- count :: Module [Located DocTest] -> Int
- type Report = StateT ReportState IO
- data ReportState = ReportState {}
- report :: String -> Report ()
- report_ :: String -> Report ()
- overwrite :: String -> Report ()
- shuffle :: Int -> [a] -> [a]
- runModule :: ModuleConfig -> Bool -> [String] -> Chan ReportUpdate -> Module [Located DocTest] -> IO ()
- data ReportUpdate
- = UpdateSuccess FromSetup Location
- | UpdateFailure FromSetup Location Expression [String]
- | UpdateError FromSetup Location Expression String
- | UpdateVerbose String
- | UpdateModuleDone
- | UpdateStart Location Expression String
- | UpdateInternalError FromSetup (Module [Located DocTest]) SomeException
- | UpdateImportError ModuleName (Either String String)
- | UpdateOptionError Location String
- makeThreadPool :: Int -> (Chan ReportUpdate -> Module [Located DocTest] -> IO ()) -> IO (Chan (Module [Located DocTest]), Chan ReportUpdate)
- reportStart :: Location -> Expression -> String -> Report ()
- reportFailure :: FromSetup -> Location -> Expression -> [String] -> Report ()
- reportError :: FromSetup -> Location -> Expression -> String -> Report ()
- reportOptionError :: Location -> String -> Report ()
- reportInternalError :: FromSetup -> Module a -> SomeException -> Report ()
- reportImportError :: ModuleName -> Either String String -> Report ()
- reportSuccess :: FromSetup -> Location -> Report ()
- verboseReport :: String -> Report ()
- updateSummary :: FromSetup -> Summary -> Report ()
- reportProgress :: Report ()
- runTestGroup :: FromSetup -> Bool -> Interpreter -> IO () -> Chan ReportUpdate -> [Located DocTest] -> IO Bool
- runExampleGroup :: FromSetup -> Bool -> Interpreter -> Chan ReportUpdate -> [Located Interaction] -> IO Bool
- safeEvalWith :: Bool -> Interpreter -> String -> IO (Either String String)
Documentation
Summary of a test run.
:: ModuleConfig | Configuration options specific to module |
-> Maybe Int | Number of threads to use. Defaults to |
-> Bool | Verbose |
-> Bool | Implicit Prelude |
-> [String] | Arguments passed to the GHCi process. |
-> Bool | Quiet mode activated |
-> [Module [Located DocTest]] | Modules under test |
-> IO Summary |
Run all examples from a list of modules.
data ReportState Source #
ReportState | |
|
runModule :: ModuleConfig -> Bool -> [String] -> Chan ReportUpdate -> Module [Located DocTest] -> IO () Source #
Run all examples from given module.
data ReportUpdate Source #
UpdateSuccess FromSetup Location | Test succeeded |
UpdateFailure FromSetup Location Expression [String] | Test failed with unexpected result |
UpdateError FromSetup Location Expression String | Test failed with an error |
UpdateVerbose String | Message to send when verbose output is activated |
UpdateModuleDone | All examples tested in module |
UpdateStart Location Expression String | Indicate test has started executing (verbose output) |
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 |
makeThreadPool :: Int -> (Chan ReportUpdate -> Module [Located DocTest] -> IO ()) -> IO (Chan (Module [Located DocTest]), Chan ReportUpdate) Source #
reportStart :: Location -> Expression -> String -> Report () Source #
reportFailure :: FromSetup -> Location -> Expression -> [String] -> Report () Source #
reportError :: FromSetup -> Location -> Expression -> String -> Report () Source #
reportInternalError :: FromSetup -> Module a -> SomeException -> Report () Source #
reportImportError :: ModuleName -> Either String String -> Report () Source #
verboseReport :: String -> Report () Source #
reportProgress :: Report () Source #
runTestGroup :: FromSetup -> Bool -> Interpreter -> IO () -> Chan ReportUpdate -> [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 -> Chan ReportUpdate -> [Located Interaction] -> IO Bool Source #
Execute all expressions from given example in given Interpreter
and verify
the output.
safeEvalWith :: Bool -> Interpreter -> String -> IO (Either String String) Source #