{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE IncoherentInstances #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}

-- | This module defines all the functions you will use to define your test suite.
module Test.Syd.SpecDef where

import Control.Monad
import Control.Monad.Random
import Data.DList (DList)
import qualified Data.DList as DList
import Data.Foldable (find)
import Data.Kind
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.List.NonEmpty as NE
import Data.Maybe
import Data.Text (Text)
import qualified Data.Text as T
import Data.Word
import GHC.Generics (Generic)
import GHC.Stack
import System.Random.Shuffle
import Test.QuickCheck.IO ()
import Test.Syd.HList
import Test.Syd.OptParse
import Test.Syd.Run
import Test.Syd.SpecForest

data TDef value = TDef {forall value. TDef value -> value
testDefVal :: value, forall value. TDef value -> CallStack
testDefCallStack :: CallStack}
  deriving (forall a b. a -> TDef b -> TDef a
forall a b. (a -> b) -> TDef a -> TDef b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> TDef b -> TDef a
$c<$ :: forall a b. a -> TDef b -> TDef a
fmap :: forall a b. (a -> b) -> TDef a -> TDef b
$cfmap :: forall a b. (a -> b) -> TDef a -> TDef b
Functor, forall a. Eq a => a -> TDef a -> Bool
forall a. Num a => TDef a -> a
forall a. Ord a => TDef a -> a
forall m. Monoid m => TDef m -> m
forall a. TDef a -> Bool
forall a. TDef a -> Int
forall a. TDef a -> [a]
forall a. (a -> a -> a) -> TDef a -> a
forall m a. Monoid m => (a -> m) -> TDef a -> m
forall b a. (b -> a -> b) -> b -> TDef a -> b
forall a b. (a -> b -> b) -> b -> TDef a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => TDef a -> a
$cproduct :: forall a. Num a => TDef a -> a
sum :: forall a. Num a => TDef a -> a
$csum :: forall a. Num a => TDef a -> a
minimum :: forall a. Ord a => TDef a -> a
$cminimum :: forall a. Ord a => TDef a -> a
maximum :: forall a. Ord a => TDef a -> a
$cmaximum :: forall a. Ord a => TDef a -> a
elem :: forall a. Eq a => a -> TDef a -> Bool
$celem :: forall a. Eq a => a -> TDef a -> Bool
length :: forall a. TDef a -> Int
$clength :: forall a. TDef a -> Int
null :: forall a. TDef a -> Bool
$cnull :: forall a. TDef a -> Bool
toList :: forall a. TDef a -> [a]
$ctoList :: forall a. TDef a -> [a]
foldl1 :: forall a. (a -> a -> a) -> TDef a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> TDef a -> a
foldr1 :: forall a. (a -> a -> a) -> TDef a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> TDef a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> TDef a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> TDef a -> b
foldl :: forall b a. (b -> a -> b) -> b -> TDef a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> TDef a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> TDef a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> TDef a -> b
foldr :: forall a b. (a -> b -> b) -> b -> TDef a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> TDef a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> TDef a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> TDef a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> TDef a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> TDef a -> m
fold :: forall m. Monoid m => TDef m -> m
$cfold :: forall m. Monoid m => TDef m -> m
Foldable, Functor TDef
Foldable TDef
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => TDef (m a) -> m (TDef a)
forall (f :: * -> *) a. Applicative f => TDef (f a) -> f (TDef a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TDef a -> m (TDef b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TDef a -> f (TDef b)
sequence :: forall (m :: * -> *) a. Monad m => TDef (m a) -> m (TDef a)
$csequence :: forall (m :: * -> *) a. Monad m => TDef (m a) -> m (TDef a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TDef a -> m (TDef b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TDef a -> m (TDef b)
sequenceA :: forall (f :: * -> *) a. Applicative f => TDef (f a) -> f (TDef a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => TDef (f a) -> f (TDef a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TDef a -> f (TDef b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TDef a -> f (TDef b)
Traversable)

type TestForest outers inner = SpecDefForest outers inner ()

type TestTree outers inner = SpecDefTree outers inner ()

type SpecDefForest (outers :: [Type]) inner extra = [SpecDefTree outers inner extra]

-- | 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.
data SpecDefTree (outers :: [Type]) inner extra where
  -- | Define a test
  DefSpecifyNode ::
    -- | The description of the test
    Text ->
    -- | How the test can be run given a function that provides the resources
    TDef (ProgressReporter -> ((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult) ->
    extra ->
    SpecDefTree outers inner extra
  -- | Define a pending test
  DefPendingNode ::
    -- | The description of the test
    Text ->
    -- | The reason why the test is pending
    Maybe Text ->
    SpecDefTree outers inner extra
  -- | Group tests using a description
  DefDescribeNode ::
    -- | The description
    Text ->
    SpecDefForest outers inner extra ->
    SpecDefTree outers inner extra
  DefSetupNode ::
    -- | The function that runs before the test
    IO () ->
    SpecDefForest outers inner extra ->
    SpecDefTree outers inner extra
  DefBeforeAllNode ::
    -- | The function to run (once), beforehand, to produce the outer resource.
    IO outer ->
    SpecDefForest (outer ': otherOuters) inner extra ->
    SpecDefTree otherOuters inner extra
  DefBeforeAllWithNode ::
    -- | The function to run (once), beforehand, to produce the outer resource.
    (oldOuter -> IO newOuter) ->
    SpecDefForest (newOuter ': oldOuter ': otherOuters) inner extra ->
    SpecDefTree (oldOuter ': otherOuters) inner extra
  DefWrapNode ::
    -- | The function that wraps running the tests.
    (IO () -> IO ()) ->
    SpecDefForest outers inner extra ->
    SpecDefTree outers inner extra
  DefAroundAllNode ::
    -- | The function that provides the outer resource (once), around the tests.
    ((outer -> IO ()) -> IO ()) ->
    SpecDefForest (outer ': otherOuters) inner extra ->
    SpecDefTree otherOuters inner extra
  DefAroundAllWithNode ::
    -- | The function that provides the new outer resource (once), using the old outer resource.
    ((newOuter -> IO ()) -> (oldOuter -> IO ())) ->
    SpecDefForest (newOuter ': oldOuter ': otherOuters) inner extra ->
    SpecDefTree (oldOuter ': otherOuters) inner extra
  DefAfterAllNode ::
    -- | The function to run (once), afterwards, using all outer resources.
    (HList outers -> IO ()) ->
    SpecDefForest outers inner extra ->
    SpecDefTree outers inner extra
  -- | Control the level of parallelism for a given group of tests
  DefParallelismNode ::
    -- | The level of parallelism
    Parallelism ->
    SpecDefForest outers inner extra ->
    SpecDefTree outers inner extra
  -- | Control the execution order randomisation for a given group of tests
  DefRandomisationNode ::
    -- | The execution order randomisation
    ExecutionOrderRandomisation ->
    SpecDefForest outers inner extra ->
    SpecDefTree outers inner extra
  DefRetriesNode ::
    -- | Modify the number of retries
    (Word -> Word) ->
    SpecDefForest outers inner extra ->
    SpecDefTree outers inner extra
  DefFlakinessNode ::
    -- | Whether to allow flakiness
    FlakinessMode ->
    SpecDefForest outers inner extra ->
    SpecDefTree outers inner extra
  DefExpectationNode ::
    -- | Whether to expect passing or failing
    ExpectationMode ->
    SpecDefForest outers inner extra ->
    SpecDefTree outers inner extra

instance Functor (SpecDefTree a c) where
  fmap :: forall e f. (e -> f) -> SpecDefTree a c e -> SpecDefTree a c f
  fmap :: forall a b. (a -> b) -> SpecDefTree a c a -> SpecDefTree a c b
fmap e -> f
f =
    let goF :: forall x y. SpecDefForest x y e -> SpecDefForest x y f
        goF :: forall (x :: [*]) y. SpecDefForest x y e -> SpecDefForest x y f
goF = forall a b. (a -> b) -> [a] -> [b]
map (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap e -> f
f)
     in \case
          DefDescribeNode Text
t SpecDefForest a c e
sdf -> forall (outers :: [*]) inner extra.
Text
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefDescribeNode Text
t forall a b. (a -> b) -> a -> b
$ forall (x :: [*]) y. SpecDefForest x y e -> SpecDefForest x y f
goF SpecDefForest a c e
sdf
          DefPendingNode Text
t Maybe Text
mr -> forall (outers :: [*]) inner extra.
Text -> Maybe Text -> SpecDefTree outers inner extra
DefPendingNode Text
t Maybe Text
mr
          DefSpecifyNode Text
t TDef
  (ProgressReporter
   -> ((HList a -> c -> IO ()) -> IO ()) -> IO TestRunResult)
td e
e -> forall (outers :: [*]) inner extra.
Text
-> TDef
     (ProgressReporter
      -> ((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult)
-> extra
-> SpecDefTree outers inner extra
DefSpecifyNode Text
t TDef
  (ProgressReporter
   -> ((HList a -> c -> IO ()) -> IO ()) -> IO TestRunResult)
td (e -> f
f e
e)
          DefSetupNode IO ()
func SpecDefForest a c e
sdf -> forall (outers :: [*]) inner extra.
IO ()
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefSetupNode IO ()
func forall a b. (a -> b) -> a -> b
$ forall (x :: [*]) y. SpecDefForest x y e -> SpecDefForest x y f
goF SpecDefForest a c e
sdf
          DefBeforeAllNode IO outer
func SpecDefForest (outer : a) c e
sdf -> forall newOuter (otherOuters :: [*]) inner extra.
IO newOuter
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefBeforeAllNode IO outer
func forall a b. (a -> b) -> a -> b
$ forall (x :: [*]) y. SpecDefForest x y e -> SpecDefForest x y f
goF SpecDefForest (outer : a) c e
sdf
          DefBeforeAllWithNode oldOuter -> IO newOuter
func SpecDefForest (newOuter : oldOuter : otherOuters) c e
sdf -> forall newOuter oldOuter (otherOuters :: [*]) inner extra.
(newOuter -> IO oldOuter)
-> SpecDefForest (oldOuter : newOuter : otherOuters) inner extra
-> SpecDefTree (newOuter : otherOuters) inner extra
DefBeforeAllWithNode oldOuter -> IO newOuter
func forall a b. (a -> b) -> a -> b
$ forall (x :: [*]) y. SpecDefForest x y e -> SpecDefForest x y f
goF SpecDefForest (newOuter : oldOuter : otherOuters) c e
sdf
          DefWrapNode IO () -> IO ()
func SpecDefForest a c e
sdf -> forall (outers :: [*]) inner extra.
(IO () -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefWrapNode IO () -> IO ()
func forall a b. (a -> b) -> a -> b
$ forall (x :: [*]) y. SpecDefForest x y e -> SpecDefForest x y f
goF SpecDefForest a c e
sdf
          DefAroundAllNode (outer -> IO ()) -> IO ()
func SpecDefForest (outer : a) c e
sdf -> forall newOuter (otherOuters :: [*]) inner extra.
((newOuter -> IO ()) -> IO ())
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefAroundAllNode (outer -> IO ()) -> IO ()
func forall a b. (a -> b) -> a -> b
$ forall (x :: [*]) y. SpecDefForest x y e -> SpecDefForest x y f
goF SpecDefForest (outer : a) c e
sdf
          DefAroundAllWithNode (newOuter -> IO ()) -> oldOuter -> IO ()
func SpecDefForest (newOuter : oldOuter : otherOuters) c e
sdf -> forall newOuter oldOuter (otherOuters :: [*]) inner extra.
((newOuter -> IO ()) -> oldOuter -> IO ())
-> SpecDefForest (newOuter : oldOuter : otherOuters) inner extra
-> SpecDefTree (oldOuter : otherOuters) inner extra
DefAroundAllWithNode (newOuter -> IO ()) -> oldOuter -> IO ()
func forall a b. (a -> b) -> a -> b
$ forall (x :: [*]) y. SpecDefForest x y e -> SpecDefForest x y f
goF SpecDefForest (newOuter : oldOuter : otherOuters) c e
sdf
          DefAfterAllNode HList a -> IO ()
func SpecDefForest a c e
sdf -> forall (outers :: [*]) inner extra.
(HList outers -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefAfterAllNode HList a -> IO ()
func forall a b. (a -> b) -> a -> b
$ forall (x :: [*]) y. SpecDefForest x y e -> SpecDefForest x y f
goF SpecDefForest a c e
sdf
          DefParallelismNode Parallelism
p SpecDefForest a c e
sdf -> forall (outers :: [*]) inner extra.
Parallelism
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefParallelismNode Parallelism
p forall a b. (a -> b) -> a -> b
$ forall (x :: [*]) y. SpecDefForest x y e -> SpecDefForest x y f
goF SpecDefForest a c e
sdf
          DefRandomisationNode ExecutionOrderRandomisation
p SpecDefForest a c e
sdf -> forall (outers :: [*]) inner extra.
ExecutionOrderRandomisation
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRandomisationNode ExecutionOrderRandomisation
p forall a b. (a -> b) -> a -> b
$ forall (x :: [*]) y. SpecDefForest x y e -> SpecDefForest x y f
goF SpecDefForest a c e
sdf
          DefRetriesNode Word -> Word
p SpecDefForest a c e
sdf -> forall (outers :: [*]) inner extra.
(Word -> Word)
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRetriesNode Word -> Word
p forall a b. (a -> b) -> a -> b
$ forall (x :: [*]) y. SpecDefForest x y e -> SpecDefForest x y f
goF SpecDefForest a c e
sdf
          DefFlakinessNode FlakinessMode
p SpecDefForest a c e
sdf -> forall (outers :: [*]) inner extra.
FlakinessMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefFlakinessNode FlakinessMode
p forall a b. (a -> b) -> a -> b
$ forall (x :: [*]) y. SpecDefForest x y e -> SpecDefForest x y f
goF SpecDefForest a c e
sdf
          DefExpectationNode ExpectationMode
p SpecDefForest a c e
sdf -> forall (outers :: [*]) inner extra.
ExpectationMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefExpectationNode ExpectationMode
p forall a b. (a -> b) -> a -> b
$ forall (x :: [*]) y. SpecDefForest x y e -> SpecDefForest x y f
goF SpecDefForest a c e
sdf

instance Foldable (SpecDefTree a c) where
  foldMap :: forall e m. Monoid m => (e -> m) -> SpecDefTree a c e -> m
  foldMap :: forall e m. Monoid m => (e -> m) -> SpecDefTree a c e -> m
foldMap e -> m
f =
    let goF :: forall x y. SpecDefForest x y e -> m
        goF :: forall (x :: [*]) y. SpecDefForest x y e -> m
goF = forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap e -> m
f)
     in \case
          DefDescribeNode Text
_ SpecDefForest a c e
sdf -> forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf
          DefPendingNode Text
_ Maybe Text
_ -> forall a. Monoid a => a
mempty
          DefSpecifyNode Text
_ TDef
  (ProgressReporter
   -> ((HList a -> c -> IO ()) -> IO ()) -> IO TestRunResult)
_ e
e -> e -> m
f e
e
          DefSetupNode IO ()
_ SpecDefForest a c e
sdf -> forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf
          DefBeforeAllNode IO outer
_ SpecDefForest (outer : a) c e
sdf -> forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest (outer : a) c e
sdf
          DefBeforeAllWithNode oldOuter -> IO newOuter
_ SpecDefForest (newOuter : oldOuter : otherOuters) c e
sdf -> forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest (newOuter : oldOuter : otherOuters) c e
sdf
          DefWrapNode IO () -> IO ()
_ SpecDefForest a c e
sdf -> forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf
          DefAroundAllNode (outer -> IO ()) -> IO ()
_ SpecDefForest (outer : a) c e
sdf -> forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest (outer : a) c e
sdf
          DefAroundAllWithNode (newOuter -> IO ()) -> oldOuter -> IO ()
_ SpecDefForest (newOuter : oldOuter : otherOuters) c e
sdf -> forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest (newOuter : oldOuter : otherOuters) c e
sdf
          DefAfterAllNode HList a -> IO ()
_ SpecDefForest a c e
sdf -> forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf
          DefParallelismNode Parallelism
_ SpecDefForest a c e
sdf -> forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf
          DefRandomisationNode ExecutionOrderRandomisation
_ SpecDefForest a c e
sdf -> forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf
          DefRetriesNode Word -> Word
_ SpecDefForest a c e
sdf -> forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf
          DefFlakinessNode FlakinessMode
_ SpecDefForest a c e
sdf -> forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf
          DefExpectationNode ExpectationMode
_ SpecDefForest a c e
sdf -> forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf

instance Traversable (SpecDefTree a c) where
  traverse :: forall u w f. Applicative f => (u -> f w) -> SpecDefTree a c u -> f (SpecDefTree a c w)
  traverse :: forall u w (f :: * -> *).
Applicative f =>
(u -> f w) -> SpecDefTree a c u -> f (SpecDefTree a c w)
traverse u -> f w
f =
    let goF :: forall x y. SpecDefForest x y u -> f (SpecDefForest x y w)
        goF :: forall (x :: [*]) y. SpecDefForest x y u -> f (SpecDefForest x y w)
goF = forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse u -> f w
f)
     in \case
          DefDescribeNode Text
t SpecDefForest a c u
sdf -> forall (outers :: [*]) inner extra.
Text
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefDescribeNode Text
t forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (x :: [*]) y. SpecDefForest x y u -> f (SpecDefForest x y w)
goF SpecDefForest a c u
sdf
          DefPendingNode Text
t Maybe Text
mr -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (outers :: [*]) inner extra.
Text -> Maybe Text -> SpecDefTree outers inner extra
DefPendingNode Text
t Maybe Text
mr
          DefSpecifyNode Text
t TDef
  (ProgressReporter
   -> ((HList a -> c -> IO ()) -> IO ()) -> IO TestRunResult)
td u
e -> forall (outers :: [*]) inner extra.
Text
-> TDef
     (ProgressReporter
      -> ((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult)
-> extra
-> SpecDefTree outers inner extra
DefSpecifyNode Text
t TDef
  (ProgressReporter
   -> ((HList a -> c -> IO ()) -> IO ()) -> IO TestRunResult)
td forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> u -> f w
f u
e
          DefSetupNode IO ()
func SpecDefForest a c u
sdf -> forall (outers :: [*]) inner extra.
IO ()
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefSetupNode IO ()
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (x :: [*]) y. SpecDefForest x y u -> f (SpecDefForest x y w)
goF SpecDefForest a c u
sdf
          DefBeforeAllNode IO outer
func SpecDefForest (outer : a) c u
sdf -> forall newOuter (otherOuters :: [*]) inner extra.
IO newOuter
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefBeforeAllNode IO outer
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (x :: [*]) y. SpecDefForest x y u -> f (SpecDefForest x y w)
goF SpecDefForest (outer : a) c u
sdf
          DefBeforeAllWithNode oldOuter -> IO newOuter
func SpecDefForest (newOuter : oldOuter : otherOuters) c u
sdf -> forall newOuter oldOuter (otherOuters :: [*]) inner extra.
(newOuter -> IO oldOuter)
-> SpecDefForest (oldOuter : newOuter : otherOuters) inner extra
-> SpecDefTree (newOuter : otherOuters) inner extra
DefBeforeAllWithNode oldOuter -> IO newOuter
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (x :: [*]) y. SpecDefForest x y u -> f (SpecDefForest x y w)
goF SpecDefForest (newOuter : oldOuter : otherOuters) c u
sdf
          DefWrapNode IO () -> IO ()
func SpecDefForest a c u
sdf -> forall (outers :: [*]) inner extra.
(IO () -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefWrapNode IO () -> IO ()
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (x :: [*]) y. SpecDefForest x y u -> f (SpecDefForest x y w)
goF SpecDefForest a c u
sdf
          DefAroundAllNode (outer -> IO ()) -> IO ()
func SpecDefForest (outer : a) c u
sdf -> forall newOuter (otherOuters :: [*]) inner extra.
((newOuter -> IO ()) -> IO ())
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefAroundAllNode (outer -> IO ()) -> IO ()
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (x :: [*]) y. SpecDefForest x y u -> f (SpecDefForest x y w)
goF SpecDefForest (outer : a) c u
sdf
          DefAroundAllWithNode (newOuter -> IO ()) -> oldOuter -> IO ()
func SpecDefForest (newOuter : oldOuter : otherOuters) c u
sdf -> forall newOuter oldOuter (otherOuters :: [*]) inner extra.
((newOuter -> IO ()) -> oldOuter -> IO ())
-> SpecDefForest (newOuter : oldOuter : otherOuters) inner extra
-> SpecDefTree (oldOuter : otherOuters) inner extra
DefAroundAllWithNode (newOuter -> IO ()) -> oldOuter -> IO ()
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (x :: [*]) y. SpecDefForest x y u -> f (SpecDefForest x y w)
goF SpecDefForest (newOuter : oldOuter : otherOuters) c u
sdf
          DefAfterAllNode HList a -> IO ()
func SpecDefForest a c u
sdf -> forall (outers :: [*]) inner extra.
(HList outers -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefAfterAllNode HList a -> IO ()
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (x :: [*]) y. SpecDefForest x y u -> f (SpecDefForest x y w)
goF SpecDefForest a c u
sdf
          DefParallelismNode Parallelism
p SpecDefForest a c u
sdf -> forall (outers :: [*]) inner extra.
Parallelism
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefParallelismNode Parallelism
p forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (x :: [*]) y. SpecDefForest x y u -> f (SpecDefForest x y w)
goF SpecDefForest a c u
sdf
          DefRandomisationNode ExecutionOrderRandomisation
p SpecDefForest a c u
sdf -> forall (outers :: [*]) inner extra.
ExecutionOrderRandomisation
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRandomisationNode ExecutionOrderRandomisation
p forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (x :: [*]) y. SpecDefForest x y u -> f (SpecDefForest x y w)
goF SpecDefForest a c u
sdf
          DefRetriesNode Word -> Word
p SpecDefForest a c u
sdf -> forall (outers :: [*]) inner extra.
(Word -> Word)
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRetriesNode Word -> Word
p forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (x :: [*]) y. SpecDefForest x y u -> f (SpecDefForest x y w)
goF SpecDefForest a c u
sdf
          DefFlakinessNode FlakinessMode
p SpecDefForest a c u
sdf -> forall (outers :: [*]) inner extra.
FlakinessMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefFlakinessNode FlakinessMode
p forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (x :: [*]) y. SpecDefForest x y u -> f (SpecDefForest x y w)
goF SpecDefForest a c u
sdf
          DefExpectationNode ExpectationMode
p SpecDefForest a c u
sdf -> forall (outers :: [*]) inner extra.
ExpectationMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefExpectationNode ExpectationMode
p forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (x :: [*]) y. SpecDefForest x y u -> f (SpecDefForest x y w)
goF SpecDefForest a c u
sdf

filterTestForest :: [Text] -> SpecDefForest outers inner result -> SpecDefForest outers inner result
filterTestForest :: forall (outers :: [*]) inner result.
[Text]
-> SpecDefForest outers inner result
-> SpecDefForest outers inner result
filterTestForest [Text]
fs = forall a. a -> Maybe a -> a
fromMaybe [] forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest forall a. DList a
DList.empty
  where
    goForest :: DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
    goForest :: forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest DList Text
ts SpecDefForest a b c
sdf = do
      let sdf' :: SpecDefForest a b c
sdf' = forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (forall (a :: [*]) b c.
DList Text -> SpecDefTree a b c -> Maybe (SpecDefTree a b c)
goTree DList Text
ts) SpecDefForest a b c
sdf
      forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Bool
null SpecDefForest a b c
sdf'
      forall (f :: * -> *) a. Applicative f => a -> f a
pure SpecDefForest a b c
sdf'

    filterGuard :: DList Text -> Bool
    filterGuard :: DList Text -> Bool
filterGuard DList Text
dl =
      forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text]
fs
        Bool -> Bool -> Bool
|| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\Text
f -> Text
f Text -> Text -> Bool
`T.isInfixOf` Text -> [Text] -> Text
T.intercalate Text
"." (forall a. DList a -> [a]
DList.toList DList Text
dl)) [Text]
fs

    goTree :: DList Text -> SpecDefTree a b c -> Maybe (SpecDefTree a b c)
    goTree :: forall (a :: [*]) b c.
DList Text -> SpecDefTree a b c -> Maybe (SpecDefTree a b c)
goTree DList Text
dl = \case
      DefSpecifyNode Text
t TDef
  (ProgressReporter
   -> ((HList a -> b -> IO ()) -> IO ()) -> IO TestRunResult)
td c
e -> do
        let tl :: DList Text
tl = forall a. DList a -> a -> DList a
DList.snoc DList Text
dl Text
t
        forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ DList Text -> Bool
filterGuard DList Text
tl
        forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (outers :: [*]) inner extra.
Text
-> TDef
     (ProgressReporter
      -> ((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult)
-> extra
-> SpecDefTree outers inner extra
DefSpecifyNode Text
t TDef
  (ProgressReporter
   -> ((HList a -> b -> IO ()) -> IO ()) -> IO TestRunResult)
td c
e
      DefPendingNode Text
t Maybe Text
mr -> do
        let tl :: DList Text
tl = forall a. DList a -> a -> DList a
DList.snoc DList Text
dl Text
t
        forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ DList Text -> Bool
filterGuard DList Text
tl
        forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (outers :: [*]) inner extra.
Text -> Maybe Text -> SpecDefTree outers inner extra
DefPendingNode Text
t Maybe Text
mr
      DefDescribeNode Text
t SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
Text
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefDescribeNode Text
t forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest (forall a. DList a -> a -> DList a
DList.snoc DList Text
dl Text
t) SpecDefForest a b c
sdf
      DefSetupNode IO ()
func SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
IO ()
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefSetupNode IO ()
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest DList Text
dl SpecDefForest a b c
sdf
      DefBeforeAllNode IO outer
func SpecDefForest (outer : a) b c
sdf -> forall newOuter (otherOuters :: [*]) inner extra.
IO newOuter
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefBeforeAllNode IO outer
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest DList Text
dl SpecDefForest (outer : a) b c
sdf
      DefBeforeAllWithNode oldOuter -> IO newOuter
func SpecDefForest (newOuter : oldOuter : otherOuters) b c
sdf -> forall newOuter oldOuter (otherOuters :: [*]) inner extra.
(newOuter -> IO oldOuter)
-> SpecDefForest (oldOuter : newOuter : otherOuters) inner extra
-> SpecDefTree (newOuter : otherOuters) inner extra
DefBeforeAllWithNode oldOuter -> IO newOuter
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest DList Text
dl SpecDefForest (newOuter : oldOuter : otherOuters) b c
sdf
      DefWrapNode IO () -> IO ()
func SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
(IO () -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefWrapNode IO () -> IO ()
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest DList Text
dl SpecDefForest a b c
sdf
      DefAroundAllNode (outer -> IO ()) -> IO ()
func SpecDefForest (outer : a) b c
sdf -> forall newOuter (otherOuters :: [*]) inner extra.
((newOuter -> IO ()) -> IO ())
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefAroundAllNode (outer -> IO ()) -> IO ()
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest DList Text
dl SpecDefForest (outer : a) b c
sdf
      DefAroundAllWithNode (newOuter -> IO ()) -> oldOuter -> IO ()
func SpecDefForest (newOuter : oldOuter : otherOuters) b c
sdf -> forall newOuter oldOuter (otherOuters :: [*]) inner extra.
((newOuter -> IO ()) -> oldOuter -> IO ())
-> SpecDefForest (newOuter : oldOuter : otherOuters) inner extra
-> SpecDefTree (oldOuter : otherOuters) inner extra
DefAroundAllWithNode (newOuter -> IO ()) -> oldOuter -> IO ()
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest DList Text
dl SpecDefForest (newOuter : oldOuter : otherOuters) b c
sdf
      DefAfterAllNode HList a -> IO ()
func SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
(HList outers -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefAfterAllNode HList a -> IO ()
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest DList Text
dl SpecDefForest a b c
sdf
      DefParallelismNode Parallelism
func SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
Parallelism
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefParallelismNode Parallelism
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest DList Text
dl SpecDefForest a b c
sdf
      DefRandomisationNode ExecutionOrderRandomisation
func SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
ExecutionOrderRandomisation
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRandomisationNode ExecutionOrderRandomisation
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest DList Text
dl SpecDefForest a b c
sdf
      DefRetriesNode Word -> Word
func SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
(Word -> Word)
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRetriesNode Word -> Word
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest DList Text
dl SpecDefForest a b c
sdf
      DefFlakinessNode FlakinessMode
func SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
FlakinessMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefFlakinessNode FlakinessMode
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest DList Text
dl SpecDefForest a b c
sdf
      DefExpectationNode ExpectationMode
func SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
ExpectationMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefExpectationNode ExpectationMode
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest DList Text
dl SpecDefForest a b c
sdf

randomiseTestForest :: MonadRandom m => SpecDefForest outers inner result -> m (SpecDefForest outers inner result)
randomiseTestForest :: forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
randomiseTestForest = forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
goForest
  where
    goForest :: MonadRandom m => SpecDefForest a b c -> m (SpecDefForest a b c)
    goForest :: forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
goForest = forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall (m :: * -> *) (a :: [*]) b c.
MonadRandom m =>
SpecDefTree a b c -> m (SpecDefTree a b c)
goTree forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall (m :: * -> *) a. MonadRandom m => [a] -> m [a]
shuffleM
    goTree :: MonadRandom m => SpecDefTree a b c -> m (SpecDefTree a b c)
    goTree :: forall (m :: * -> *) (a :: [*]) b c.
MonadRandom m =>
SpecDefTree a b c -> m (SpecDefTree a b c)
goTree = \case
      DefSpecifyNode Text
t TDef
  (ProgressReporter
   -> ((HList a -> b -> IO ()) -> IO ()) -> IO TestRunResult)
td c
e -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (outers :: [*]) inner extra.
Text
-> TDef
     (ProgressReporter
      -> ((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult)
-> extra
-> SpecDefTree outers inner extra
DefSpecifyNode Text
t TDef
  (ProgressReporter
   -> ((HList a -> b -> IO ()) -> IO ()) -> IO TestRunResult)
td c
e
      DefPendingNode Text
t Maybe Text
mr -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (outers :: [*]) inner extra.
Text -> Maybe Text -> SpecDefTree outers inner extra
DefPendingNode Text
t Maybe Text
mr
      DefDescribeNode Text
t SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
Text
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefDescribeNode Text
t forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
goForest SpecDefForest a b c
sdf
      DefSetupNode IO ()
func SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
IO ()
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefSetupNode IO ()
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
goForest SpecDefForest a b c
sdf
      DefBeforeAllNode IO outer
func SpecDefForest (outer : a) b c
sdf -> forall newOuter (otherOuters :: [*]) inner extra.
IO newOuter
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefBeforeAllNode IO outer
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
goForest SpecDefForest (outer : a) b c
sdf
      DefBeforeAllWithNode oldOuter -> IO newOuter
func SpecDefForest (newOuter : oldOuter : otherOuters) b c
sdf -> forall newOuter oldOuter (otherOuters :: [*]) inner extra.
(newOuter -> IO oldOuter)
-> SpecDefForest (oldOuter : newOuter : otherOuters) inner extra
-> SpecDefTree (newOuter : otherOuters) inner extra
DefBeforeAllWithNode oldOuter -> IO newOuter
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
goForest SpecDefForest (newOuter : oldOuter : otherOuters) b c
sdf
      DefWrapNode IO () -> IO ()
func SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
(IO () -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefWrapNode IO () -> IO ()
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
goForest SpecDefForest a b c
sdf
      DefAroundAllNode (outer -> IO ()) -> IO ()
func SpecDefForest (outer : a) b c
sdf -> forall newOuter (otherOuters :: [*]) inner extra.
((newOuter -> IO ()) -> IO ())
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefAroundAllNode (outer -> IO ()) -> IO ()
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
goForest SpecDefForest (outer : a) b c
sdf
      DefAroundAllWithNode (newOuter -> IO ()) -> oldOuter -> IO ()
func SpecDefForest (newOuter : oldOuter : otherOuters) b c
sdf -> forall newOuter oldOuter (otherOuters :: [*]) inner extra.
((newOuter -> IO ()) -> oldOuter -> IO ())
-> SpecDefForest (newOuter : oldOuter : otherOuters) inner extra
-> SpecDefTree (oldOuter : otherOuters) inner extra
DefAroundAllWithNode (newOuter -> IO ()) -> oldOuter -> IO ()
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
goForest SpecDefForest (newOuter : oldOuter : otherOuters) b c
sdf
      DefAfterAllNode HList a -> IO ()
func SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
(HList outers -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefAfterAllNode HList a -> IO ()
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
goForest SpecDefForest a b c
sdf
      DefParallelismNode Parallelism
func SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
Parallelism
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefParallelismNode Parallelism
func forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
goForest SpecDefForest a b c
sdf
      DefRetriesNode Word -> Word
i SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
(Word -> Word)
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRetriesNode Word -> Word
i forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
goForest SpecDefForest a b c
sdf
      DefFlakinessNode FlakinessMode
i SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
FlakinessMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefFlakinessNode FlakinessMode
i forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
goForest SpecDefForest a b c
sdf
      DefExpectationNode ExpectationMode
i SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
ExpectationMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefExpectationNode ExpectationMode
i forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
goForest SpecDefForest a b c
sdf
      DefRandomisationNode ExecutionOrderRandomisation
eor SpecDefForest a b c
sdf ->
        forall (outers :: [*]) inner extra.
ExecutionOrderRandomisation
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRandomisationNode ExecutionOrderRandomisation
eor forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case ExecutionOrderRandomisation
eor of
          ExecutionOrderRandomisation
RandomiseExecutionOrder -> forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
goForest SpecDefForest a b c
sdf
          ExecutionOrderRandomisation
DoNotRandomiseExecutionOrder -> forall (f :: * -> *) a. Applicative f => a -> f a
pure SpecDefForest a b c
sdf

markSpecForestAsPending :: Maybe Text -> SpecDefForest outers inner result -> SpecDefForest outers inner result
markSpecForestAsPending :: forall (outers :: [*]) inner result.
Maybe Text
-> SpecDefForest outers inner result
-> SpecDefForest outers inner result
markSpecForestAsPending Maybe Text
mMessage = forall (a :: [*]) b c. SpecDefForest a b c -> SpecDefForest a b c
goForest
  where
    goForest :: SpecDefForest a b c -> SpecDefForest a b c
    goForest :: forall (a :: [*]) b c. SpecDefForest a b c -> SpecDefForest a b c
goForest = forall a b. (a -> b) -> [a] -> [b]
map forall (a :: [*]) b c. SpecDefTree a b c -> SpecDefTree a b c
goTree

    goTree :: SpecDefTree a b c -> SpecDefTree a b c
    goTree :: forall (a :: [*]) b c. SpecDefTree a b c -> SpecDefTree a b c
goTree = \case
      DefSpecifyNode Text
t TDef
  (ProgressReporter
   -> ((HList a -> b -> IO ()) -> IO ()) -> IO TestRunResult)
_ c
_ -> forall (outers :: [*]) inner extra.
Text -> Maybe Text -> SpecDefTree outers inner extra
DefPendingNode Text
t Maybe Text
mMessage
      DefPendingNode Text
t Maybe Text
mr -> forall (outers :: [*]) inner extra.
Text -> Maybe Text -> SpecDefTree outers inner extra
DefPendingNode Text
t Maybe Text
mr
      DefDescribeNode Text
t SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
Text
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefDescribeNode Text
t forall a b. (a -> b) -> a -> b
$ forall (a :: [*]) b c. SpecDefForest a b c -> SpecDefForest a b c
goForest SpecDefForest a b c
sdf
      DefSetupNode IO ()
func SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
IO ()
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefSetupNode IO ()
func forall a b. (a -> b) -> a -> b
$ forall (a :: [*]) b c. SpecDefForest a b c -> SpecDefForest a b c
goForest SpecDefForest a b c
sdf
      DefBeforeAllNode IO outer
func SpecDefForest (outer : a) b c
sdf -> forall newOuter (otherOuters :: [*]) inner extra.
IO newOuter
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefBeforeAllNode IO outer
func forall a b. (a -> b) -> a -> b
$ forall (a :: [*]) b c. SpecDefForest a b c -> SpecDefForest a b c
goForest SpecDefForest (outer : a) b c
sdf
      DefBeforeAllWithNode oldOuter -> IO newOuter
func SpecDefForest (newOuter : oldOuter : otherOuters) b c
sdf -> forall newOuter oldOuter (otherOuters :: [*]) inner extra.
(newOuter -> IO oldOuter)
-> SpecDefForest (oldOuter : newOuter : otherOuters) inner extra
-> SpecDefTree (newOuter : otherOuters) inner extra
DefBeforeAllWithNode oldOuter -> IO newOuter
func forall a b. (a -> b) -> a -> b
$ forall (a :: [*]) b c. SpecDefForest a b c -> SpecDefForest a b c
goForest SpecDefForest (newOuter : oldOuter : otherOuters) b c
sdf
      DefWrapNode IO () -> IO ()
func SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
(IO () -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefWrapNode IO () -> IO ()
func forall a b. (a -> b) -> a -> b
$ forall (a :: [*]) b c. SpecDefForest a b c -> SpecDefForest a b c
goForest SpecDefForest a b c
sdf
      DefAroundAllNode (outer -> IO ()) -> IO ()
func SpecDefForest (outer : a) b c
sdf -> forall newOuter (otherOuters :: [*]) inner extra.
((newOuter -> IO ()) -> IO ())
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefAroundAllNode (outer -> IO ()) -> IO ()
func forall a b. (a -> b) -> a -> b
$ forall (a :: [*]) b c. SpecDefForest a b c -> SpecDefForest a b c
goForest SpecDefForest (outer : a) b c
sdf
      DefAroundAllWithNode (newOuter -> IO ()) -> oldOuter -> IO ()
func SpecDefForest (newOuter : oldOuter : otherOuters) b c
sdf -> forall newOuter oldOuter (otherOuters :: [*]) inner extra.
((newOuter -> IO ()) -> oldOuter -> IO ())
-> SpecDefForest (newOuter : oldOuter : otherOuters) inner extra
-> SpecDefTree (oldOuter : otherOuters) inner extra
DefAroundAllWithNode (newOuter -> IO ()) -> oldOuter -> IO ()
func forall a b. (a -> b) -> a -> b
$ forall (a :: [*]) b c. SpecDefForest a b c -> SpecDefForest a b c
goForest SpecDefForest (newOuter : oldOuter : otherOuters) b c
sdf
      DefAfterAllNode HList a -> IO ()
func SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
(HList outers -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefAfterAllNode HList a -> IO ()
func forall a b. (a -> b) -> a -> b
$ forall (a :: [*]) b c. SpecDefForest a b c -> SpecDefForest a b c
goForest SpecDefForest a b c
sdf
      DefParallelismNode Parallelism
func SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
Parallelism
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefParallelismNode Parallelism
func forall a b. (a -> b) -> a -> b
$ forall (a :: [*]) b c. SpecDefForest a b c -> SpecDefForest a b c
goForest SpecDefForest a b c
sdf
      DefRetriesNode Word -> Word
i SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
(Word -> Word)
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRetriesNode Word -> Word
i forall a b. (a -> b) -> a -> b
$ forall (a :: [*]) b c. SpecDefForest a b c -> SpecDefForest a b c
goForest SpecDefForest a b c
sdf
      DefFlakinessNode FlakinessMode
i SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
FlakinessMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefFlakinessNode FlakinessMode
i forall a b. (a -> b) -> a -> b
$ forall (a :: [*]) b c. SpecDefForest a b c -> SpecDefForest a b c
goForest SpecDefForest a b c
sdf
      DefRandomisationNode ExecutionOrderRandomisation
eor SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
ExecutionOrderRandomisation
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRandomisationNode ExecutionOrderRandomisation
eor (forall (a :: [*]) b c. SpecDefForest a b c -> SpecDefForest a b c
goForest SpecDefForest a b c
sdf)
      DefExpectationNode ExpectationMode
i SpecDefForest a b c
sdf -> forall (outers :: [*]) inner extra.
ExpectationMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefExpectationNode ExpectationMode
i forall a b. (a -> b) -> a -> b
$ forall (a :: [*]) b c. SpecDefForest a b c -> SpecDefForest a b c
goForest SpecDefForest a b c
sdf

data Parallelism
  = Parallel
  | Sequential
  deriving (Int -> Parallelism -> ShowS
[Parallelism] -> ShowS
Parallelism -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Parallelism] -> ShowS
$cshowList :: [Parallelism] -> ShowS
show :: Parallelism -> String
$cshow :: Parallelism -> String
showsPrec :: Int -> Parallelism -> ShowS
$cshowsPrec :: Int -> Parallelism -> ShowS
Show, Parallelism -> Parallelism -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Parallelism -> Parallelism -> Bool
$c/= :: Parallelism -> Parallelism -> Bool
== :: Parallelism -> Parallelism -> Bool
$c== :: Parallelism -> Parallelism -> Bool
Eq, forall x. Rep Parallelism x -> Parallelism
forall x. Parallelism -> Rep Parallelism x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Parallelism x -> Parallelism
$cfrom :: forall x. Parallelism -> Rep Parallelism x
Generic)

data ExecutionOrderRandomisation
  = RandomiseExecutionOrder
  | DoNotRandomiseExecutionOrder
  deriving (Int -> ExecutionOrderRandomisation -> ShowS
[ExecutionOrderRandomisation] -> ShowS
ExecutionOrderRandomisation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExecutionOrderRandomisation] -> ShowS
$cshowList :: [ExecutionOrderRandomisation] -> ShowS
show :: ExecutionOrderRandomisation -> String
$cshow :: ExecutionOrderRandomisation -> String
showsPrec :: Int -> ExecutionOrderRandomisation -> ShowS
$cshowsPrec :: Int -> ExecutionOrderRandomisation -> ShowS
Show, ExecutionOrderRandomisation -> ExecutionOrderRandomisation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExecutionOrderRandomisation -> ExecutionOrderRandomisation -> Bool
$c/= :: ExecutionOrderRandomisation -> ExecutionOrderRandomisation -> Bool
== :: ExecutionOrderRandomisation -> ExecutionOrderRandomisation -> Bool
$c== :: ExecutionOrderRandomisation -> ExecutionOrderRandomisation -> Bool
Eq, forall x.
Rep ExecutionOrderRandomisation x -> ExecutionOrderRandomisation
forall x.
ExecutionOrderRandomisation -> Rep ExecutionOrderRandomisation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ExecutionOrderRandomisation x -> ExecutionOrderRandomisation
$cfrom :: forall x.
ExecutionOrderRandomisation -> Rep ExecutionOrderRandomisation x
Generic)

data FlakinessMode
  = MayNotBeFlaky
  | MayBeFlaky !(Maybe String) -- A message to show whenever the test is flaky.
  deriving (Int -> FlakinessMode -> ShowS
[FlakinessMode] -> ShowS
FlakinessMode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FlakinessMode] -> ShowS
$cshowList :: [FlakinessMode] -> ShowS
show :: FlakinessMode -> String
$cshow :: FlakinessMode -> String
showsPrec :: Int -> FlakinessMode -> ShowS
$cshowsPrec :: Int -> FlakinessMode -> ShowS
Show, FlakinessMode -> FlakinessMode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FlakinessMode -> FlakinessMode -> Bool
$c/= :: FlakinessMode -> FlakinessMode -> Bool
== :: FlakinessMode -> FlakinessMode -> Bool
$c== :: FlakinessMode -> FlakinessMode -> Bool
Eq, forall x. Rep FlakinessMode x -> FlakinessMode
forall x. FlakinessMode -> Rep FlakinessMode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FlakinessMode x -> FlakinessMode
$cfrom :: forall x. FlakinessMode -> Rep FlakinessMode x
Generic)

data ExpectationMode
  = ExpectPassing
  | ExpectFailing
  deriving (Int -> ExpectationMode -> ShowS
[ExpectationMode] -> ShowS
ExpectationMode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExpectationMode] -> ShowS
$cshowList :: [ExpectationMode] -> ShowS
show :: ExpectationMode -> String
$cshow :: ExpectationMode -> String
showsPrec :: Int -> ExpectationMode -> ShowS
$cshowsPrec :: Int -> ExpectationMode -> ShowS
Show, ExpectationMode -> ExpectationMode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExpectationMode -> ExpectationMode -> Bool
$c/= :: ExpectationMode -> ExpectationMode -> Bool
== :: ExpectationMode -> ExpectationMode -> Bool
$c== :: ExpectationMode -> ExpectationMode -> Bool
Eq, forall x. Rep ExpectationMode x -> ExpectationMode
forall x. ExpectationMode -> Rep ExpectationMode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExpectationMode x -> ExpectationMode
$cfrom :: forall x. ExpectationMode -> Rep ExpectationMode x
Generic)

type ResultForest = SpecForest (TDef (Timed TestRunReport))

type ResultTree = SpecTree (TDef (Timed TestRunReport))

computeTestSuiteStats :: Settings -> ResultForest -> TestSuiteStats
computeTestSuiteStats :: Settings -> ResultForest -> TestSuiteStats
computeTestSuiteStats Settings
settings = [Text] -> ResultForest -> TestSuiteStats
goF []
  where
    goF :: [Text] -> ResultForest -> TestSuiteStats
    goF :: [Text] -> ResultForest -> TestSuiteStats
goF [Text]
ts = forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ([Text] -> ResultTree -> TestSuiteStats
goT [Text]
ts)
    goT :: [Text] -> ResultTree -> TestSuiteStats
    goT :: [Text] -> ResultTree -> TestSuiteStats
goT [Text]
ts = \case
      SpecifyNode Text
_ (TDef timed :: Timed TestRunReport
timed@Timed {Int
Word64
TestRunReport
timedEnd :: forall a. Timed a -> Word64
timedBegin :: forall a. Timed a -> Word64
timedWorker :: forall a. Timed a -> Int
timedValue :: forall a. Timed a -> a
timedEnd :: Word64
timedBegin :: Word64
timedWorker :: Int
timedValue :: TestRunReport
..} CallStack
_) ->
        let status :: TestStatus
status = Settings -> TestRunReport -> TestStatus
testRunReportStatus Settings
settings TestRunReport
timedValue
         in TestSuiteStats
              { testSuiteStatSuccesses :: Word
testSuiteStatSuccesses = case TestStatus
status of
                  TestStatus
TestPassed -> Word
1
                  TestStatus
TestFailed -> Word
0,
                testSuiteStatExamples :: Word
testSuiteStatExamples =
                  TestRunReport -> Word
testRunReportExamples TestRunReport
timedValue,
                testSuiteStatFailures :: Word
testSuiteStatFailures = case TestStatus
status of
                  TestStatus
TestPassed -> Word
0
                  TestStatus
TestFailed -> Word
1,
                testSuiteStatFlakyTests :: Word
testSuiteStatFlakyTests =
                  if TestRunReport -> Bool
testRunReportWasFlaky TestRunReport
timedValue
                    then Word
1
                    else Word
0,
                testSuiteStatPending :: Word
testSuiteStatPending = Word
0,
                testSuiteStatSumTime :: Word64
testSuiteStatSumTime = forall a. Timed a -> Word64
timedTime Timed TestRunReport
timed
              }
      PendingNode Text
_ Maybe Text
_ ->
        TestSuiteStats
          { testSuiteStatSuccesses :: Word
testSuiteStatSuccesses = Word
0,
            testSuiteStatExamples :: Word
testSuiteStatExamples = Word
0,
            testSuiteStatFailures :: Word
testSuiteStatFailures = Word
0,
            testSuiteStatFlakyTests :: Word
testSuiteStatFlakyTests = Word
0,
            testSuiteStatPending :: Word
testSuiteStatPending = Word
1,
            testSuiteStatSumTime :: Word64
testSuiteStatSumTime = Word64
0
          }
      DescribeNode Text
t ResultForest
sf -> [Text] -> ResultForest -> TestSuiteStats
goF (Text
t forall a. a -> [a] -> [a]
: [Text]
ts) ResultForest
sf
      SubForestNode ResultForest
sf -> [Text] -> ResultForest -> TestSuiteStats
goF [Text]
ts ResultForest
sf

data TestSuiteStats = TestSuiteStats
  { TestSuiteStats -> Word
testSuiteStatSuccesses :: !Word,
    TestSuiteStats -> Word
testSuiteStatExamples :: !Word,
    TestSuiteStats -> Word
testSuiteStatFailures :: !Word,
    TestSuiteStats -> Word
testSuiteStatFlakyTests :: !Word,
    TestSuiteStats -> Word
testSuiteStatPending :: !Word,
    TestSuiteStats -> Word64
testSuiteStatSumTime :: !Word64
  }
  deriving (Int -> TestSuiteStats -> ShowS
[TestSuiteStats] -> ShowS
TestSuiteStats -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestSuiteStats] -> ShowS
$cshowList :: [TestSuiteStats] -> ShowS
show :: TestSuiteStats -> String
$cshow :: TestSuiteStats -> String
showsPrec :: Int -> TestSuiteStats -> ShowS
$cshowsPrec :: Int -> TestSuiteStats -> ShowS
Show, TestSuiteStats -> TestSuiteStats -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestSuiteStats -> TestSuiteStats -> Bool
$c/= :: TestSuiteStats -> TestSuiteStats -> Bool
== :: TestSuiteStats -> TestSuiteStats -> Bool
$c== :: TestSuiteStats -> TestSuiteStats -> Bool
Eq)

instance Semigroup TestSuiteStats where
  <> :: TestSuiteStats -> TestSuiteStats -> TestSuiteStats
(<>) TestSuiteStats
tss1 TestSuiteStats
tss2 =
    TestSuiteStats
      { testSuiteStatSuccesses :: Word
testSuiteStatSuccesses = TestSuiteStats -> Word
testSuiteStatSuccesses TestSuiteStats
tss1 forall a. Num a => a -> a -> a
+ TestSuiteStats -> Word
testSuiteStatSuccesses TestSuiteStats
tss2,
        testSuiteStatExamples :: Word
testSuiteStatExamples = TestSuiteStats -> Word
testSuiteStatExamples TestSuiteStats
tss1 forall a. Num a => a -> a -> a
+ TestSuiteStats -> Word
testSuiteStatExamples TestSuiteStats
tss2,
        testSuiteStatFailures :: Word
testSuiteStatFailures = TestSuiteStats -> Word
testSuiteStatFailures TestSuiteStats
tss1 forall a. Num a => a -> a -> a
+ TestSuiteStats -> Word
testSuiteStatFailures TestSuiteStats
tss2,
        testSuiteStatFlakyTests :: Word
testSuiteStatFlakyTests = TestSuiteStats -> Word
testSuiteStatFlakyTests TestSuiteStats
tss1 forall a. Num a => a -> a -> a
+ TestSuiteStats -> Word
testSuiteStatFlakyTests TestSuiteStats
tss2,
        testSuiteStatPending :: Word
testSuiteStatPending = TestSuiteStats -> Word
testSuiteStatPending TestSuiteStats
tss1 forall a. Num a => a -> a -> a
+ TestSuiteStats -> Word
testSuiteStatPending TestSuiteStats
tss2,
        testSuiteStatSumTime :: Word64
testSuiteStatSumTime = TestSuiteStats -> Word64
testSuiteStatSumTime TestSuiteStats
tss1 forall a. Num a => a -> a -> a
+ TestSuiteStats -> Word64
testSuiteStatSumTime TestSuiteStats
tss2
      }

instance Monoid TestSuiteStats where
  mappend :: TestSuiteStats -> TestSuiteStats -> TestSuiteStats
mappend = forall a. Semigroup a => a -> a -> a
(<>)
  mempty :: TestSuiteStats
mempty =
    TestSuiteStats
      { testSuiteStatSuccesses :: Word
testSuiteStatSuccesses = Word
0,
        testSuiteStatExamples :: Word
testSuiteStatExamples = Word
0,
        testSuiteStatFailures :: Word
testSuiteStatFailures = Word
0,
        testSuiteStatFlakyTests :: Word
testSuiteStatFlakyTests = Word
0,
        testSuiteStatPending :: Word
testSuiteStatPending = Word
0,
        testSuiteStatSumTime :: Word64
testSuiteStatSumTime = Word64
0
      }

shouldExitFail :: Settings -> ResultForest -> Bool
shouldExitFail :: Settings -> ResultForest -> Bool
shouldExitFail Settings
settings = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Settings -> TestRunReport -> Bool
testRunReportFailed Settings
settings forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Timed a -> a
timedValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall value. TDef value -> value
testDefVal))

data TestRunReport = TestRunReport
  { TestRunReport -> ExpectationMode
testRunReportExpectationMode :: !ExpectationMode,
    -- | Raw results, including retries, in order
    TestRunReport -> NonEmpty TestRunResult
testRunReportRawResults :: !(NonEmpty TestRunResult),
    TestRunReport -> FlakinessMode
testRunReportFlakinessMode :: !FlakinessMode
  }
  deriving (Int -> TestRunReport -> ShowS
[TestRunReport] -> ShowS
TestRunReport -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestRunReport] -> ShowS
$cshowList :: [TestRunReport] -> ShowS
show :: TestRunReport -> String
$cshow :: TestRunReport -> String
showsPrec :: Int -> TestRunReport -> ShowS
$cshowsPrec :: Int -> TestRunReport -> ShowS
Show, forall x. Rep TestRunReport x -> TestRunReport
forall x. TestRunReport -> Rep TestRunReport x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestRunReport x -> TestRunReport
$cfrom :: forall x. TestRunReport -> Rep TestRunReport x
Generic)

testRunReportReportedRun :: TestRunReport -> TestRunResult
testRunReportReportedRun :: TestRunReport -> TestRunResult
testRunReportReportedRun TestRunReport {NonEmpty TestRunResult
ExpectationMode
FlakinessMode
testRunReportFlakinessMode :: FlakinessMode
testRunReportRawResults :: NonEmpty TestRunResult
testRunReportExpectationMode :: ExpectationMode
testRunReportFlakinessMode :: TestRunReport -> FlakinessMode
testRunReportRawResults :: TestRunReport -> NonEmpty TestRunResult
testRunReportExpectationMode :: TestRunReport -> ExpectationMode
..} =
  -- We always want to report the last failure if there are any failures.
  -- This is because a passed test does not give us any information, and we
  -- only want to do that if there are no failures.
  let reversed :: NonEmpty TestRunResult
reversed = forall a. NonEmpty a -> NonEmpty a
NE.reverse NonEmpty TestRunResult
testRunReportRawResults
   in case forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((forall a. Eq a => a -> a -> Bool
== TestStatus
TestFailed) forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestRunResult -> TestStatus
testRunResultStatus) NonEmpty TestRunResult
testRunReportRawResults of
        Maybe TestRunResult
Nothing -> forall a. NonEmpty a -> a
NE.head NonEmpty TestRunResult
reversed
        Just TestRunResult
trr -> TestRunResult
trr

testRunReportFailed :: Settings -> TestRunReport -> Bool
testRunReportFailed :: Settings -> TestRunReport -> Bool
testRunReportFailed Settings
settings TestRunReport
testRunReport =
  Settings -> TestRunReport -> TestStatus
testRunReportStatus Settings
settings TestRunReport
testRunReport forall a. Eq a => a -> a -> Bool
/= TestStatus
TestPassed

testRunReportStatus :: Settings -> TestRunReport -> TestStatus
testRunReportStatus :: Settings -> TestRunReport -> TestStatus
testRunReportStatus Settings {Bool
Int
[Text]
Maybe Bool
Word
SeedSetting
ReportProgress
Iterations
Threads
settingProfile :: Settings -> Bool
settingDebug :: Settings -> Bool
settingReportProgress :: Settings -> ReportProgress
settingFailOnFlaky :: Settings -> Bool
settingRetries :: Settings -> Word
settingIterations :: Settings -> Iterations
settingFailFast :: Settings -> Bool
settingFilters :: Settings -> [Text]
settingColour :: Settings -> Maybe Bool
settingGoldenReset :: Settings -> Bool
settingGoldenStart :: Settings -> Bool
settingMaxShrinks :: Settings -> Int
settingMaxDiscard :: Settings -> Int
settingMaxSize :: Settings -> Int
settingMaxSuccess :: Settings -> Int
settingThreads :: Settings -> Threads
settingRandomiseExecutionOrder :: Settings -> Bool
settingSeed :: Settings -> SeedSetting
settingProfile :: Bool
settingDebug :: Bool
settingReportProgress :: ReportProgress
settingFailOnFlaky :: Bool
settingRetries :: Word
settingIterations :: Iterations
settingFailFast :: Bool
settingFilters :: [Text]
settingColour :: Maybe Bool
settingGoldenReset :: Bool
settingGoldenStart :: Bool
settingMaxShrinks :: Int
settingMaxDiscard :: Int
settingMaxSize :: Int
settingMaxSuccess :: Int
settingThreads :: Threads
settingRandomiseExecutionOrder :: Bool
settingSeed :: SeedSetting
..} testRunReport :: TestRunReport
testRunReport@TestRunReport {NonEmpty TestRunResult
ExpectationMode
FlakinessMode
testRunReportFlakinessMode :: FlakinessMode
testRunReportRawResults :: NonEmpty TestRunResult
testRunReportExpectationMode :: ExpectationMode
testRunReportFlakinessMode :: TestRunReport -> FlakinessMode
testRunReportRawResults :: TestRunReport -> NonEmpty TestRunResult
testRunReportExpectationMode :: TestRunReport -> ExpectationMode
..} =
  let wasFlaky :: Bool
wasFlaky = TestRunReport -> Bool
testRunReportWasFlaky TestRunReport
testRunReport
      lastResult :: TestRunResult
lastResult = forall a. NonEmpty a -> a
NE.last NonEmpty TestRunResult
testRunReportRawResults
      actualStatus :: TestStatus
actualStatus = case FlakinessMode
testRunReportFlakinessMode of
        FlakinessMode
MayNotBeFlaky ->
          if Bool
wasFlaky
            then TestStatus
TestFailed
            else TestRunResult -> TestStatus
testRunResultStatus TestRunResult
lastResult
        MayBeFlaky Maybe String
_ ->
          if Bool
settingFailOnFlaky Bool -> Bool -> Bool
&& Bool
wasFlaky
            then TestStatus
TestFailed
            else
              if forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((forall a. Eq a => a -> a -> Bool
== TestStatus
TestPassed) forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestRunResult -> TestStatus
testRunResultStatus) NonEmpty TestRunResult
testRunReportRawResults
                then TestStatus
TestPassed
                else TestStatus
TestFailed
      consideredStatus :: TestStatus
consideredStatus =
        if TestStatus -> ExpectationMode -> Bool
testStatusMatchesExpectationMode TestStatus
actualStatus ExpectationMode
testRunReportExpectationMode
          then TestStatus
TestPassed
          else TestStatus
TestFailed
   in TestStatus
consideredStatus

testStatusMatchesExpectationMode :: TestStatus -> ExpectationMode -> Bool
testStatusMatchesExpectationMode :: TestStatus -> ExpectationMode -> Bool
testStatusMatchesExpectationMode TestStatus
actualStatus ExpectationMode
expectationMode = case (TestStatus
actualStatus, ExpectationMode
expectationMode) of
  (TestStatus
TestPassed, ExpectationMode
ExpectPassing) -> Bool
True
  (TestStatus
TestFailed, ExpectationMode
ExpectFailing) -> Bool
True
  (TestStatus, ExpectationMode)
_ -> Bool
False

testRunReportExamples :: TestRunReport -> Word
testRunReportExamples :: TestRunReport -> Word
testRunReportExamples = forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map TestRunResult -> Word
testRunResultExamples forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestRunReport -> NonEmpty TestRunResult
testRunReportRawResults

testRunResultExamples :: TestRunResult -> Word
testRunResultExamples :: TestRunResult -> Word
testRunResultExamples TestRunResult {[String]
Maybe String
Maybe Word
Maybe (Map String Int)
Maybe (Map String (Map String Int))
Maybe (Map [String] Int)
Maybe SomeException
Maybe GoldenCase
TestStatus
testRunResultExtraInfo :: TestRunResult -> Maybe String
testRunResultGoldenCase :: TestRunResult -> Maybe GoldenCase
testRunResultTables :: TestRunResult -> Maybe (Map String (Map String Int))
testRunResultClasses :: TestRunResult -> Maybe (Map String Int)
testRunResultLabels :: TestRunResult -> Maybe (Map [String] Int)
testRunResultFailingInputs :: TestRunResult -> [String]
testRunResultNumShrinks :: TestRunResult -> Maybe Word
testRunResultNumTests :: TestRunResult -> Maybe Word
testRunResultException :: TestRunResult -> Maybe SomeException
testRunResultExtraInfo :: Maybe String
testRunResultGoldenCase :: Maybe GoldenCase
testRunResultTables :: Maybe (Map String (Map String Int))
testRunResultClasses :: Maybe (Map String Int)
testRunResultLabels :: Maybe (Map [String] Int)
testRunResultFailingInputs :: [String]
testRunResultNumShrinks :: Maybe Word
testRunResultNumTests :: Maybe Word
testRunResultException :: Maybe SomeException
testRunResultStatus :: TestStatus
testRunResultStatus :: TestRunResult -> TestStatus
..} =
  forall a. a -> Maybe a -> a
fromMaybe Word
1 Maybe Word
testRunResultNumTests forall a. Num a => a -> a -> a
+ forall a. a -> Maybe a -> a
fromMaybe Word
0 Maybe Word
testRunResultNumShrinks

testRunReportWasFlaky :: TestRunReport -> Bool
testRunReportWasFlaky :: TestRunReport -> Bool
testRunReportWasFlaky =
  (forall a. Ord a => a -> a -> Bool
> Int
1)
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Int
length
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. (Foldable f, Eq a) => f a -> [NonEmpty a]
NE.group
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map TestRunResult -> TestStatus
testRunResultStatus
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestRunReport -> NonEmpty TestRunResult
testRunReportRawResults

testRunReportRetries :: TestRunReport -> Maybe Word
testRunReportRetries :: TestRunReport -> Maybe Word
testRunReportRetries TestRunReport {NonEmpty TestRunResult
ExpectationMode
FlakinessMode
testRunReportFlakinessMode :: FlakinessMode
testRunReportRawResults :: NonEmpty TestRunResult
testRunReportExpectationMode :: ExpectationMode
testRunReportFlakinessMode :: TestRunReport -> FlakinessMode
testRunReportRawResults :: TestRunReport -> NonEmpty TestRunResult
testRunReportExpectationMode :: TestRunReport -> ExpectationMode
..} = case forall a. NonEmpty a -> Int
NE.length NonEmpty TestRunResult
testRunReportRawResults of
  Int
1 -> forall a. Maybe a
Nothing
  Int
l -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l