Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Test :: Effect
- testDir :: forall r. Member Test r => Sem r (Path Abs Dir)
- tempDir :: forall r. Member Test r => Path Rel Dir -> Sem r (Path Abs Dir)
- tempFile :: forall r. Member Test r => [Text] -> Path Rel File -> Sem r (Path Abs File)
- tempFileContent :: forall r. Member Test r => Path Rel File -> Sem r Text
- fixturePath :: forall p r. Member Test r => Path Rel p -> Sem r (Path Abs p)
- fixture :: forall r. Member Test r => Path Rel File -> Sem r Text
- tempFileLines :: forall r. Member Test r => Path Rel File -> Sem r [Text]
- fixtureLines :: forall r. Member Test r => Path Rel File -> Sem r [Text]
- 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
- data Hedgehog m :: Effect
- liftH :: forall m a r. Member (Hedgehog m) r => TestT m a -> Sem r a
- assert :: forall m r. Monad m => HasCallStack => Member (Hedgehog m) r => Bool -> Sem r ()
- (===) :: forall a m r. Monad m => Eq a => Show a => HasCallStack => Member (Hedgehog m) r => a -> a -> Sem r ()
- assertEq :: forall a m r. Monad m => Eq a => Show a => HasCallStack => Member (Hedgehog m) r => a -> a -> Sem r ()
- (/==) :: forall a m r. Monad m => Eq a => Show a => HasCallStack => Member (Hedgehog m) r => a -> a -> Sem r ()
- assertNeq :: forall a m r. Monad m => Eq a => Show a => HasCallStack => Member (Hedgehog m) r => a -> a -> Sem r ()
- assertRight :: forall a m e r. Eq a => Show e => Show a => Monad m => HasCallStack => Member (Hedgehog m) r => a -> Either e a -> Sem r ()
- assertRight2 :: forall a m e1 e2 r. Eq a => Show e1 => Show e2 => Show a => Monad m => HasCallStack => Member (Hedgehog m) r => a -> Either e1 (Either e2 a) -> Sem r ()
- assertRight3 :: forall a m e1 e2 e3 r. Eq a => Show e1 => Show e2 => Show e3 => Show a => Monad m => HasCallStack => Member (Hedgehog m) r => a -> Either e1 (Either e2 (Either e3 a)) -> Sem r ()
- assertJust :: forall a m r. Eq a => Show a => Monad m => HasCallStack => Member (Hedgehog m) r => a -> Maybe a -> Sem r ()
- evalEither :: forall a m e r. Show e => Monad m => HasCallStack => Member (Hedgehog m) r => Either e a -> Sem r a
- evalLeft :: forall a m e r. Show a => Monad m => HasCallStack => Member (Hedgehog m) r => Either e a -> Sem r e
- assertLeft :: forall a m e r. Eq e => Show e => Show a => Monad m => HasCallStack => Member (Hedgehog m) r => e -> Either e a -> Sem r ()
- evalMaybe :: forall a m r. Monad m => HasCallStack => Member (Hedgehog m) r => Maybe a -> Sem r a
- evalError :: forall e a m r. Show e => Monad m => HasCallStack => Member (Hedgehog m) r => Sem (Error e ': r) a -> Sem r a
- assertCloseBy :: forall a m r. Num a => Ord a => Monad m => HasCallStack => Member (Hedgehog m) r => a -> a -> a -> Sem r ()
- assertClose :: forall a m r. Ord a => Fractional a => Monad m => HasCallStack => Member (Hedgehog m) r => a -> a -> Sem r ()
- interpretHedgehog :: Member (Embed (TestT m)) r => InterpreterFor (Hedgehog m) r
- runTestAutoWith :: HasCallStack => Members [Resource, Embed IO] r => (forall x. Sem r x -> IO x) -> Sem (Test ': (Fail ': (Error TestError ': (Hedgehog IO ': r)))) a -> TestT IO a
- runTestAuto :: HasCallStack => Sem [Test, Fail, Error TestError, Hedgehog IO, Embed IO, Resource, Final IO] a -> TestT IO a
- runTest :: Path Abs Dir -> Sem TestEffects a -> TestT IO a
- runTestInSubdir :: Text -> Sem TestEffects a -> TestT IO a
- unwrapLiftedTestT :: Monad m => Member (Embed m) r => Sem (Fail ': (Error TestError ': (Hedgehog m ': 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 ': r))) a -> TestT m a
- semToTestTFinal :: Monad m => Sem [Fail, Error TestError, Hedgehog m, Embed m, Final m] a -> TestT m a
- type UnitTest = TestT IO ()
- unitTest :: TestName -> UnitTest -> TestTree
- newtype TestError = TestError Text
Documentation
import Path (relfile) import Polysemy.Test import Test.Tasty (defaultMain) test_fixture :: UnitTest test_fixture = runTestAuto do fixContent1 <- fixtureLines fixRel fixPath <- Test.fixturePath fixRel fixContent2 <- Text.lines <$> embed (Text.readFile (toFilePath fixPath)) fixContent1 === fixContent2 fixContent1 === ["file", "content"] where fixRel = [relfile|files/file1|] main :: IO () main = defaultMain (unitTest test_fixture)
Operations for interacting with fixtures and temp files in a test.
Instances
type DefiningModule Test Source # | |
Defined in Polysemy.Test.Data.Test |
testDir :: forall r. Member Test r => Sem r (Path Abs Dir) Source #
Return the base dir in which tests are executed.
tempDir :: forall r. Member Test r => Path Rel Dir -> Sem r (Path Abs Dir) Source #
Create a subdirectory of the directory for temporary files and return its absolute path.
tempFile :: forall r. Member Test r => [Text] -> Path Rel File -> Sem r (Path Abs File) Source #
Write the specified lines of Text
to a file under the temp dir and return its absolute path.
tempFileContent :: forall r. Member Test r => Path Rel File -> Sem r Text Source #
Read the contents of a temporary file.
fixturePath :: forall p r. Member Test r => Path Rel p -> Sem r (Path Abs p) Source #
Construct a path relative to the fixture directory.
fixture :: forall r. Member Test r => Path Rel File -> Sem r Text Source #
Read the contents of a file relative to the fixture directory.
tempFileLines :: forall r. Member Test r => Path Rel File -> Sem r [Text] Source #
Read the contents of a temporary file as a list of lines.
fixtureLines :: forall r. Member Test r => Path Rel File -> Sem r [Text] Source #
Read the contents of a file relative to the fixture directory as a list of lines.
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.
Hedgehog effect
liftH :: forall m a r. Member (Hedgehog m) r => TestT m a -> Sem r a Source #
Lift a
into Sem.TestT
m
>>>
liftH (Hedgehog.evalEither (Left 0))
liftH (Hedgehog.evalEither (Left 0)) ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ │ 0
assert :: forall m r. Monad m => HasCallStack => Member (Hedgehog m) r => Bool -> Sem r () Source #
Embeds assert
.
(===) :: forall a m r. Monad m => Eq a => Show a => HasCallStack => Member (Hedgehog m) r => a -> a -> Sem r () infix 4 Source #
Embeds ===
.
>>>
5 === 6
5 === 6 ^^^^^^^ │ ━━━ Failed (- lhs) (+ rhs) ━━━ │ - 5 │ + 6
assertEq :: forall a m r. Monad m => Eq a => Show a => HasCallStack => Member (Hedgehog m) r => a -> a -> Sem r () Source #
Prefix variant of (===)
.
(/==) :: forall a m r. Monad m => Eq a => Show a => HasCallStack => Member (Hedgehog m) r => a -> a -> Sem r () infix 4 Source #
Embeds /==
.
>>>
5 /== 5
5 /== 5 ^^^^^^^ │ ━━━ Failed (no differences) ━━━ │ 5
assertNeq :: forall a m r. Monad m => Eq a => Show a => HasCallStack => Member (Hedgehog m) r => a -> a -> Sem r () Source #
Prefix variant of (===)
.
assertRight :: forall a m e r. Eq a => Show e => Show a => Monad m => HasCallStack => Member (Hedgehog m) r => a -> Either e a -> Sem r () Source #
Given a reference value, unpacks an Either
with evalEither
and applies ===
to the result in the
Right
case, and produces a test failure in the Left
case.
assertRight2 :: forall a m e1 e2 r. Eq a => Show e1 => Show e2 => Show a => Monad m => HasCallStack => Member (Hedgehog m) r => a -> Either e1 (Either e2 a) -> Sem r () Source #
Like assertRight
, but for two nested Eithers.
assertRight3 :: forall a m e1 e2 e3 r. Eq a => Show e1 => Show e2 => Show e3 => Show a => Monad m => HasCallStack => Member (Hedgehog m) r => a -> Either e1 (Either e2 (Either e3 a)) -> Sem r () Source #
Like assertRight
, but for three nested Eithers.
assertJust :: forall a m r. Eq a => Show a => Monad m => HasCallStack => Member (Hedgehog m) r => a -> Maybe a -> Sem r () Source #
Given a reference value, asserts that the scrutinee is Just
and its contained value matches the target.
evalEither :: forall a m e r. Show e => Monad m => HasCallStack => Member (Hedgehog m) r => Either e a -> Sem r a Source #
Embeds evalEither
.
evalLeft :: forall a m e r. Show a => Monad m => HasCallStack => Member (Hedgehog m) r => Either e a -> Sem r e Source #
Like evalEither
, but for Left
.
assertLeft :: forall a m e r. Eq e => Show e => Show a => Monad m => HasCallStack => Member (Hedgehog m) r => e -> Either e a -> Sem r () Source #
Like assertRight
, but for Left
.
evalMaybe :: forall a m r. Monad m => HasCallStack => Member (Hedgehog m) r => Maybe a -> Sem r a Source #
Like evalEither
, but for Maybe
.
evalError :: forall e a m r. Show e => Monad m => HasCallStack => Member (Hedgehog m) r => Sem (Error e ': r) a -> Sem r a Source #
Run a Polysemy Error
effect and assert its result.
assertCloseBy :: forall a m r. Num a => Ord a => Monad m => HasCallStack => Member (Hedgehog m) r => a -> a -> a -> Sem r () Source #
Assert that two numeric values are closer to each other than the specified delta
.
assertClose :: forall a m r. Ord a => Fractional a => Monad m => HasCallStack => Member (Hedgehog m) r => a -> a -> Sem r () Source #
Assert that two fractional values are closer to each other than 0.001
.
interpretHedgehog :: Member (Embed (TestT m)) r => InterpreterFor (Hedgehog m) r Source #
Running Hedgehog
and Test
as TestT
runTestAutoWith :: HasCallStack => Members [Resource, Embed IO] r => (forall x. Sem r x -> IO x) -> Sem (Test ': (Fail ': (Error TestError ': (Hedgehog IO ': 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
.
runTestAuto :: HasCallStack => Sem [Test, Fail, Error TestError, Hedgehog IO, Embed IO, Resource, Final IO] a -> TestT IO a Source #
Version of runTestAutoWith
specialized to Final
IO
runTestInSubdir :: Text -> Sem TestEffects a -> TestT IO a Source #
Same as runTest
, but uses interpretTestInSubdir
.
unwrapLiftedTestT :: Monad m => Member (Embed m) r => Sem (Fail ': (Error TestError ': (Hedgehog m ': 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 ': 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, Embed m, Final m] a -> TestT m a Source #
Final
version of semToTestT
.