Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type HasCallStack = ?callStack :: CallStack
- fork' :: Test a -> Test (Test a)
- fork :: Test a -> Test ()
- skip :: Test ()
- ok :: Test ()
- note' :: Show s => s -> Test ()
- rerun :: Int -> Test a -> IO ()
- run :: Test a -> IO ()
- rerunOnly :: Int -> Text -> Test a -> IO ()
- runOnly :: Text -> Test a -> IO ()
- using :: IO r -> (r -> IO ()) -> (r -> Test a) -> Test a
- expectEq :: (Eq a, Show a, HasCallStack) => a -> a -> Test ()
- expectLeftNoShow :: HasCallStack => Either e a -> Test ()
- expectLeft :: (Show a, HasCallStack) => Either e a -> Test ()
- expectRightNoShow :: HasCallStack => Either e a -> Test ()
- expectRight :: (Show e, HasCallStack) => Either e a -> Test ()
- expectJust :: HasCallStack => Maybe a -> Test ()
- expect :: HasCallStack -> Bool -> Test ()
- io :: IO a -> Test a
- mapsOf :: Ord k => [Int] -> Test k -> Test v -> Test [Map k v]
- mapOf :: Ord k => Int -> Test k -> Test v -> Test (Map k v)
- pair :: Test a -> Test b -> Test (a, b)
- listsOf :: [Int] -> Test a -> Test [[a]]
- listOf :: Int -> Test a -> Test [a]
- pick :: [a] -> Test a
- word8' :: Word8 -> Word8 -> Test Word8
- word' :: Word -> Word -> Test Word
- double' :: Double -> Double -> Test Double
- int' :: Int -> Int -> Test Int
- word :: Test Word
- double :: Test Double
- int :: Test Int
- word8 :: Test Word8
- bool :: Test Bool
- random' :: Random a => a -> a -> Test a
- random :: Random a => Test a
- note :: Text -> Test ()
- scope :: Text -> Test a -> Test a
- crash :: HasCallStack => Text -> Test a
- data Test a
- runEasytests :: [String] -> Test () -> IO Bool
- tests :: Text -> [Test ()] -> Test ()
- _tests :: Text -> [Test ()] -> Test ()
- test :: Text -> Test a -> Test a
- _test :: Text -> Test a -> Test a
- it :: Text -> Test a -> Test a
- _it :: Text -> Test a -> Test a
- is :: (Eq a, Show a, HasCallStack) => a -> a -> Test ()
- expectEqPP :: (Eq a, Show a, HasCallStack) => a -> a -> Test ()
- expectParse :: (Monoid st, Eq a, Show a, HasCallStack) => StateT st (ParsecT CustomErr Text IO) a -> Text -> Test ()
- expectParseE :: (Monoid st, Eq a, Show a, HasCallStack) => StateT st (ParsecT CustomErr Text (ExceptT FinalParseError IO)) a -> Text -> Test ()
- expectParseError :: (Monoid st, Eq a, Show a, HasCallStack) => StateT st (ParsecT CustomErr Text IO) a -> Text -> String -> Test ()
- expectParseErrorE :: (Monoid st, Eq a, Show a, HasCallStack) => StateT st (ParsecT CustomErr Text (ExceptT FinalParseError IO)) a -> Text -> String -> Test ()
- expectParseEq :: (Monoid st, Eq a, Show a, HasCallStack) => StateT st (ParsecT CustomErr Text IO) a -> Text -> a -> Test ()
- expectParseEqE :: (Monoid st, Eq a, Show a, HasCallStack) => StateT st (ParsecT CustomErr Text (ExceptT FinalParseError IO)) a -> Text -> a -> Test ()
- expectParseEqOn :: (Monoid st, Eq b, Show b, HasCallStack) => StateT st (ParsecT CustomErr Text IO) a -> Text -> (a -> b) -> b -> Test ()
- expectParseEqOnE :: (Monoid st, Eq b, Show b, HasCallStack) => StateT st (ParsecT CustomErr Text (ExceptT FinalParseError IO)) a -> Text -> (a -> b) -> b -> Test ()
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.
rerunOnly :: Int -> Text -> Test a -> IO () #
Rerun all tests with the given seed and whose scope starts with the given prefix
expectLeftNoShow :: HasCallStack => Either e a -> Test () #
expectLeft :: (Show a, HasCallStack) => Either e a -> Test () #
expectRightNoShow :: HasCallStack => Either e a -> Test () #
expectRight :: (Show e, HasCallStack) => Either e a -> Test () #
expectJust :: HasCallStack => Maybe a -> Test () #
expect :: HasCallStack -> Bool -> Test () #
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.
listsOf :: [Int] -> Test a -> Test [[a]] #
Generate a list of lists of the given sizes,
an alias for sizes `forM` \n -> listOf n gen
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
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
Tests are values of type Test a
, and Test
forms a monad with access to:
- repeatable randomness (the
random
andrandom'
functions for random and bounded random values, or handy specializedint
,int'
,double
,double'
, etc) - I/O (via
liftIO
orio
, which is an alias forliftIO
) - failure (via
crash
, which yields a stack trace, orfail
, which does not) - logging (via
note
,noteScoped
, ornote'
) - hierarchically-named subcomputations (under
scope
) which can be switched on and off viarunOnly
- 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 justmsum
).
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 | |
Functor Test | |
Applicative Test | |
Alternative Test | |
MonadPlus Test | |
MonadIO Test | |
Defined in EasyTest.Internal | |
MonadReader Env Test | |
IsString (Test a -> Test a) | |
Defined in EasyTest.Internal 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 #
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.
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 #