{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE IncoherentInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}

-- | This module defines all the functions you will use to define your test suite.
module Test.Syd.Def.Specify
  ( -- * API Functions

    -- ** Declaring tests
    describe,
    it,
    itWithOuter,
    itWithBoth,
    itWithAll,
    specify,
    specifyWithOuter,
    specifyWithBoth,
    specifyWithAll,
    prop,

    -- ** Declaring commented-out tests
    xdescribe,
    xit,
    xitWithOuter,
    xitWithBoth,
    xitWithAll,
    xspecify,
    xspecifyWithOuter,
    xspecifyWithBoth,
    xspecifyWithAll,

    -- ** Pending tests
    pending,
    pendingWith,
  )
where

import Control.Monad.RWS.Strict
import qualified Data.Text as T
import GHC.Stack
import Test.QuickCheck
import Test.QuickCheck.IO ()
import Test.Syd.Def.TestDefM
import Test.Syd.HList
import Test.Syd.Run
import Test.Syd.SpecDef

-- | 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
describe ::
  -- | The test group description
  String ->
  TestDefM outers inner () ->
  TestDefM outers inner ()
describe :: String -> TestDefM outers inner () -> TestDefM outers inner ()
describe String
s TestDefM outers inner ()
func = ([SpecDefTree outers inner ()] -> [SpecDefTree outers inner ()])
-> TestDefM outers inner () -> TestDefM outers inner ()
forall w (m :: * -> *) a. MonadWriter w m => (w -> w) -> m a -> m a
censor ((SpecDefTree outers inner ()
-> [SpecDefTree outers inner ()] -> [SpecDefTree outers inner ()]
forall a. a -> [a] -> [a]
: []) (SpecDefTree outers inner () -> [SpecDefTree outers inner ()])
-> ([SpecDefTree outers inner ()] -> SpecDefTree outers inner ())
-> [SpecDefTree outers inner ()]
-> [SpecDefTree outers inner ()]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text
-> [SpecDefTree outers inner ()] -> SpecDefTree outers inner ()
forall (outers :: [*]) inner extra.
Text
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefDescribeNode (String -> Text
T.pack String
s)) TestDefM outers inner ()
func

-- TODO maybe we want to keep all tests below but replace them with a "Pending" instead.
xdescribe :: String -> TestDefM outers inner () -> TestDefM outers inner ()
xdescribe :: String -> TestDefM outers inner () -> TestDefM outers inner ()
xdescribe String
s TestDefM outers inner ()
_ = String -> TestDefM outers inner ()
forall (outers :: [*]) inner. String -> TestDefM outers inner ()
pending String
s

-- | 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
it ::
  forall outers inner test.
  (HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) =>
  -- | The description of the test
  String ->
  -- | The test itself
  test ->
  TestDefM outers inner ()
it :: String -> test -> TestDefM outers inner ()
it String
s test
t = do
  TestRunSettings
