hledger-lib-1.15: Core data types, parsers and functionality for the hledger accounting tools

Safe HaskellNone
LanguageHaskell2010

Hledger.Utils.Test

Synopsis

Documentation

type HasCallStack = ?callStack :: CallStack #

Request a CallStack.

NOTE: The implicit parameter ?callStack :: CallStack is an implementation detail and should not be considered part of the CallStack API, we may decide to change the implementation in the future.

Since: base-4.9.0.0

fork' :: Test a -> Test (Test a) #

Run a test in a separate thread, return a future which can be used to block on its result.

fork :: Test a -> Test () #

Run a test in a separate thread, not blocking for its result.

skip :: Test () #

Explicitly skip this test

ok :: Test () #

Record a successful test at the current scope

note' :: Show s => s -> Test () #

Log a showable value

rerun :: Int -> Test a -> IO () #

Rerun all tests with the given seed

run :: Test a -> IO () #

Run all tests

rerunOnly :: Int -> Text -> Test a -> IO () #

Rerun all tests with the given seed and whose scope starts with the given prefix

runOnly :: Text -> Test a -> IO () #

Run all tests whose scope starts with the given prefix

using :: IO r -> (r -> IO ()) -> (r -> Test a) -> Test a #

A test with a setup and teardown

expectEq :: (Eq a, Show a, HasCallStack) => a -> a -> Test () #

expectLeft :: (Show a, HasCallStack) => Either e a -> Test () #

expectRight :: (Show e, HasCallStack) => Either e a -> Test () #

io :: IO a -> Test a #

Convenient alias for liftIO

mapsOf :: Ord k => [Int] -> Test k -> Test v -> Test [Map k v] #

Generate a [Data.Map k v] of the given sizes.

mapOf :: Ord k => Int -> Test k -> Test v -> Test (Map k v) #

Generate a Data.Map k v of the given size.

pair :: Test a -> Test b -> Test (a, b) #

Alias for liftA2 (,).

listsOf :: [Int] -> Test a -> Test [[a]] #

Generate a list of lists of the given sizes, an alias for sizes `forM` \n -> listOf n gen

listOf :: Int -> Test a -> Test [a] #

Alias for replicateM

pick :: [a] -> Test a #

Sample uniformly from the given list of possibilities

word8' :: Word8 -> Word8 -> Test Word8 #

Generate a random Double in the given range Note: word8' 0 10 includes both 0 and 10.

word' :: Word -> Word -> Test Word #

Generate a random Double in the given range Note: word' 0 10 includes both 0 and 10.

double' :: Double -> Double -> Test Double #

Generate a random Double in the given range Note: double' 0 1 includes both 0 and 1.

int' :: Int -> Int -> Test Int #

Generate a random Int in the given range Note: int' 0 5 includes both 0 and 5

word :: Test Word #

Generate a random Word

double :: Test Double #

Generate a random Double

int :: Test Int #

Generate a random Int

random' :: Random a => a -> a -> Test a #

Generate a bounded random value. Inclusive on both sides.

random :: Random a => Test a #

Generate a random value

note :: Text -> Test () #

Log a message

scope :: Text -> Test a -> Test a #

Label a test. Can be nested. A "." is placed between nested scopes, so scope "foo" . scope "bar" is equivalent to scope "foo.bar"

crash :: HasCallStack => Text -> Test a #

Record a failure at the current scope

data Test a #

