{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
module Test.Hspec.Core.Runner (
hspec
, evalSpec
, runSpecForest
, evaluateResult
, Config (..)
, ColorMode (..)
, UnicodeMode(..)
, Path
, defaultConfig
, configAddFilter
, readConfig
, Test.Hspec.Core.Runner.Result.SpecResult
, Test.Hspec.Core.Runner.Result.specResultItems
, Test.Hspec.Core.Runner.Result.specResultSuccess
, Test.Hspec.Core.Runner.Result.ResultItem
, Test.Hspec.Core.Runner.Result.resultItemPath
, Test.Hspec.Core.Runner.Result.resultItemStatus
, Test.Hspec.Core.Runner.Result.resultItemIsFailure
, Test.Hspec.Core.Runner.Result.ResultItemStatus(..)
, hspecWith
, hspecResult
, hspecWithResult
, runSpec
, Summary (..)
, toSummary
, isSuccess
, evaluateSummary
#ifdef TEST
, rerunAll
, specToEvalForest
, colorOutputSupported
, unicodeOutputSupported
#endif
) where
import Prelude ()
import Test.Hspec.Core.Compat
import Data.Maybe
import NonEmpty (nonEmpty)
import System.IO
import System.Environment (getArgs, withArgs)
import System.Exit
import Control.Arrow
import qualified Control.Exception as E
import System.Random
import Control.Monad.ST
import Data.STRef
import System.Console.ANSI (hSupportsANSI)
import System.Console.ANSI (hHideCursor, hShowCursor)
import qualified Test.QuickCheck as QC
import Test.Hspec.Core.Util (Path)
import Test.Hspec.Core.Spec hiding (pruneTree, pruneForest)
import Test.Hspec.Core.Config
import Test.Hspec.Core.Format (FormatConfig(..))
import qualified Test.Hspec.Core.Formatters.V1 as V1
import qualified Test.Hspec.Core.Formatters.V2 as V2
import Test.Hspec.Core.FailureReport
import Test.Hspec.Core.QuickCheckUtil
import Test.Hspec.Core.Shuffle
import Test.Hspec.Core.Runner.PrintSlowSpecItems
import Test.Hspec.Core.Runner.Eval hiding (Tree(..))
import qualified Test.Hspec.Core.Runner.Eval as Eval
import Test.Hspec.Core.Runner.Result
applyFilterPredicates :: Config -> [Tree c EvalItem] -> [Tree c EvalItem]
applyFilterPredicates :: Config -> [Tree c EvalItem] -> [Tree c EvalItem]
applyFilterPredicates Config
c = ([String] -> EvalItem -> Bool)
-> [Tree c EvalItem] -> [Tree c EvalItem]
forall a c. ([String] -> a -> Bool) -> [Tree c a] -> [Tree c a]
filterForestWithLabels [String] -> EvalItem -> Bool
p
where
include :: Path -> Bool
include :: Path -> Bool
include = (Path -> Bool) -> Maybe (Path -> Bool) -> Path -> Bool
forall a. a -> Maybe a -> a
fromMaybe (Bool -> Path -> Bool
forall a b. a -> b -> a
const Bool
True) (Config -> Maybe (Path -> Bool)
configFilterPredicate Config
c)
skip :: Path -> Bool
skip :: Path -> Bool
skip = (Path -> Bool) -> Maybe (Path -> Bool) -> Path -> Bool
forall a. a -> Maybe a -> a
fromMaybe (Bool -> Path -> Bool
forall a b. a -> b -> a
const Bool
False) (Config -> Maybe (Path -> Bool)
configSkipPredicate Config
c)
p :: [String] -> EvalItem -> Bool
p :: [String] -> EvalItem -> Bool
p [String]
groups EvalItem
item = Path -> Bool
include Path
path Bool -> Bool -> Bool
&& Bool -> Bool
not (Path -> Bool
skip Path
path)
where
path :: Path
path = ([String]
groups, EvalItem -> String
evalItemDescription EvalItem
item)
applyDryRun :: Config -> [EvalItemTree] -> [EvalItemTree]
applyDryRun :: Config -> [EvalItemTree] -> [EvalItemTree]
applyDryRun Config
c
| Config -> Bool
configDryRun Config
c = (IO () -> IO ())
-> (EvalItem -> EvalItem) -> [EvalItemTree] -> [EvalItemTree]
forall a b c d. (a -> b) -> (c -> d) -> [Tree a c] -> [Tree b d]
bimapForest IO () -> IO ()
removeCleanup EvalItem -> EvalItem
markSuccess
| Bool
otherwise = [EvalItemTree] -> [EvalItemTree]
forall a. a -> a
id
where
removeCleanup :: IO () -> IO ()
removeCleanup :: IO () -> IO ()
removeCleanup IO ()
_ = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
markSuccess :: EvalItem -> EvalItem
markSuccess :: EvalItem -> EvalItem
markSuccess EvalItem
item = EvalItem
item {evalItemAction :: ProgressCallback -> IO Result
evalItemAction = \ ProgressCallback
_ -> Result -> IO Result
forall (m :: * -> *) a. Monad m => a -> m a
return (Result -> IO Result) -> Result -> IO Result
forall a b. (a -> b) -> a -> b
$ String -> ResultStatus -> Result
Result String
"" ResultStatus
Success}
hspec :: Spec -> IO ()
hspec :: Spec -> IO ()
hspec = Config -> Spec -> IO (Config, [SpecTree ()])
forall a. Config -> SpecWith a -> IO (Config, [SpecTree a])
evalSpec Config
defaultConfig (Spec -> IO (Config, [SpecTree ()]))
-> ((Config, [SpecTree ()]) -> IO ()) -> Spec -> IO ()
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> \ (Config
config, [SpecTree ()]
spec) ->
IO [String]
getArgs
IO [String] -> ([String] -> IO Config) -> IO Config
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Config -> [String] -> IO Config
readConfig Config
config
IO Config -> (Config -> IO SpecResult) -> IO SpecResult
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO SpecResult -> IO SpecResult
forall a. IO a -> IO a
doNotLeakCommandLineArgumentsToExamples (IO SpecResult -> IO SpecResult)
-> (Config -> IO SpecResult) -> Config -> IO SpecResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [SpecTree ()] -> Config -> IO SpecResult
runSpecForest [SpecTree ()]
spec
IO SpecResult -> (SpecResult -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= SpecResult -> IO ()
evaluateResult
evalSpec :: Config -> SpecWith a -> IO (Config, [SpecTree a])
evalSpec :: Config -> SpecWith a -> IO (Config, [SpecTree a])
evalSpec Config
config SpecWith a
spec = do
(Endo Config -> Config
f, [SpecTree a]
forest) <- SpecWith a -> IO (Endo Config, [SpecTree a])
forall a. SpecWith a -> IO (Endo Config, [SpecTree a])
runSpecM SpecWith a
spec
(Config, [SpecTree a]) -> IO (Config, [SpecTree a])
forall (m :: * -> *) a. Monad m => a -> m a
return (Config -> Config
f Config
config, [SpecTree a]
forest)
ensureSeed :: Config -> IO Config
ensureSeed :: Config -> IO Config
ensureSeed Config
c = case Config -> Maybe Integer
configQuickCheckSeed Config
c of
Maybe Integer
Nothing -> do
Int
seed <- IO Int
newSeed
Config -> IO Config
forall (m :: * -> *) a. Monad m => a -> m a
return Config
c {configQuickCheckSeed :: Maybe Integer
configQuickCheckSeed = Integer -> Maybe Integer
forall a. a -> Maybe a
Just (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
seed)}
Maybe Integer
_ -> Config -> IO Config
forall (m :: * -> *) a. Monad m => a -> m a
return Config
c
hspecWith :: Config -> Spec -> IO ()
hspecWith :: Config -> Spec -> IO ()
hspecWith Config
defaults = Config -> Spec -> IO Summary
hspecWithResult Config
defaults (Spec -> IO Summary) -> (Summary -> IO ()) -> Spec -> IO ()
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Summary -> IO ()
evaluateSummary
isSuccess :: Summary -> Bool
isSuccess :: Summary -> Bool
isSuccess Summary
summary = Summary -> Int
summaryFailures Summary
summary Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
evaluateSummary :: Summary -> IO ()
evaluateSummary :: Summary -> IO ()
evaluateSummary Summary
summary = Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Summary -> Bool
isSuccess Summary
summary) IO ()
forall a. IO a
exitFailure
evaluateResult :: SpecResult -> IO ()
evaluateResult :: SpecResult -> IO ()
evaluateResult SpecResult
result = Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (SpecResult -> Bool
specResultSuccess SpecResult
result) IO ()
forall a. IO a
exitFailure
hspecResult :: Spec -> IO Summary
hspecResult :: Spec -> IO Summary
hspecResult = Config -> Spec -> IO Summary
hspecWithResult Config
defaultConfig
hspecWithResult :: Config -> Spec -> IO Summary
hspecWithResult :: Config -> Spec -> IO Summary
hspecWithResult Config
defaults = Config -> Spec -> IO (Config, [SpecTree ()])
forall a. Config -> SpecWith a -> IO (Config, [SpecTree a])
evalSpec Config
defaults (Spec -> IO (Config, [SpecTree ()]))
-> ((Config, [SpecTree ()]) -> IO Summary) -> Spec -> IO Summary
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> \ (Config
config, [SpecTree ()]
spec) ->
IO [String]
getArgs
IO [String] -> ([String] -> IO Config) -> IO Config
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Config -> [String] -> IO Config
readConfig Config
config
IO Config -> (Config -> IO Summary) -> IO Summary
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= IO Summary -> IO Summary
forall a. IO a -> IO a
doNotLeakCommandLineArgumentsToExamples (IO Summary -> IO Summary)
-> (Config -> IO Summary) -> Config -> IO Summary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SpecResult -> Summary) -> IO SpecResult -> IO Summary
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SpecResult -> Summary
toSummary (IO SpecResult -> IO Summary)
-> (Config -> IO SpecResult) -> Config -> IO Summary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [SpecTree ()] -> Config -> IO SpecResult
runSpecForest [SpecTree ()]
spec
runSpec :: Spec -> Config -> IO Summary
runSpec :: Spec -> Config -> IO Summary
runSpec Spec
spec Config
config = Config -> Spec -> IO (Config, [SpecTree ()])
forall a. Config -> SpecWith a -> IO (Config, [SpecTree a])
evalSpec Config
defaultConfig Spec
spec IO (Config, [SpecTree ()])
-> ((Config, [SpecTree ()]) -> IO Summary) -> IO Summary
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (SpecResult -> Summary) -> IO SpecResult -> IO Summary
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SpecResult -> Summary
toSummary (IO SpecResult -> IO Summary)
-> ((Config, [SpecTree ()]) -> IO SpecResult)
-> (Config, [SpecTree ()])
-> IO Summary
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([SpecTree ()] -> Config -> IO SpecResult)
-> Config -> [SpecTree ()] -> IO SpecResult
forall a b c. (a -> b -> c) -> b -> a -> c
flip [SpecTree ()] -> Config -> IO SpecResult
runSpecForest Config
config ([SpecTree ()] -> IO SpecResult)
-> ((Config, [SpecTree ()]) -> [SpecTree ()])
-> (Config, [SpecTree ()])
-> IO SpecResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Config, [SpecTree ()]) -> [SpecTree ()]
forall a b. (a, b) -> b
snd
runSpecForest :: [SpecTree ()] -> Config -> IO SpecResult
runSpecForest :: [SpecTree ()] -> Config -> IO SpecResult
runSpecForest [SpecTree ()]
spec Config
c_ = do
Maybe FailureReport
oldFailureReport <- Config -> IO (Maybe FailureReport)
readFailureReportOnRerun Config
c_
Config
c <- Config -> IO Config
ensureSeed (Maybe FailureReport -> Config -> Config
applyFailureReport Maybe FailureReport
oldFailureReport Config
c_)
if Config -> Bool
configRerunAllOnSuccess Config
c
then Config -> Maybe FailureReport -> IO SpecResult
rerunAllMode Config
c Maybe FailureReport
oldFailureReport
else Config -> IO SpecResult
normalMode Config
c
where
normalMode :: Config -> IO SpecResult
normalMode Config
c = Config -> [SpecTree ()] -> IO SpecResult
runSpecForest_ Config
c [SpecTree ()]
spec
rerunAllMode :: Config -> Maybe FailureReport -> IO SpecResult
rerunAllMode Config
c Maybe FailureReport
oldFailureReport = do
SpecResult
result <- Config -> [SpecTree ()] -> IO SpecResult
runSpecForest_ Config
c [SpecTree ()]
spec
if Config -> Maybe FailureReport -> SpecResult -> Bool
rerunAll Config
c Maybe FailureReport
oldFailureReport SpecResult
result
then [SpecTree ()] -> Config -> IO SpecResult
runSpecForest [SpecTree ()]
spec Config
c_
else SpecResult -> IO SpecResult
forall (m :: * -> *) a. Monad m => a -> m a
return SpecResult
result
runSpecForest_ :: Config -> [SpecTree ()] -> IO SpecResult
runSpecForest_ :: Config -> [SpecTree ()] -> IO SpecResult
runSpecForest_ Config
config [SpecTree ()]
spec = Config -> [EvalTree] -> IO SpecResult
runEvalTree Config
config (Config -> [SpecTree ()] -> [EvalTree]
specToEvalForest Config
config [SpecTree ()]
spec)
failFocused :: Item a -> Item a
failFocused :: Item a -> Item a
failFocused Item a
item = Item a
item {itemExample :: Params -> (ActionWith a -> IO ()) -> ProgressCallback -> IO Result
itemExample = Params -> (ActionWith a -> IO ()) -> ProgressCallback -> IO Result
example}
where
failure :: ResultStatus
failure = Maybe Location -> FailureReason -> ResultStatus
Failure Maybe Location
forall a. Maybe a
Nothing (String -> FailureReason
Reason String
"item is focused; failing due to --fail-on-focused")
example :: Params -> (ActionWith a -> IO ()) -> ProgressCallback -> IO Result
example
| Item a -> Bool
forall a. Item a -> Bool
itemIsFocused Item a
item = \ Params
params ActionWith a -> IO ()
hook ProgressCallback
p -> do
Result String
info ResultStatus
status <- Item a
-> Params
-> (ActionWith a -> IO ())
-> ProgressCallback
-> IO Result
forall a.
Item a
-> Params
-> (ActionWith a -> IO ())
-> ProgressCallback
-> IO Result
itemExample Item a
item Params
params ActionWith a -> IO ()
hook ProgressCallback
p
Result -> IO Result
forall (m :: * -> *) a. Monad m => a -> m a
return (Result -> IO Result) -> Result -> IO Result
forall a b. (a -> b) -> a -> b
$ String -> ResultStatus -> Result
Result String
info (ResultStatus -> Result) -> ResultStatus -> Result
forall a b. (a -> b) -> a -> b
$ case ResultStatus
status of
ResultStatus
Success -> ResultStatus
failure
Pending Maybe Location
_ Maybe String
_ -> ResultStatus
failure
Failure{} -> ResultStatus
status
| Bool
otherwise = Item a
-> Params
-> (ActionWith a -> IO ())
-> ProgressCallback
-> IO Result
forall a.
Item a
-> Params
-> (ActionWith a -> IO ())
-> ProgressCallback
-> IO Result
itemExample Item a
item
failFocusedItems :: Config -> [SpecTree a] -> [SpecTree a]
failFocusedItems :: Config -> [SpecTree a] -> [SpecTree a]
failFocusedItems Config
config [SpecTree a]
spec
| Config -> Bool
configFailOnFocused Config
config = (SpecTree a -> SpecTree a) -> [SpecTree a] -> [SpecTree a]
forall a b. (a -> b) -> [a] -> [b]
map ((Item a -> Item a) -> SpecTree a -> SpecTree a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Item a -> Item a
forall a. Item a -> Item a
failFocused) [SpecTree a]
spec
| Bool
otherwise = [SpecTree a]
spec
focusSpec :: Config -> [SpecTree a] -> [SpecTree a]
focusSpec :: Config -> [SpecTree a] -> [SpecTree a]
focusSpec Config
config [SpecTree a]
spec
| Config -> Bool
configFocusedOnly Config
config = [SpecTree a]
spec
| Bool
otherwise = [SpecTree a] -> [SpecTree a]
forall a. [SpecTree a] -> [SpecTree a]
focusForest [SpecTree a]
spec
runEvalTree :: Config -> [EvalTree] -> IO SpecResult
runEvalTree :: Config -> [EvalTree] -> IO SpecResult
runEvalTree Config
config [EvalTree]
spec = do
let
seed :: Integer
seed = (Maybe Integer -> Integer
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Integer -> Integer)
-> (Config -> Maybe Integer) -> Config -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> Maybe Integer
configQuickCheckSeed) Config
config
qcArgs :: Args
qcArgs = Config -> Args
configQuickCheckArgs Config
config
!numberOfItems :: Int
numberOfItems = [EvalTree] -> Int
forall c a. [Tree c a] -> Int
countSpecItems [EvalTree]
spec
Int
concurrentJobs <- case Config -> Maybe Int
configConcurrentJobs Config
config of
Maybe Int
Nothing -> IO Int
getDefaultConcurrentJobs
Just Int
n -> Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
n
(Bool
reportProgress, Bool
useColor) <- ColorMode -> IO Bool -> IO (Bool, Bool)
colorOutputSupported (Config -> ColorMode
configColorMode Config
config) (Handle -> IO Bool
hSupportsANSI Handle
stdout)
Bool
outputUnicode <- UnicodeMode -> Handle -> IO Bool
unicodeOutputSupported (Config -> UnicodeMode
configUnicodeMode Config
config) Handle
stdout
SpecResult
results <- ([(Path, Item)] -> SpecResult)
-> IO [(Path, Item)] -> IO SpecResult
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [(Path, Item)] -> SpecResult
toSpecResult (IO [(Path, Item)] -> IO SpecResult)
-> (IO [(Path, Item)] -> IO [(Path, Item)])
-> IO [(Path, Item)]
-> IO SpecResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Handle -> IO [(Path, Item)] -> IO [(Path, Item)]
forall a. Bool -> Handle -> IO a -> IO a
withHiddenCursor Bool
reportProgress Handle
stdout (IO [(Path, Item)] -> IO SpecResult)
-> IO [(Path, Item)] -> IO SpecResult
forall a b. (a -> b) -> a -> b
$ do
let
formatConfig :: FormatConfig
formatConfig = FormatConfig :: Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Maybe (String -> String -> (String, String))
-> Bool
-> Bool
-> Bool
-> Integer
-> Int
-> FormatConfig
FormatConfig {
formatConfigUseColor :: Bool
formatConfigUseColor = Bool
useColor
, formatConfigReportProgress :: Bool
formatConfigReportProgress = Bool
reportProgress
, formatConfigOutputUnicode :: Bool
formatConfigOutputUnicode = Bool
outputUnicode
, formatConfigUseDiff :: Bool
formatConfigUseDiff = Config -> Bool
configDiff Config
config
, formatConfigPrettyPrint :: Bool
formatConfigPrettyPrint = Config -> Bool
configPrettyPrint Config
config
, formatConfigPrettyPrintFunction :: Maybe (String -> String -> (String, String))
formatConfigPrettyPrintFunction = if Config -> Bool
configPrettyPrint Config
config then (String -> String -> (String, String))
-> Maybe (String -> String -> (String, String))
forall a. a -> Maybe a
Just (Config -> Bool -> String -> String -> (String, String)
configPrettyPrintFunction Config
config Bool
outputUnicode) else Maybe (String -> String -> (String, String))
forall a. Maybe a
Nothing
, formatConfigPrintTimes :: Bool
formatConfigPrintTimes = Config -> Bool
configTimes Config
config
, formatConfigHtmlOutput :: Bool
formatConfigHtmlOutput = Config -> Bool
configHtmlOutput Config
config
, formatConfigPrintCpuTime :: Bool
formatConfigPrintCpuTime = Config -> Bool
configPrintCpuTime Config
config
, formatConfigUsedSeed :: Integer
formatConfigUsedSeed = Integer
seed
, formatConfigExpectedTotalCount :: Int
formatConfigExpectedTotalCount = Int
numberOfItems
}
formatter :: FormatConfig -> IO Format
formatter = (FormatConfig -> IO Format)
-> Maybe (FormatConfig -> IO Format) -> FormatConfig -> IO Format
forall a. a -> Maybe a -> a
fromMaybe (Formatter -> FormatConfig -> IO Format
V2.formatterToFormat Formatter
V2.checks) (Config -> Maybe (FormatConfig -> IO Format)
configFormat Config
config Maybe (FormatConfig -> IO Format)
-> Maybe (FormatConfig -> IO Format)
-> Maybe (FormatConfig -> IO Format)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Formatter -> FormatConfig -> IO Format
V1.formatterToFormat (Formatter -> FormatConfig -> IO Format)
-> Maybe Formatter -> Maybe (FormatConfig -> IO Format)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Config -> Maybe Formatter
configFormatter Config
config)
Format
format <- (Format -> Format)
-> (Int -> Format -> Format) -> Maybe Int -> Format -> Format
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Format -> Format
forall a. a -> a
id Int -> Format -> Format
printSlowSpecItems (Config -> Maybe Int
configPrintSlowItems Config
config) (Format -> Format) -> IO Format -> IO Format
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FormatConfig -> IO Format
formatter FormatConfig
formatConfig
let
evalConfig :: EvalConfig
evalConfig = EvalConfig :: Format -> Int -> Bool -> EvalConfig
EvalConfig {
evalConfigFormat :: Format
evalConfigFormat = Format
format
, evalConfigConcurrentJobs :: Int
evalConfigConcurrentJobs = Int
concurrentJobs
, evalConfigFailFast :: Bool
evalConfigFailFast = Config -> Bool
configFailFast Config
config
}
EvalConfig -> [EvalTree] -> IO [(Path, Item)]
runFormatter EvalConfig
evalConfig [EvalTree]
spec
let
failures :: [Path]
failures :: [Path]
failures = (ResultItem -> Path) -> [ResultItem] -> [Path]
forall a b. (a -> b) -> [a] -> [b]
map ResultItem -> Path
resultItemPath ([ResultItem] -> [Path]) -> [ResultItem] -> [Path]
forall a b. (a -> b) -> a -> b
$ (ResultItem -> Bool) -> [ResultItem] -> [ResultItem]
forall a. (a -> Bool) -> [a] -> [a]
filter ResultItem -> Bool
resultItemIsFailure ([ResultItem] -> [ResultItem]) -> [ResultItem] -> [ResultItem]
forall a b. (a -> b) -> a -> b
$ SpecResult -> [ResultItem]
specResultItems SpecResult
results
Config -> Integer -> Args -> [Path] -> IO ()
dumpFailureReport Config
config Integer
seed Args
qcArgs [Path]
failures
SpecResult -> IO SpecResult
forall (m :: * -> *) a. Monad m => a -> m a
return SpecResult
results
toSummary :: SpecResult -> Summary
toSummary :: SpecResult -> Summary
toSummary SpecResult
result = Summary :: Int -> Int -> Summary
Summary {
summaryExamples :: Int
summaryExamples = [ResultItem] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ResultItem]
items
, summaryFailures :: Int
summaryFailures = [ResultItem] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ResultItem]
failures
} where
items :: [ResultItem]
items = SpecResult -> [ResultItem]
specResultItems SpecResult
result
failures :: [ResultItem]
failures = (ResultItem -> Bool) -> [ResultItem] -> [ResultItem]
forall a. (a -> Bool) -> [a] -> [a]
filter ResultItem -> Bool
resultItemIsFailure [ResultItem]
items
specToEvalForest :: Config -> [SpecTree ()] -> [EvalTree]
specToEvalForest :: Config -> [SpecTree ()] -> [EvalTree]
specToEvalForest Config
config =
Config -> [SpecTree ()] -> [SpecTree ()]
forall a. Config -> [SpecTree a] -> [SpecTree a]
failFocusedItems Config
config
([SpecTree ()] -> [SpecTree ()])
-> ([SpecTree ()] -> [EvalTree]) -> [SpecTree ()] -> [EvalTree]
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> Config -> [SpecTree ()] -> [SpecTree ()]
forall a. Config -> [SpecTree a] -> [SpecTree a]
focusSpec Config
config
([SpecTree ()] -> [SpecTree ()])
-> ([SpecTree ()] -> [EvalTree]) -> [SpecTree ()] -> [EvalTree]
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> Params -> [SpecTree ()] -> [EvalItemTree]
toEvalItemForest Params
params
([SpecTree ()] -> [EvalItemTree])
-> ([EvalItemTree] -> [EvalTree]) -> [SpecTree ()] -> [EvalTree]
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> Config -> [EvalItemTree] -> [EvalItemTree]
applyDryRun Config
config
([EvalItemTree] -> [EvalItemTree])
-> ([EvalItemTree] -> [EvalTree]) -> [EvalItemTree] -> [EvalTree]
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> Config -> [EvalItemTree] -> [EvalItemTree]
forall c. Config -> [Tree c EvalItem] -> [Tree c EvalItem]
applyFilterPredicates Config
config
([EvalItemTree] -> [EvalItemTree])
-> ([EvalItemTree] -> [EvalTree]) -> [EvalItemTree] -> [EvalTree]
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> [EvalItemTree] -> [EvalItemTree]
forall c a. [Tree c a] -> [Tree c a]
randomize
([EvalItemTree] -> [EvalItemTree])
-> ([EvalItemTree] -> [EvalTree]) -> [EvalItemTree] -> [EvalTree]
forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> [EvalItemTree] -> [EvalTree]
forall c a. [Tree c a] -> [Tree c a]
pruneForest
where
seed :: Integer
seed = (Maybe Integer -> Integer
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Integer -> Integer)
-> (Config -> Maybe Integer) -> Config -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> Maybe Integer
configQuickCheckSeed) Config
config
params :: Params
params = Args -> Maybe Int -> Params
Params (Config -> Args
configQuickCheckArgs Config
config) (Config -> Maybe Int
configSmallCheckDepth Config
config)
randomize :: [Tree c a] -> [Tree c a]
randomize
| Config -> Bool
configRandomize Config
config = Integer -> [Tree c a] -> [Tree c a]
forall c a. Integer -> [Tree c a] -> [Tree c a]
randomizeForest Integer
seed
| Bool
otherwise = [Tree c a] -> [Tree c a]
forall a. a -> a
id
pruneForest :: [Tree c a] -> [Eval.Tree c a]
pruneForest :: [Tree c a] -> [Tree c a]
pruneForest = (Tree c a -> Maybe (Tree c a)) -> [Tree c a] -> [Tree c a]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Tree c a -> Maybe (Tree c a)
forall c a. Tree c a -> Maybe (Tree c a)
pruneTree
pruneTree :: Tree c a -> Maybe (Eval.Tree c a)
pruneTree :: Tree c a -> Maybe (Tree c a)
pruneTree Tree c a
node = case Tree c a
node of
Node String
group [Tree c a]
xs -> String -> NonEmpty (Tree c a) -> Tree c a
forall c a. String -> NonEmpty (Tree c a) -> Tree c a
Eval.Node String
group (NonEmpty (Tree c a) -> Tree c a)
-> Maybe (NonEmpty (Tree c a)) -> Maybe (Tree c a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Tree c a] -> Maybe (NonEmpty (Tree c a))
forall c a. [Tree c a] -> Maybe (NonEmpty (Tree c a))
prune [Tree c a]
xs
NodeWithCleanup Maybe (String, Location)
loc c
action [Tree c a]
xs -> Maybe (String, Location) -> c -> NonEmpty (Tree c a) -> Tree c a
forall c a.
Maybe (String, Location) -> c -> NonEmpty (Tree c a) -> Tree c a
Eval.NodeWithCleanup Maybe (String, Location)
loc c
action (NonEmpty (Tree c a) -> Tree c a)
-> Maybe (NonEmpty (Tree c a)) -> Maybe (Tree c a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Tree c a] -> Maybe (NonEmpty (Tree c a))
forall c a. [Tree c a] -> Maybe (NonEmpty (Tree c a))
prune [Tree c a]
xs
Leaf a
item -> Tree c a -> Maybe (Tree c a)
forall a. a -> Maybe a
Just (a -> Tree c a
forall c a. a -> Tree c a
Eval.Leaf a
item)
where
prune :: [Tree c a] -> Maybe (NonEmpty (Tree c a))
prune = [Tree c a] -> Maybe (NonEmpty (Tree c a))
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty ([Tree c a] -> Maybe (NonEmpty (Tree c a)))
-> ([Tree c a] -> [Tree c a])
-> [Tree c a]
-> Maybe (NonEmpty (Tree c a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tree c a] -> [Tree c a]
forall c a. [Tree c a] -> [Tree c a]
pruneForest
type EvalItemTree = Tree (IO ()) EvalItem
toEvalItemForest :: Params -> [SpecTree ()] -> [EvalItemTree]
toEvalItemForest :: Params -> [SpecTree ()] -> [EvalItemTree]
toEvalItemForest Params
params = (IO () -> IO ())
-> (Item () -> EvalItem) -> [SpecTree ()] -> [EvalItemTree]
forall a b c d. (a -> b) -> (c -> d) -> [Tree a c] -> [Tree b d]
bimapForest IO () -> IO ()
forall a. a -> a
id Item () -> EvalItem
toEvalItem ([SpecTree ()] -> [EvalItemTree])
-> ([SpecTree ()] -> [SpecTree ()])
-> [SpecTree ()]
-> [EvalItemTree]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Item () -> Bool) -> [SpecTree ()] -> [SpecTree ()]
forall a c. (a -> Bool) -> [Tree c a] -> [Tree c a]
filterForest Item () -> Bool
forall a. Item a -> Bool
itemIsFocused
where
toEvalItem :: Item () -> EvalItem
toEvalItem :: Item () -> EvalItem
toEvalItem (Item String
requirement Maybe Location
loc Maybe Bool
isParallelizable Bool
_isFocused Params -> ((() -> IO ()) -> IO ()) -> ProgressCallback -> IO Result
e) = String
-> Maybe Location
-> Bool
-> (ProgressCallback -> IO Result)
-> EvalItem
EvalItem String
requirement Maybe Location
loc (Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
False Maybe Bool
isParallelizable) (Params -> ((() -> IO ()) -> IO ()) -> ProgressCallback -> IO Result
e Params
params (() -> IO ()) -> IO ()
withUnit)
withUnit :: ActionWith () -> IO ()
withUnit :: (() -> IO ()) -> IO ()
withUnit () -> IO ()
action = () -> IO ()
action ()
dumpFailureReport :: Config -> Integer -> QC.Args -> [Path] -> IO ()
dumpFailureReport :: Config -> Integer -> Args -> [Path] -> IO ()
dumpFailureReport Config
config Integer
seed Args
qcArgs [Path]
xs = do
Config -> FailureReport -> IO ()
writeFailureReport Config
config FailureReport :: Integer -> Int -> Int -> Int -> [Path] -> FailureReport
FailureReport {
failureReportSeed :: Integer
failureReportSeed = Integer
seed
, failureReportMaxSuccess :: Int
failureReportMaxSuccess = Args -> Int
QC.maxSuccess Args
qcArgs
, failureReportMaxSize :: Int
failureReportMaxSize = Args -> Int
QC.maxSize Args
qcArgs
, failureReportMaxDiscardRatio :: Int
failureReportMaxDiscardRatio = Args -> Int
QC.maxDiscardRatio Args
qcArgs
, failureReportPaths :: [Path]
failureReportPaths = [Path]
xs
}
doNotLeakCommandLineArgumentsToExamples :: IO a -> IO a
doNotLeakCommandLineArgumentsToExamples :: IO a -> IO a
doNotLeakCommandLineArgumentsToExamples = [String] -> IO a -> IO a
forall a. [String] -> IO a -> IO a
withArgs []
withHiddenCursor :: Bool -> Handle -> IO a -> IO a
withHiddenCursor :: Bool -> Handle -> IO a -> IO a
withHiddenCursor Bool
useColor Handle
h
| Bool
useColor = IO () -> IO () -> IO a -> IO a
forall a b c. IO a -> IO b -> IO c -> IO c
E.bracket_ (Handle -> IO ()
hHideCursor Handle
h) (Handle -> IO ()
hShowCursor Handle
h)
| Bool
otherwise = IO a -> IO a
forall a. a -> a
id
colorOutputSupported :: ColorMode -> IO Bool -> IO (Bool, Bool)
colorOutputSupported :: ColorMode -> IO Bool -> IO (Bool, Bool)
colorOutputSupported ColorMode
mode IO Bool
isTerminalDevice = do
Bool
github <- IO Bool
githubActions
Bool
buildkite <- String -> IO (Maybe String)
lookupEnv String
"BUILDKITE" IO (Maybe String) -> (Maybe String -> Bool) -> IO Bool
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Maybe String -> Maybe String -> Bool
forall a. Eq a => a -> a -> Bool
== String -> Maybe String
forall a. a -> Maybe a
Just String
"true")
Bool
useColor <- case ColorMode
mode of
ColorMode
ColorAuto -> (Bool
github Bool -> Bool -> Bool
||) (Bool -> Bool) -> IO Bool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO Bool
colorTerminal
ColorMode
ColorNever -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
ColorMode
ColorAlways -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
let reportProgress :: Bool
reportProgress = Bool -> Bool
not Bool
github Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
buildkite Bool -> Bool -> Bool
&& Bool
useColor
(Bool, Bool) -> IO (Bool, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
reportProgress, Bool
useColor)
where
githubActions :: IO Bool
githubActions :: IO Bool
githubActions = String -> IO (Maybe String)
lookupEnv String
"GITHUB_ACTIONS" IO (Maybe String) -> (Maybe String -> Bool) -> IO Bool
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Maybe String -> Maybe String -> Bool
forall a. Eq a => a -> a -> Bool
== String -> Maybe String
forall a. a -> Maybe a
Just String
"true")
colorTerminal :: IO Bool
colorTerminal :: IO Bool
colorTerminal = Bool -> Bool -> Bool
(&&) (Bool -> Bool -> Bool) -> IO Bool -> IO (Bool -> Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Bool -> Bool
not (Bool -> Bool) -> IO Bool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO Bool
noColor) IO (Bool -> Bool) -> IO Bool -> IO Bool
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> IO Bool
isTerminalDevice
noColor :: IO Bool
noColor :: IO Bool
noColor = String -> IO (Maybe String)
lookupEnv String
"NO_COLOR" IO (Maybe String) -> (Maybe String -> Bool) -> IO Bool
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Maybe String -> Maybe String -> Bool
forall a. Eq a => a -> a -> Bool
/= Maybe String
forall a. Maybe a
Nothing)
unicodeOutputSupported :: UnicodeMode -> Handle -> IO Bool
unicodeOutputSupported :: UnicodeMode -> Handle -> IO Bool
unicodeOutputSupported UnicodeMode
mode Handle
h = case UnicodeMode
mode of
UnicodeMode
UnicodeAuto -> (Maybe String -> Maybe String -> Bool
forall a. Eq a => a -> a -> Bool
== String -> Maybe String
forall a. a -> Maybe a
Just String
"UTF-8") (Maybe String -> Bool)
-> (Maybe TextEncoding -> Maybe String)
-> Maybe TextEncoding
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TextEncoding -> String) -> Maybe TextEncoding -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TextEncoding -> String
forall a. Show a => a -> String
show (Maybe TextEncoding -> Bool) -> IO (Maybe TextEncoding) -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> IO (Maybe TextEncoding)
hGetEncoding Handle
h
UnicodeMode
UnicodeNever -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
UnicodeMode
UnicodeAlways -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
rerunAll :: Config -> Maybe FailureReport -> SpecResult -> Bool
rerunAll :: Config -> Maybe FailureReport -> SpecResult -> Bool
rerunAll Config
config Maybe FailureReport
mOldFailureReport SpecResult
result = case Maybe FailureReport
mOldFailureReport of
Maybe FailureReport
Nothing -> Bool
False
Just FailureReport
oldFailureReport ->
Config -> Bool
configRerunAllOnSuccess Config
config
Bool -> Bool -> Bool
&& Config -> Bool
configRerun Config
config
Bool -> Bool -> Bool
&& SpecResult -> Bool
specResultSuccess SpecResult
result
Bool -> Bool -> Bool
&& (Bool -> Bool
not (Bool -> Bool) -> ([Path] -> Bool) -> [Path] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Path] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) (FailureReport -> [Path]
failureReportPaths FailureReport
oldFailureReport)
data Summary = Summary {
Summary -> Int
summaryExamples :: !Int
, Summary -> Int
summaryFailures :: !Int
} deriving (Summary -> Summary -> Bool
(Summary -> Summary -> Bool)
-> (Summary -> Summary -> Bool) -> Eq Summary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Summary -> Summary -> Bool
$c/= :: Summary -> Summary -> Bool
== :: Summary -> Summary -> Bool
$c== :: Summary -> Summary -> Bool
Eq, Int -> Summary -> ShowS
[Summary] -> ShowS
Summary -> String
(Int -> Summary -> ShowS)
-> (Summary -> String) -> ([Summary] -> ShowS) -> Show Summary
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Summary] -> ShowS
$cshowList :: [Summary] -> ShowS
show :: Summary -> String
$cshow :: Summary -> String
showsPrec :: Int -> Summary -> ShowS
$cshowsPrec :: Int -> Summary -> ShowS
Show)
instance Monoid Summary where
mempty :: Summary
mempty = Int -> Int -> Summary
Summary Int
0 Int
0
#if MIN_VERSION_base(4,11,0)
instance Semigroup Summary where
#endif
(Summary Int
x1 Int
x2)
#if MIN_VERSION_base(4,11,0)
<> :: Summary -> Summary -> Summary
<>
#else
`mappend`
#endif
(Summary Int
y1 Int
y2) = Int -> Int -> Summary
Summary (Int
x1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
y1) (Int
x2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
y2)
randomizeForest :: Integer -> [Tree c a] -> [Tree c a]
randomizeForest :: Integer -> [Tree c a] -> [Tree c a]
randomizeForest Integer
seed [Tree c a]
t = (forall s. ST s [Tree c a]) -> [Tree c a]
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s [Tree c a]) -> [Tree c a])
-> (forall s. ST s [Tree c a]) -> [Tree c a]
forall a b. (a -> b) -> a -> b
$ do
STRef s StdGen
ref <- StdGen -> ST s (STRef s StdGen)
forall a s. a -> ST s (STRef s a)
newSTRef (Int -> StdGen
mkStdGen (Int -> StdGen) -> Int -> StdGen
forall a b. (a -> b) -> a -> b
$ Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
seed)
STRef s StdGen -> [Tree c a] -> ST s [Tree c a]
forall s c a. STRef s StdGen -> [Tree c a] -> ST s [Tree c a]
shuffleForest STRef s StdGen
ref [Tree c a]
t
countSpecItems :: [Eval.Tree c a] -> Int
countSpecItems :: [Tree c a] -> Int
countSpecItems = Sum Int -> Int
forall a. Sum a -> a
getSum (Sum Int -> Int) -> ([Tree c a] -> Sum Int) -> [Tree c a] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Tree c a -> Sum Int) -> [Tree c a] -> Sum Int
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((a -> Sum Int) -> Tree c a -> Sum Int
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((a -> Sum Int) -> Tree c a -> Sum Int)
-> (Sum Int -> a -> Sum Int) -> Sum Int -> Tree c a -> Sum Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sum Int -> a -> Sum Int
forall a b. a -> b -> a
const (Sum Int -> Tree c a -> Sum Int) -> Sum Int -> Tree c a -> Sum Int
forall a b. (a -> b) -> a -> b
$ Int -> Sum Int
forall a. a -> Sum a
Sum Int
1)