Safe Haskell | None |
---|---|
Language | Haskell2010 |
polysemy-test
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]
- interpretTest :: Member (Embed IO) r => Path Abs Dir -> InterpreterFor Test r
- interpretTestInSubdir :: Member (Embed IO) r => Text -> InterpreterFor Test r
- runTestAuto :: HasCallStack => Sem (Test ': TestEffects) a -> TestT IO a
- runTest :: Path Abs Dir -> Sem (Test ': TestEffects) a -> TestT IO a
- runTestInSubdir :: Text -> Sem (Test ': TestEffects) a -> TestT IO a
- data Hedgehog :: Effect
- liftH :: forall a r. Member Hedgehog r => TestT IO a -> Sem r a
- assert :: forall r. Member Hedgehog r => Bool -> Sem r ()
- assertEqual :: forall a r. Eq a => Show a => Member Hedgehog r => a -> a -> Sem r ()
- evalEither :: forall a e r. Show e => Member Hedgehog r => Either e a -> Sem r a
- assertRight :: forall a e r. Show e => Eq a => Show a => Member Hedgehog r => a -> Either e a -> Sem r ()
- (===) :: Eq a => Show a => Member Hedgehog r => a -> a -> Sem r ()
- interpretHedgehog :: Member (Embed (TestT IO)) r => InterpreterFor Hedgehog r
- type UnitTest = TestT IO ()
- unitTest :: TestName -> UnitTest -> TestTree
Documentation
This package provides utilities for testing Polysemy programs:
- An effect,
Test
, that gives access to temporary files and fixtures - An effect,
Hedgehog
, for lifted Hedgehog assertions
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 type DefiningModule Test = "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.
interpretTest :: Member (Embed IO) r => Path Abs Dir -> InterpreterFor Test r Source #
Interpret Test
so that all file system operations are performed in the directory base
.
The temp
directory will be removed before running.
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
.
interpretTestInSubdir :: Member (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.
runTestAuto :: HasCallStack => Sem (Test ': TestEffects) a -> TestT IO a Source #
Wrapper for runTest
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
.
runTestInSubdir :: Text -> Sem (Test ': TestEffects) a -> TestT IO a Source #
Same as runTest
, but uses interpretTestInSubdir
.
Hedgehog effect
data Hedgehog :: Effect Source #
Convenience effect for embedding Hedgehog assertions.
Instances
type DefiningModule Hedgehog Source # | |
Defined in Polysemy.Test.Data.Hedgehog type DefiningModule Hedgehog = "Polysemy.Test.Data.Hedgehog" |
liftH :: forall a r. Member Hedgehog r => TestT IO a -> Sem r a Source #
Lift a
into Sem.
>>> liftH (Hedgehog.evalEither (Right 0))TestT
IO
assertEqual :: forall a r. Eq a => Show a => Member Hedgehog r => a -> a -> Sem r () Source #
Embeds 'Hedgehog.(===)'.
evalEither :: forall a e r. Show e => Member Hedgehog r => Either e a -> Sem r a Source #
Embeds evalEither
.
assertRight :: forall a e r. Show e => Eq a => Show a => Member Hedgehog r => a -> Either e a -> Sem r () Source #
Given a reference value, unpacks an Either
with evalEither
and applies assertEqual
to the result in the
Right
case, and produces a test failure in the Left
case.
(===) :: Eq a => Show a => Member Hedgehog r => a -> a -> Sem r () Source #
Alias for assertEqual
.
>>> 5 === 6
interpretHedgehog :: Member (Embed (TestT IO)) r => InterpreterFor Hedgehog r Source #
Interpret Hedgehog
into
by simple embedding of the native combinators.TestT
IO