Tests are values of type Test a, and Test forms a monad with access to:

  • repeatable randomness (the random and random' functions for random and bounded random values, or handy specialized int, int', double, double', etc)
  • I/O (via liftIO or io, which is an alias for liftIO)
  • failure (via crash, which yields a stack trace, or fail, which does not)
  • logging (via note, noteScoped, or note')
  • hierarchically-named subcomputations (under scope) which can be switched on and off via runOnly
  • parallelism (via fork)
  • conjunction of tests via MonadPlus (the <|> operation runs both tests, even if the first test fails, and the tests function used above is just msum).

Using any or all of these capabilities, you assemble Test values into a "test suite" (just another Test value) using ordinary Haskell code, not framework magic. Notice that to generate a list of random values, we just replicateM and forM as usual.

Instances
Monad Test 
Instance details

Defined in EasyTest.Internal

Methods

(>>=) :: Test a -> (a -> Test b) -> Test b #

(>>) :: Test a -> Test b -> Test b #

return :: a -> Test a #

fail :: String -> Test a #

Functor Test 
Instance details

Defined in EasyTest.Internal

Methods

fmap :: (a -> b) -> Test a -> Test b #

(<$) :: a -> Test b -> Test a #

Applicative Test 
Instance details

Defined in EasyTest.Internal

Methods

pure :: a -> Test a #

(<*>) :: Test (a -> b) -> Test a -> Test b #

liftA2 :: (a -> b -> c) -> Test a -> Test b -> Test c #

(*>) :: Test a -> Test b -> Test b #

(<*) :: Test a -> Test b -> Test a #

Alternative Test 
Instance details

Defined in EasyTest.Internal

Methods

empty :: Test a #

(<|>) :: Test a -> Test a -> Test a #

some :: Test a -> Test [a] #

many :: Test a -> Test [a] #

MonadPlus Test 
Instance details

Defined in EasyTest.Internal

Methods

mzero :: Test a #

mplus :: Test a -> Test a -> Test a #

MonadIO Test 
Instance details

Defined in EasyTest.Internal

Methods

liftIO :: IO a -> Test a #

MonadReader Env Test 
Instance details

Defined in EasyTest.Internal

Methods

ask :: Test Env #

local :: (Env -> Env) -> Test a -> Test a #

reader :: (Env -> a) -> Test a #

IsString (Test a -> Test a) 
Instance details

Defined in EasyTest.Internal

Methods

fromString :: String -> Test a -> Test a #

runEasytests :: [String] -> Test () -> IO Bool Source #

Run some easytest tests, catching easytest's ExitCode exception, returning True if there was a problem. With arguments, runs only the scope (or single test) named by the first argument (exact, case sensitive). If there is a second argument, it should be an integer and will be used as the seed for randomness.

tests :: Text -> [Test ()] -> Test () Source #

Name and group a list of tests. Combines easytest's "scope" and "tests".

_tests :: Text -> [Test ()] -> Test () Source #

Skip the given list of tests, and any following tests in a monadic sequence, with the same type signature as "group".

test :: Text -> Test a -> Test a Source #

Name the given test(s). A readability synonym for easytest's "scope".

_test :: Text -> Test a -> Test a Source #

Skip the given test(s), with the same type signature as "test". If called in a monadic sequence of tests, also skips following tests.

it :: Text -> Test a -> Test a Source #

Name the given test(s). A synonym for "test".

_it :: Text -> Test a -> Test a Source #

Skip the given test(s), and any following tests in a monadic sequence. A synonym for "_test".

is :: (Eq a, Show a, HasCallStack) => a -> a -> Test () Source #

Shorter and flipped version of expectEqPP. The expected value goes last.

expectEqPP :: (Eq a, Show a, HasCallStack) => a -> a -> Test () Source #

Like easytest's expectEq (asserts the second (actual) value equals the first (expected) value) but pretty-prints the values in the failure output.

expectParse :: (Monoid st, Eq a, Show a, HasCallStack) => StateT st (ParsecT CustomErr Text IO) a -> Text -> Test () Source #

Test 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.

expectParseE :: (Monoid st, Eq a, Show a, HasCallStack) => StateT st (ParsecT CustomErr Text (ExceptT FinalParseError IO)) a -> Text -> Test () Source #

expectParseError :: (Monoid st, Eq a, Show a, HasCallStack) => StateT st (ParsecT CustomErr Text IO) a -> Text -> String -> Test () Source #

Test that this stateful parser runnable in IO fails to parse the given input text, with a parse error containing the given string.

expectParseErrorE :: (Monoid st, Eq a, Show a, HasCallStack) => StateT st (ParsecT CustomErr Text (ExceptT FinalParseError IO)) a -> Text -> String -> Test () Source #

expectParseEq :: (Monoid st, Eq a, Show a, HasCallStack) => StateT st (ParsecT CustomErr Text IO) a -> Text -> a -> Test () Source #

Like expectParse, but also test the parse result is an expected value, pretty-printing both if it fails.

expectParseEqE :: (Monoid st, Eq a, Show a, HasCallStack) => StateT st (ParsecT CustomErr Text (ExceptT FinalParseError IO)) a -> Text -> a -> Test () Source #

expectParseEqOn :: (Monoid st, Eq b, Show b, HasCallStack) => StateT st (ParsecT CustomErr Text IO) a -> Text -> (a -> b) -> b -> Test () Source #

Like expectParseEq, but transform the parse result with the given function before comparing it.

expectParseEqOnE :: (Monoid st, Eq b, Show b, HasCallStack) => StateT st (ParsecT CustomErr Text (ExceptT FinalParseError IO)) a -> Text -> (a -> b) -> b -> Test () Source #

expectParseStateOn :: (HasCallStack, Monoid st, Eq b, Show b) => StateT st (ParsecT CustomErr Text IO) a -> Text -> (st -> b) -> b -> Test () Source #

Run a stateful parser in IO like expectParse, then compare the final state (the wrapped state, not megaparsec's internal state), transformed by the given function, with the given expected value.