sydtest-0.1.0.0: A modern testing framework for Haskell with good defaults and advanced testing features.
Safe HaskellNone
LanguageHaskell2010

Test.Syd

Description

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 pure Bool, an IO (), a GoldenTest, some combination of those, or any type that you can implement IsTest 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, an Arg1 type and an Arg2 type. These correspond to two function arguments. Arg1 corresponds to the first and Arg2 corresponds to the second. For example, IO () is an instance of IsTest, but arg -> IO () and outerArgs -> innerArg -> IO () are as well.

    • For outerArgs -> innerArgs -> IO (), Arg1 is outerArgs and Arg2 is innerArgs.
    • For arg -> IO (), Arg1 is () and Arg2 is arg.
    • For IO (), both Arg1 and Arg2 are ().
  • When using it or specify to define tests, the Arg1 and Arg2 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 and aroundAll functions.
Synopsis

Top level API functions

sydTest :: Spec -> IO () Source #

Evaluate a test suite definition and then run it, with default Settings

sydTestWith :: Settings -> Spec -> IO () Source #

Evaluate a test suite definition and then run it, with given Settings

Defining a test suite

Declaring tests

describe Source #

Arguments

:: String

The test group description

-> TestDefM outers inner () 
-> TestDefM outers inner () 

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

it Source #

Arguments

:: 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
Expand

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
Expand

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
Expand

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
Expand

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)

specify Source #

Arguments

:: 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

Commented-out tests

xdescribe :: String -> TestDefM outers inner () -> TestDefM outers inner () Source #

xit Source #

Arguments

:: 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 () 

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 #

xspecify Source #

Arguments

:: 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

pending :: String -> TestDefM outers inner () Source #

Declare a test that has not been written yet.

pendingWith :: String -> String -> TestDefM outers inner () Source #

Declare a test that has not been written yet for the given reason.

Environment-based tests

eit :: HasCallStack => String -> ReaderT env IO () -> TestDef outers env Source #

For defining a part of a test suite in 'ReaderT IO' instead of in IO.

This way you can write this:

spec :: Spec
spec = around withConnectionPool $
  it "can read what it writes" $ \pool ->
    let person = Person { name = "Dave", age = 25 }
    i <- runSqlPool (insert person) pool
    person' <- runSqlPool (get i) pool
    person' `shouldBe` person

like this instead:

spec :: Spec
spec = around withConnectionPool $
  eit "can read what it writes" $ do
    let person = Person { name = "Dave", age = 25 }
    i <- runDB $ insert person
    person' <- runDB $ get i
    liftIO $ person' `shouldBe` person

runDB :: ReaderT ConnectionPool IO a -> IO a

Note that you use eit with a property test. In that case you would have to write it like this:

spec :: Spec
spec = around withConnectionPool $
  it "can read what it writes" $ \pool -> do
    forAllValid $ \person -> withTestEnv pool $ do
      i <- runDB $ insert person
      person' <- runDB $ get i
      liftIO $ person' `shouldBe` person

withTestEnv :: env -> ReaderT env IO a -> IO a Source #

Helper function to run a property test with an env.

withTestEnv = flip runReaderT

Golden tests

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.

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.

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.

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

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

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

type Selector a = a -> Bool Source #

For easy hspec migration

String expectations

stringShouldBe :: HasCallStack => String -> String -> IO () Source #

Assert that two Strings are equal according to ==.

Note that using function could mess up the colours in your terminal if the Texts contain ANSI codes. In that case you may want to show your values first or use shouldBe instead.

textShouldBe :: HasCallStack => Text -> Text -> IO () Source #

Assert that two Texts are equal according to ==.

Note that using function could mess up the colours in your terminal if the Texts contain ANSI codes. In that case you may want to show your values first or use shouldBe instead.

For throwing raw assertions

stringsNotEqualButShouldHaveBeenEqual :: String -> String -> Assertion Source #

An assertion that says two Strings should have been equal according to ==.

Note that using function could mess up the colours in your terminal if the Texts contain ANSI codes. In that case you may want to show your values first or use shouldBe instead.

textsNotEqualButShouldHaveBeenEqual :: Text -> Text -> Assertion Source #

An assertion that says two Texts should have been equal according to ==.

Note that using function could mess up the colours in your terminal if the Texts contain ANSI codes. In that case you may want to show your values first or use shouldBe instead.

bytestringsNotEqualButShouldHaveBeenEqual :: ByteString -> ByteString -> Assertion Source #

An assertion that says two ByteStrings should have been equal according to ==.

data Assertion Source #

Instances

Instances details
Eq Assertion Source # 
Instance details

