Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Test Interpreters, Internal
Synopsis
- interpretTestKeepTemp :: Members [Error TestError, Embed IO] r => Path Abs Dir -> InterpreterFor Test r
- interpretTest :: Members [Error TestError, Resource, Embed IO] r => Path Abs Dir -> InterpreterFor Test r
- interpretTestInSubdir :: Members [Error TestError, Resource, Embed IO] r => Text -> InterpreterFor Test r
- unwrapLiftedTestT :: forall m r a. Monad m => Member (Embed m) r => Sem (Fail ': (Error TestError ': (Hedgehog m ': (Error Failure ': r)))) a -> Sem r (Journal, Either Failure a)
- semToTestT :: Monad m => Member (Embed m) r => (forall x. Sem r x -> m x) -> Sem (Fail ': (Error TestError ': (Hedgehog m ': (Error Failure ': r)))) a -> TestT m a
- semToTestTFinal :: Monad m => Sem [Fail, Error TestError, Hedgehog m, Error Failure, Embed m, Final m] a -> TestT m a
- runTest :: Path Abs Dir -> Sem TestEffects a -> TestT IO a
- runTestInSubdir :: Text -> Sem TestEffects a -> TestT IO a
- runTestAutoWith :: HasCallStack => Members [Resource, Embed IO] r => (forall x. Sem r x -> IO x) -> Sem (Test ': (Fail ': (Error TestError ': (Hedgehog IO ': (Error Failure ': r))))) a -> TestT IO a
- runTestAuto :: HasCallStack => Sem [Test, Fail, Error TestError, Hedgehog IO, Error Failure, Embed IO, Resource, Final IO] a -> TestT IO a
Documentation
interpretTestKeepTemp :: Members [Error TestError, Embed IO] r => Path Abs Dir -> InterpreterFor Test r Source #
Interpret Test
so that fixtures are read from the directory base
and temp operations are performed in
tmppolysemy-test-XXX
.
This library uses Path
for all file system related tasks, so in order to construct paths manually, you'll have to
use the quasiquoters absdir
and reldir
or the functions parseAbsDir
and parseRelDir
.
interpretTest :: Members [Error TestError, Resource, Embed IO] r => Path Abs Dir -> InterpreterFor Test r Source #
like interpretTestKeepTemp
, but deletes the temp dir after the test.
interpretTestInSubdir :: Members [Error TestError, Resource, Embed IO] r => Text -> InterpreterFor Test r Source #
Call interpretTest
with the subdirectory prefix
of the current working directory as the base dir, which is
most likely something like test
.
This is not necessarily consistent, it depends on which directory your test runner uses as cwd.
unwrapLiftedTestT :: forall m r a. Monad m => Member (Embed m) r => Sem (Fail ': (Error TestError ': (Hedgehog m ': (Error Failure ': r)))) a -> Sem r (Journal, Either Failure a) Source #
semToTestT :: Monad m => Member (Embed m) r => (forall x. Sem r x -> m x) -> Sem (Fail ': (Error TestError ': (Hedgehog m ': (Error Failure ': r)))) a -> TestT m a Source #
Run Hedgehog
with unwrapLiftedTestT
and wrap it back into the TestT
stack.
semToTestTFinal :: Monad m => Sem [Fail, Error TestError, Hedgehog m, Error Failure, Embed m, Final m] a -> TestT m a Source #
Final
version of semToTestT
.
runTestInSubdir :: Text -> Sem TestEffects a -> TestT IO a Source #
Same as runTest
, but uses interpretTestInSubdir
.
runTestAutoWith :: HasCallStack => Members [Resource, Embed IO] r => (forall x. Sem r x -> IO x) -> Sem (Test ': (Fail ': (Error TestError ': (Hedgehog IO ': (Error Failure ': r))))) a -> TestT IO a Source #
Wrapper for semToTestT
that uses the call stack to determine the base dir of the test run.
Note that if you wrap this function, you'll have to use the HasCallStack
constraint to supply the implicit
CallStack
.