{-# 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 #-}
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 -> b) -> TDef a -> TDef b)
-> (forall a b. a -> TDef b -> TDef a) -> Functor TDef
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
$cfmap :: forall a b. (a -> b) -> TDef a -> TDef b
fmap :: forall a b. (a -> b) -> TDef a -> TDef b
$c<$ :: forall a b. a -> TDef b -> TDef a
<$ :: forall a b. a -> TDef b -> TDef a
Functor, (forall m. Monoid m => TDef m -> m)
-> (forall m a. Monoid m => (a -> m) -> TDef a -> m)
-> (forall m a. Monoid m => (a -> m) -> TDef a -> m)
-> (forall a b. (a -> b -> b) -> b -> TDef a -> b)
-> (forall a b. (a -> b -> b) -> b -> TDef a -> b)
-> (forall b a. (b -> a -> b) -> b -> TDef a -> b)
-> (forall b a. (b -> a -> b) -> b -> TDef a -> b)
-> (forall a. (a -> a -> a) -> TDef a -> a)
-> (forall a. (a -> a -> a) -> TDef a -> a)
-> (forall a. TDef a -> [a])
-> (forall a. TDef a -> Bool)
-> (forall a. TDef a -> Int)
-> (forall a. Eq a => a -> TDef a -> Bool)
-> (forall a. Ord a => TDef a -> a)
-> (forall a. Ord a => TDef a -> a)
-> (forall a. Num a => TDef a -> a)
-> (forall a. Num a => TDef a -> a)
-> Foldable TDef
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
$cfold :: forall m. Monoid m => TDef m -> m
fold :: forall m. Monoid m => TDef m -> 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
foldMap' :: forall m a. Monoid m => (a -> m) -> TDef a -> m
$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
foldr' :: forall a b. (a -> b -> 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
foldl' :: forall b a. (b -> a -> b) -> b -> TDef a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> TDef a -> a
foldr1 :: forall a. (a -> a -> a) -> TDef a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> TDef a -> a
foldl1 :: forall a. (a -> a -> a) -> TDef a -> a
$ctoList :: forall a. TDef a -> [a]
toList :: forall a. TDef a -> [a]
$cnull :: forall a. TDef a -> Bool
null :: forall a. TDef a -> Bool
$clength :: forall a. TDef a -> Int
length :: forall a. TDef a -> Int
$celem :: forall a. Eq a => a -> TDef a -> Bool
elem :: forall a. Eq a => a -> TDef a -> Bool
$cmaximum :: forall a. Ord a => TDef a -> a
maximum :: forall a. Ord a => TDef a -> a
$cminimum :: forall a. Ord a => TDef a -> a
minimum :: forall a. Ord a => TDef a -> a
$csum :: forall a. Num a => TDef a -> a
sum :: forall a. Num a => TDef a -> a
$cproduct :: forall a. Num a => TDef a -> a
product :: forall a. Num a => TDef a -> a
Foldable, Functor TDef
Foldable TDef
(Functor TDef, Foldable TDef) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TDef a -> f (TDef b))
-> (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 (m :: * -> *) a. Monad m => TDef (m a) -> m (TDef a))
-> Traversable 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)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TDef a -> f (TDef b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TDef a -> f (TDef b)
$csequenceA :: forall (f :: * -> *) a. Applicative f => TDef (f a) -> f (TDef a)
sequenceA :: forall (f :: * -> *) a. Applicative f => TDef (f a) -> f (TDef a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TDef a -> m (TDef b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TDef a -> m (TDef b)
$csequence :: forall (m :: * -> *) a. Monad m => TDef (m a) -> m (TDef a)
sequence :: forall (m :: * -> *) a. Monad m => TDef (m a) -> m (TDef a)
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]
data SpecDefTree (outers :: [Type]) inner extra where
DefSpecifyNode ::
Text ->
TDef (ProgressReporter -> ((HList outers -> inner -> IO ()) -> IO ()) -> IO TestRunResult) ->
extra ->
SpecDefTree outers inner extra
DefPendingNode ::
Text ->
Maybe Text ->
SpecDefTree outers inner extra
DefDescribeNode ::
Text ->
SpecDefForest outers inner extra ->
SpecDefTree outers inner extra
DefSetupNode ::
IO () ->
SpecDefForest outers inner extra ->
SpecDefTree outers inner extra
DefBeforeAllNode ::
IO outer ->
SpecDefForest (outer ': otherOuters) inner extra ->
SpecDefTree otherOuters inner extra
DefBeforeAllWithNode ::
(oldOuter -> IO newOuter) ->
SpecDefForest (newOuter ': oldOuter ': otherOuters) inner extra ->
SpecDefTree (oldOuter ': otherOuters) inner extra
DefWrapNode ::
(IO () -> IO ()) ->
SpecDefForest outers inner extra ->
SpecDefTree outers inner extra
DefAroundAllNode ::
((outer -> IO ()) -> IO ()) ->
SpecDefForest (outer ': otherOuters) inner extra ->
SpecDefTree otherOuters inner extra
DefAroundAllWithNode ::
((newOuter -> IO ()) -> (oldOuter -> IO ())) ->
SpecDefForest (newOuter ': oldOuter ': otherOuters) inner extra ->
SpecDefTree (oldOuter ': otherOuters) inner extra
DefAfterAllNode ::
(HList outers -> IO ()) ->
SpecDefForest outers inner extra ->
SpecDefTree outers inner extra
DefParallelismNode ::
Parallelism ->
SpecDefForest outers inner extra ->
SpecDefTree outers inner extra
DefRandomisationNode ::
ExecutionOrderRandomisation ->
SpecDefForest outers inner extra ->
SpecDefTree outers inner extra
DefRetriesNode ::
(Word -> Word) ->
SpecDefForest outers inner extra ->
SpecDefTree outers inner extra
DefFlakinessNode ::
FlakinessMode ->
SpecDefForest outers inner extra ->
SpecDefTree outers inner extra
DefExpectationNode ::
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 = (SpecDefTree x y e -> SpecDefTree x y f)
-> [SpecDefTree x y e] -> [SpecDefTree x y f]
forall a b. (a -> b) -> [a] -> [b]
map ((e -> f) -> SpecDefTree x y e -> SpecDefTree x y f
forall a b. (a -> b) -> SpecDefTree x y a -> SpecDefTree x y b
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 -> Text -> SpecDefForest a c f -> SpecDefTree a c f
forall (outers :: [*]) inner extra.
Text
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefDescribeNode Text
t (SpecDefForest a c f -> SpecDefTree a c f)
-> SpecDefForest a c f -> SpecDefTree a c f
forall a b. (a -> b) -> a -> b
$ SpecDefForest a c e -> SpecDefForest a c f
forall (x :: [*]) y. SpecDefForest x y e -> SpecDefForest x y f
goF SpecDefForest a c e
sdf
DefPendingNode Text
t Maybe Text
mr -> Text -> Maybe Text -> SpecDefTree a c f
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 -> Text
-> TDef
(ProgressReporter
-> ((HList a -> c -> IO ()) -> IO ()) -> IO TestRunResult)
-> f
-> SpecDefTree a c f
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 -> IO () -> SpecDefForest a c f -> SpecDefTree a c f
forall (outers :: [*]) inner extra.
IO ()
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefSetupNode IO ()
func (SpecDefForest a c f -> SpecDefTree a c f)
-> SpecDefForest a c f -> SpecDefTree a c f
forall a b. (a -> b) -> a -> b
$ SpecDefForest a c e -> SpecDefForest a c f
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 -> IO outer -> SpecDefForest (outer : a) c f -> SpecDefTree a c f
forall newOuter (otherOuters :: [*]) inner extra.
IO newOuter
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefBeforeAllNode IO outer
func (SpecDefForest (outer : a) c f -> SpecDefTree a c f)
-> SpecDefForest (outer : a) c f -> SpecDefTree a c f
forall a b. (a -> b) -> a -> b
$ SpecDefForest (outer : a) c e -> SpecDefForest (outer : a) c f
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 -> (oldOuter -> IO newOuter)
-> SpecDefForest (newOuter : oldOuter : otherOuters) c f
-> SpecDefTree (oldOuter : otherOuters) c f
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 (SpecDefForest (newOuter : oldOuter : otherOuters) c f
-> SpecDefTree (oldOuter : otherOuters) c f)
-> SpecDefForest (newOuter : oldOuter : otherOuters) c f
-> SpecDefTree (oldOuter : otherOuters) c f
forall a b. (a -> b) -> a -> b
$ SpecDefForest (newOuter : oldOuter : otherOuters) c e
-> SpecDefForest (newOuter : oldOuter : otherOuters) c f
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 -> (IO () -> IO ()) -> SpecDefForest a c f -> SpecDefTree a c f
forall (outers :: [*]) inner extra.
(IO () -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefWrapNode IO () -> IO ()
func (SpecDefForest a c f -> SpecDefTree a c f)
-> SpecDefForest a c f -> SpecDefTree a c f
forall a b. (a -> b) -> a -> b
$ SpecDefForest a c e -> SpecDefForest a c f
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 -> ((outer -> IO ()) -> IO ())
-> SpecDefForest (outer : a) c f -> SpecDefTree a c f
forall newOuter (otherOuters :: [*]) inner extra.
((newOuter -> IO ()) -> IO ())
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefAroundAllNode (outer -> IO ()) -> IO ()
func (SpecDefForest (outer : a) c f -> SpecDefTree a c f)
-> SpecDefForest (outer : a) c f -> SpecDefTree a c f
forall a b. (a -> b) -> a -> b
$ SpecDefForest (outer : a) c e -> SpecDefForest (outer : a) c f
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 -> ((newOuter -> IO ()) -> oldOuter -> IO ())
-> SpecDefForest (newOuter : oldOuter : otherOuters) c f
-> SpecDefTree (oldOuter : otherOuters) c f
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 (SpecDefForest (newOuter : oldOuter : otherOuters) c f
-> SpecDefTree (oldOuter : otherOuters) c f)
-> SpecDefForest (newOuter : oldOuter : otherOuters) c f
-> SpecDefTree (oldOuter : otherOuters) c f
forall a b. (a -> b) -> a -> b
$ SpecDefForest (newOuter : oldOuter : otherOuters) c e
-> SpecDefForest (newOuter : oldOuter : otherOuters) c f
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 -> (HList a -> IO ()) -> SpecDefForest a c f -> SpecDefTree a c f
forall (outers :: [*]) inner extra.
(HList outers -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefAfterAllNode HList a -> IO ()
func (SpecDefForest a c f -> SpecDefTree a c f)
-> SpecDefForest a c f -> SpecDefTree a c f
forall a b. (a -> b) -> a -> b
$ SpecDefForest a c e -> SpecDefForest a c f
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 -> Parallelism -> SpecDefForest a c f -> SpecDefTree a c f
forall (outers :: [*]) inner extra.
Parallelism
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefParallelismNode Parallelism
p (SpecDefForest a c f -> SpecDefTree a c f)
-> SpecDefForest a c f -> SpecDefTree a c f
forall a b. (a -> b) -> a -> b
$ SpecDefForest a c e -> SpecDefForest a c f
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 -> ExecutionOrderRandomisation
-> SpecDefForest a c f -> SpecDefTree a c f
forall (outers :: [*]) inner extra.
ExecutionOrderRandomisation
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRandomisationNode ExecutionOrderRandomisation
p (SpecDefForest a c f -> SpecDefTree a c f)
-> SpecDefForest a c f -> SpecDefTree a c f
forall a b. (a -> b) -> a -> b
$ SpecDefForest a c e -> SpecDefForest a c f
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 -> (Word -> Word) -> SpecDefForest a c f -> SpecDefTree a c f
forall (outers :: [*]) inner extra.
(Word -> Word)
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRetriesNode Word -> Word
p (SpecDefForest a c f -> SpecDefTree a c f)
-> SpecDefForest a c f -> SpecDefTree a c f
forall a b. (a -> b) -> a -> b
$ SpecDefForest a c e -> SpecDefForest a c f
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 -> FlakinessMode -> SpecDefForest a c f -> SpecDefTree a c f
forall (outers :: [*]) inner extra.
FlakinessMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefFlakinessNode FlakinessMode
p (SpecDefForest a c f -> SpecDefTree a c f)
-> SpecDefForest a c f -> SpecDefTree a c f
forall a b. (a -> b) -> a -> b
$ SpecDefForest a c e -> SpecDefForest a c f
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 -> ExpectationMode -> SpecDefForest a c f -> SpecDefTree a c f
forall (outers :: [*]) inner extra.
ExpectationMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefExpectationNode ExpectationMode
p (SpecDefForest a c f -> SpecDefTree a c f)
-> SpecDefForest a c f -> SpecDefTree a c f
forall a b. (a -> b) -> a -> b
$ SpecDefForest a c e -> SpecDefForest a c f
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 = (SpecDefTree x y e -> m) -> [SpecDefTree x y e] -> m
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((e -> m) -> SpecDefTree x y e -> m
forall m a. Monoid m => (a -> m) -> SpecDefTree x y a -> m
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 -> SpecDefForest a c e -> m
forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf
DefPendingNode Text
_ Maybe Text
_ -> m
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 -> SpecDefForest a c e -> m
forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf
DefBeforeAllNode IO outer
_ SpecDefForest (outer : a) c e
sdf -> SpecDefForest (outer : a) c e -> m
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 -> SpecDefForest (newOuter : oldOuter : otherOuters) c e -> m
forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest (newOuter : oldOuter : otherOuters) c e
sdf
DefWrapNode IO () -> IO ()
_ SpecDefForest a c e
sdf -> SpecDefForest a c e -> m
forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf
DefAroundAllNode (outer -> IO ()) -> IO ()
_ SpecDefForest (outer : a) c e
sdf -> SpecDefForest (outer : a) c e -> m
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 -> SpecDefForest (newOuter : oldOuter : otherOuters) c e -> m
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 -> SpecDefForest a c e -> m
forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf
DefParallelismNode Parallelism
_ SpecDefForest a c e
sdf -> SpecDefForest a c e -> m
forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf
DefRandomisationNode ExecutionOrderRandomisation
_ SpecDefForest a c e
sdf -> SpecDefForest a c e -> m
forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf
DefRetriesNode Word -> Word
_ SpecDefForest a c e
sdf -> SpecDefForest a c e -> m
forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf
DefFlakinessNode FlakinessMode
_ SpecDefForest a c e
sdf -> SpecDefForest a c e -> m
forall (x :: [*]) y. SpecDefForest x y e -> m
goF SpecDefForest a c e
sdf
DefExpectationNode ExpectationMode
_ SpecDefForest a c e
sdf -> SpecDefForest a c e -> m
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 = (SpecDefTree x y u -> f (SpecDefTree x y w))
-> [SpecDefTree x y u] -> f [SpecDefTree x y w]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse ((u -> f w) -> SpecDefTree x y u -> f (SpecDefTree x y w)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SpecDefTree x y a -> f (SpecDefTree x y b)
traverse u -> f w
f)
in \case
DefDescribeNode Text
t SpecDefForest a c u
sdf -> Text -> SpecDefForest a c w -> SpecDefTree a c w
forall (outers :: [*]) inner extra.
Text
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefDescribeNode Text
t (SpecDefForest a c w -> SpecDefTree a c w)
-> f (SpecDefForest a c w) -> f (SpecDefTree a c w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a c u -> f (SpecDefForest a c w)
forall (x :: [*]) y. SpecDefForest x y u -> f (SpecDefForest x y w)
goF SpecDefForest a c u
sdf
DefPendingNode Text
t Maybe Text
mr -> SpecDefTree a c w -> f (SpecDefTree a c w)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SpecDefTree a c w -> f (SpecDefTree a c w))
-> SpecDefTree a c w -> f (SpecDefTree a c w)
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text -> SpecDefTree a c w
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 -> Text
-> TDef
(ProgressReporter
-> ((HList a -> c -> IO ()) -> IO ()) -> IO TestRunResult)
-> w
-> SpecDefTree a c w
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 (w -> SpecDefTree a c w) -> f w -> f (SpecDefTree a c w)
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 -> IO () -> SpecDefForest a c w -> SpecDefTree a c w
forall (outers :: [*]) inner extra.
IO ()
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefSetupNode IO ()
func (SpecDefForest a c w -> SpecDefTree a c w)
-> f (SpecDefForest a c w) -> f (SpecDefTree a c w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a c u -> f (SpecDefForest a c w)
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 -> IO outer -> SpecDefForest (outer : a) c w -> SpecDefTree a c w
forall newOuter (otherOuters :: [*]) inner extra.
IO newOuter
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefBeforeAllNode IO outer
func (SpecDefForest (outer : a) c w -> SpecDefTree a c w)
-> f (SpecDefForest (outer : a) c w) -> f (SpecDefTree a c w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest (outer : a) c u -> f (SpecDefForest (outer : a) c w)
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 -> (oldOuter -> IO newOuter)
-> SpecDefForest (newOuter : oldOuter : otherOuters) c w
-> SpecDefTree (oldOuter : otherOuters) c w
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 (SpecDefForest (newOuter : oldOuter : otherOuters) c w
-> SpecDefTree a c w)
-> f (SpecDefForest (newOuter : oldOuter : otherOuters) c w)
-> f (SpecDefTree a c w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest (newOuter : oldOuter : otherOuters) c u
-> f (SpecDefForest (newOuter : oldOuter : otherOuters) c w)
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 -> (IO () -> IO ()) -> SpecDefForest a c w -> SpecDefTree a c w
forall (outers :: [*]) inner extra.
(IO () -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefWrapNode IO () -> IO ()
func (SpecDefForest a c w -> SpecDefTree a c w)
-> f (SpecDefForest a c w) -> f (SpecDefTree a c w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a c u -> f (SpecDefForest a c w)
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 -> ((outer -> IO ()) -> IO ())
-> SpecDefForest (outer : a) c w -> SpecDefTree a c w
forall newOuter (otherOuters :: [*]) inner extra.
((newOuter -> IO ()) -> IO ())
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefAroundAllNode (outer -> IO ()) -> IO ()
func (SpecDefForest (outer : a) c w -> SpecDefTree a c w)
-> f (SpecDefForest (outer : a) c w) -> f (SpecDefTree a c w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest (outer : a) c u -> f (SpecDefForest (outer : a) c w)
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 -> ((newOuter -> IO ()) -> oldOuter -> IO ())
-> SpecDefForest (newOuter : oldOuter : otherOuters) c w
-> SpecDefTree (oldOuter : otherOuters) c w
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 (SpecDefForest (newOuter : oldOuter : otherOuters) c w
-> SpecDefTree a c w)
-> f (SpecDefForest (newOuter : oldOuter : otherOuters) c w)
-> f (SpecDefTree a c w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest (newOuter : oldOuter : otherOuters) c u
-> f (SpecDefForest (newOuter : oldOuter : otherOuters) c w)
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 -> (HList a -> IO ()) -> SpecDefForest a c w -> SpecDefTree a c w
forall (outers :: [*]) inner extra.
(HList outers -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefAfterAllNode HList a -> IO ()
func (SpecDefForest a c w -> SpecDefTree a c w)
-> f (SpecDefForest a c w) -> f (SpecDefTree a c w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a c u -> f (SpecDefForest a c w)
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 -> Parallelism -> SpecDefForest a c w -> SpecDefTree a c w
forall (outers :: [*]) inner extra.
Parallelism
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefParallelismNode Parallelism
p (SpecDefForest a c w -> SpecDefTree a c w)
-> f (SpecDefForest a c w) -> f (SpecDefTree a c w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a c u -> f (SpecDefForest a c w)
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 -> ExecutionOrderRandomisation
-> SpecDefForest a c w -> SpecDefTree a c w
forall (outers :: [*]) inner extra.
ExecutionOrderRandomisation
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRandomisationNode ExecutionOrderRandomisation
p (SpecDefForest a c w -> SpecDefTree a c w)
-> f (SpecDefForest a c w) -> f (SpecDefTree a c w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a c u -> f (SpecDefForest a c w)
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 -> (Word -> Word) -> SpecDefForest a c w -> SpecDefTree a c w
forall (outers :: [*]) inner extra.
(Word -> Word)
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRetriesNode Word -> Word
p (SpecDefForest a c w -> SpecDefTree a c w)
-> f (SpecDefForest a c w) -> f (SpecDefTree a c w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a c u -> f (SpecDefForest a c w)
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 -> FlakinessMode -> SpecDefForest a c w -> SpecDefTree a c w
forall (outers :: [*]) inner extra.
FlakinessMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefFlakinessNode FlakinessMode
p (SpecDefForest a c w -> SpecDefTree a c w)
-> f (SpecDefForest a c w) -> f (SpecDefTree a c w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a c u -> f (SpecDefForest a c w)
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 -> ExpectationMode -> SpecDefForest a c w -> SpecDefTree a c w
forall (outers :: [*]) inner extra.
ExpectationMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefExpectationNode ExpectationMode
p (SpecDefForest a c w -> SpecDefTree a c w)
-> f (SpecDefForest a c w) -> f (SpecDefTree a c w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a c u -> f (SpecDefForest a c w)
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 = SpecDefForest outers inner result
-> Maybe (SpecDefForest outers inner result)
-> SpecDefForest outers inner result
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe (SpecDefForest outers inner result)
-> SpecDefForest outers inner result)
-> (SpecDefForest outers inner result
-> Maybe (SpecDefForest outers inner result))
-> SpecDefForest outers inner result
-> SpecDefForest outers inner result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DList Text
-> SpecDefForest outers inner result
-> Maybe (SpecDefForest outers inner result)
forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest DList Text
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' = (SpecDefTree a b c -> Maybe (SpecDefTree a b c))
-> SpecDefForest a b c -> SpecDefForest a b c
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (DList Text -> SpecDefTree a b c -> Maybe (SpecDefTree a b c)
forall (a :: [*]) b c.
DList Text -> SpecDefTree a b c -> Maybe (SpecDefTree a b c)
goTree DList Text
ts) SpecDefForest a b c
sdf
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ SpecDefForest a b c -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null SpecDefForest a b c
sdf'
SpecDefForest a b c -> Maybe (SpecDefForest a b c)
forall a. a -> Maybe a
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 =
[Text] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text]
fs
Bool -> Bool -> Bool
|| (Text -> Bool) -> [Text] -> 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
"." (DList Text -> [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 = DList Text -> Text -> DList Text
forall a. DList a -> a -> DList a
DList.snoc DList Text
dl Text
t
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ DList Text -> Bool
filterGuard DList Text
tl
SpecDefTree a b c -> Maybe (SpecDefTree a b c)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SpecDefTree a b c -> Maybe (SpecDefTree a b c))
-> SpecDefTree a b c -> Maybe (SpecDefTree a b c)
forall a b. (a -> b) -> a -> b
$ Text
-> TDef
(ProgressReporter
-> ((HList a -> b -> IO ()) -> IO ()) -> IO TestRunResult)
-> c
-> SpecDefTree a b c
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 = DList Text -> Text -> DList Text
forall a. DList a -> a -> DList a
DList.snoc DList Text
dl Text
t
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ DList Text -> Bool
filterGuard DList Text
tl
SpecDefTree a b c -> Maybe (SpecDefTree a b c)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SpecDefTree a b c -> Maybe (SpecDefTree a b c))
-> SpecDefTree a b c -> Maybe (SpecDefTree a b c)
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text -> SpecDefTree a b c
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 -> Text -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
Text
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefDescribeNode Text
t (SpecDefForest a b c -> SpecDefTree a b c)
-> Maybe (SpecDefForest a b c) -> Maybe (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
forall (a :: [*]) b c.
DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
goForest (DList Text -> Text -> DList Text
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 -> IO () -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
IO ()
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefSetupNode IO ()
func (SpecDefForest a b c -> SpecDefTree a b c)
-> Maybe (SpecDefForest a b c) -> Maybe (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
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 -> IO outer -> SpecDefForest (outer : a) b c -> SpecDefTree a b c
forall newOuter (otherOuters :: [*]) inner extra.
IO newOuter
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefBeforeAllNode IO outer
func (SpecDefForest (outer : a) b c -> SpecDefTree a b c)
-> Maybe (SpecDefForest (outer : a) b c)
-> Maybe (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DList Text
-> SpecDefForest (outer : a) b c
-> Maybe (SpecDefForest (outer : a) b c)
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 -> (oldOuter -> IO newOuter)
-> SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> SpecDefTree (oldOuter : otherOuters) b c
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 (SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> SpecDefTree a b c)
-> Maybe (SpecDefForest (newOuter : oldOuter : otherOuters) b c)
-> Maybe (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DList Text
-> SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> Maybe (SpecDefForest (newOuter : oldOuter : otherOuters) b c)
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 -> (IO () -> IO ()) -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
(IO () -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefWrapNode IO () -> IO ()
func (SpecDefForest a b c -> SpecDefTree a b c)
-> Maybe (SpecDefForest a b c) -> Maybe (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
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 -> ((outer -> IO ()) -> IO ())
-> SpecDefForest (outer : a) b c -> SpecDefTree a b c
forall newOuter (otherOuters :: [*]) inner extra.
((newOuter -> IO ()) -> IO ())
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefAroundAllNode (outer -> IO ()) -> IO ()
func (SpecDefForest (outer : a) b c -> SpecDefTree a b c)
-> Maybe (SpecDefForest (outer : a) b c)
-> Maybe (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DList Text
-> SpecDefForest (outer : a) b c
-> Maybe (SpecDefForest (outer : a) b c)
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 -> ((newOuter -> IO ()) -> oldOuter -> IO ())
-> SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> SpecDefTree (oldOuter : otherOuters) b c
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 (SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> SpecDefTree a b c)
-> Maybe (SpecDefForest (newOuter : oldOuter : otherOuters) b c)
-> Maybe (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DList Text
-> SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> Maybe (SpecDefForest (newOuter : oldOuter : otherOuters) b c)
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 -> (HList a -> IO ()) -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
(HList outers -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefAfterAllNode HList a -> IO ()
func (SpecDefForest a b c -> SpecDefTree a b c)
-> Maybe (SpecDefForest a b c) -> Maybe (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
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 -> Parallelism -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
Parallelism
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefParallelismNode Parallelism
func (SpecDefForest a b c -> SpecDefTree a b c)
-> Maybe (SpecDefForest a b c) -> Maybe (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
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 -> ExecutionOrderRandomisation
-> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
ExecutionOrderRandomisation
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRandomisationNode ExecutionOrderRandomisation
func (SpecDefForest a b c -> SpecDefTree a b c)
-> Maybe (SpecDefForest a b c) -> Maybe (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
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 -> (Word -> Word) -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
(Word -> Word)
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRetriesNode Word -> Word
func (SpecDefForest a b c -> SpecDefTree a b c)
-> Maybe (SpecDefForest a b c) -> Maybe (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
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 -> FlakinessMode -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
FlakinessMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefFlakinessNode FlakinessMode
func (SpecDefForest a b c -> SpecDefTree a b c)
-> Maybe (SpecDefForest a b c) -> Maybe (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
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 -> ExpectationMode -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
ExpectationMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefExpectationNode ExpectationMode
func (SpecDefForest a b c -> SpecDefTree a b c)
-> Maybe (SpecDefForest a b c) -> Maybe (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DList Text -> SpecDefForest a b c -> Maybe (SpecDefForest a b c)
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 = SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
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 = (SpecDefTree a b c -> m (SpecDefTree a b c))
-> [SpecDefTree a b c] -> m [SpecDefTree a b c]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse SpecDefTree a b c -> m (SpecDefTree a b c)
forall (m :: * -> *) (a :: [*]) b c.
MonadRandom m =>
SpecDefTree a b c -> m (SpecDefTree a b c)
goTree ([SpecDefTree a b c] -> m [SpecDefTree a b c])
-> ([SpecDefTree a b c] -> m [SpecDefTree a b c])
-> [SpecDefTree a b c]
-> m [SpecDefTree a b c]
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> [SpecDefTree a b c] -> m [SpecDefTree a b 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 -> SpecDefTree a b c -> m (SpecDefTree a b c)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SpecDefTree a b c -> m (SpecDefTree a b c))
-> SpecDefTree a b c -> m (SpecDefTree a b c)
forall a b. (a -> b) -> a -> b
$ Text
-> TDef
(ProgressReporter
-> ((HList a -> b -> IO ()) -> IO ()) -> IO TestRunResult)
-> c
-> SpecDefTree a b c
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 -> SpecDefTree a b c -> m (SpecDefTree a b c)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SpecDefTree a b c -> m (SpecDefTree a b c))
-> SpecDefTree a b c -> m (SpecDefTree a b c)
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text -> SpecDefTree a b c
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 -> Text -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
Text
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefDescribeNode Text
t (SpecDefForest a b c -> SpecDefTree a b c)
-> m (SpecDefForest a b c) -> m (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a b c -> m (SpecDefForest a b c)
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 -> IO () -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
IO ()
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefSetupNode IO ()
func (SpecDefForest a b c -> SpecDefTree a b c)
-> m (SpecDefForest a b c) -> m (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a b c -> m (SpecDefForest a b c)
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 -> IO outer -> SpecDefForest (outer : a) b c -> SpecDefTree a b c
forall newOuter (otherOuters :: [*]) inner extra.
IO newOuter
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefBeforeAllNode IO outer
func (SpecDefForest (outer : a) b c -> SpecDefTree a b c)
-> m (SpecDefForest (outer : a) b c) -> m (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest (outer : a) b c -> m (SpecDefForest (outer : a) b c)
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 -> (oldOuter -> IO newOuter)
-> SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> SpecDefTree (oldOuter : otherOuters) b c
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 (SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> SpecDefTree a b c)
-> m (SpecDefForest (newOuter : oldOuter : otherOuters) b c)
-> m (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> m (SpecDefForest (newOuter : oldOuter : otherOuters) b c)
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 -> (IO () -> IO ()) -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
(IO () -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefWrapNode IO () -> IO ()
func (SpecDefForest a b c -> SpecDefTree a b c)
-> m (SpecDefForest a b c) -> m (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a b c -> m (SpecDefForest a b c)
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 -> ((outer -> IO ()) -> IO ())
-> SpecDefForest (outer : a) b c -> SpecDefTree a b c
forall newOuter (otherOuters :: [*]) inner extra.
((newOuter -> IO ()) -> IO ())
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefAroundAllNode (outer -> IO ()) -> IO ()
func (SpecDefForest (outer : a) b c -> SpecDefTree a b c)
-> m (SpecDefForest (outer : a) b c) -> m (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest (outer : a) b c -> m (SpecDefForest (outer : a) b c)
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 -> ((newOuter -> IO ()) -> oldOuter -> IO ())
-> SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> SpecDefTree (oldOuter : otherOuters) b c
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 (SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> SpecDefTree a b c)
-> m (SpecDefForest (newOuter : oldOuter : otherOuters) b c)
-> m (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> m (SpecDefForest (newOuter : oldOuter : otherOuters) b c)
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 -> (HList a -> IO ()) -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
(HList outers -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefAfterAllNode HList a -> IO ()
func (SpecDefForest a b c -> SpecDefTree a b c)
-> m (SpecDefForest a b c) -> m (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a b c -> m (SpecDefForest a b c)
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 -> Parallelism -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
Parallelism
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefParallelismNode Parallelism
func (SpecDefForest a b c -> SpecDefTree a b c)
-> m (SpecDefForest a b c) -> m (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a b c -> m (SpecDefForest a b c)
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 -> (Word -> Word) -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
(Word -> Word)
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRetriesNode Word -> Word
i (SpecDefForest a b c -> SpecDefTree a b c)
-> m (SpecDefForest a b c) -> m (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a b c -> m (SpecDefForest a b c)
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 -> FlakinessMode -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
FlakinessMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefFlakinessNode FlakinessMode
i (SpecDefForest a b c -> SpecDefTree a b c)
-> m (SpecDefForest a b c) -> m (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a b c -> m (SpecDefForest a b c)
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 -> ExpectationMode -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
ExpectationMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefExpectationNode ExpectationMode
i (SpecDefForest a b c -> SpecDefTree a b c)
-> m (SpecDefForest a b c) -> m (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SpecDefForest a b c -> m (SpecDefForest a b c)
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 ->
ExecutionOrderRandomisation
-> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
ExecutionOrderRandomisation
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRandomisationNode ExecutionOrderRandomisation
eor (SpecDefForest a b c -> SpecDefTree a b c)
-> m (SpecDefForest a b c) -> m (SpecDefTree a b c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case ExecutionOrderRandomisation
eor of
ExecutionOrderRandomisation
RandomiseExecutionOrder -> SpecDefForest a b c -> m (SpecDefForest a b c)
forall (m :: * -> *) (outers :: [*]) inner result.
MonadRandom m =>
SpecDefForest outers inner result
-> m (SpecDefForest outers inner result)
goForest SpecDefForest a b c
sdf
ExecutionOrderRandomisation
DoNotRandomiseExecutionOrder -> SpecDefForest a b c -> m (SpecDefForest a b c)
forall a. a -> m a
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 = SpecDefForest outers inner result
-> SpecDefForest outers inner result
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 = (SpecDefTree a b c -> SpecDefTree a b c)
-> [SpecDefTree a b c] -> [SpecDefTree a b c]
forall a b. (a -> b) -> [a] -> [b]
map SpecDefTree a b c -> SpecDefTree a b c
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
_ -> Text -> Maybe Text -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
Text -> Maybe Text -> SpecDefTree outers inner extra
DefPendingNode Text
t Maybe Text
mMessage
DefPendingNode Text
t Maybe Text
mr -> Text -> Maybe Text -> SpecDefTree a b c
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 -> Text -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
Text
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefDescribeNode Text
t (SpecDefForest a b c -> SpecDefTree a b c)
-> SpecDefForest a b c -> SpecDefTree a b c
forall a b. (a -> b) -> a -> b
$ SpecDefForest a b c -> SpecDefForest a b c
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 -> IO () -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
IO ()
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefSetupNode IO ()
func (SpecDefForest a b c -> SpecDefTree a b c)
-> SpecDefForest a b c -> SpecDefTree a b c
forall a b. (a -> b) -> a -> b
$ SpecDefForest a b c -> SpecDefForest a b c
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 -> IO outer -> SpecDefForest (outer : a) b c -> SpecDefTree a b c
forall newOuter (otherOuters :: [*]) inner extra.
IO newOuter
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefBeforeAllNode IO outer
func (SpecDefForest (outer : a) b c -> SpecDefTree a b c)
-> SpecDefForest (outer : a) b c -> SpecDefTree a b c
forall a b. (a -> b) -> a -> b
$ SpecDefForest (outer : a) b c -> SpecDefForest (outer : a) b c
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 -> (oldOuter -> IO newOuter)
-> SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> SpecDefTree (oldOuter : otherOuters) b c
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 (SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> SpecDefTree (oldOuter : otherOuters) b c)
-> SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> SpecDefTree (oldOuter : otherOuters) b c
forall a b. (a -> b) -> a -> b
$ SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> SpecDefForest (newOuter : oldOuter : otherOuters) b c
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 -> (IO () -> IO ()) -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
(IO () -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefWrapNode IO () -> IO ()
func (SpecDefForest a b c -> SpecDefTree a b c)
-> SpecDefForest a b c -> SpecDefTree a b c
forall a b. (a -> b) -> a -> b
$ SpecDefForest a b c -> SpecDefForest a b c
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 -> ((outer -> IO ()) -> IO ())
-> SpecDefForest (outer : a) b c -> SpecDefTree a b c
forall newOuter (otherOuters :: [*]) inner extra.
((newOuter -> IO ()) -> IO ())
-> SpecDefForest (newOuter : otherOuters) inner extra
-> SpecDefTree otherOuters inner extra
DefAroundAllNode (outer -> IO ()) -> IO ()
func (SpecDefForest (outer : a) b c -> SpecDefTree a b c)
-> SpecDefForest (outer : a) b c -> SpecDefTree a b c
forall a b. (a -> b) -> a -> b
$ SpecDefForest (outer : a) b c -> SpecDefForest (outer : a) b c
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 -> ((newOuter -> IO ()) -> oldOuter -> IO ())
-> SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> SpecDefTree (oldOuter : otherOuters) b c
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 (SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> SpecDefTree (oldOuter : otherOuters) b c)
-> SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> SpecDefTree (oldOuter : otherOuters) b c
forall a b. (a -> b) -> a -> b
$ SpecDefForest (newOuter : oldOuter : otherOuters) b c
-> SpecDefForest (newOuter : oldOuter : otherOuters) b c
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 -> (HList a -> IO ()) -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
(HList outers -> IO ())
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefAfterAllNode HList a -> IO ()
func (SpecDefForest a b c -> SpecDefTree a b c)
-> SpecDefForest a b c -> SpecDefTree a b c
forall a b. (a -> b) -> a -> b
$ SpecDefForest a b c -> SpecDefForest a b c
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 -> Parallelism -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
Parallelism
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefParallelismNode Parallelism
func (SpecDefForest a b c -> SpecDefTree a b c)
-> SpecDefForest a b c -> SpecDefTree a b c
forall a b. (a -> b) -> a -> b
$ SpecDefForest a b c -> SpecDefForest a b c
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 -> (Word -> Word) -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
(Word -> Word)
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRetriesNode Word -> Word
i (SpecDefForest a b c -> SpecDefTree a b c)
-> SpecDefForest a b c -> SpecDefTree a b c
forall a b. (a -> b) -> a -> b
$ SpecDefForest a b c -> SpecDefForest a b c
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 -> FlakinessMode -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
FlakinessMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefFlakinessNode FlakinessMode
i (SpecDefForest a b c -> SpecDefTree a b c)
-> SpecDefForest a b c -> SpecDefTree a b c
forall a b. (a -> b) -> a -> b
$ SpecDefForest a b c -> SpecDefForest a b c
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 -> ExecutionOrderRandomisation
-> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
ExecutionOrderRandomisation
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefRandomisationNode ExecutionOrderRandomisation
eor (SpecDefForest a b c -> SpecDefForest a b c
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 -> ExpectationMode -> SpecDefForest a b c -> SpecDefTree a b c
forall (outers :: [*]) inner extra.
ExpectationMode
-> SpecDefForest outers inner extra
-> SpecDefTree outers inner extra
DefExpectationNode ExpectationMode
i (SpecDefForest a b c -> SpecDefTree a b c)
-> SpecDefForest a b c -> SpecDefTree a b c
forall a b. (a -> b) -> a -> b
$ SpecDefForest a b c -> SpecDefForest a b c
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
(Int -> Parallelism -> ShowS)
-> (Parallelism -> String)
-> ([Parallelism] -> ShowS)
-> Show Parallelism
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Parallelism -> ShowS
showsPrec :: Int -> Parallelism -> ShowS
$cshow :: Parallelism -> String
show :: Parallelism -> String
$cshowList :: [Parallelism] -> ShowS
showList :: [Parallelism] -> ShowS
Show, Parallelism -> Parallelism -> Bool
(Parallelism -> Parallelism -> Bool)
-> (Parallelism -> Parallelism -> Bool) -> Eq Parallelism
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Parallelism -> Parallelism -> Bool
== :: Parallelism -> Parallelism -> Bool
$c/= :: Parallelism -> Parallelism -> Bool
/= :: Parallelism -> Parallelism -> Bool
Eq, (forall x. Parallelism -> Rep Parallelism x)
-> (forall x. Rep Parallelism x -> Parallelism)
-> Generic Parallelism
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
$cfrom :: forall x. Parallelism -> Rep Parallelism x
from :: forall x. Parallelism -> Rep Parallelism x
$cto :: forall x. Rep Parallelism x -> Parallelism
to :: forall x. Rep Parallelism x -> Parallelism
Generic)
data ExecutionOrderRandomisation
= RandomiseExecutionOrder
| DoNotRandomiseExecutionOrder
deriving (Int -> ExecutionOrderRandomisation -> ShowS
[ExecutionOrderRandomisation] -> ShowS
ExecutionOrderRandomisation -> String
(Int -> ExecutionOrderRandomisation -> ShowS)
-> (ExecutionOrderRandomisation -> String)
-> ([ExecutionOrderRandomisation] -> ShowS)
-> Show ExecutionOrderRandomisation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExecutionOrderRandomisation -> ShowS
showsPrec :: Int -> ExecutionOrderRandomisation -> ShowS
$cshow :: ExecutionOrderRandomisation -> String
show :: ExecutionOrderRandomisation -> String
$cshowList :: [ExecutionOrderRandomisation] -> ShowS
showList :: [ExecutionOrderRandomisation] -> ShowS
Show, ExecutionOrderRandomisation -> ExecutionOrderRandomisation -> Bool
(ExecutionOrderRandomisation
-> ExecutionOrderRandomisation -> Bool)
-> (ExecutionOrderRandomisation
-> ExecutionOrderRandomisation -> Bool)
-> Eq ExecutionOrderRandomisation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExecutionOrderRandomisation -> ExecutionOrderRandomisation -> Bool
== :: ExecutionOrderRandomisation -> ExecutionOrderRandomisation -> Bool
$c/= :: ExecutionOrderRandomisation -> ExecutionOrderRandomisation -> Bool
/= :: ExecutionOrderRandomisation -> ExecutionOrderRandomisation -> Bool
Eq, (forall x.
ExecutionOrderRandomisation -> Rep ExecutionOrderRandomisation x)
-> (forall x.
Rep ExecutionOrderRandomisation x -> ExecutionOrderRandomisation)
-> Generic ExecutionOrderRandomisation
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
$cfrom :: forall x.
ExecutionOrderRandomisation -> Rep ExecutionOrderRandomisation x
from :: forall x.
ExecutionOrderRandomisation -> Rep ExecutionOrderRandomisation x
$cto :: forall x.
Rep ExecutionOrderRandomisation x -> ExecutionOrderRandomisation
to :: forall x.
Rep ExecutionOrderRandomisation x -> ExecutionOrderRandomisation
Generic)
data FlakinessMode
= MayNotBeFlaky
| MayBeFlaky !(Maybe String)
deriving (Int -> FlakinessMode -> ShowS
[FlakinessMode] -> ShowS
FlakinessMode -> String
(Int -> FlakinessMode -> ShowS)
-> (FlakinessMode -> String)
-> ([FlakinessMode] -> ShowS)
-> Show FlakinessMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FlakinessMode -> ShowS
showsPrec :: Int -> FlakinessMode -> ShowS
$cshow :: FlakinessMode -> String
show :: FlakinessMode -> String
$cshowList :: [FlakinessMode] -> ShowS
showList :: [FlakinessMode] -> ShowS
Show, FlakinessMode -> FlakinessMode -> Bool
(FlakinessMode -> FlakinessMode -> Bool)
-> (FlakinessMode -> FlakinessMode -> Bool) -> Eq FlakinessMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FlakinessMode -> FlakinessMode -> Bool
== :: FlakinessMode -> FlakinessMode -> Bool
$c/= :: FlakinessMode -> FlakinessMode -> Bool
/= :: FlakinessMode -> FlakinessMode -> Bool
Eq, (forall x. FlakinessMode -> Rep FlakinessMode x)
-> (forall x. Rep FlakinessMode x -> FlakinessMode)
-> Generic FlakinessMode
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
$cfrom :: forall x. FlakinessMode -> Rep FlakinessMode x
from :: forall x. FlakinessMode -> Rep FlakinessMode x
$cto :: forall x. Rep FlakinessMode x -> FlakinessMode
to :: forall x. Rep FlakinessMode x -> FlakinessMode
Generic)
data ExpectationMode
= ExpectPassing
| ExpectFailing
deriving (Int -> ExpectationMode -> ShowS
[ExpectationMode] -> ShowS
ExpectationMode -> String
(Int -> ExpectationMode -> ShowS)
-> (ExpectationMode -> String)
-> ([ExpectationMode] -> ShowS)
-> Show ExpectationMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExpectationMode -> ShowS
showsPrec :: Int -> ExpectationMode -> ShowS
$cshow :: ExpectationMode -> String
show :: ExpectationMode -> String
$cshowList :: [ExpectationMode] -> ShowS
showList :: [ExpectationMode] -> ShowS
Show, ExpectationMode -> ExpectationMode -> Bool
(ExpectationMode -> ExpectationMode -> Bool)
-> (ExpectationMode -> ExpectationMode -> Bool)
-> Eq ExpectationMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExpectationMode -> ExpectationMode -> Bool
== :: ExpectationMode -> ExpectationMode -> Bool
$c/= :: ExpectationMode -> ExpectationMode -> Bool
/= :: ExpectationMode -> ExpectationMode -> Bool
Eq, (forall x. ExpectationMode -> Rep ExpectationMode x)
-> (forall x. Rep ExpectationMode x -> ExpectationMode)
-> Generic ExpectationMode
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
$cfrom :: forall x. ExpectationMode -> Rep ExpectationMode x
from :: forall x. ExpectationMode -> Rep ExpectationMode x
$cto :: forall x. Rep ExpectationMode x -> ExpectationMode
to :: forall x. Rep ExpectationMode x -> ExpectationMode
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 = (SpecTree (TDef (Timed TestRunReport)) -> TestSuiteStats)
-> ResultForest -> TestSuiteStats
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ([Text] -> SpecTree (TDef (Timed TestRunReport)) -> TestSuiteStats
goT [Text]
ts)
goT :: [Text] -> ResultTree -> TestSuiteStats
goT :: [Text] -> SpecTree (TDef (Timed TestRunReport)) -> TestSuiteStats
goT [Text]
ts = \case
SpecifyNode Text
_ (TDef timed :: Timed TestRunReport
timed@Timed {Int
Word64
TestRunReport
timedValue :: TestRunReport
timedWorker :: Int
timedBegin :: Word64
timedEnd :: Word64
timedValue :: forall a. Timed a -> a
timedWorker :: forall a. Timed a -> Int
timedBegin :: forall a. Timed a -> Word64
timedEnd :: forall a. Timed a -> Word64
..} 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 = Timed TestRunReport -> Word64
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 Text -> [Text] -> [Text]
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
(Int -> TestSuiteStats -> ShowS)
-> (TestSuiteStats -> String)
-> ([TestSuiteStats] -> ShowS)
-> Show TestSuiteStats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TestSuiteStats -> ShowS
showsPrec :: Int -> TestSuiteStats -> ShowS
$cshow :: TestSuiteStats -> String
show :: TestSuiteStats -> String
$cshowList :: [TestSuiteStats] -> ShowS
showList :: [TestSuiteStats] -> ShowS
Show, TestSuiteStats -> TestSuiteStats -> Bool
(TestSuiteStats -> TestSuiteStats -> Bool)
-> (TestSuiteStats -> TestSuiteStats -> Bool) -> Eq TestSuiteStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TestSuiteStats -> TestSuiteStats -> Bool
== :: TestSuiteStats -> TestSuiteStats -> Bool
$c/= :: TestSuiteStats -> TestSuiteStats -> Bool
/= :: TestSuiteStats -> TestSuiteStats -> Bool
Eq)
instance Semigroup TestSuiteStats where
<> :: TestSuiteStats -> TestSuiteStats -> TestSuiteStats
(<>) TestSuiteStats
tss1 TestSuiteStats
tss2 =
TestSuiteStats
{ testSuiteStatSuccesses :: Word
testSuiteStatSuccesses = TestSuiteStats -> Word
testSuiteStatSuccesses TestSuiteStats
tss1 Word -> Word -> Word
forall a. Num a => a -> a -> a
+ TestSuiteStats -> Word
testSuiteStatSuccesses TestSuiteStats
tss2,
testSuiteStatExamples :: Word
testSuiteStatExamples = TestSuiteStats -> Word
testSuiteStatExamples TestSuiteStats
tss1 Word -> Word -> Word
forall a. Num a => a -> a -> a
+ TestSuiteStats -> Word
testSuiteStatExamples TestSuiteStats
tss2,
testSuiteStatFailures :: Word
testSuiteStatFailures = TestSuiteStats -> Word
testSuiteStatFailures TestSuiteStats
tss1 Word -> Word -> Word
forall a. Num a => a -> a -> a
+ TestSuiteStats -> Word
testSuiteStatFailures TestSuiteStats
tss2,
testSuiteStatFlakyTests :: Word
testSuiteStatFlakyTests = TestSuiteStats -> Word
testSuiteStatFlakyTests TestSuiteStats
tss1 Word -> Word -> Word
forall a. Num a => a -> a -> a
+ TestSuiteStats -> Word
testSuiteStatFlakyTests TestSuiteStats
tss2,
testSuiteStatPending :: Word
testSuiteStatPending = TestSuiteStats -> Word
testSuiteStatPending TestSuiteStats
tss1 Word -> Word -> Word
forall a. Num a => a -> a -> a
+ TestSuiteStats -> Word
testSuiteStatPending TestSuiteStats
tss2,
testSuiteStatSumTime :: Word64
testSuiteStatSumTime = TestSuiteStats -> Word64
testSuiteStatSumTime TestSuiteStats
tss1 Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ TestSuiteStats -> Word64
testSuiteStatSumTime TestSuiteStats
tss2
}
instance Monoid TestSuiteStats where
mappend :: TestSuiteStats -> TestSuiteStats -> TestSuiteStats
mappend = TestSuiteStats -> TestSuiteStats -> TestSuiteStats
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 = (SpecTree (TDef (Timed TestRunReport)) -> Bool)
-> ResultForest -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((TDef (Timed TestRunReport) -> Bool)
-> SpecTree (TDef (Timed TestRunReport)) -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Settings -> TestRunReport -> Bool
testRunReportFailed Settings
settings (TestRunReport -> Bool)
-> (TDef (Timed TestRunReport) -> TestRunReport)
-> TDef (Timed TestRunReport)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Timed TestRunReport -> TestRunReport
forall a. Timed a -> a
timedValue (Timed TestRunReport -> TestRunReport)
-> (TDef (Timed TestRunReport) -> Timed TestRunReport)
-> TDef (Timed TestRunReport)
-> TestRunReport
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TDef (Timed TestRunReport) -> Timed TestRunReport
forall value. TDef value -> value
testDefVal))
data TestRunReport = TestRunReport
{ TestRunReport -> ExpectationMode
testRunReportExpectationMode :: !ExpectationMode,
TestRunReport -> NonEmpty TestRunResult
testRunReportRawResults :: !(NonEmpty TestRunResult),
TestRunReport -> FlakinessMode
testRunReportFlakinessMode :: !FlakinessMode
}
deriving (Int -> TestRunReport -> ShowS
[TestRunReport] -> ShowS
TestRunReport -> String
(Int -> TestRunReport -> ShowS)
-> (TestRunReport -> String)
-> ([TestRunReport] -> ShowS)
-> Show TestRunReport
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TestRunReport -> ShowS
showsPrec :: Int -> TestRunReport -> ShowS
$cshow :: TestRunReport -> String
show :: TestRunReport -> String
$cshowList :: [TestRunReport] -> ShowS
showList :: [TestRunReport] -> ShowS
Show, (forall x. TestRunReport -> Rep TestRunReport x)
-> (forall x. Rep TestRunReport x -> TestRunReport)
-> Generic TestRunReport
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
$cfrom :: forall x. TestRunReport -> Rep TestRunReport x
from :: forall x. TestRunReport -> Rep TestRunReport x
$cto :: forall x. Rep TestRunReport x -> TestRunReport
to :: forall x. Rep TestRunReport x -> TestRunReport
Generic)
testRunReportReportedRun :: TestRunReport -> TestRunResult
testRunReportReportedRun :: TestRunReport -> TestRunResult
testRunReportReportedRun TestRunReport {NonEmpty TestRunResult
ExpectationMode
FlakinessMode
testRunReportExpectationMode :: TestRunReport -> ExpectationMode
testRunReportRawResults :: TestRunReport -> NonEmpty TestRunResult
testRunReportFlakinessMode :: TestRunReport -> FlakinessMode
testRunReportExpectationMode :: ExpectationMode
testRunReportRawResults :: NonEmpty TestRunResult
testRunReportFlakinessMode :: FlakinessMode
..} =
let reversed :: NonEmpty TestRunResult
reversed = NonEmpty TestRunResult -> NonEmpty TestRunResult
forall a. NonEmpty a -> NonEmpty a
NE.reverse NonEmpty TestRunResult
testRunReportRawResults
in case (TestRunResult -> Bool)
-> NonEmpty TestRunResult -> Maybe TestRunResult
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((TestStatus -> TestStatus -> Bool
forall a. Eq a => a -> a -> Bool
== TestStatus
TestFailed) (TestStatus -> Bool)
-> (TestRunResult -> TestStatus) -> TestRunResult -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestRunResult -> TestStatus
testRunResultStatus) NonEmpty TestRunResult
testRunReportRawResults of
Maybe TestRunResult
Nothing -> NonEmpty TestRunResult -> TestRunResult
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 TestStatus -> TestStatus -> Bool
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
settingSeed :: SeedSetting
settingRandomiseExecutionOrder :: Bool
settingThreads :: Threads
settingMaxSuccess :: Int
settingMaxSize :: Int
settingMaxDiscard :: Int
settingMaxShrinks :: Int
settingGoldenStart :: Bool
settingGoldenReset :: Bool
settingColour :: Maybe Bool
settingFilters :: [Text]
settingFailFast :: Bool
settingIterations :: Iterations
settingRetries :: Word
settingFailOnFlaky :: Bool
settingReportProgress :: ReportProgress
settingProfile :: Bool
settingSeed :: Settings -> SeedSetting
settingRandomiseExecutionOrder :: Settings -> Bool
settingThreads :: Settings -> Threads
settingMaxSuccess :: Settings -> Int
settingMaxSize :: Settings -> Int
settingMaxDiscard :: Settings -> Int
settingMaxShrinks :: Settings -> Int
settingGoldenStart :: Settings -> Bool
settingGoldenReset :: Settings -> Bool
settingColour :: Settings -> Maybe Bool
settingFilters :: Settings -> [Text]
settingFailFast :: Settings -> Bool
settingIterations :: Settings -> Iterations
settingRetries :: Settings -> Word
settingFailOnFlaky :: Settings -> Bool
settingReportProgress :: Settings -> ReportProgress
settingProfile :: Settings -> Bool
..} testRunReport :: TestRunReport
testRunReport@TestRunReport {NonEmpty TestRunResult
ExpectationMode
FlakinessMode
testRunReportExpectationMode :: TestRunReport -> ExpectationMode
testRunReportRawResults :: TestRunReport -> NonEmpty TestRunResult
testRunReportFlakinessMode :: TestRunReport -> FlakinessMode
testRunReportExpectationMode :: ExpectationMode
testRunReportRawResults :: NonEmpty TestRunResult
testRunReportFlakinessMode :: FlakinessMode
..} =
let wasFlaky :: Bool
wasFlaky = TestRunReport -> Bool
testRunReportWasFlaky TestRunReport
testRunReport
lastResult :: TestRunResult
lastResult = NonEmpty TestRunResult -> TestRunResult
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 (TestRunResult -> Bool) -> NonEmpty TestRunResult -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((TestStatus -> TestStatus -> Bool
forall a. Eq a => a -> a -> Bool
== TestStatus
TestPassed) (TestStatus -> Bool)
-> (TestRunResult -> TestStatus) -> TestRunResult -> Bool
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 = NonEmpty Word -> Word
forall a. Num a => NonEmpty a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (NonEmpty Word -> Word)
-> (TestRunReport -> NonEmpty Word) -> TestRunReport -> Word
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TestRunResult -> Word) -> NonEmpty TestRunResult -> NonEmpty Word
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map TestRunResult -> Word
testRunResultExamples (NonEmpty TestRunResult -> NonEmpty Word)
-> (TestRunReport -> NonEmpty TestRunResult)
-> TestRunReport
-> NonEmpty Word
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
testRunResultStatus :: TestRunResult -> TestStatus
testRunResultStatus :: TestStatus
testRunResultException :: Maybe SomeException
testRunResultNumTests :: Maybe Word
testRunResultNumShrinks :: Maybe Word
testRunResultFailingInputs :: [String]
testRunResultLabels :: Maybe (Map [String] Int)
testRunResultClasses :: Maybe (Map String Int)
testRunResultTables :: Maybe (Map String (Map String Int))
testRunResultGoldenCase :: Maybe GoldenCase
testRunResultExtraInfo :: Maybe String
testRunResultException :: TestRunResult -> Maybe SomeException
testRunResultNumTests :: TestRunResult -> Maybe Word
testRunResultNumShrinks :: TestRunResult -> Maybe Word
testRunResultFailingInputs :: TestRunResult -> [String]
testRunResultLabels :: TestRunResult -> Maybe (Map [String] Int)
testRunResultClasses :: TestRunResult -> Maybe (Map String Int)
testRunResultTables :: TestRunResult -> Maybe (Map String (Map String Int))
testRunResultGoldenCase :: TestRunResult -> Maybe GoldenCase
testRunResultExtraInfo :: TestRunResult -> Maybe String
..} =
Word -> Maybe Word -> Word
forall a. a -> Maybe a -> a
fromMaybe Word
1 Maybe Word
testRunResultNumTests Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word -> Maybe Word -> Word
forall a. a -> Maybe a -> a
fromMaybe Word
0 Maybe Word
testRunResultNumShrinks
testRunReportWasFlaky :: TestRunReport -> Bool
testRunReportWasFlaky :: TestRunReport -> Bool
testRunReportWasFlaky =
(Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1)
(Int -> Bool) -> (TestRunReport -> Int) -> TestRunReport -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [NonEmpty TestStatus] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length
([NonEmpty TestStatus] -> Int)
-> (TestRunReport -> [NonEmpty TestStatus]) -> TestRunReport -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty TestStatus -> [NonEmpty TestStatus]
forall (f :: * -> *) a. (Foldable f, Eq a) => f a -> [NonEmpty a]
NE.group
(NonEmpty TestStatus -> [NonEmpty TestStatus])
-> (TestRunReport -> NonEmpty TestStatus)
-> TestRunReport
-> [NonEmpty TestStatus]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TestRunResult -> TestStatus)
-> NonEmpty TestRunResult -> NonEmpty TestStatus
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map TestRunResult -> TestStatus
testRunResultStatus
(NonEmpty TestRunResult -> NonEmpty TestStatus)
-> (TestRunReport -> NonEmpty TestRunResult)
-> TestRunReport
-> NonEmpty TestStatus
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
testRunReportExpectationMode :: TestRunReport -> ExpectationMode
testRunReportRawResults :: TestRunReport -> NonEmpty TestRunResult
testRunReportFlakinessMode :: TestRunReport -> FlakinessMode
testRunReportExpectationMode :: ExpectationMode
testRunReportRawResults :: NonEmpty TestRunResult
testRunReportFlakinessMode :: FlakinessMode
..} = case NonEmpty TestRunResult -> Int
forall a. NonEmpty a -> Int
NE.length NonEmpty TestRunResult
testRunReportRawResults of
Int
1 -> Maybe Word
forall a. Maybe a
Nothing
Int
l -> Word -> Maybe Word
forall a. a -> Maybe a
Just (Word -> Maybe Word) -> Word -> Maybe Word
forall a b. (a -> b) -> a -> b
$ Int -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l