sets <- TestDefM outers inner TestRunSettings
forall r (m :: * -> *). MonadReader r m => m r
ask
  let testDef :: TDef
  (((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult)
testDef =
        TDef :: forall value. value -> CallStack -> TDef value
TDef
          { testDefVal :: ((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult
testDefVal = \(HList outers -> inner -> IO ()) -> IO ()
supplyArgs ->
              test
-> TestRunSettings
-> ((Arg1 test -> Arg2 test -> IO ()) -> IO ())
-> IO TestRunResult
forall e.
IsTest e =>
e
-> TestRunSettings
-> ((Arg1 e -> Arg2 e -> IO ()) -> IO ())
-> IO TestRunResult
runTest
                test
t
                TestRunSettings
sets
                ( \Arg1 test -> Arg2 test -> IO ()
func -> (HList outers -> inner -> IO ()) -> IO ()
supplyArgs (\HList outers
_ inner
arg2 -> Arg1 test -> Arg2 test -> IO ()
func () inner
Arg2 test
arg2)
                ),
            testDefCallStack :: CallStack
testDefCallStack = CallStack
HasCallStack => CallStack
callStack
          }
  [SpecDefTree outers inner ()] -> TestDefM outers inner ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell [Text
-> TDef
     (((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult)
-> ()
-> SpecDefTree outers inner ()
forall (outers :: [*]) inner extra.
Text
-> TDef
     (((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult)
-> extra
-> SpecDefTree outers inner extra
DefSpecifyNode (String -> Text
T.pack String
s) TDef
  (((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult)
testDef ()]

xit ::
  forall outers inner test.
  (HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) =>
  -- | The description of the test
  String ->
  -- | The test itself
  test ->
  TestDefM outers inner ()
xit :: String -> test -> TestDefM outers inner ()
xit String
s test
_ = String -> TestDefM outers inner ()
forall (outers :: [*]) inner. String -> TestDefM outers inner ()
pending String
s

-- | A synonym for 'it'
specify ::
  forall outers inner test.
  (HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) =>
  -- | The description of the test
  String ->
  -- | The test itself
  test ->
  TestDefM outers inner ()
specify :: String -> test -> TestDefM outers inner ()
specify = String -> test -> TestDefM outers inner ()
forall (outers :: [*]) inner test.
(HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) =>
String -> test -> TestDefM outers inner ()
it

-- | A synonym for 'xit'
xspecify ::
  forall outers inner test.
  (HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) =>
  -- | The description of the test
  String ->
  -- | The test itself
  test ->
  TestDefM outers inner ()
xspecify :: String -> test -> TestDefM outers inner ()
xspecify = String -> test -> TestDefM outers inner ()
forall (outers :: [*]) inner test.
(HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) =>
String -> test -> TestDefM outers inner ()
xit

-- | 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
itWithOuter ::
  (HasCallStack, IsTest test, Arg1 test ~ inner, Arg2 test ~ outer) =>
  -- The test description
  String ->
  -- The test itself
  test ->
  TestDefM (outer ': otherOuters) inner ()
itWithOuter :: String -> test -> TestDefM (outer : otherOuters) inner ()
itWithOuter String
s test
t = do
  TestRunSettings
sets <- TestDefM (outer : otherOuters) inner TestRunSettings
forall r (m :: * -> *). MonadReader r m => m r
ask
  let testDef :: TDef
  (((HList (outer : otherOuters) -> inner -> IO ()) -> IO ())
   -> IO TestRunResult)
testDef =
        TDef :: forall value. value -> CallStack -> TDef value
TDef
          { testDefVal :: ((HList (outer : otherOuters) -> inner -> IO ()) -> IO ())
-> IO TestRunResult
testDefVal = \(HList (outer : otherOuters) -> inner -> IO ()) -> IO ()
supplyArgs ->
              test
-> TestRunSettings
-> ((Arg1 test -> Arg2 test -> IO ()) -> IO ())
-> IO TestRunResult
forall e.
IsTest e =>
e
-> TestRunSettings
-> ((Arg1 e -> Arg2 e -> IO ()) -> IO ())
-> IO TestRunResult
runTest
                test
t
                TestRunSettings
sets
                (\Arg1 test -> Arg2 test -> IO ()
func -> (HList (outer : otherOuters) -> inner -> IO ()) -> IO ()
supplyArgs ((HList (outer : otherOuters) -> inner -> IO ()) -> IO ())
-> (HList (outer : otherOuters) -> inner -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(HCons e
outerArgs HList l
_) inner
innerArg -> Arg1 test -> Arg2 test -> IO ()
func inner
Arg1 test
innerArg e
Arg2 test
outerArgs),
            testDefCallStack :: CallStack
testDefCallStack = CallStack
HasCallStack => CallStack
callStack
          }
  [SpecDefTree (outer : otherOuters) inner ()]
-> TestDefM (outer : otherOuters) inner ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell [Text
-> TDef
     (((HList (outer : otherOuters) -> inner -> IO ()) -> IO ())
      -> IO TestRunResult)
-> ()
-> SpecDefTree (outer : otherOuters) inner ()
forall (outers :: [*]) inner extra.
Text
-> TDef
     (((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult)
-> extra
-> SpecDefTree outers inner extra
DefSpecifyNode (String -> Text
T.pack String
s) TDef
  (((HList (outer : otherOuters) -> inner -> IO ()) -> IO ())
   -> IO TestRunResult)
testDef ()]

xitWithOuter ::
  (HasCallStack, IsTest test, Arg1 test ~ inner, Arg2 test ~ outer) =>
  -- The test description
  String ->
  -- The test itself
  test ->
  TestDefM (outer ': otherOuters) inner ()
xitWithOuter :: String -> test -> TestDefM (outer : otherOuters) inner ()
xitWithOuter String
s test
_ = String -> TestDefM (outer : otherOuters) inner ()
forall (outers :: [*]) inner. String -> TestDefM outers inner ()
pending String
s

-- | A synonym for 'itWithOuter'
specifyWithOuter ::
  (HasCallStack, IsTest test, Arg1 test ~ inner, Arg2 test ~ outer) =>
  -- The test description
  String ->
  -- The test itself
  test ->
  TestDefM (outer ': otherOuters) inner ()
specifyWithOuter :: String -> test -> TestDefM (outer : otherOuters) inner ()
specifyWithOuter = String -> test -> TestDefM (outer : otherOuters) inner ()
forall test inner outer (otherOuters :: [*]).
(HasCallStack, IsTest test, Arg1 test ~ inner,
 Arg2 test ~ outer) =>
String -> test -> TestDefM (outer : otherOuters) inner ()
itWithOuter

-- | A synonym for 'xitWithOuter'
xspecifyWithOuter ::
  (HasCallStack, IsTest test, Arg1 test ~ inner, Arg2 test ~ outer) =>
  -- The test description
  String ->
  -- The test itself
  test ->
  TestDefM (outer ': otherOuters) inner ()
xspecifyWithOuter :: String -> test -> TestDefM (outer : otherOuters) inner ()
xspecifyWithOuter = String -> test -> TestDefM (outer : otherOuters) inner ()
forall test inner outer (otherOuters :: [*]).
(HasCallStack, IsTest test, Arg1 test ~ inner,
 Arg2 test ~ outer) =>
String -> test -> TestDefM (outer : otherOuters) inner ()
xitWithOuter

-- | 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
itWithBoth ::
  ( HasCallStack,
    IsTest test,
    Arg1 test ~ outer,
    Arg2 test ~ inner
  ) =>
  String ->
  test ->
  TestDefM (outer ': otherOuters) inner ()
itWithBoth :: String -> test -> TestDefM (outer : otherOuters) inner ()
itWithBoth String
s test
t = do
  TestRunSettings
sets <- TestDefM (outer : otherOuters) inner TestRunSettings
forall r (m :: * -> *). MonadReader r m => m r
ask
  let testDef :: TDef
  (((HList (outer : otherOuters) -> inner -> IO ()) -> IO ())
   -> IO TestRunResult)
testDef =
        TDef :: forall value. value -> CallStack -> TDef value
TDef
          { testDefVal :: ((HList (outer : otherOuters) -> inner -> IO ()) -> IO ())
-> IO TestRunResult
testDefVal = \(HList (outer : otherOuters) -> inner -> IO ()) -> IO ()
supplyArgs ->
              test
-> TestRunSettings
-> ((Arg1 test -> Arg2 test -> IO ()) -> IO ())
-> IO TestRunResult
forall e.
IsTest e =>
e
-> TestRunSettings
-> ((Arg1 e -> Arg2 e -> IO ()) -> IO ())
-> IO TestRunResult
runTest
                test
t
                TestRunSettings
sets
                (\Arg1 test -> Arg2 test -> IO ()
func -> (HList (outer : otherOuters) -> inner -> IO ()) -> IO ()
supplyArgs ((HList (outer : otherOuters) -> inner -> IO ()) -> IO ())
-> (HList (outer : otherOuters) -> inner -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(HCons e
outerArgs HList l
_) inner
innerArg -> Arg1 test -> Arg2 test -> IO ()
func e
Arg1 test
outerArgs inner
Arg2 test
innerArg),
            testDefCallStack :: CallStack
testDefCallStack = CallStack
HasCallStack => CallStack
callStack
          }
  [SpecDefTree (outer : otherOuters) inner ()]
-> TestDefM (outer : otherOuters) inner ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell [Text
-> TDef
     (((HList (outer : otherOuters) -> inner -> IO ()) -> IO ())
      -> IO TestRunResult)
-> ()
-> SpecDefTree (outer : otherOuters) inner ()
forall (outers :: [*]) inner extra.
Text
-> TDef
     (((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult)
-> extra
-> SpecDefTree outers inner extra
DefSpecifyNode (String -> Text
T.pack String
s) TDef
  (((HList (outer : otherOuters) -> inner -> IO ()) -> IO ())
   -> IO TestRunResult)
testDef ()]

xitWithBoth ::
  ( HasCallStack,
    IsTest test,
    Arg1 test ~ outer,
    Arg2 test ~ inner
  ) =>
  String ->
  test ->
  TestDefM (outer ': otherOuters) inner ()
xitWithBoth :: String -> test -> TestDefM (outer : otherOuters) inner ()
xitWithBoth String
s test
_ = String -> TestDefM (outer : otherOuters) inner ()
forall (outers :: [*]) inner. String -> TestDefM outers inner ()
pending String
s

-- | A synonym for 'itWithBoth'
specifyWithBoth ::
  ( HasCallStack,
    IsTest test,
    Arg1 test ~ outer,
    Arg2 test ~ inner
  ) =>
  String ->
  test ->
  TestDefM (outer ': otherOuters) inner ()
specifyWithBoth :: String -> test -> TestDefM (outer : otherOuters) inner ()
specifyWithBoth = String -> test -> TestDefM (outer : otherOuters) inner ()
forall test outer inner (otherOuters :: [*]).
(HasCallStack, IsTest test, Arg1 test ~ outer,
 Arg2 test ~ inner) =>
String -> test -> TestDefM (outer : otherOuters) inner ()
itWithBoth

-- | A synonym for 'xitWithBoth'
xspecifyWithBoth ::
  ( HasCallStack,
    IsTest test,
    Arg1 test ~ outer,
    Arg2 test ~ inner
  ) =>
  String ->
  test ->
  TestDefM (outer ': otherOuters) inner ()
xspecifyWithBoth :: String -> test -> TestDefM (outer : otherOuters) inner ()
xspecifyWithBoth = String -> test -> TestDefM (outer : otherOuters) inner ()
forall test outer inner (otherOuters :: [*]).
(HasCallStack, IsTest test, Arg1 test ~ outer,
 Arg2 test ~ inner) =>
String -> test -> TestDefM (outer : otherOuters) inner ()
xitWithBoth

-- | 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)
itWithAll ::
  ( HasCallStack,
    IsTest test,
    Arg1 test ~ HList outers,
    Arg2 test ~ inner
  ) =>
  String ->
  test ->
  TestDefM outers inner ()
itWithAll :: String -> test -> TestDefM outers inner ()
itWithAll String
s test
t = do
  TestRunSettings
sets <- TestDefM outers inner TestRunSettings
forall r (m :: * -> *). MonadReader r m => m r
ask
  let testDef :: TDef
  (((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult)
testDef =
        TDef :: forall value. value -> CallStack -> TDef value
TDef
          { testDefVal :: ((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult
testDefVal = \(HList outers -> inner -> IO ()) -> IO ()
supplyArgs ->
              test
-> TestRunSettings
-> ((Arg1 test -> Arg2 test -> IO ()) -> IO ())
-> IO TestRunResult
forall e.
IsTest e =>
e
-> TestRunSettings
-> ((Arg1 e -> Arg2 e -> IO ()) -> IO ())
-> IO TestRunResult
runTest
                test
t
                TestRunSettings
sets
                (\Arg1 test -> Arg2 test -> IO ()
func -> (HList outers -> inner -> IO ()) -> IO ()
supplyArgs HList outers -> inner -> IO ()
Arg1 test -> Arg2 test -> IO ()
func),
            testDefCallStack :: CallStack
testDefCallStack = CallStack
HasCallStack => CallStack
callStack
          }
  [SpecDefTree outers inner ()] -> TestDefM outers inner ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell [Text
-> TDef
     (((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult)
-> ()
-> SpecDefTree outers inner ()
forall (outers :: [*]) inner extra.
Text
-> TDef
     (((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult)
-> extra
-> SpecDefTree outers inner extra
DefSpecifyNode (String -> Text
T.pack String
s) TDef
  (((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult)
testDef ()]

xitWithAll ::
  ( HasCallStack,
    IsTest test,
    Arg1 test ~ HList outers,
    Arg2 test ~ inner
  ) =>
  String ->
  test ->
  TestDefM outers inner ()
xitWithAll :: String -> test -> TestDefM outers inner ()
xitWithAll String
s test
_ = String -> TestDefM outers inner ()
forall (outers :: [*]) inner. String -> TestDefM outers inner ()
pending String
s

-- | A synonym for 'itWithAll'
specifyWithAll ::
  ( HasCallStack,
    IsTest test,
    Arg1 test ~ HList outers,
    Arg2 test ~ inner
  ) =>
  String ->
  test ->
  TestDefM outers inner ()
specifyWithAll :: String -> test -> TestDefM outers inner ()
specifyWithAll = String -> test -> TestDefM outers inner ()
forall test (outers :: [*]) inner.
(HasCallStack, IsTest test, Arg1 test ~ HList outers,
 Arg2 test ~ inner) =>
String -> test -> TestDefM outers inner ()
itWithAll

-- | A synonym for 'xitWithAll'
xspecifyWithAll ::
  ( HasCallStack,
    IsTest test,
    Arg1 test ~ HList outers,
    Arg2 test ~ inner
  ) =>
  String ->
  test ->
  TestDefM outers inner ()
xspecifyWithAll :: String -> test -> TestDefM outers inner ()
xspecifyWithAll = String -> test -> TestDefM outers inner ()
forall test (outers :: [*]) inner.
(HasCallStack, IsTest test, Arg1 test ~ HList outers,
 Arg2 test ~ inner) =>
String -> test -> TestDefM outers inner ()
xitWithAll

-- | Convenience function for backwards compatibility with @hspec@
--
-- > prop s p = it s $ property p
prop :: Testable prop => String -> prop -> Spec
prop :: String -> prop -> Spec
prop String
s prop
p = String -> Property -> Spec
forall (outers :: [*]) inner test.
(HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) =>
String -> test -> TestDefM outers inner ()
it String
s (Property -> Spec) -> Property -> Spec
forall a b. (a -> b) -> a -> b
$ prop -> Property
forall prop. Testable prop => prop -> Property
property prop
p

-- | Declare a test that has not been written yet.
pending :: String -> TestDefM outers inner ()
pending :: String -> TestDefM outers inner ()
pending String
s = [SpecDefTree outers inner ()] -> TestDefM outers inner ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell [Text -> Maybe Text -> SpecDefTree outers inner ()
forall (outers :: [*]) inner extra.
Text -> Maybe Text -> SpecDefTree outers inner extra
DefPendingNode (String -> Text
T.pack String
s) Maybe Text
forall a. Maybe a
Nothing]

-- | Declare a test that has not been written yet for the given reason.
pendingWith :: String -> String -> TestDefM outers inner ()
pendingWith :: String -> String -> TestDefM outers inner ()
pendingWith String
description String
reasonWhyItsPending = [SpecDefTree outers inner ()] -> TestDefM outers inner ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell [Text -> Maybe Text -> SpecDefTree outers inner ()
forall (outers :: [*]) inner extra.
Text -> Maybe Text -> SpecDefTree outers inner extra
DefPendingNode (String -> Text
T.pack String
description) (Text -> Maybe Text
forall a. a -> Maybe a
Just (String -> Text
T.pack String
reasonWhyItsPending))]