Copyright | (c) John Maraist 2022 |
---|---|
License | GPL3 |
Maintainer | haskell-tlt@maraist.org |
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Main state and monad definitions for the TLT
testing system. See
TLT
for more information.
Synopsis
- type TLTstate = (TLTopts, TRBuf)
- newtype TLT (m :: * -> *) r = TLT {}
- class (Monad m, Monad n) => MonadTLT m n | m -> n where
- runTLT :: Monad m => TLT m r -> m (TLTopts, [TestResult])
- reportAllTestResults :: MonadTLT m n => Bool -> m ()
- setExitAfterFailDisplay :: MonadTLT m n => Bool -> m ()
- tltFail :: MonadTLT m n => String -> String -> m ()
- tltPass :: MonadTLT m n => String -> m ()
- inGroup :: MonadTLT m n => String -> m a -> m a
- class (MonadTLT m nt, Monad m, MonadTLT ne nt) => MonadTLTExcept m e nt ne | m -> e, m -> ne where
- liftTLTExcept :: ExceptT e ne a -> m a
- runToExcept :: m a -> ExceptT e ne a
- noUncaught_ :: MonadTLTExcept m e nt ne => String -> m a -> m ()
- noUncaught :: (MonadTLTExcept m e nt ne, Show e) => String -> m a -> m ()
- uncaughtWith :: MonadTLTExcept m e nt ne => String -> m a -> (e -> ExceptT e ne ()) -> m ()
- uncaught :: forall {m} {e} {nt :: Type -> Type} {ne :: Type -> Type} {a}. MonadTLTExcept m e nt ne => String -> m a -> m ()
Documentation
newtype TLT (m :: * -> *) r Source #
Monad transformer for TLT tests. This layer stores the results from tests as they are executed.
class (Monad m, Monad n) => MonadTLT m n | m -> n where Source #
Extending TLT
operations across other monad transformers. For
easiest and most flexible testing, declare the monad transformers
of your application as instances of this class.
liftTLT :: TLT n a -> m a Source #
Lift TLT operations within a monad transformer stack. Note that
with enough transformer types included in this class, the
liftTLT
function should usually be unnecessary: the commands in
this module which actually configure testing, or specify a test,
already liftTLT
their own result. So they will all act as
top-level transformers in MonadTLT
.
Instances
Monad m => MonadTLT (TLT m) m Source # | |
MonadTLT m n => MonadTLT (ResourceT m) n Source # | |
MonadTLT m n => MonadTLT (MaybeT m) n Source # | |
MonadTLT m n => MonadTLT (STT s m) n Source # | |
(MonadTLT m n, Functor f) => MonadTLT (FreeT f m) n Source # | |
MonadTLT m n => MonadTLT (ExceptT e m) n Source # | |
MonadTLT m n => MonadTLT (IdentityT m) n Source # | |
MonadTLT m n => MonadTLT (ReaderT r m) n Source # | |
MonadTLT m n => MonadTLT (StateT s m) n Source # | |
MonadTLT m n => MonadTLT (StateT s m) n Source # | |
(MonadTLT m n, Monoid w) => MonadTLT (WriterT w m) n Source # | |
(MonadTLT m n, Monoid w) => MonadTLT (WriterT w m) n Source # | |
runTLT :: Monad m => TLT m r -> m (TLTopts, [TestResult]) Source #
Execute the tests specified in a TLT
monad without output
side-effects, returning the final options and result reports.
This function is primarily useful when calling TLT from some other
package. If you are using TLT itself as your test framework, and
wishing to see its human-oriented output directly, consider using
tlt
instead.
reportAllTestResults :: MonadTLT m n => Bool -> m () Source #
This function controls whether tlt
will report only
tests which fail, suppressing any display of tests which pass, or
else report the results of all tests. The default is the former:
the idea is that no news should be good news, with the programmer
bothered only with problems which need fixing.
setExitAfterFailDisplay :: MonadTLT m n => Bool -> m () Source #
This function controls whether the main tlt
executable
should exit after displaying test results which include at least
one failing test. By default, it will exit in this situation. The
idea is that a test suite can be broken into parts when it makes
sense to run the latter parts only when the former parts all pass.
tltFail :: MonadTLT m n => String -> String -> m () Source #
Report a failure. Useful in pattern-matching cases which are entirely not expected.
inGroup :: MonadTLT m n => String -> m a -> m a Source #
Organize the tests in the given subcomputation as a separate group within the test results we will report.
class (MonadTLT m nt, Monad m, MonadTLT ne nt) => MonadTLTExcept m e nt ne | m -> e, m -> ne where Source #
Enabling TLT checking of the completion of computations with- or
without uncaught exceptions in a (possibly embedded) ExceptT
or
Except
monad.
In general, it is more difficult to automatically deduce
MonadTLTExcept
instances than MonadTLT
because runToExcept
instances bodies will frequently require additional parameters to
functions such as runReaderT
, or values corresponding to
Nothing
, which are specific to a particular scenario.
Note that using MonadTLTExcept
imposes the restriction that the
TLT
transformer layer must be wrapped within the ExceptT
transformer layer.
liftTLTExcept :: ExceptT e ne a -> m a Source #
Encodes how an embedded ExceptT
monad can be lifted to the
top-level monad stack type m
.
runToExcept :: m a -> ExceptT e ne a Source #
Runs the layers of the monad stack above the ExceptT
layer,
exposing that latter layer. Serves as an inverse of
liftTLTExcept
.
Instances
MonadTLT m nt => MonadTLTExcept (ExceptT e m) e nt m Source # | The |
Defined in Test.TLT.Class liftTLTExcept :: ExceptT e m a -> ExceptT e m a Source # runToExcept :: ExceptT e m a -> ExceptT e m a Source # | |
MonadTLTExcept m e nt ne => MonadTLTExcept (IdentityT m) e nt ne Source # | We can infer general instances for other monad transformer types
when their |
Defined in Test.TLT.Class liftTLTExcept :: ExceptT e ne a -> IdentityT m a Source # runToExcept :: IdentityT m a -> ExceptT e ne a Source # | |
(MonadTLTExcept m e nt ne, Monoid w) => MonadTLTExcept (WriterT w m) e nt ne Source # | The |
Defined in Test.TLT.Class liftTLTExcept :: ExceptT e ne a -> WriterT w m a Source # runToExcept :: WriterT w m a -> ExceptT e ne a Source # | |
(MonadTLTExcept m e nt ne, Monoid w) => MonadTLTExcept (WriterT w m) e nt ne Source # | The |
Defined in Test.TLT.Class liftTLTExcept :: ExceptT e ne a -> WriterT w m a Source # runToExcept :: WriterT w m a -> ExceptT e ne a Source # |
noUncaught_ :: MonadTLTExcept m e nt ne => String -> m a -> m () Source #
Ensure that a computation in ExceptT
completes without an
uncaught exception.
noUncaught :: (MonadTLTExcept m e nt ne, Show e) => String -> m a -> m () Source #
Ensure that a computation in ExceptT
completes without an
uncaught exception.
uncaughtWith :: MonadTLTExcept m e nt ne => String -> m a -> (e -> ExceptT e ne ()) -> m () Source #
Ensure that a computation in ExceptT
does throw an uncaught
exception, allowing further testing of the exception.