module Polysemy.Test (
  
  
  module Polysemy.Test.Data.Test,
  tempFileLines,
  fixtureLines,
  interpretTestKeepTemp,
  interpretTest,
  interpretTestInSubdir,
  
  module Polysemy.Test.Data.Hedgehog,
  assert,
  (===),
  assertEq,
  (/==),
  assertNeq,
  assertRight,
  assertRight2,
  assertRight3,
  assertJust,
  evalEither,
  evalLeft,
  assertLeft,
  evalMaybe,
  evalError,
  assertCloseBy,
  assertClose,
  interpretHedgehog,
  
  runTestAutoWith,
  runTestAuto,
  runTest,
  runTestInSubdir,
  unwrapLiftedTestT,
  semToTestT,
  semToTestTFinal,
  
  UnitTest,
  unitTest,
  unitTestTimes,
  TestError (TestError),
  testError,
) where
import qualified Data.Text as Text
import Hedgehog (TestLimit, TestT, property, test, withTests)
import Path (File, Path, Rel)
import Test.Tasty (TestName, TestTree)
import Test.Tasty.Hedgehog (testProperty)
import Polysemy.Test.Data.Hedgehog (Hedgehog, liftH)
import Polysemy.Test.Data.Test (Test, fixture, fixturePath, tempDir, tempFile, tempFileContent, testDir)
import Polysemy.Test.Data.TestError (TestError (TestError), testError)
import Polysemy.Test.Hedgehog (
  assert,
  assertClose,
  assertCloseBy,
  assertEq,
  assertJust,
  assertLeft,
  assertNeq,
  assertRight,
  assertRight2,
  assertRight3,
  evalEither,
  evalError,
  evalLeft,
  evalMaybe,
  interpretHedgehog,
  (/==),
  (===),
  )
import Polysemy.Test.Run (
  interpretTest,
  interpretTestInSubdir,
  interpretTestKeepTemp,
  runTest,
  runTestAuto,
  runTestAutoWith,
  runTestInSubdir,
  semToTestT,
  semToTestTFinal,
  unwrapLiftedTestT,
  )
type UnitTest = TestT IO ()
unitTestTimes ::
  TestLimit ->
  TestName ->
  UnitTest ->
  TestTree
unitTestTimes :: TestLimit -> TestName -> UnitTest -> TestTree
unitTestTimes TestLimit
n TestName
desc =
  TestName -> Property -> TestTree
testProperty TestName
desc (Property -> TestTree)
-> (UnitTest -> Property) -> UnitTest -> TestTree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestLimit -> Property -> Property
withTests TestLimit
n (Property -> Property)
-> (UnitTest -> Property) -> UnitTest -> Property
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => PropertyT IO () -> Property
PropertyT IO () -> Property
property (PropertyT IO () -> Property)
-> (UnitTest -> PropertyT IO ()) -> UnitTest -> Property
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnitTest -> PropertyT IO ()
forall (m :: * -> *) a. Monad m => TestT m a -> PropertyT m a
test
unitTest ::
  TestName ->
  UnitTest ->
  TestTree
unitTest :: TestName -> UnitTest -> TestTree
unitTest =
  TestLimit -> TestName -> UnitTest -> TestTree
unitTestTimes TestLimit
1
fixtureLines ::
  ∀ r .
  Member Test r =>
  Path Rel File ->
  Sem r [Text]
fixtureLines :: forall (r :: EffectRow).
Member Test r =>
Path Rel File -> Sem r [Text]
fixtureLines =
  (Text -> [Text]) -> Sem r Text -> Sem r [Text]
forall a b. (a -> b) -> Sem r a -> Sem r b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> [Text]
Text.lines (Sem r Text -> Sem r [Text])
-> (Path Rel File -> Sem r Text) -> Path Rel File -> Sem r [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path Rel File -> Sem r Text
forall (r :: EffectRow).
Member Test r =>
Path Rel File -> Sem r Text
fixture
tempFileLines ::
  ∀ r .
  Member Test r =>
  Path Rel File ->
  Sem r [Text]
tempFileLines :: forall (r :: EffectRow).
Member Test r =>
Path Rel File -> Sem r [Text]
tempFileLines =
  (Text -> [Text]) -> Sem r Text -> Sem r [Text]
forall a b. (a -> b) -> Sem r a -> Sem r b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> [Text]
Text.lines (Sem r Text -> Sem r [Text])
-> (Path Rel File -> Sem r Text) -> Path Rel File -> Sem r [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path Rel File -> Sem r Text
forall (r :: EffectRow).
Member Test r =>
Path Rel File -> Sem r Text
tempFileContent