Defined in Test.Syd.Run

Show Assertion Source # 
Instance details

Defined in Test.Syd.Run

Generic Assertion Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Rep Assertion :: Type -> Type #

Exception Assertion Source # 
Instance details

Defined in Test.Syd.Run

type Rep Assertion Source # 
Instance details

Defined in Test.Syd.Run

type Rep Assertion = D1 ('MetaData "Assertion" "Test.Syd.Run" "sydtest-0.1.0.0-JD50o4fziYEPTOY150AFK" 'False) ((C1 ('MetaCons "NotEqualButShouldHaveBeenEqual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "EqualButShouldNotHaveBeenEqual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "PredicateSucceededButShouldHaveFailed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))))) :+: (C1 ('MetaCons "PredicateFailedButShouldHaveSucceeded" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :+: (C1 ('MetaCons "ExpectationFailed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "Context" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Assertion) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))

Declaring test dependencies

Dependencies around all of a group of tests

beforeAll Source #

Arguments

:: 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.

beforeAll_ Source #

Arguments

:: 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.

beforeAllWith Source #

Arguments

:: (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.

afterAll Source #

Arguments

:: (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.

afterAll' Source #

Arguments

:: (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.

afterAll_ Source #

Arguments

:: 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.

aroundAll Source #

Arguments

:: ((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_.

aroundAll_ Source #

Arguments

:: (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

Expand

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.

aroundAllWith Source #

Arguments

:: 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

before Source #

Arguments

:: 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 c.

before_ Source #

Arguments

:: 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.

after Source #

Arguments

:: (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.

after_ Source #

Arguments

:: 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.

around Source #

Arguments

:: ((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_.

around_ Source #

Arguments

:: (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

Expand

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.

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_.

Setup functions

Using setup functions

setupAround :: SetupFunc () inner -> TestDefM outers inner result -> TestDefM outers () result Source #

Use around with a SetupFunc

setupAroundWith :: SetupFunc oldInner newInner -> TestDefM outers newInner result -> TestDefM outers oldInner result Source #

setupAroundWith' :: HContains outers outer => (outer -> SetupFunc oldInner newInner) -> TestDefM outers newInner result -> TestDefM outers oldInner result Source #

Creating setup functions

newtype SetupFunc old new Source #

A function that can provide an new given an old.

You can think of this as a potentially-resource-aware version of 'old -> IO new'.

This type has a monad instance, which means you can now compose setup functions using regular do-notation.

Constructors

SetupFunc 

Fields

Instances

Instances details
Monad (SetupFunc old) Source # 
Instance details

Defined in Test.Syd.Def.SetupFunc

Methods

(>>=) :: SetupFunc old a -> (a -> SetupFunc old b) -> SetupFunc old b #

(>>) :: SetupFunc old a -> SetupFunc old b -> SetupFunc old b #

return :: a -> SetupFunc old a #

Functor (SetupFunc old) Source # 
Instance details

Defined in Test.Syd.Def.SetupFunc

Methods

fmap :: (a -> b) -> SetupFunc old a -> SetupFunc old b #

(<$) :: a -> SetupFunc old b -> SetupFunc old a #

Applicative (SetupFunc old) Source # 
Instance details

Defined in Test.Syd.Def.SetupFunc

Methods

pure :: a -> SetupFunc old a #

(<*>) :: SetupFunc old (a -> b) -> SetupFunc old a -> SetupFunc old b #

liftA2 :: (a -> b -> c) -> SetupFunc old a -> SetupFunc old b -> SetupFunc old c #

(*>) :: SetupFunc old a -> SetupFunc old b -> SetupFunc old b #

(<*) :: SetupFunc old a -> SetupFunc old b -> SetupFunc old a #

MonadIO (SetupFunc old) Source # 
Instance details

Defined in Test.Syd.Def.SetupFunc

Methods

liftIO :: IO a -> SetupFunc old a #

Category SetupFunc Source # 
Instance details

Defined in Test.Syd.Def.SetupFunc

Methods

id :: forall (a :: k). SetupFunc a a #

(.) :: forall (b :: k) (c :: k) (a :: k). SetupFunc b c -> SetupFunc a b -> SetupFunc a c #

makeSimpleSetupFunc :: (forall result. (resource -> IO result) -> IO result) -> SetupFunc () resource Source #

Turn a simple provider function into a SetupFunc.

This works together nicely with most supplier functions. Some examples:

useSimpleSetupFunc :: SetupFunc () resource -> forall result. (resource -> IO result) -> IO result Source #

Use a 'SetupFunc ()' as a simple provider function.

This is the opposite of the makeSimpleSetupFunc function

connectSetupFunc :: SetupFunc old newer -> SetupFunc newer newest -> SetupFunc old newest Source #

Connect two setup functions.

This is basically 'flip (.)' but for SetupFuncs. It's exactly 'flip composeSetupFunc'.

composeSetupFunc :: SetupFunc newer newest -> SetupFunc old newer -> SetupFunc old newest Source #

Compose two setup functions.

This is (.) but for SetupFuncs

wrapSetupFunc :: (old -> SetupFunc () new) -> SetupFunc old new Source #

Wrap a function that produces a SetupFunc to into a SetupFunc.

This is useful to combine a given 'SetupFunc b' with other 'SetupFunc ()'s as follows:

mySetupFunc :: SetupFunc B A
mySetupFunc = wrapSetupFunc $ \b -> do
  r <- setupSomething
  c <- setupSomethingElse b r
  pure $ somehowCombine c r

setupSomething :: SetupFunc () R
setupSomething :: B -> R -> SetupFunc () C
somehowCombine :: C -> R -> A

unwrapSetupFunc :: SetupFunc old new -> old -> SetupFunc () new Source #

Unwrap a SetupFunc into a function that produces a SetupFunc

This is the opposite of wrapSetupFunc.

Declaring different test settings

modifyMaxSuccess :: (Int -> Int) -> TestDefM a b c -> TestDefM a b c Source #

modifyMaxSize :: (Int -> Int) -> TestDefM a b c -> TestDefM a b c Source #

modifyMaxShrinks :: (Int -> Int) -> TestDefM a b c -> TestDefM a b c Source #

data TestRunSettings Source #

Instances

Instances details
Show TestRunSettings Source # 
Instance details

Defined in Test.Syd.Run

Generic TestRunSettings Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Rep TestRunSettings :: Type -> Type #

MonadReader TestRunSettings (TestDefM outers inner) Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Methods

ask :: TestDefM outers inner TestRunSettings #

local :: (TestRunSettings -> TestRunSettings) -> TestDefM outers inner a -> TestDefM outers inner a #

reader :: (TestRunSettings -> a) -> TestDefM outers inner a #

type Rep TestRunSettings Source # 
Instance details

Defined in Test.Syd.Run

type Rep TestRunSettings = D1 ('MetaData "TestRunSettings" "Test.Syd.Run" "sydtest-0.1.0.0-JD50o4fziYEPTOY150AFK" 'False) (C1 ('MetaCons "TestRunSettings" 'PrefixI 'True) ((S1 ('MetaSel ('Just "testRunSettingSeed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "testRunSettingMaxSuccess") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "testRunSettingMaxSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :*: ((S1 ('MetaSel ('Just "testRunSettingMaxDiscardRatio") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "testRunSettingMaxShrinks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "testRunSettingGoldenStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "testRunSettingGoldenReset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))

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.)

Declaring randomisation order

Doing IO during test definition

runIO :: IO e -> TestDefM a b e Source #

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 of aroundAll.)
  • 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 of around.)
  • result: The result (TestDefM is a monad.)

In practice, all of these three parameters should be () at the top level.

Constructors

TestDefM 

Fields

Instances

Instances details
MonadState () (TestDefM outers inner) Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Methods

get :: TestDefM outers inner () #

put :: () -> TestDefM outers inner () #

state :: (() -> (a, ())) -> TestDefM outers inner a #

MonadReader TestRunSettings (TestDefM outers inner) Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Methods

ask :: TestDefM outers inner TestRunSettings #

local :: (TestRunSettings -> TestRunSettings) -> TestDefM outers inner a -> TestDefM outers inner a #

reader :: (TestRunSettings -> a) -> TestDefM outers inner a #

Monad (TestDefM outers inner) Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Methods

(>>=) :: TestDefM outers inner a -> (a -> TestDefM outers inner b) -> TestDefM outers inner b #

(>>) :: TestDefM outers inner a -> TestDefM outers inner b -> TestDefM outers inner b #

return :: a -> TestDefM outers inner a #

Functor (TestDefM outers inner) Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Methods

fmap :: (a -> b) -> TestDefM outers inner a -> TestDefM outers inner b #

(<$) :: a -> TestDefM outers inner b -> TestDefM outers inner a #

Applicative (TestDefM outers inner) Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Methods

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 #

MonadIO (TestDefM outers inner) Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Methods

liftIO :: IO a -> TestDefM outers inner a #

MonadWriter (TestForest outers inner) (TestDefM outers inner) Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Methods

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 TestDef outer inner = TestDefM outer inner () Source #

A synonym for a test suite definition

execTestDefM :: Settings -> TestDefM outers inner result -> IO (TestForest outers inner) Source #

runTestDefM :: Settings -> TestDefM outers inner result -> IO (result, TestForest outers inner) Source #

class IsTest e where Source #

Associated Types

type Arg1 e Source #

type Arg2 e Source #

Methods

runTest :: e -> TestRunSettings -> ((Arg1 e -> Arg2 e -> IO ()) -> IO ()) -> IO TestRunResult Source #

Instances

Instances details
IsTest Bool Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 Bool Source #

type Arg2 Bool Source #

Methods

runTest :: Bool -> TestRunSettings -> ((Arg1 Bool -> Arg2 Bool -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest Property Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 Property Source #

type Arg2 Property Source #

IsTest (IO ()) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (IO ()) Source #

type Arg2 (IO ()) Source #

Methods

runTest :: IO () -> TestRunSettings -> ((Arg1 (IO ()) -> Arg2 (IO ()) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (IO (GoldenTest a)) Source #

type Arg2 (IO (GoldenTest a)) Source #

Methods

runTest :: IO (GoldenTest a) -> TestRunSettings -> ((Arg1 (IO (GoldenTest a)) -> Arg2 (IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (GoldenTest a) Source #

type Arg2 (GoldenTest a) Source #

Methods

runTest :: GoldenTest a -> TestRunSettings -> ((Arg1 (GoldenTest a) -> Arg2 (GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (outerArgs -> innerArg -> IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (outerArgs -> innerArg -> IO (GoldenTest a)) Source #

type Arg2 (outerArgs -> innerArg -> IO (GoldenTest a)) Source #

Methods

runTest :: (outerArgs -> innerArg -> IO (GoldenTest a)) -> TestRunSettings -> ((Arg1 (outerArgs -> innerArg -> IO (GoldenTest a)) -> Arg2 (outerArgs -> innerArg -> IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (arg -> IO (GoldenTest a)) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (arg -> IO (GoldenTest a)) Source #

type Arg2 (arg -> IO (GoldenTest a)) Source #

Methods

runTest :: (arg -> IO (GoldenTest a)) -> TestRunSettings -> ((Arg1 (arg -> IO (GoldenTest a)) -> Arg2 (arg -> IO (GoldenTest a)) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (outerArgs -> innerArg -> GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (outerArgs -> innerArg -> GoldenTest a) Source #

type Arg2 (outerArgs -> innerArg -> GoldenTest a) Source #

Methods

runTest :: (outerArgs -> innerArg -> GoldenTest a) -> TestRunSettings -> ((Arg1 (outerArgs -> innerArg -> GoldenTest a) -> Arg2 (outerArgs -> innerArg -> GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (arg -> GoldenTest a) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (arg -> GoldenTest a) Source #

type Arg2 (arg -> GoldenTest a) Source #

Methods

runTest :: (arg -> GoldenTest a) -> TestRunSettings -> ((Arg1 (arg -> GoldenTest a) -> Arg2 (arg -> GoldenTest a) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (outerArgs -> innerArg -> Property) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (outerArgs -> innerArg -> Property) Source #

type Arg2 (outerArgs -> innerArg -> Property) Source #

Methods

runTest :: (outerArgs -> innerArg -> Property) -> TestRunSettings -> ((Arg1 (outerArgs -> innerArg -> Property) -> Arg2 (outerArgs -> innerArg -> Property) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (arg -> Property) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (arg -> Property) Source #

type Arg2 (arg -> Property) Source #

Methods

runTest :: (arg -> Property) -> TestRunSettings -> ((Arg1 (arg -> Property) -> Arg2 (arg -> Property) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (outerArgs -> innerArg -> IO ()) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (outerArgs -> innerArg -> IO ()) Source #

type Arg2 (outerArgs -> innerArg -> IO ()) Source #

Methods

runTest :: (outerArgs -> innerArg -> IO ()) -> TestRunSettings -> ((Arg1 (outerArgs -> innerArg -> IO ()) -> Arg2 (outerArgs -> innerArg -> IO ()) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (arg -> IO ()) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (arg -> IO ()) Source #

type Arg2 (arg -> IO ()) Source #

Methods

runTest :: (arg -> IO ()) -> TestRunSettings -> ((Arg1 (arg -> IO ()) -> Arg2 (arg -> IO ()) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (outerArgs -> innerArg -> Bool) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (outerArgs -> innerArg -> Bool) Source #

type Arg2 (outerArgs -> innerArg -> Bool) Source #

Methods

runTest :: (outerArgs -> innerArg -> Bool) -> TestRunSettings -> ((Arg1 (outerArgs -> innerArg -> Bool) -> Arg2 (outerArgs -> innerArg -> Bool) -> IO ()) -> IO ()) -> IO TestRunResult Source #

IsTest (arg -> Bool) Source # 
Instance details

Defined in Test.Syd.Run

Associated Types

type Arg1 (arg -> Bool) Source #

type Arg2 (arg -> Bool) Source #

Methods

runTest :: (arg -> Bool) -> TestRunSettings -> ((Arg1 (arg -> Bool) -> Arg2 (arg -> Bool) -> IO ()) -> IO ()) -> IO TestRunResult Source #

Test suite types

data TDef value Source #

Constructors

TDef 

Instances

Instances details
Functor TDef Source # 
Instance details

Defined in Test.Syd.SpecDef

Methods

fmap :: (a -> b) -> TDef a -> TDef b #

(<$) :: a -> TDef b -> TDef a #

Foldable TDef Source # 
Instance details

Defined in Test.Syd.SpecDef

Methods

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 #

toList :: TDef a -> [a] #

null :: TDef a -> Bool #

length :: TDef a -> Int #

elem :: Eq a => a -> TDef a -> Bool #

maximum :: Ord a => TDef a -> a #

minimum :: Ord a => TDef a -> a #

sum :: Num a => TDef a -> a #

product :: Num a => TDef a -> a #

Traversable TDef Source # 
Instance details

Defined in Test.Syd.SpecDef

Methods

traverse :: Applicative f => (a -> f b) -> TDef a -> f (TDef b) #

sequenceA :: Applicative f => TDef (f a) -> f (TDef a) #

mapM :: Monad m => (a -> m b) -> TDef a -> m (TDef b) #

sequence :: Monad m => TDef (m a) -> m (TDef a) #

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 of aroundAll.)
  • 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 of around.)
  • 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.

Constructors

DefSpecifyNode

Define a test

Fields

  • :: Text

    The description of the test

  • -> TDef (((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult)

    How the test can be run given a function that provides the resources

  • -> extra
     
  • -> SpecDefTree outers inner extra
     
DefPendingNode

Define a pending test

Fields

DefDescribeNode

Group tests using a description

Fields

DefWrapNode 

Fields

DefBeforeAllNode 

Fields

  • :: IO outer

    The function to run (once), beforehand, to produce the outer resource.

  • -> SpecDefForest (outer ': otherOuters) inner extra
     
  • -> SpecDefTree otherOuters inner extra
     
DefAroundAllNode 

Fields

  • :: ((outer -> IO ()) -> IO ())

    The function that provides the outer resource (once), around the tests.

  • -> SpecDefForest (outer ': otherOuters) inner extra
     
  • -> SpecDefTree otherOuters inner extra
     
DefAroundAllWithNode 

Fields

  • :: ((newOuter -> IO ()) -> oldOuter -> IO ())

    The function that provides the new outer resource (once), using the old outer resource.

  • -> SpecDefForest (newOuter ': (oldOuter ': otherOuters)) inner extra
     
  • -> SpecDefTree (oldOuter ': otherOuters) inner extra
     
DefAfterAllNode 

Fields

  • :: (HList outers -> IO ())

    The function to run (once), afterwards, using all outer resources.

  • -> SpecDefForest outers inner extra
     
  • -> SpecDefTree outers inner extra
     
DefParallelismNode

Control the level of parallelism for a given group of tests

Fields

DefRandomisationNode

Control the execution order randomisation for a given group of tests

Fields

Instances

Instances details
Functor (SpecDefTree a c) Source # 
Instance details

Defined in Test.Syd.SpecDef

Methods

fmap :: (a0 -> b) -> SpecDefTree a c a0 -> SpecDefTree a c b #

(<$) :: a0 -> SpecDefTree a c b -> SpecDefTree a c a0 #

Foldable (SpecDefTree a c) Source # 
Instance details

Defined in Test.Syd.SpecDef

Methods

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 # 
Instance details

Defined in Test.Syd.SpecDef

Methods

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) #

MonadWriter (TestForest outers inner) (TestDefM outers inner) Source # 
Instance details

Defined in Test.Syd.Def.TestDefM

Methods

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 #

Hspec synonyms

type Spec = SpecWith () Source #

A synonym for easy migration from hspec

type SpecWith inner = SpecM inner () Source #

A synonym for easy migration from hspec

type SpecM inner result = TestDefM '[] inner result Source #

A synonym for easy migration from hspec

Utilities

ppShow :: Show a => a -> String #

Convert a generic value into a pretty String, if possible.

Reexports