Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
- Top level API functions
- Defining a test suite
- Declaring tests
- Commented-out tests
- Pending tests
- Golden tests
- Scenario tests
- Expectations
- Declaring test dependencies
- Test definition types
- Test suite types
- Hspec synonyms
- Utilities
- Reexports
Modern testing of Haskell code using sydtest
For a full overview of features and comparisons, please see the README.
What's in a test
To use sydtest
, you don't necessarily need to know the following, but for advanced usage you definitely will.
If you're just starting out, you can ignore this section and just follow the examples in the docs below.
- Every test is an instance of the
IsTest
type class. A test can be a pureBool
, anIO ()
, aGoldenTest
, some combination of those, or any type that you can implementIsTest
for. sydtest
allows you to declare resources for use during your tests. This could be things like a database connection or a server to connect to, for example.- Every resource is either an outer resource (set up once for a test group) or an inner resource (set up again for each test).
Every
IsTest
instance defines two associated types, anArg1
type and anArg2
type. These correspond to two function arguments.Arg1
corresponds to the first andArg2
corresponds to the second. For example,IO ()
is an instance ofIsTest
, butarg -> IO ()
andouterArgs -> innerArg -> IO ()
are as well.- When using
it
orspecify
to define tests, theArg1
andArg2
arguments of the test that you pass in have to correspond to the outer and inner resources of your test suite, respectively. - You can declare how to set up or tear down resources using the
around
andaroundAll
functions.
Synopsis
- sydTest :: Spec -> IO ()
- sydTestWith :: Settings -> Spec -> IO ()
- describe :: String -> TestDefM outers inner () -> TestDefM outers inner ()
- it :: forall outers inner test. (HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) => String -> test -> TestDefM outers inner ()
- itWithOuter :: (HasCallStack, IsTest test, Arg1 test ~ inner, Arg2 test ~ outer) => String -> test -> TestDefM (outer ': otherOuters) inner ()
- itWithBoth :: (HasCallStack, IsTest test, Arg1 test ~ outer, Arg2 test ~ inner) => String -> test -> TestDefM (outer ': otherOuters) inner ()
- itWithAll :: (HasCallStack, IsTest test, Arg1 test ~ HList outers, Arg2 test ~ inner) => String -> test -> TestDefM outers inner ()
- specify :: forall outers inner test. (HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) => String -> test -> TestDefM outers inner ()
- specifyWithOuter :: (HasCallStack, IsTest test, Arg1 test ~ inner, Arg2 test ~ outer) => String -> test -> TestDefM (outer ': otherOuters) inner ()
- specifyWithBoth :: (HasCallStack, IsTest test, Arg1 test ~ outer, Arg2 test ~ inner) => String -> test -> TestDefM (outer ': otherOuters) inner ()
- specifyWithAll :: (HasCallStack, IsTest test, Arg1 test ~ HList outers, Arg2 test ~ inner) => String -> test -> TestDefM outers inner ()
- prop :: Testable prop => String -> prop -> Spec
- getTestDescriptionPath :: TestDefM outers inner [Text]
- xdescribe :: String -> TestDefM outers inner () -> TestDefM outers inner ()
- xit :: forall outers inner test. (HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) => String -> test -> TestDefM outers inner ()
- xitWithOuter :: (HasCallStack, IsTest test, Arg1 test ~ inner, Arg2 test ~ outer) => String -> test -> TestDefM (outer ': otherOuters) inner ()
- xitWithBoth :: (HasCallStack, IsTest test, Arg1 test ~ outer, Arg2 test ~ inner) => String -> test -> TestDefM (outer ': otherOuters) inner ()
- xitWithAll :: (HasCallStack, IsTest test, Arg1 test ~ HList outers, Arg2 test ~ inner) => String -> test -> TestDefM outers inner ()
- xspecify :: forall outers inner test. (HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) => String -> test -> TestDefM outers inner ()
- xspecifyWithOuter :: (HasCallStack, IsTest test, Arg1 test ~ inner, Arg2 test ~ outer) => String -> test -> TestDefM (outer ': otherOuters) inner ()
- xspecifyWithBoth :: (HasCallStack, IsTest test, Arg1 test ~ outer, Arg2 test ~ inner) => String -> test -> TestDefM (outer ': otherOuters) inner ()
- xspecifyWithAll :: (HasCallStack, IsTest test, Arg1 test ~ HList outers, Arg2 test ~ inner) => String -> test -> TestDefM outers inner ()
- pending :: String -> TestDefM outers inner ()
- pendingWith :: String -> String -> TestDefM outers inner ()
- pureGoldenTextFile :: FilePath -> Text -> GoldenTest Text
- goldenTextFile :: FilePath -> IO Text -> GoldenTest Text
- pureGoldenByteStringFile :: FilePath -> ByteString -> GoldenTest ByteString
- goldenByteStringFile :: FilePath -> IO ByteString -> GoldenTest ByteString
- pureGoldenLazyByteStringFile :: FilePath -> ByteString -> GoldenTest ByteString
- goldenLazyByteStringFile :: FilePath -> IO ByteString -> GoldenTest ByteString
- pureGoldenByteStringBuilderFile :: FilePath -> Builder -> GoldenTest Builder
- goldenByteStringBuilderFile :: FilePath -> IO Builder -> GoldenTest Builder
- pureGoldenStringFile :: FilePath -> String -> GoldenTest String
- goldenStringFile :: FilePath -> IO String -> GoldenTest String
- goldenShowInstance :: Show a => FilePath -> a -> GoldenTest String
- goldenPrettyShowInstance :: Show a => FilePath -> a -> GoldenTest String
- goldenContext :: FilePath -> String
- data GoldenTest a = GoldenTest {
- goldenTestRead :: IO (Maybe a)
- goldenTestProduce :: IO a
- goldenTestWrite :: a -> IO ()
- goldenTestCompare :: a -> a -> IO (Maybe Assertion)
- scenarioDir :: FilePath -> (FilePath -> TestDefM outers inner ()) -> TestDefM outers inner ()
- scenarioDirRecur :: FilePath -> (FilePath -> TestDefM outers inner ()) -> TestDefM outers inner ()
- shouldBe :: (HasCallStack, Show a, Eq a) => a -> a -> IO ()
- shouldNotBe :: (HasCallStack, Show a, Eq a) => a -> a -> IO ()
- shouldSatisfy :: (HasCallStack, Show a) => a -> (a -> Bool) -> IO ()
- shouldSatisfyNamed :: (HasCallStack, Show a) => a -> String -> (a -> Bool) -> IO ()
- shouldNotSatisfy :: (HasCallStack, Show a) => a -> (a -> Bool) -> IO ()
- shouldNotSatisfyNamed :: (HasCallStack, Show a) => a -> String -> (a -> Bool) -> IO ()
- shouldReturn :: (HasCallStack, Show a, Eq a) => IO a -> a -> IO ()
- shouldNotReturn :: (HasCallStack, Show a, Eq a) => IO a -> a -> IO ()
- shouldStartWith :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation
- shouldEndWith :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation
- shouldContain :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation
- shouldMatchList :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation
- expectationFailure :: HasCallStack => String -> IO a
- context :: String -> IO a -> IO a
- type Expectation = IO ()
- shouldThrow :: forall e a. (HasCallStack, Exception e) => IO a -> Selector e -> Expectation
- type Selector a = a -> Bool
- anyException :: Selector SomeException
- anyErrorCall :: Selector ErrorCall
- errorCall :: String -> Selector ErrorCall
- anyIOException :: Selector IOException
- anyArithException :: Selector ArithException
- stringShouldBe :: HasCallStack => String -> String -> IO ()
- textShouldBe :: HasCallStack => Text -> Text -> IO ()
- stringsNotEqualButShouldHaveBeenEqual :: String -> String -> Assertion
- textsNotEqualButShouldHaveBeenEqual :: Text -> Text -> Assertion
- bytestringsNotEqualButShouldHaveBeenEqual :: ByteString -> ByteString -> Assertion
- data Assertion
- beforeAll :: IO outer -> TestDefM (outer ': otherOuters) inner result -> TestDefM otherOuters inner result
- beforeAll_ :: IO () -> TestDefM outers inner result -> TestDefM outers inner result
- beforeAllWith :: (previousOuter -> IO newOuter) -> TestDefM (newOuter ': (previousOuter ': otherOuters)) inner result -> TestDefM (previousOuter ': otherOuters) inner result
- afterAll :: (outer -> IO ()) -> TestDefM (outer ': otherOuters) inner result -> TestDefM (outer ': otherOuters) inner result
- afterAll' :: (HList outers -> IO ()) -> TestDefM outers inner result -> TestDefM outers inner result
- afterAll_ :: IO () -> TestDefM outers inner result -> TestDefM outers inner result
- aroundAll :: ((outer -> IO ()) -> IO ()) -> TestDefM (outer ': otherOuters) inner result -> TestDefM otherOuters inner result
- aroundAll_ :: (IO () -> IO ()) -> TestDefM outers inner result -> TestDefM outers inner result
- aroundAllWith :: forall newOuter oldOuter otherOuters inner result. ((newOuter -> IO ()) -> oldOuter -> IO ()) -> TestDefM (newOuter ': (oldOuter ': otherOuters)) inner result -> TestDefM (oldOuter ': otherOuters) inner result
- before :: IO inner -> TestDefM outers inner result -> TestDefM outers () result
- before_ :: IO () -> TestDefM outers inner result -> TestDefM outers inner result
- after :: (inner -> IO ()) -> TestDefM outers inner result -> TestDefM outers inner result
- after_ :: IO () -> TestDefM outers inner result -> TestDefM outers inner result
- around :: ((inner -> IO ()) -> IO ()) -> TestDefM outers inner result -> TestDefM outers () result
- around_ :: (IO () -> IO ()) -> TestDefM outers inner result -> TestDefM outers inner result
- aroundWith :: forall newInner oldInner outers result. ((newInner -> IO ()) -> oldInner -> IO ()) -> TestDefM outers newInner result -> TestDefM outers oldInner result
- newtype SetupFunc resource = SetupFunc {
- unSetupFunc :: forall r. (resource -> IO r) -> IO r
- setupAround :: SetupFunc inner -> TestDefM outers inner result -> TestDefM outers any result
- setupAroundWith :: (oldInner -> SetupFunc newInner) -> TestDefM outers newInner result -> TestDefM outers oldInner result
- setupAroundWith' :: HContains outers outer => (outer -> oldInner -> SetupFunc newInner) -> TestDefM outers newInner result -> TestDefM outers oldInner result
- setupAroundAll :: SetupFunc outer -> TestDefM (outer : outers) inner result -> TestDefM outers inner result
- setupAroundAllWith :: (oldOuter -> SetupFunc newOuter) -> TestDefM (newOuter ': (oldOuter ': outers)) inner result -> TestDefM (oldOuter ': outers) inner result
- modifyMaxSuccess :: (Int -> Int) -> TestDefM a b c -> TestDefM a b c
- modifyMaxDiscardRatio :: (Int -> Int) -> TestDefM a b c -> TestDefM a b c
- modifyMaxSize :: (Int -> Int) -> TestDefM a b c -> TestDefM a b c
- modifyMaxShrinks :: (Int -> Int) -> TestDefM a b c -> TestDefM a b c
- modifyRunSettings :: (TestRunSettings -> TestRunSettings) -> TestDefM a b c -> TestDefM a b c
- data TestRunSettings = TestRunSettings {}
- sequential :: TestDefM a b c -> TestDefM a b c
- parallel :: TestDefM a b c -> TestDefM a b c
- withParallelism :: Parallelism -> TestDefM a b c -> TestDefM a b c
- data Parallelism
- randomiseExecutionOrder :: TestDefM a b c -> TestDefM a b c
- doNotRandomiseExecutionOrder :: TestDefM a b c -> TestDefM a b c
- withExecutionOrderRandomisation :: ExecutionOrderRandomisation -> TestDefM a b c -> TestDefM a b c
- data ExecutionOrderRandomisation
- modifyRetries :: (Word -> Word) -> TestDefM a b c -> TestDefM a b c
- withoutRetries :: TestDefM a b c -> TestDefM a b c
- withRetries :: Word -> TestDefM a b c -> TestDefM a b c
- flaky :: Word -> TestDefM a b c -> TestDefM a b c
- flakyWith :: Word -> String -> TestDefM a b c -> TestDefM a b c
- notFlaky :: TestDefM a b c -> TestDefM a b c
- potentiallyFlaky :: TestDefM a b c -> TestDefM a b c
- potentiallyFlakyWith :: String -> TestDefM a b c -> TestDefM a b c
- withFlakiness :: FlakinessMode -> TestDefM a b c -> TestDefM a b c
- data FlakinessMode
- = MayNotBeFlaky
- | MayBeFlaky !(Maybe String)
- expectPassing :: TestDefM a b c -> TestDefM a b c
- expectFailing :: TestDefM a b c -> TestDefM a b c
- withExpectationMode :: ExpectationMode -> TestDefM a b c -> TestDefM a b c
- data ExpectationMode
- runIO :: IO e -> TestDefM a b e
- newtype TestDefM (outers :: [Type]) inner result = TestDefM {
- unTestDefM :: WriterT (TestForest outers inner) (ReaderT TestDefEnv IO) result
- type TestDef outers inner = TestDefM outers inner ()
- execTestDefM :: Settings -> TestDefM outers inner result -> IO (TestForest outers inner)
- runTestDefM :: Settings -> TestDefM outers inner result -> IO (result, TestForest outers inner)
- class IsTest e where
- type Arg1 e
- type Arg2 e
- runTest :: e -> TestRunSettings -> ProgressReporter -> ((Arg1 e -> Arg2 e -> IO ()) -> IO ()) -> IO TestRunResult
- data TDef value = TDef {
- testDefVal :: value
- testDefCallStack :: CallStack
- type TestForest outers inner = SpecDefForest outers inner ()
- type TestTree outers inner = SpecDefTree outers inner ()
- type SpecDefForest (outers :: [Type]) inner extra = [SpecDefTree outers inner extra]
- data SpecDefTree (outers :: [Type]) inner extra where
- DefSpecifyNode :: Text -> TDef (ProgressReporter -> ((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult) -> extra -> SpecDefTree outers inner extra
- DefPendingNode :: Text -> Maybe Text -> SpecDefTree outers inner extra
- DefDescribeNode :: Text -> SpecDefForest outers inner extra -> SpecDefTree outers inner extra
- DefSetupNode :: IO () -> SpecDefForest outers inner extra -> SpecDefTree outers inner extra
- DefBeforeAllNode :: IO outer -> SpecDefForest (outer ': otherOuters) inner extra -> SpecDefTree otherOuters inner extra
- DefBeforeAllWithNode :: (oldOuter -> IO newOuter) -> SpecDefForest (newOuter ': (oldOuter ': otherOuters)) inner extra -> SpecDefTree (oldOuter ': otherOuters) inner extra
- DefWrapNode :: (IO () -> IO ()) -> SpecDefForest outers inner extra -> SpecDefTree outers inner extra
- DefAroundAllNode :: ((outer -> IO ()) -> IO ()) -> SpecDefForest (outer ': otherOuters) inner extra -> SpecDefTree otherOuters inner extra
- DefAroundAllWithNode :: ((newOuter -> IO ()) -> oldOuter -> IO ()) -> SpecDefForest (newOuter ': (oldOuter ': otherOuters)) inner extra -> SpecDefTree (oldOuter ': otherOuters) inner extra
- DefAfterAllNode :: (HList outers -> IO ()) -> SpecDefForest outers inner extra -> SpecDefTree outers inner extra
- DefParallelismNode :: Parallelism -> SpecDefForest outers inner extra -> SpecDefTree outers inner extra
- DefRandomisationNode :: ExecutionOrderRandomisation -> SpecDefForest outers inner extra -> SpecDefTree outers inner extra
- DefRetriesNode :: (Word -> Word) -> SpecDefForest outers inner extra -> SpecDefTree outers inner extra
- DefFlakinessNode :: FlakinessMode -> SpecDefForest outers inner extra -> SpecDefTree outers inner extra
- DefExpectationNode :: ExpectationMode -> SpecDefForest outers inner extra -> SpecDefTree outers inner extra
- type ResultForest = SpecForest (TDef (Timed TestRunReport))
- type ResultTree = SpecTree (TDef (Timed TestRunReport))
- shouldExitFail :: Settings -> ResultForest -> Bool
- type Spec = SpecWith ()
- type SpecWith inner = SpecM inner ()
- type SpecM inner result = TestDefM '[] inner result
- ppShow :: Show a => a -> String
- pPrint :: Show a => a -> IO ()
- module Test.Syd.Def
- module Test.Syd.Expectation
- module Test.Syd.HList
- module Test.Syd.Modify
- module Test.Syd.Output
- module Test.Syd.Run
- module Test.Syd.Runner
- module Test.Syd.SpecDef
- module Test.Syd.SpecForest
- module Control.Monad.IO.Class
Top level API functions
sydTest :: Spec -> IO () Source #
Evaluate a test suite definition and then run it.
This function perform option-parsing to construct the Settings
and then call sydTestWith
.
sydTestWith :: Settings -> Spec -> IO () Source #
Evaluate a test suite definition and then run it, with given Settings
This function performs no option-parsing.
Defining a test suite
Declaring tests
Declare a test group
Example usage:
describe "addition" $ do it "adds 3 to 5 to result in 8" $ 3 + 5 `shouldBe` 8 it "adds 4 to 7 to result in 11" $ 4 + 7 `shouldBe` 11
:: forall outers inner test. (HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) | |
=> String | The description of the test |
-> test | The test itself |
-> TestDefM outers inner () |
Declare a test
Note: Don't look at the type signature unless you really have to, just follow the examples.
Example usage:
Tests without resources
Pure test
describe "addition" $ it "adds 3 to 5 to result in 8" $ 3 + 5 == 8
IO test
describe "readFile and writeFile" $ it "reads back what it wrote for this example" $ do let cts = "hello world" let fp = "test.txt" writeFile fp cts cts' <- readFile fp cts' `shouldBe` cts
Pure Property test
describe "sort" $ it "is idempotent" $ forAllValid $ \ls -> sort (sort ls) `shouldBe` (sort (ls :: [Int]))
IO Property test
describe "readFile and writeFile" $ it "reads back what it wrote for any example" $ do forAllValid $ \fp -> forAllValid $ \cts -> do writeFile fp cts cts' <- readFile fp cts' `shouldBe` cts
Tests with an inner resource
Pure test
This is quite a rare use-case but here is an example anyway:
before (pure 3) $ describe "addition" $ it "adds 3 to 5 to result in 8" $ \i -> i + 5 == 8
IO test
This test sets up a temporary directory as an inner resource, and makes it available to each test in the group below.
let setUpTempDir func = withSystemTempDir $ \tempDir -> func tempDir in around setUpTempDir $ describe "readFile and writeFile" $ it "reads back what it wrote for this example" $ \tempDir -> do let cts = "hello world" let fp = tempDir </> "test.txt" writeFile fp cts cts' <- readFile fp cts' `shouldBe` cts
Pure property test
This is quite a rare use-case but here is an example anyway:
before (pure 3) $ describe "multiplication" $ it "is commutative for 5" $ \i -> i * 5 == 5 * 3
IO property test
let setUpTempDir func = withSystemTempDir $ \tempDir -> func tempDir in around setUpTempDir $ describe "readFile and writeFile" $ it "reads back what it wrote for this example" $ \tempDir -> property $ \cts -> do let fp = tempDir </> "test.txt" writeFile fp cts cts' <- readFile fp cts' `shouldBe` cts
itWithOuter :: (HasCallStack, IsTest test, Arg1 test ~ inner, Arg2 test ~ outer) => String -> test -> TestDefM (outer ': otherOuters) inner () Source #
Declare a test that uses an outer resource
Example usage:
Tests with an outer resource
Pure test
This is quite a rare use-case but here is an example anyway:
beforeAll (pure 3) $ describe "addition" $ itWithOuter "adds 3 to 5 to result in 8" $ \i -> i + 5 == 8
IO test
This test sets up a temporary directory as an inner resource, and makes it available to each test in the group below.
let setUpTempDir func = withSystemTempDir $ \tempDir -> func tempDir in aroundAll setUpTempDir describe "readFile and writeFile" $ itWithOuter "reads back what it wrote for this example" $ \tempDir -> do let cts = "hello world" let fp = tempDir </> "test.txt" writeFile fp cts cts' <- readFile fp cts' `shouldBe` cts
Pure property test
This is quite a rare use-case but here is an example anyway:
beforeAll (pure 3) $ describe "multiplication" $ itWithOuter "is commutative for 5" $ \i -> i * 5 == 5 * 3
IO property test
let setUpTempDir func = withSystemTempDir $ \tempDir -> func tempDir in aroundAll setUpTempDir describe "readFile and writeFile" $ itWithouter "reads back what it wrote for this example" $ \tempDir -> property $ \cts -> do let fp = tempDir </> "test.txt" writeFile fp cts cts' <- readFile fp cts' `shouldBe` cts
itWithBoth :: (HasCallStack, IsTest test, Arg1 test ~ outer, Arg2 test ~ inner) => String -> test -> TestDefM (outer ': otherOuters) inner () Source #
Declare a test that uses both an inner and an outer resource
Example usage:
Tests with both an inner and an outer resource
Pure test
This is quite a rare use-case but here is an example anyway:
beforeAll (pure 3) $ before (pure 5) $ describe "addition" $ itWithBoth "adds 3 to 5 to result in 8" $ \i j -> i + j == 8
IO test
This test sets up a temporary directory as an inner resource, and makes it available to each test in the group below.
let setUpTempDir func = withSystemTempDir $ \tempDir -> func tempDir in aroundAll setUpTempDir describe "readFile and writeFile" $ before (pure "hello world") $ itWithBoth "reads back what it wrote for this example" $ \tempDir cts -> do let fp = tempDir </> "test.txt" writeFile fp cts cts' <- readFile fp cts' `shouldBe` cts
Pure property test
This is quite a rare use-case but here is an example anyway:
beforeAll (pure 3) $ before (pure 5) $ describe "multiplication" $ itWithBoth "is commutative" $ \i j -> i * j == 5 * 3
IO property test
let setUpTempDir func = withSystemTempDir $ \tempDir -> func tempDir in aroundAll setUpTempDir describe "readFile and writeFile" $ before (pure "test.txt") $ itWithBoth "reads back what it wrote for this example" $ \tempDir fileName -> property $ \cts -> do let fp = tempDir </> fileName writeFile fp cts cts' <- readFile fp cts' `shouldBe` cts
itWithAll :: (HasCallStack, IsTest test, Arg1 test ~ HList outers, Arg2 test ~ inner) => String -> test -> TestDefM outers inner () Source #
Declare a test that uses all outer resources
You will most likely never need this function, but in case you do:
Note that this will always require a type annotation, along with the GADTs
and ScopedTypeVariables
extensions.
Example usage
beforeAll (pure 'a') $ beforeAll (pure 5) $ itWithAll "example" $ \(HCons c (HCons i HNil) :: HList '[Char, Int]) () -> (c, i) `shouldeBe` ('a', 5)
:: forall outers inner test. (HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) | |
=> String | The description of the test |
-> test | The test itself |
-> TestDefM outers inner () |
A synonym for it
specifyWithOuter :: (HasCallStack, IsTest test, Arg1 test ~ inner, Arg2 test ~ outer) => String -> test -> TestDefM (outer ': otherOuters) inner () Source #
A synonym for itWithOuter
specifyWithBoth :: (HasCallStack, IsTest test, Arg1 test ~ outer, Arg2 test ~ inner) => String -> test -> TestDefM (outer ': otherOuters) inner () Source #
A synonym for itWithBoth
specifyWithAll :: (HasCallStack, IsTest test, Arg1 test ~ HList outers, Arg2 test ~ inner) => String -> test -> TestDefM outers inner () Source #
A synonym for itWithAll
prop :: Testable prop => String -> prop -> Spec Source #
Convenience function for backwards compatibility with hspec
prop s p = it s $ property p
getTestDescriptionPath :: TestDefM outers inner [Text] Source #
Get the path of describe
strings upwards.
Note that using this function makes tests less movable, depending on what
you do with these strings.
For example, if you use these strings to define the path to a golden test
file, then that path will change if you move the tests somewhere else.
This combines unfortunately with the way sydtest-discover
makes the module
name part of this path.
Indeed: moving your tests to another module will change their path as well,
if you use sydtest-discover
.
Also note that while test forests can be randomised, their description path
upwards will not, because of how trees are structured.
Commented-out tests
xitWithOuter :: (HasCallStack, IsTest test, Arg1 test ~ inner, Arg2 test ~ outer) => String -> test -> TestDefM (outer ': otherOuters) inner () Source #
xitWithBoth :: (HasCallStack, IsTest test, Arg1 test ~ outer, Arg2 test ~ inner) => String -> test -> TestDefM (outer ': otherOuters) inner () Source #
xitWithAll :: (HasCallStack, IsTest test, Arg1 test ~ HList outers, Arg2 test ~ inner) => String -> test -> TestDefM outers inner () Source #
:: forall outers inner test. (HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) | |
=> String | The description of the test |
-> test | The test itself |
-> TestDefM outers inner () |
A synonym for xit
xspecifyWithOuter :: (HasCallStack, IsTest test, Arg1 test ~ inner, Arg2 test ~ outer) => String -> test -> TestDefM (outer ': otherOuters) inner () Source #
A synonym for xitWithOuter
xspecifyWithBoth :: (HasCallStack, IsTest test, Arg1 test ~ outer, Arg2 test ~ inner) => String -> test -> TestDefM (outer ': otherOuters) inner () Source #
A synonym for xitWithBoth
xspecifyWithAll :: (HasCallStack, IsTest test, Arg1 test ~ HList outers, Arg2 test ~ inner) => String -> test -> TestDefM outers inner () Source #
A synonym for xitWithAll
Pending tests
pendingWith :: String -> String -> TestDefM outers inner () Source #
Declare a test that has not been written yet for the given reason.
Golden tests
pureGoldenTextFile :: FilePath -> Text -> GoldenTest Text Source #
Test that the given text is the same as what we find in the given golden file.
goldenTextFile :: FilePath -> IO Text -> GoldenTest Text Source #
Test that the produced text is the same as what we find in the given golden file.
pureGoldenByteStringFile :: FilePath -> ByteString -> GoldenTest ByteString Source #
Test that the given bytestring is the same as what we find in the given golden file.
goldenByteStringFile :: FilePath -> IO ByteString -> GoldenTest ByteString Source #
Test that the produced bytestring is the same as what we find in the given golden file.
pureGoldenLazyByteStringFile :: FilePath -> ByteString -> GoldenTest ByteString Source #
Test that the given lazy bytestring is the same as what we find in the given golden file.
Note: This converts the lazy bytestring to a strict bytestring first.
goldenLazyByteStringFile :: FilePath -> IO ByteString -> GoldenTest ByteString Source #
Test that the produced bytestring is the same as what we find in the given golden file.
Note: This converts the lazy bytestring to a strict bytestring first.
pureGoldenByteStringBuilderFile :: FilePath -> Builder -> GoldenTest Builder Source #
Test that the given lazy bytestring is the same as what we find in the given golden file.
Note: This converts the builder to a strict bytestring first.
goldenByteStringBuilderFile :: FilePath -> IO Builder -> GoldenTest Builder Source #
Test that the produced bytestring is the same as what we find in the given golden file.
Note: This converts the builder to a strict bytestring first.
pureGoldenStringFile :: FilePath -> String -> GoldenTest String Source #
Test that the given string is the same as what we find in the given golden file.
goldenStringFile :: FilePath -> IO String -> GoldenTest String Source #
Test that the produced string is the same as what we find in the given golden file.
goldenShowInstance :: Show a => FilePath -> a -> GoldenTest String Source #
Test that the show instance has not changed for the given value.
goldenPrettyShowInstance :: Show a => FilePath -> a -> GoldenTest String Source #
Test that the show instance has not changed for the given value, via ppShow
.
goldenContext :: FilePath -> String Source #
The golden test context for adding context to a golden test assertion:
goldenTestCompare = \actual expected -> if actual == expected then Nothing else Just $ Context (stringsNotEqualButShouldHaveBeenEqual actual expected) (goldenContext fp)
data GoldenTest a Source #
A golden test for output of type a
.
The purpose of a golden test is to ensure that the output of a certain process does not change even over time.
Golden tests can also be used to show how the output of a certain process changes over time and force code reviewers to review the diff that they see in the PR.
This works by saving a golden
output in the repository somewhere,
committing it, and then compare that golden output to the output that is
currently being produced. You can use `--golden-reset` to have sydtest
update the golden output by writing the current output.
GoldenTest | |
|
Instances
Scenario tests
scenarioDir :: FilePath -> (FilePath -> TestDefM outers inner ()) -> TestDefM outers inner () Source #
Define a test for each file in the given directory.
Example:
scenarioDir "test_resources/even" $ \fp -> it "contains an even number" $ do s <- readFile fp n <- readIO s (n :: Int) `shouldSatisfy` even
scenarioDirRecur :: FilePath -> (FilePath -> TestDefM outers inner ()) -> TestDefM outers inner () Source #
Define a test for each file in the given directory, recursively.
Example:
scenarioDirRecur "test_resources/odd" $ \fp -> it "contains an odd number" $ do s <- readFile fp n <- readIO s (n :: Int) `shouldSatisfy` odd
Expectations
shouldBe :: (HasCallStack, Show a, Eq a) => a -> a -> IO () infix 1 Source #
Assert that two values are equal according to ==
.
shouldNotBe :: (HasCallStack, Show a, Eq a) => a -> a -> IO () infix 1 Source #
Assert that two values are not equal according to ==
.
shouldSatisfy :: (HasCallStack, Show a) => a -> (a -> Bool) -> IO () infix 1 Source #
Assert that a value satisfies the given predicate.
shouldSatisfyNamed :: (HasCallStack, Show a) => a -> String -> (a -> Bool) -> IO () Source #
Assert that a value satisfies the given predicate with the given predicate name.
shouldNotSatisfy :: (HasCallStack, Show a) => a -> (a -> Bool) -> IO () infix 1 Source #
Assert that a value does not satisfy the given predicate.
shouldNotSatisfyNamed :: (HasCallStack, Show a) => a -> String -> (a -> Bool) -> IO () Source #
Assert that a value does not satisfy the given predicate with the given predicate name.
shouldReturn :: (HasCallStack, Show a, Eq a) => IO a -> a -> IO () infix 1 Source #
Assert that computation returns the given value (according to ==
).
shouldNotReturn :: (HasCallStack, Show a, Eq a) => IO a -> a -> IO () infix 1 Source #
Assert that computation returns the given value (according to ==
).
shouldStartWith :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation infix 1 Source #
Assert that the given list has the given prefix
shouldEndWith :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation infix 1 Source #
Assert that the given list has the given suffix
shouldContain :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation infix 1 Source #
Assert that the given list has the given infix
shouldMatchList :: (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation Source #
Assert that the given list contains all elements from the other given list and only them, perhaps in a different order.
expectationFailure :: HasCallStack => String -> IO a Source #
Make a test fail
Note that this is mostly backward compatible, but it has return type a
instead of ()
because execution will not continue beyond this function.
In this way it is not entirely backward compatible with hspec because now there could be an ambiguous type error.
context :: String -> IO a -> IO a Source #
Annotate a given action with a context, for contextual assertions
This is a completely different function from the function with the same name in hspec. In hspec, context is a synonym for describe, but in sydtest, context is used for contextual failures.
type Expectation = IO () Source #
For easy hspec migration
shouldThrow :: forall e a. (HasCallStack, Exception e) => IO a -> Selector e -> Expectation infix 1 Source #
Assert that a given IO action throws an exception that matches the given exception
String expectations
stringShouldBe :: HasCallStack => String -> String -> IO () Source #
textShouldBe :: HasCallStack => Text -> Text -> IO () Source #
For throwing raw assertions
bytestringsNotEqualButShouldHaveBeenEqual :: ByteString -> ByteString -> Assertion Source #
An assertion that says two ByteString
s should have been equal according to ==
.
A special exception that sydtest knows about and can display nicely in the error output
This is exported outwards so that you can define golden tests for custom types.
You will probably not want to use this directly in everyday tests, use shouldBe
or a similar function instead.
Instances
Declaring test dependencies
Dependencies around all of a group of tests
:: IO outer | The function to run (once), beforehand, to produce the outer resource. |
-> TestDefM (outer ': otherOuters) inner result | |
-> TestDefM otherOuters inner result |
Run a custom action before all spec items in a group, to set up an outer resource a
.
:: IO () | The function to run (once), beforehand. |
-> TestDefM outers inner result | |
-> TestDefM outers inner result |
Run a custom action before all spec items in a group without setting up any outer resources.
:: (previousOuter -> IO newOuter) | The function to run (once), beforehand, to produce a new outer resource while using a previous outer resource |
-> TestDefM (newOuter ': (previousOuter ': otherOuters)) inner result | |
-> TestDefM (previousOuter ': otherOuters) inner result |
Run a custom action before all spec items in a group, to set up an outer resource b
by using the outer resource a
.
:: (outer -> IO ()) | The function to run (once), afterwards, using the outer resource. |
-> TestDefM (outer ': otherOuters) inner result | |
-> TestDefM (outer ': otherOuters) inner result |
Run a custom action after all spec items, using the outer resource a
.
:: (HList outers -> IO ()) | The function to run (once), afterwards, using all outer resources. |
-> TestDefM outers inner result | |
-> TestDefM outers inner result |
Run a custom action after all spec items, using all the outer resources.
:: IO () | The function to run (once), afterwards. |
-> TestDefM outers inner result | |
-> TestDefM outers inner result |
Run a custom action after all spec items without using any outer resources.
:: ((outer -> IO ()) -> IO ()) | The function that provides the outer resource (once), around the tests. |
-> TestDefM (outer ': otherOuters) inner result | |
-> TestDefM otherOuters inner result |
Run a custom action before and/or after all spec items in group, to provide access to a resource a
.
See the FOOTGUN
note in the docs for around_
.
:: (IO () -> IO ()) | The function that wraps running the tests. |
-> TestDefM outers inner result | |
-> TestDefM outers inner result |
Run a custom action before and/or after all spec items in a group without accessing any resources.
FOOTGUN
This combinator gives the programmer a lot of power. In fact, it gives the programmer enough power to break the test framework. Indeed, you can provide a wrapper function that just _doesn't_ run the function like this:
spec :: Spec spec = do let don'tDo :: IO () -> IO () don'tDo _ = pure () aroundAll_ don'tDo $ do it "should pass" True
During execution, you'll then get an error like this:
thread blocked indefinitely in an MVar operation
The same problem exists when using around_
.
Something even more pernicious goes wrong when you run the given action more than once like this:
spec :: Spec spec = do let doTwice :: IO () -> IO () doTwice f = f >> f aroundAll_ doTwice $ do it "should pass" True
In this case, the test will "just work", but it will be executed twice even if the output reports that it only passed once.
Note: If you're interested in fixing this, talk to me, but only after GHC has gotten impredicative types because that will likely be a requirement.
:: forall newOuter oldOuter otherOuters inner result. ((newOuter -> IO ()) -> oldOuter -> IO ()) | The function that provides the new outer resource (once), using the old outer resource. |
-> TestDefM (newOuter ': (oldOuter ': otherOuters)) inner result | |
-> TestDefM (oldOuter ': otherOuters) inner result |
Run a custom action before and/or after all spec items in a group to provide access to a resource a
while using a resource b
See the FOOTGUN
note in the docs for around_
.
Dependencies around each of a group of tests
:: IO inner | The function to run before every test, to produce the inner resource |
-> TestDefM outers inner result | |
-> TestDefM outers () result |
Run a custom action before every spec item, to set up an inner resource inner
.
Note that this function turns off shrinking. See https://github.com/nick8325/quickcheck/issues/331
:: IO () | The function to run before every test |
-> TestDefM outers inner result | |
-> TestDefM outers inner result |
Run a custom action before every spec item without setting up any inner resources.
Note that this function turns off shrinking. See https://github.com/nick8325/quickcheck/issues/331
:: (inner -> IO ()) | The function to run after every test, using the inner resource |
-> TestDefM outers inner result | |
-> TestDefM outers inner result |
Run a custom action after every spec item, using the inner resource c
.
Note that this function turns off shrinking. See https://github.com/nick8325/quickcheck/issues/331
:: IO () | The function to run after every test |
-> TestDefM outers inner result | |
-> TestDefM outers inner result |
Run a custom action after every spec item without using any inner resources.
Note that this function turns off shrinking. See https://github.com/nick8325/quickcheck/issues/331
:: ((inner -> IO ()) -> IO ()) | The function to provide the inner resource around every test |
-> TestDefM outers inner result | |
-> TestDefM outers () result |
Run a custom action before and/or after every spec item, to provide access to an inner resource c
.
See the FOOTGUN
note in the docs for around_
.
Note that this function turns off shrinking. See https://github.com/nick8325/quickcheck/issues/331
:: (IO () -> IO ()) | The function to wrap every test with |
-> TestDefM outers inner result | |
-> TestDefM outers inner result |
Run a custom action before and/or after every spec item without accessing any inner resources.
It is important that the wrapper function that you provide runs the action that it gets _exactly once_.
FOOTGUN
This combinator gives the programmer a lot of power. In fact, it gives the programmer enough power to break the test framework. Indeed, you can provide a wrapper function that just _doesn't_ run the function like this:
spec :: Spec spec = do let don'tDo :: IO () -> IO () don'tDo _ = pure () around_ don'tDo $ do it "should pass" True
During execution, you'll then get an error like this:
thread blocked indefinitely in an MVar operation
The same problem exists when using aroundAll_
.
The same thing will go wrong if you run the given action more than once like this:
spec :: Spec spec = do let doTwice :: IO () -> IO () doTwice f = f >> f around_ doTwice $ do it "should pass" True
Note: If you're interested in fixing this, talk to me, but only after GHC has gotten impredicative types because that will likely be a requirement.
Note that this function turns off shrinking. See https://github.com/nick8325/quickcheck/issues/331
aroundWith :: forall newInner oldInner outers result. ((newInner -> IO ()) -> oldInner -> IO ()) -> TestDefM outers newInner result -> TestDefM outers oldInner result Source #
Run a custom action before and/or after every spec item, to provide access to an inner resource c
while using the inner resource d
.
See the FOOTGUN
note in the docs for around_
.
Note that this function turns off shrinking. See https://github.com/nick8325/quickcheck/issues/331
Setup functions
Creating setup functions
newtype SetupFunc resource Source #
A function that can provide a resource
.
You can think of this as a potentially-resource-aware version of 'IO resource'. In other words, it's like an 'IO resource' that can clean up after itself.
This type has a monad instance, which means you can now compose setup functions using regular do-notation. This works together nicely with most supplier functions. Some examples:
Note that these examples already have functions defined for them in sydtest companion libraries.
SetupFunc | |
|
Using setup functions
Around
setupAround :: SetupFunc inner -> TestDefM outers inner result -> TestDefM outers any result Source #
setupAroundWith :: (oldInner -> SetupFunc newInner) -> TestDefM outers newInner result -> TestDefM outers oldInner result Source #
Use aroundWith
with a SetupFunc
setupAroundWith' :: HContains outers outer => (outer -> oldInner -> SetupFunc newInner) -> TestDefM outers newInner result -> TestDefM outers oldInner result Source #
Use aroundWith'
with a SetupFunc
AroundAll
setupAroundAll :: SetupFunc outer -> TestDefM (outer : outers) inner result -> TestDefM outers inner result Source #
setupAroundAllWith :: (oldOuter -> SetupFunc newOuter) -> TestDefM (newOuter ': (oldOuter ': outers)) inner result -> TestDefM (oldOuter ': outers) inner result Source #
Use aroundAllWith
with a SetupFunc
Declaring different test settings
modifyRunSettings :: (TestRunSettings -> TestRunSettings) -> TestDefM a b c -> TestDefM a b c Source #
data TestRunSettings Source #
Instances
Declaring parallelism
sequential :: TestDefM a b c -> TestDefM a b c Source #
Declare that all tests below must be run sequentially
parallel :: TestDefM a b c -> TestDefM a b c Source #
Declare that all tests below may be run in parallel. (This is the default.)
withParallelism :: Parallelism -> TestDefM a b c -> TestDefM a b c Source #
Annotate a test group with Parallelism
.
data Parallelism Source #
Instances
Generic Parallelism Source # | |
Defined in Test.Syd.SpecDef type Rep Parallelism :: Type -> Type # from :: Parallelism -> Rep Parallelism x # to :: Rep Parallelism x -> Parallelism # | |
Show Parallelism Source # | |
Defined in Test.Syd.SpecDef showsPrec :: Int -> Parallelism -> ShowS # show :: Parallelism -> String # showList :: [Parallelism] -> ShowS # | |
Eq Parallelism Source # | |
Defined in Test.Syd.SpecDef (==) :: Parallelism -> Parallelism -> Bool # (/=) :: Parallelism -> Parallelism -> Bool # | |
type Rep Parallelism Source # | |
Declaring randomisation order
randomiseExecutionOrder :: TestDefM a b c -> TestDefM a b c Source #
Declare that the order of execution of all tests below may be randomised.
doNotRandomiseExecutionOrder :: TestDefM a b c -> TestDefM a b c Source #
Declare that the order of execution of all tests below must not be randomised.
withExecutionOrderRandomisation :: ExecutionOrderRandomisation -> TestDefM a b c -> TestDefM a b c Source #
Annotate a test group with ExecutionOrderRandomisation
.
data ExecutionOrderRandomisation Source #
Instances
Generic ExecutionOrderRandomisation Source # | |
Defined in Test.Syd.SpecDef type Rep ExecutionOrderRandomisation :: Type -> Type # | |
Show ExecutionOrderRandomisation Source # | |
Defined in Test.Syd.SpecDef showsPrec :: Int -> ExecutionOrderRandomisation -> ShowS # show :: ExecutionOrderRandomisation -> String # showList :: [ExecutionOrderRandomisation] -> ShowS # | |
Eq ExecutionOrderRandomisation Source # | |
Defined in Test.Syd.SpecDef | |
type Rep ExecutionOrderRandomisation Source # | |
Defined in Test.Syd.SpecDef type Rep ExecutionOrderRandomisation = D1 ('MetaData "ExecutionOrderRandomisation" "Test.Syd.SpecDef" "sydtest-0.17.0.0-L6KbQfkPwEtDkg8pbVjSrz" 'False) (C1 ('MetaCons "RandomiseExecutionOrder" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoNotRandomiseExecutionOrder" 'PrefixI 'False) (U1 :: Type -> Type)) |
Modifying the number of retries
modifyRetries :: (Word -> Word) -> TestDefM a b c -> TestDefM a b c Source #
Modify the number of retries to use in flakiness diagnostics.
withoutRetries :: TestDefM a b c -> TestDefM a b c Source #
Turn off retries
withRetries :: Word -> TestDefM a b c -> TestDefM a b c Source #
Make the number of retries this constant
Declaring flakiness
flaky :: Word -> TestDefM a b c -> TestDefM a b c Source #
Mark a test suite as "potentially flaky" with a given number of retries.
This will retry any test in the given test group up to the given number of tries, and pass a test if it passes once. The test output will show which tests were flaky.
WARNING: This is only a valid approach to dealing with test flakiness if it is true that tests never pass accidentally. In other words: tests using flaky must be guaranteed to fail every time if an error is introduced in the code, it should only be added to deal with accidental failures, never accidental passes.
flakyWith :: Word -> String -> TestDefM a b c -> TestDefM a b c Source #
Like flaky
, but also shows the given message to the user whenever the test is flaky.
You could use it like this:
>>>
flakyWith 3 "Something sometimes goes wrong with the database, see issue 6346" ourTestSuite
notFlaky :: TestDefM a b c -> TestDefM a b c Source #
Mark a test suite as "must not be flaky".
This is useful to have a subgroup of a group marked as flaky
that must not be flaky afteral.
potentiallyFlaky :: TestDefM a b c -> TestDefM a b c Source #
Mark a test suite as 'potentially flaky', such that it will not fail if it is flaky but passes at least once.
potentiallyFlakyWith :: String -> TestDefM a b c -> TestDefM a b c Source #
Like potentiallyFlaky
, but with a message.
withFlakiness :: FlakinessMode -> TestDefM a b c -> TestDefM a b c Source #
Annotate a test group with FlakinessMode
.
data FlakinessMode Source #
Instances
Generic FlakinessMode Source # | |
Defined in Test.Syd.SpecDef type Rep FlakinessMode :: Type -> Type # from :: FlakinessMode -> Rep FlakinessMode x # to :: Rep FlakinessMode x -> FlakinessMode # | |
Show FlakinessMode Source # | |
Defined in Test.Syd.SpecDef showsPrec :: Int -> FlakinessMode -> ShowS # show :: FlakinessMode -> String # showList :: [FlakinessMode] -> ShowS # | |
Eq FlakinessMode Source # | |
Defined in Test.Syd.SpecDef (==) :: FlakinessMode -> FlakinessMode -> Bool # (/=) :: FlakinessMode -> FlakinessMode -> Bool # | |
type Rep FlakinessMode Source # | |
Defined in Test.Syd.SpecDef type Rep FlakinessMode = D1 ('MetaData "FlakinessMode" "Test.Syd.SpecDef" "sydtest-0.17.0.0-L6KbQfkPwEtDkg8pbVjSrz" 'False) (C1 ('MetaCons "MayNotBeFlaky" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MayBeFlaky" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe String)))) |
Declaring expectations
expectPassing :: TestDefM a b c -> TestDefM a b c Source #
Mark a test suite as 'should pass'
expectFailing :: TestDefM a b c -> TestDefM a b c Source #
Mark a test suite as 'should fail'
withExpectationMode :: ExpectationMode -> TestDefM a b c -> TestDefM a b c Source #
Annotate a test suite with ExpectationMode
data ExpectationMode Source #
Instances
Generic ExpectationMode Source # | |
Defined in Test.Syd.SpecDef type Rep ExpectationMode :: Type -> Type # from :: ExpectationMode -> Rep ExpectationMode x # to :: Rep ExpectationMode x -> ExpectationMode # | |
Show ExpectationMode Source # | |
Defined in Test.Syd.SpecDef showsPrec :: Int -> ExpectationMode -> ShowS # show :: ExpectationMode -> String # showList :: [ExpectationMode] -> ShowS # | |
Eq ExpectationMode Source # | |
Defined in Test.Syd.SpecDef (==) :: ExpectationMode -> ExpectationMode -> Bool # (/=) :: ExpectationMode -> ExpectationMode -> Bool # | |
type Rep ExpectationMode Source # | |
Doing IO during test definition
runIO :: IO e -> TestDefM a b e Source #
Run a test suite during test suite definition.
This function only exists for backward compatibility.
You can also just use liftIO
instead.
Test definition types
newtype TestDefM (outers :: [Type]) inner result Source #
The test definition monad
This type has three parameters:
outers
: A type-level list of the outer resources. These are resources that are prived once, around a group of tests. (This is the type of the results ofaroundAll
.)inner
: The inner resource. This is a resource that is set up around every test, and even every example of a property test. (This is the type of the result ofaround
.)result
: The result (TestDefM
is a monad.)
In practice, all of these three parameters should be ()
at the top level.
TestDefM | |
|
Instances
MonadReader TestDefEnv (TestDefM outers inner) Source # | |
Defined in Test.Syd.Def.TestDefM ask :: TestDefM outers inner TestDefEnv # local :: (TestDefEnv -> TestDefEnv) -> TestDefM outers inner a -> TestDefM outers inner a # reader :: (TestDefEnv -> a) -> TestDefM outers inner a # | |
MonadIO (TestDefM outers inner) Source # | |
Defined in Test.Syd.Def.TestDefM | |
Applicative (TestDefM outers inner) Source # | |
Defined in Test.Syd.Def.TestDefM pure :: a -> TestDefM outers inner a # (<*>) :: TestDefM outers inner (a -> b) -> TestDefM outers inner a -> TestDefM outers inner b # liftA2 :: (a -> b -> c) -> TestDefM outers inner a -> TestDefM outers inner b -> TestDefM outers inner c # (*>) :: TestDefM outers inner a -> TestDefM outers inner b -> TestDefM outers inner b # (<*) :: TestDefM outers inner a -> TestDefM outers inner b -> TestDefM outers inner a # | |
Functor (TestDefM outers inner) Source # | |
Monad (TestDefM outers inner) Source # | |
MonadWriter (TestForest outers inner) (TestDefM outers inner) Source # | |
Defined in Test.Syd.Def.TestDefM writer :: (a, TestForest outers inner) -> TestDefM outers inner a # tell :: TestForest outers inner -> TestDefM outers inner () # listen :: TestDefM outers inner a -> TestDefM outers inner (a, TestForest outers inner) # pass :: TestDefM outers inner (a, TestForest outers inner -> TestForest outers inner) -> TestDefM outers inner a # |
execTestDefM :: Settings -> TestDefM outers inner result -> IO (TestForest outers inner) Source #
runTestDefM :: Settings -> TestDefM outers inner result -> IO (result, TestForest outers inner) Source #
runTest :: e -> TestRunSettings -> ProgressReporter -> ((Arg1 e -> Arg2 e -> IO ()) -> IO ()) -> IO TestRunResult Source #
Running the test, safely
Instances
IsTest Property Source # | |
IsTest Bool Source # | |
IsTest (IO (GoldenTest a)) Source # | |
Defined in Test.Syd.Run type Arg1 (IO (GoldenTest a)) Source # type Arg2 (IO (GoldenTest a)) Source # runTest :: IO (GoldenTest a) -> TestRunSettings -> ProgressReporter -> ((Arg1 (IO (GoldenTest a)) -> Arg2 (IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (IO ()) Source # | |
IsTest (GoldenTest a) Source # | |
Defined in Test.Syd.Run type Arg1 (GoldenTest a) Source # type Arg2 (GoldenTest a) Source # runTest :: GoldenTest a -> TestRunSettings -> ProgressReporter -> ((Arg1 (GoldenTest a) -> Arg2 (GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (arg -> Property) Source # | |
IsTest (arg -> IO (GoldenTest a)) Source # | |
Defined in Test.Syd.Run type Arg1 (arg -> IO (GoldenTest a)) Source # type Arg2 (arg -> IO (GoldenTest a)) Source # runTest :: (arg -> IO (GoldenTest a)) -> TestRunSettings -> ProgressReporter -> ((Arg1 (arg -> IO (GoldenTest a)) -> Arg2 (arg -> IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (arg -> IO ()) Source # | |
IsTest (arg -> GoldenTest a) Source # | |
Defined in Test.Syd.Run type Arg1 (arg -> GoldenTest a) Source # type Arg2 (arg -> GoldenTest a) Source # runTest :: (arg -> GoldenTest a) -> TestRunSettings -> ProgressReporter -> ((Arg1 (arg -> GoldenTest a) -> Arg2 (arg -> GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (arg -> Bool) Source # | |
IsTest (outerArgs -> ReaderT env IO ()) Source # | |
IsTest (outerArgs -> innerArg -> Property) Source # | |
Defined in Test.Syd.Run runTest :: (outerArgs -> innerArg -> Property) -> TestRunSettings -> ProgressReporter -> ((Arg1 (outerArgs -> innerArg -> Property) -> Arg2 (outerArgs -> innerArg -> Property) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (outerArgs -> innerArg -> IO (GoldenTest a)) Source # | |
Defined in Test.Syd.Run type Arg1 (outerArgs -> innerArg -> IO (GoldenTest a)) Source # type Arg2 (outerArgs -> innerArg -> IO (GoldenTest a)) Source # runTest :: (outerArgs -> innerArg -> IO (GoldenTest a)) -> TestRunSettings -> ProgressReporter -> ((Arg1 (outerArgs -> innerArg -> IO (GoldenTest a)) -> Arg2 (outerArgs -> innerArg -> IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (outerArgs -> innerArg -> IO ()) Source # | |
Defined in Test.Syd.Run runTest :: (outerArgs -> innerArg -> IO ()) -> TestRunSettings -> ProgressReporter -> ((Arg1 (outerArgs -> innerArg -> IO ()) -> Arg2 (outerArgs -> innerArg -> IO ()) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (outerArgs -> innerArg -> GoldenTest a) Source # | |
Defined in Test.Syd.Run type Arg1 (outerArgs -> innerArg -> GoldenTest a) Source # type Arg2 (outerArgs -> innerArg -> GoldenTest a) Source # runTest :: (outerArgs -> innerArg -> GoldenTest a) -> TestRunSettings -> ProgressReporter -> ((Arg1 (outerArgs -> innerArg -> GoldenTest a) -> Arg2 (outerArgs -> innerArg -> GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (outerArgs -> innerArg -> Bool) Source # | |
Defined in Test.Syd.Run runTest :: (outerArgs -> innerArg -> Bool) -> TestRunSettings -> ProgressReporter -> ((Arg1 (outerArgs -> innerArg -> Bool) -> Arg2 (outerArgs -> innerArg -> Bool) -> IO ()) -> IO ()) -> IO TestRunResult Source # | |
IsTest (ReaderT env IO ()) Source # | |
Test suite types
TDef | |
|
Instances
Foldable TDef Source # | |
Defined in Test.Syd.SpecDef fold :: Monoid m => TDef m -> m # foldMap :: Monoid m => (a -> m) -> TDef a -> m # foldMap' :: Monoid m => (a -> m) -> TDef a -> m # foldr :: (a -> b -> b) -> b -> TDef a -> b # foldr' :: (a -> b -> b) -> b -> TDef a -> b # foldl :: (b -> a -> b) -> b -> TDef a -> b # foldl' :: (b -> a -> b) -> b -> TDef a -> b # foldr1 :: (a -> a -> a) -> TDef a -> a # foldl1 :: (a -> a -> a) -> TDef a -> a # elem :: Eq a => a -> TDef a -> Bool # maximum :: Ord a => TDef a -> a # | |
Traversable TDef Source # | |
Functor TDef Source # | |
type TestForest outers inner = SpecDefForest outers inner () Source #
type TestTree outers inner = SpecDefTree outers inner () Source #
type SpecDefForest (outers :: [Type]) inner extra = [SpecDefTree outers inner extra] Source #
data SpecDefTree (outers :: [Type]) inner extra where Source #
A tree of tests
This type has three parameters:
outers
: A type-level list of the outer resources. These are resources that are prived once, around a group of tests. (This is the type of the results ofaroundAll
.)inner
: The inner resource. This is a resource that is set up around every test, and even every example of a property test. (This is the type of the result ofaround
.)result
: The result (TestDefM
is a monad.)
In practice, all of these three parameters should be ()
at the top level.
When you're just using sydtest and not writing a library for sydtest, you probably don't even want to concern yourself with this type.
DefSpecifyNode | Define a test |
| |
DefPendingNode | Define a pending test |
| |
DefDescribeNode | Group tests using a description |
| |
DefSetupNode | |
| |
DefBeforeAllNode | |
| |
DefBeforeAllWithNode | |
| |
DefWrapNode | |
| |
DefAroundAllNode | |
| |
DefAroundAllWithNode | |
| |
DefAfterAllNode | |
| |
DefParallelismNode | Control the level of parallelism for a given group of tests |
| |
DefRandomisationNode | Control the execution order randomisation for a given group of tests |
| |
DefRetriesNode | |
| |
DefFlakinessNode | |
| |
DefExpectationNode | |
|
Instances
Foldable (SpecDefTree a c) Source # | |
Defined in Test.Syd.SpecDef fold :: Monoid m => SpecDefTree a c m -> m # foldMap :: Monoid m => (a0 -> m) -> SpecDefTree a c a0 -> m # foldMap' :: Monoid m => (a0 -> m) -> SpecDefTree a c a0 -> m # foldr :: (a0 -> b -> b) -> b -> SpecDefTree a c a0 -> b # foldr' :: (a0 -> b -> b) -> b -> SpecDefTree a c a0 -> b # foldl :: (b -> a0 -> b) -> b -> SpecDefTree a c a0 -> b # foldl' :: (b -> a0 -> b) -> b -> SpecDefTree a c a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> SpecDefTree a c a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> SpecDefTree a c a0 -> a0 # toList :: SpecDefTree a c a0 -> [a0] # null :: SpecDefTree a c a0 -> Bool # length :: SpecDefTree a c a0 -> Int # elem :: Eq a0 => a0 -> SpecDefTree a c a0 -> Bool # maximum :: Ord a0 => SpecDefTree a c a0 -> a0 # minimum :: Ord a0 => SpecDefTree a c a0 -> a0 # sum :: Num a0 => SpecDefTree a c a0 -> a0 # product :: Num a0 => SpecDefTree a c a0 -> a0 # | |
Traversable (SpecDefTree a c) Source # | |
Defined in Test.Syd.SpecDef traverse :: Applicative f => (a0 -> f b) -> SpecDefTree a c a0 -> f (SpecDefTree a c b) # sequenceA :: Applicative f => SpecDefTree a c (f a0) -> f (SpecDefTree a c a0) # mapM :: Monad m => (a0 -> m b) -> SpecDefTree a c a0 -> m (SpecDefTree a c b) # sequence :: Monad m => SpecDefTree a c (m a0) -> m (SpecDefTree a c a0) # | |
Functor (SpecDefTree a c) Source # | |
Defined in Test.Syd.SpecDef fmap :: (a0 -> b) -> SpecDefTree a c a0 -> SpecDefTree a c b # (<$) :: a0 -> SpecDefTree a c b -> SpecDefTree a c a0 # | |
MonadWriter (TestForest outers inner) (TestDefM outers inner) Source # | |
Defined in Test.Syd.Def.TestDefM writer :: (a, TestForest outers inner) -> TestDefM outers inner a # tell :: TestForest outers inner -> TestDefM outers inner () # listen :: TestDefM outers inner a -> TestDefM outers inner (a, TestForest outers inner) # pass :: TestDefM outers inner (a, TestForest outers inner -> TestForest outers inner) -> TestDefM outers inner a # |
type ResultForest = SpecForest (TDef (Timed TestRunReport)) Source #
type ResultTree = SpecTree (TDef (Timed TestRunReport)) Source #
shouldExitFail :: Settings -> ResultForest -> Bool Source #
Hspec synonyms
Utilities
pPrint :: Show a => a -> IO () #
Pretty print a generic value to stdout. This is particularly useful in the GHCi interactive environment.
Reexports
module Test.Syd.Def
module Test.Syd.Expectation
module Test.Syd.HList
module Test.Syd.Modify
module Test.Syd.Output
module Test.Syd.Run
module Test.Syd.Runner
module Test.Syd.SpecDef
module Test.Syd.SpecForest
module Control.Monad.IO.Class