Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Hledger.Utils.Test
Synopsis
- data Timeout
- data TestTree
- data DependencyType
- type TestName = String
- after :: DependencyType -> String -> TestTree -> TestTree
- askOption :: IsOption v => (v -> TestTree) -> TestTree
- localOption :: IsOption v => v -> TestTree -> TestTree
- defaultIngredients :: [Ingredient]
- mkTimeout :: Integer -> Timeout
- testGroup :: TestName -> [TestTree] -> TestTree
- sequentialTestGroup :: TestName -> DependencyType -> [TestTree] -> TestTree
- after_ :: DependencyType -> Expr -> TestTree -> TestTree
- includingOptions :: [OptionDescription] -> Ingredient
- defaultMainWithIngredients :: [Ingredient] -> TestTree -> IO ()
- adjustOption :: IsOption v => (v -> v) -> TestTree -> TestTree
- withResource :: IO a -> (a -> IO ()) -> (IO a -> TestTree) -> TestTree
- module Test.Tasty.HUnit
- assertLeft :: (HasCallStack, Eq b, Show b) => Either a b -> Assertion
- assertRight :: (HasCallStack, Eq a, Show a) => Either a b -> Assertion
- assertParse :: (HasCallStack, Default st) => StateT st (ParsecT HledgerParseErrorData Text IO) a -> Text -> Assertion
- assertParseEq :: (HasCallStack, Eq a, Show a, Default st) => StateT st (ParsecT HledgerParseErrorData Text IO) a -> Text -> a -> Assertion
- assertParseEqOn :: (HasCallStack, Eq b, Show b, Default st) => StateT st (ParsecT HledgerParseErrorData Text IO) a -> Text -> (a -> b) -> b -> Assertion
- assertParseError :: (HasCallStack, Eq a, Show a, Default st) => StateT st (ParsecT HledgerParseErrorData Text IO) a -> Text -> String -> Assertion
- assertParseE :: (HasCallStack, Eq a, Show a, Default st) => StateT st (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO)) a -> Text -> Assertion
- assertParseEqE :: (Default st, Eq a, Show a, HasCallStack) => StateT st (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO)) a -> Text -> a -> Assertion
- assertParseErrorE :: (Default st, Eq a, Show a, HasCallStack) => StateT st (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO)) a -> Text -> String -> Assertion
- assertParseStateOn :: (HasCallStack, Eq b, Show b, Default st) => StateT st (ParsecT HledgerParseErrorData Text IO) a -> Text -> (st -> b) -> b -> Assertion
Documentation
Timeout to be applied to individual tests.
Since: tasty-0.8
Constructors
Timeout Integer String |
|
NoTimeout |
Instances
Show Timeout | |
Eq Timeout | Auto-derived instance, just to allow storing in a Since: tasty-1.5.1 |
Ord Timeout | Auto-derived instance, just to allow storing in a Since: tasty-1.5.1 |
Defined in Test.Tasty.Options.Core | |
IsOption Timeout | |
Defined in Test.Tasty.Options.Core Methods defaultValue :: Timeout # parseValue :: String -> Maybe Timeout # optionName :: Tagged Timeout String # optionHelp :: Tagged Timeout String # showDefaultValue :: Timeout -> Maybe String # |
The main data structure defining a test suite.
It consists of individual test cases and properties, organized in named groups which form a tree-like hierarchy.
There is no generic way to create a test case. Instead, every test
provider (tasty-hunit, tasty-smallcheck etc.) provides a function to
turn a test case into a TestTree
.
Groups can be created using testGroup
.
Since: tasty-0.1
data DependencyType #
These are the two ways in which one test may depend on the others.
This is the same distinction as the hard vs soft dependencies in TestNG.
Since: tasty-1.2
Constructors
AllSucceed | The current test tree will be executed after its dependencies finish, and only if all of the dependencies succeed. |
AllFinish | The current test tree will be executed after its dependencies finish, regardless of whether they succeed or not. |
Instances
Read DependencyType | Since: tasty-1.5 |
Defined in Test.Tasty.Core Methods readsPrec :: Int -> ReadS DependencyType # readList :: ReadS [DependencyType] # | |
Show DependencyType | |
Defined in Test.Tasty.Core Methods showsPrec :: Int -> DependencyType -> ShowS # show :: DependencyType -> String # showList :: [DependencyType] -> ShowS # | |
Eq DependencyType | |
Defined in Test.Tasty.Core Methods (==) :: DependencyType -> DependencyType -> Bool # (/=) :: DependencyType -> DependencyType -> Bool # |
Arguments
:: DependencyType | whether to run the tests even if some of the dependencies fail |
-> String | the pattern |
-> TestTree | the subtree that depends on other tests |
-> TestTree | the subtree annotated with dependency information |
The after
combinator declares dependencies between tests.
If a TestTree
is wrapped in after
, the tests in this tree will not run
until certain other tests («dependencies») have finished. These
dependencies are specified using an AWK pattern (see the «Patterns» section
in the README).
Moreover, if the DependencyType
argument is set to AllSucceed
and
at least one dependency has failed, this test tree will not run at all.
Tasty does not check that the pattern matches any tests (let alone the correct set of tests), so it is on you to supply the right pattern.
Examples
The following test will be executed only after all tests that contain
Foo
anywhere in their path finish.
after
AllFinish
"Foo" $
testCase "A test that depends on Foo.Bar" $ ...
Note, however, that our test also happens to contain Foo
as part of its name,
so it also matches the pattern and becomes a dependency of itself. This
will result in a DependencyLoop
exception. To avoid this, either
change the test name so that it doesn't mention Foo
or make the
pattern more specific.
You can use AWK patterns, for instance, to specify the full path to the dependency.
after
AllFinish
"$0 == \"Tests.Foo.Bar\"" $
testCase "A test that depends on Foo.Bar" $ ...
Or only specify the dependency's own name, ignoring the group names:
after
AllFinish
"$NF == \"Bar\"" $
testCase "A test that depends on Foo.Bar" $ ...
Since: tasty-1.2
askOption :: IsOption v => (v -> TestTree) -> TestTree #
Customize the test tree based on the run-time options.
Since: tasty-0.6
localOption :: IsOption v => v -> TestTree -> TestTree #
Locally set the option value for the given test subtree.
Since: tasty-0.1
defaultIngredients :: [Ingredient] #
List of the default ingredients. This is what defaultMain
uses.
At the moment it consists of listingTests
and consoleTestReporter
.
Since: tasty-0.4.2
A shortcut for creating Timeout
values.
Since: tasty-0.8
testGroup :: TestName -> [TestTree] -> TestTree #
Create a named group of test cases or other groups. Tests are executed in
parallel. For sequential execution, see sequentialTestGroup
.
Since: tasty-0.1
sequentialTestGroup :: TestName -> DependencyType -> [TestTree] -> TestTree #
Create a named group of test cases or other groups. Tests are executed in
order. For parallel execution, see testGroup
.
Arguments
:: DependencyType | whether to run the tests even if some of the dependencies fail |
-> Expr | the pattern |
-> TestTree | the subtree that depends on other tests |
-> TestTree | the subtree annotated with dependency information |
Like after
, but accepts the pattern as a syntax tree instead
of a string. Useful for generating a test tree programmatically.
Examples
Only match on the test's own name, ignoring the group names:
after_
AllFinish
(EQ
(Field
NF
) (StringLit
"Bar")) $
testCase "A test that depends on Foo.Bar" $ ...
Since: tasty-1.2
includingOptions :: [OptionDescription] -> Ingredient #
This ingredient doesn't do anything apart from registering additional options.
The option values can be accessed using askOption
.
Since: tasty-0.6
defaultMainWithIngredients :: [Ingredient] -> TestTree -> IO () #
Parse the command line arguments and run the tests using the provided ingredient list.
When the tests finish, this function calls exitWith
with the exit code
that indicates whether any tests have failed. See defaultMain
for
details.
Since: tasty-0.4
adjustOption :: IsOption v => (v -> v) -> TestTree -> TestTree #
Locally adjust the option value for the given test subtree.
Since: tasty-0.1
Arguments
:: IO a | initialize the resource |
-> (a -> IO ()) | free the resource |
-> (IO a -> TestTree) |
|
-> TestTree |
Acquire the resource to run this test (sub)tree and release it afterwards.
Since: tasty-0.5
module Test.Tasty.HUnit
assertLeft :: (HasCallStack, Eq b, Show b) => Either a b -> Assertion Source #
Assert any Left value.
assertRight :: (HasCallStack, Eq a, Show a) => Either a b -> Assertion Source #
Assert any Right value.
assertParse :: (HasCallStack, Default st) => StateT st (ParsecT HledgerParseErrorData Text IO) a -> Text -> Assertion Source #
Assert that this stateful parser runnable in IO successfully parses all of the given input text, showing the parse error if it fails. Suitable for hledger's JournalParser parsers.
assertParseEq :: (HasCallStack, Eq a, Show a, Default st) => StateT st (ParsecT HledgerParseErrorData Text IO) a -> Text -> a -> Assertion Source #
Assert a parser produces an expected value.
assertParseEqOn :: (HasCallStack, Eq b, Show b, Default st) => StateT st (ParsecT HledgerParseErrorData Text IO) a -> Text -> (a -> b) -> b -> Assertion Source #
Like assertParseEq, but transform the parse result with the given function before comparing it.
assertParseError :: (HasCallStack, Eq a, Show a, Default st) => StateT st (ParsecT HledgerParseErrorData Text IO) a -> Text -> String -> Assertion Source #
Assert that this stateful parser runnable in IO fails to parse the given input text, with a parse error containing the given string.
assertParseE :: (HasCallStack, Eq a, Show a, Default st) => StateT st (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO)) a -> Text -> Assertion Source #
assertParseEqE :: (Default st, Eq a, Show a, HasCallStack) => StateT st (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO)) a -> Text -> a -> Assertion Source #
assertParseErrorE :: (Default st, Eq a, Show a, HasCallStack) => StateT st (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO)) a -> Text -> String -> Assertion Source #
assertParseStateOn :: (HasCallStack, Eq b, Show b, Default st) => StateT st (ParsecT HledgerParseErrorData Text IO) a -> Text -> (st -> b) -> b -> Assertion Source #
Run a stateful parser in IO like assertParse, then assert that the final state (the wrapped state, not megaparsec's internal state), transformed by the given function, matches the given expected value.