{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-duplicate-exports #-}
module Test.Syd
  ( 
    sydTest,
    sydTestWith,
    
    
    describe,
    it,
    itWithOuter,
    itWithBoth,
    itWithAll,
    specify,
    specifyWithOuter,
    specifyWithBoth,
    specifyWithAll,
    prop,
    
    xdescribe,
    xit,
    xitWithOuter,
    xitWithBoth,
    xitWithAll,
    xspecify,
    xspecifyWithOuter,
    xspecifyWithBoth,
    xspecifyWithAll,
    
    pending,
    pendingWith,
    
    eit,
    withTestEnv,
    
    pureGoldenTextFile,
    goldenTextFile,
    pureGoldenByteStringFile,
    goldenByteStringFile,
    pureGoldenLazyByteStringFile,
    goldenLazyByteStringFile,
    pureGoldenByteStringBuilderFile,
    goldenByteStringBuilderFile,
    pureGoldenStringFile,
    goldenStringFile,
    goldenShowInstance,
    goldenPrettyShowInstance,
    goldenContext,
    GoldenTest (..),
    
    scenarioDir,
    scenarioDirRecur,
    
    shouldBe,
    shouldNotBe,
    shouldSatisfy,
    shouldSatisfyNamed,
    shouldNotSatisfy,
    shouldNotSatisfyNamed,
    shouldReturn,
    shouldNotReturn,
    shouldStartWith,
    shouldEndWith,
    shouldContain,
    expectationFailure,
    context,
    Expectation,
    shouldThrow,
    Selector,
    anyException,
    anyErrorCall,
    errorCall,
    anyIOException,
    anyArithException,
    
    stringShouldBe,
    textShouldBe,
    
    stringsNotEqualButShouldHaveBeenEqual,
    textsNotEqualButShouldHaveBeenEqual,
    bytestringsNotEqualButShouldHaveBeenEqual,
    Assertion (..),
    
    
    beforeAll,
    beforeAll_,
    beforeAllWith,
    afterAll,
    afterAll',
    afterAll_,
    aroundAll,
    aroundAll_,
    aroundAllWith,
    
    before,
    before_,
    after,
    after_,
    around,
    around_,
    aroundWith,
    
    
    SetupFunc (..),
    
    
    setupAround,
    setupAroundWith,
    setupAroundWith',
    
    setupAroundAll,
    setupAroundAllWith,
    
    modifyMaxSuccess,
    modifyMaxDiscardRatio,
    modifyMaxSize,
    modifyMaxShrinks,
    modifyRunSettings,
    TestRunSettings (..),
    
    sequential,
    parallel,
    withParallelism,
    Parallelism (..),
    
    randomiseExecutionOrder,
    doNotRandomiseExecutionOrder,
    withExecutionOrderRandomisation,
    ExecutionOrderRandomisation (..),
    
    runIO,
    
    TestDefM (..),
    TestDef,
    execTestDefM,
    runTestDefM,
    IsTest (..),
    
    TDef (..),
    TestForest,
    TestTree,
    SpecDefForest,
    SpecDefTree (..),
    ResultForest,
    ResultTree,
    shouldExitFail,
    
    
    
    
    Spec,
    SpecWith,
    SpecM,
    
    ppShow,
    
    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,
  )
where
import Control.Monad
import Control.Monad.IO.Class
import System.Exit
import Test.QuickCheck.IO ()
import Test.Syd.Def
import Test.Syd.Expectation
import Test.Syd.HList
import Test.Syd.Modify
import Test.Syd.OptParse
import Test.Syd.Output
import Test.Syd.Run
import Test.Syd.Runner
import Test.Syd.SpecDef
import Test.Syd.SpecForest
import Text.Show.Pretty (ppShow)
sydTest :: Spec -> IO ()
sydTest :: Spec -> IO ()
sydTest Spec
spec = do
  Settings
sets <- IO Settings
getSettings
  Settings -> Spec -> IO ()
sydTestWith Settings
sets Spec
spec
sydTestWith :: Settings -> Spec -> IO ()
sydTestWith :: Settings -> Spec -> IO ()
sydTestWith Settings
sets Spec
spec = do
  Timed ResultForest
resultForest <- Settings -> Spec -> IO (Timed ResultForest)
forall r. Settings -> TestDefM '[] () r -> IO (Timed ResultForest)
sydTestResult Settings
sets Spec
spec
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ResultForest -> Bool
shouldExitFail (Timed ResultForest -> ResultForest
forall a. Timed a -> a
timedValue Timed ResultForest
resultForest)) (ExitCode -> IO ()
forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
1))
runIO :: IO e -> TestDefM a b e
runIO :: IO e -> TestDefM a b e
runIO = IO e -> TestDefM a b e
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO