{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
module Test.Tasty.Core
( FailureReason(..)
, Outcome(..)
, Time
, Result(..)
, resultSuccessful
, exceptionResult
, Progress(..)
, emptyProgress
, IsTest(..)
, TestName
, ResourceSpec(..)
, ResourceError(..)
, DependencyType(..)
, ExecutionMode(..)
, TestTree(..)
, testGroup
, sequentialTestGroup
, after
, after_
, TreeFold(..)
, trivialFold
, foldTestTree
, foldTestTree0
, treeOptions
) where
import Control.Exception
import qualified Data.Map as Map
import Data.Bifunctor (Bifunctor(second, bimap))
import Data.List (mapAccumR)
import Data.Monoid (Any (getAny, Any))
import Data.Sequence ((|>))
import qualified Data.Sequence as Seq
import Data.Tagged
import Data.Typeable
import GHC.Generics
import Options.Applicative (internal)
import Test.Tasty.Options
import Test.Tasty.Patterns
import Test.Tasty.Patterns.Types
import Test.Tasty.Providers.ConsoleFormat
import Text.Printf
import Text.Read (readMaybe)
data FailureReason
= TestFailed
| TestThrewException SomeException
| TestTimedOut Integer
| TestDepFailed
deriving Int -> FailureReason -> ShowS
[FailureReason] -> ShowS
FailureReason -> TestName
(Int -> FailureReason -> ShowS)
-> (FailureReason -> TestName)
-> ([FailureReason] -> ShowS)
-> Show FailureReason
forall a.
(Int -> a -> ShowS) -> (a -> TestName) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FailureReason -> ShowS
showsPrec :: Int -> FailureReason -> ShowS
$cshow :: FailureReason -> TestName
show :: FailureReason -> TestName
$cshowList :: [FailureReason] -> ShowS
showList :: [FailureReason] -> ShowS
Show
data Outcome
= Success
| Failure FailureReason
deriving (Int -> Outcome -> ShowS
[Outcome] -> ShowS
Outcome -> TestName
(Int -> Outcome -> ShowS)
-> (Outcome -> TestName) -> ([Outcome] -> ShowS) -> Show Outcome
forall a.
(Int -> a -> ShowS) -> (a -> TestName) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Outcome -> ShowS
showsPrec :: Int -> Outcome -> ShowS
$cshow :: Outcome -> TestName
show :: Outcome -> TestName
$cshowList :: [Outcome] -> ShowS
showList :: [Outcome] -> ShowS
Show, (forall x. Outcome -> Rep Outcome x)
-> (forall x. Rep Outcome x -> Outcome) -> Generic Outcome
forall x. Rep Outcome x -> Outcome
forall x. Outcome -> Rep Outcome x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Outcome -> Rep Outcome x
from :: forall x. Outcome -> Rep Outcome x
$cto :: forall x. Rep Outcome x -> Outcome
to :: forall x. Rep Outcome x -> Outcome
Generic)
type Time = Double
data Result = Result
{ Result -> Outcome
resultOutcome :: Outcome
, Result -> TestName
resultDescription :: String
, Result -> TestName
resultShortDescription :: String
, Result -> Time
resultTime :: Time
, Result -> ResultDetailsPrinter
resultDetailsPrinter :: ResultDetailsPrinter
}
deriving
( Int -> Result -> ShowS
[Result] -> ShowS
Result -> TestName
(Int -> Result -> ShowS)
-> (Result -> TestName) -> ([Result] -> ShowS) -> Show Result
forall a.
(Int -> a -> ShowS) -> (a -> TestName) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Result -> ShowS
showsPrec :: Int -> Result -> ShowS
$cshow :: Result -> TestName
show :: Result -> TestName
$cshowList :: [Result] -> ShowS
showList :: [Result] -> ShowS
Show
)
resultSuccessful :: Result -> Bool
resultSuccessful :: Result -> Bool
resultSuccessful Result
r =
case Result -> Outcome
resultOutcome Result
r of
Outcome
Success -> Bool
True
Failure {} -> Bool
False
exceptionResult :: SomeException -> Result
exceptionResult :: SomeException -> Result
exceptionResult SomeException
e = Result
{ resultOutcome :: Outcome
resultOutcome = FailureReason -> Outcome
Failure (FailureReason -> Outcome) -> FailureReason -> Outcome
forall a b. (a -> b) -> a -> b
$ SomeException -> FailureReason
TestThrewException SomeException
e
, resultDescription :: TestName
resultDescription = TestName
"Exception: " TestName -> ShowS
forall a. [a] -> [a] -> [a]
++ SomeException -> TestName
forall e. Exception e => e -> TestName
displayException SomeException
e
, resultShortDescription :: TestName
resultShortDescription = TestName
"FAIL"
, resultTime :: Time
resultTime = Time
0
, resultDetailsPrinter :: ResultDetailsPrinter
resultDetailsPrinter = ResultDetailsPrinter
noResultDetails
}
data Progress = Progress
{ Progress -> TestName
progressText :: String
, Progress -> Float
progressPercent :: Float
}
deriving
( Int -> Progress -> ShowS
[Progress] -> ShowS
Progress -> TestName
(Int -> Progress -> ShowS)
-> (Progress -> TestName) -> ([Progress] -> ShowS) -> Show Progress
forall a.
(Int -> a -> ShowS) -> (a -> TestName) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Progress -> ShowS
showsPrec :: Int -> Progress -> ShowS
$cshow :: Progress -> TestName
show :: Progress -> TestName
$cshowList :: [Progress] -> ShowS
showList :: [Progress] -> ShowS
Show
, Progress -> Progress -> Bool
(Progress -> Progress -> Bool)
-> (Progress -> Progress -> Bool) -> Eq Progress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Progress -> Progress -> Bool
== :: Progress -> Progress -> Bool
$c/= :: Progress -> Progress -> Bool
/= :: Progress -> Progress -> Bool
Eq
)
emptyProgress :: Progress
emptyProgress :: Progress
emptyProgress = TestName -> Float -> Progress
Progress TestName
forall a. Monoid a => a
mempty Float
0.0
class Typeable t => IsTest t where
run
:: OptionSet
-> t
-> (Progress -> IO ())
-> IO Result
testOptions :: Tagged t [OptionDescription]
type TestName = String
data ResourceSpec a = ResourceSpec (IO a) (a -> IO ())
data ResourceError
= NotRunningTests
| UnexpectedState String String
| UseOutsideOfTest
deriving Typeable
instance Show ResourceError where
show :: ResourceError -> TestName
show ResourceError
NotRunningTests =
TestName
"Unhandled resource. Probably a bug in the runner you're using."
show (UnexpectedState TestName
where_ TestName
what) =
TestName -> TestName -> ShowS
forall r. PrintfType r => TestName -> r
printf TestName
"Unexpected state of the resource (%s) in %s. Report as a tasty bug."
TestName
what TestName
where_
show ResourceError
UseOutsideOfTest =
TestName
"It looks like you're attempting to use a resource outside of its test. Don't do that!"
instance Exception ResourceError
data DependencyType
= AllSucceed
| AllFinish
deriving
( DependencyType -> DependencyType -> Bool
(DependencyType -> DependencyType -> Bool)
-> (DependencyType -> DependencyType -> Bool) -> Eq DependencyType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DependencyType -> DependencyType -> Bool
== :: DependencyType -> DependencyType -> Bool
$c/= :: DependencyType -> DependencyType -> Bool
/= :: DependencyType -> DependencyType -> Bool
Eq
, Int -> DependencyType -> ShowS
[DependencyType] -> ShowS
DependencyType -> TestName
(Int -> DependencyType -> ShowS)
-> (DependencyType -> TestName)
-> ([DependencyType] -> ShowS)
-> Show DependencyType
forall a.
(Int -> a -> ShowS) -> (a -> TestName) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DependencyType -> ShowS
showsPrec :: Int -> DependencyType -> ShowS
$cshow :: DependencyType -> TestName
show :: DependencyType -> TestName
$cshowList :: [DependencyType] -> ShowS
showList :: [DependencyType] -> ShowS
Show
, ReadPrec [DependencyType]
ReadPrec DependencyType
Int -> ReadS DependencyType
ReadS [DependencyType]
(Int -> ReadS DependencyType)
-> ReadS [DependencyType]
-> ReadPrec DependencyType
-> ReadPrec [DependencyType]
-> Read DependencyType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DependencyType
readsPrec :: Int -> ReadS DependencyType
$creadList :: ReadS [DependencyType]
readList :: ReadS [DependencyType]
$creadPrec :: ReadPrec DependencyType
readPrec :: ReadPrec DependencyType
$creadListPrec :: ReadPrec [DependencyType]
readListPrec :: ReadPrec [DependencyType]
Read
)
data ExecutionMode
= Sequential DependencyType
| Parallel
deriving (Int -> ExecutionMode -> ShowS
[ExecutionMode] -> ShowS
ExecutionMode -> TestName
(Int -> ExecutionMode -> ShowS)
-> (ExecutionMode -> TestName)
-> ([ExecutionMode] -> ShowS)
-> Show ExecutionMode
forall a.
(Int -> a -> ShowS) -> (a -> TestName) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExecutionMode -> ShowS
showsPrec :: Int -> ExecutionMode -> ShowS
$cshow :: ExecutionMode -> TestName
show :: ExecutionMode -> TestName
$cshowList :: [ExecutionMode] -> ShowS
showList :: [ExecutionMode] -> ShowS
Show, ReadPrec [ExecutionMode]
ReadPrec ExecutionMode
Int -> ReadS ExecutionMode
ReadS [ExecutionMode]
(Int -> ReadS ExecutionMode)
-> ReadS [ExecutionMode]
-> ReadPrec ExecutionMode
-> ReadPrec [ExecutionMode]
-> Read ExecutionMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ExecutionMode
readsPrec :: Int -> ReadS ExecutionMode
$creadList :: ReadS [ExecutionMode]
readList :: ReadS [ExecutionMode]
$creadPrec :: ReadPrec ExecutionMode
readPrec :: ReadPrec ExecutionMode
$creadListPrec :: ReadPrec [ExecutionMode]
readListPrec :: ReadPrec [ExecutionMode]
Read)
instance IsOption ExecutionMode where
defaultValue :: ExecutionMode
defaultValue = ExecutionMode
Parallel
parseValue :: TestName -> Maybe ExecutionMode
parseValue = TestName -> Maybe ExecutionMode
forall a. Read a => TestName -> Maybe a
readMaybe
optionName :: Tagged ExecutionMode TestName
optionName = TestName -> Tagged ExecutionMode TestName
forall {k} (s :: k) b. b -> Tagged s b
Tagged TestName
"execution-mode"
optionHelp :: Tagged ExecutionMode TestName
optionHelp = TestName -> Tagged ExecutionMode TestName
forall {k} (s :: k) b. b -> Tagged s b
Tagged TestName
"Whether to execute tests sequentially or in parallel"
optionCLParser :: Parser ExecutionMode
optionCLParser = Mod OptionFields ExecutionMode -> Parser ExecutionMode
forall v. IsOption v => Mod OptionFields v -> Parser v
mkOptionCLParser Mod OptionFields ExecutionMode
forall (f :: * -> *) a. Mod f a
internal
data TestTree
= forall t . IsTest t => SingleTest TestName t
| TestGroup TestName [TestTree]
| PlusTestOptions (OptionSet -> OptionSet) TestTree
| forall a . WithResource (ResourceSpec a) (IO a -> TestTree)
| AskOptions (OptionSet -> TestTree)
| After DependencyType Expr TestTree
testGroup :: TestName -> [TestTree] -> TestTree
testGroup :: TestName -> [TestTree] -> TestTree
testGroup = TestName -> [TestTree] -> TestTree
TestGroup
sequentialTestGroup :: TestName -> DependencyType -> [TestTree] -> TestTree
sequentialTestGroup :: TestName -> DependencyType -> [TestTree] -> TestTree
sequentialTestGroup TestName
nm DependencyType
depType = TestTree -> TestTree
setSequential (TestTree -> TestTree)
-> ([TestTree] -> TestTree) -> [TestTree] -> TestTree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestName -> [TestTree] -> TestTree
TestGroup TestName
nm ([TestTree] -> TestTree)
-> ([TestTree] -> [TestTree]) -> [TestTree] -> TestTree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TestTree -> TestTree) -> [TestTree] -> [TestTree]
forall a b. (a -> b) -> [a] -> [b]
map TestTree -> TestTree
setParallel
where
setParallel :: TestTree -> TestTree
setParallel = (OptionSet -> OptionSet) -> TestTree -> TestTree
PlusTestOptions (ExecutionMode -> OptionSet -> OptionSet
forall v. IsOption v => v -> OptionSet -> OptionSet
setOption ExecutionMode
Parallel)
setSequential :: TestTree -> TestTree
setSequential = (OptionSet -> OptionSet) -> TestTree -> TestTree
PlusTestOptions (ExecutionMode -> OptionSet -> OptionSet
forall v. IsOption v => v -> OptionSet -> OptionSet
setOption (DependencyType -> ExecutionMode
Sequential DependencyType
depType))
after_
:: DependencyType
-> Expr
-> TestTree
-> TestTree
after_ :: DependencyType -> Expr -> TestTree -> TestTree
after_ = DependencyType -> Expr -> TestTree -> TestTree
After
after
:: DependencyType
-> String
-> TestTree
-> TestTree
after :: DependencyType -> TestName -> TestTree -> TestTree
after DependencyType
deptype TestName
s =
case TestName -> Maybe Expr
parseExpr TestName
s of
Maybe Expr
Nothing -> TestName -> TestTree -> TestTree
forall a. HasCallStack => TestName -> a
error (TestName -> TestTree -> TestTree)
-> TestName -> TestTree -> TestTree
forall a b. (a -> b) -> a -> b
$ TestName
"Could not parse pattern " TestName -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> TestName
show TestName
s
Just Expr
e -> DependencyType -> Expr -> TestTree -> TestTree
after_ DependencyType
deptype Expr
e
data TreeFold b = TreeFold
{ forall b.
TreeFold b -> forall t. IsTest t => OptionSet -> TestName -> t -> b
foldSingle :: forall t . IsTest t => OptionSet -> TestName -> t -> b
, forall b. TreeFold b -> OptionSet -> TestName -> [b] -> b
foldGroup :: OptionSet -> TestName -> [b] -> b
, forall b.
TreeFold b
-> forall a. OptionSet -> ResourceSpec a -> (IO a -> b) -> b
foldResource :: forall a . OptionSet -> ResourceSpec a -> (IO a -> b) -> b
, forall b.
TreeFold b -> OptionSet -> DependencyType -> Expr -> b -> b
foldAfter :: OptionSet -> DependencyType -> Expr -> b -> b
}
trivialFold :: Monoid b => TreeFold b
trivialFold :: forall b. Monoid b => TreeFold b
trivialFold = TreeFold
{ foldSingle :: forall t. IsTest t => OptionSet -> TestName -> t -> b
foldSingle = \OptionSet
_ TestName
_ t
_ -> b
forall a. Monoid a => a
mempty
, foldGroup :: OptionSet -> TestName -> [b] -> b
foldGroup = \OptionSet
_ TestName
_ [b]
bs -> [b] -> b
forall a. Monoid a => [a] -> a
mconcat [b]
bs
, foldResource :: forall a. OptionSet -> ResourceSpec a -> (IO a -> b) -> b
foldResource = \OptionSet
_ ResourceSpec a
_ IO a -> b
f -> IO a -> b
f (IO a -> b) -> IO a -> b
forall a b. (a -> b) -> a -> b
$ ResourceError -> IO a
forall e a. Exception e => e -> IO a
throwIO ResourceError
NotRunningTests
, foldAfter :: OptionSet -> DependencyType -> Expr -> b -> b
foldAfter = \OptionSet
_ DependencyType
_ Expr
_ b
b -> b
b
}
type TestMatched = Any
type ForceTestMatch = Any
foldTestTree
:: forall b . Monoid b
=> TreeFold b
-> OptionSet
-> TestTree
-> b
foldTestTree :: forall b. Monoid b => TreeFold b -> OptionSet -> TestTree -> b
foldTestTree = b -> TreeFold b -> OptionSet -> TestTree -> b
forall b. b -> TreeFold b -> OptionSet -> TestTree -> b
foldTestTree0 b
forall a. Monoid a => a
mempty
foldTestTree0
:: forall b
. b
-> TreeFold b
-> OptionSet
-> TestTree
-> b
foldTestTree0 :: forall b. b -> TreeFold b -> OptionSet -> TestTree -> b
foldTestTree0 b
empty (TreeFold forall t. IsTest t => OptionSet -> TestName -> t -> b
fTest OptionSet -> TestName -> [b] -> b
fGroup forall a. OptionSet -> ResourceSpec a -> (IO a -> b) -> b
fResource OptionSet -> DependencyType -> Expr -> b -> b
fAfter) OptionSet
opts0 TestTree
tree0 =
AnnTestTree OptionSet -> b
go (AnnTestTree (OptionSet, Seq TestName) -> AnnTestTree OptionSet
filterByPattern (AnnTestTree OptionSet -> AnnTestTree (OptionSet, Seq TestName)
annotatePath (OptionSet -> TestTree -> AnnTestTree OptionSet
evaluateOptions OptionSet
opts0 TestTree
tree0)))
where
go :: AnnTestTree OptionSet -> b
go :: AnnTestTree OptionSet -> b
go = \case
AnnTestTree OptionSet
AnnEmptyTestTree -> b
empty
AnnSingleTest OptionSet
opts TestName
name t
test -> OptionSet -> TestName -> t -> b
forall t. IsTest t => OptionSet -> TestName -> t -> b
fTest OptionSet
opts TestName
name t
test
AnnTestGroup OptionSet
opts TestName
name [AnnTestTree OptionSet]
trees -> OptionSet -> TestName -> [b] -> b
fGroup OptionSet
opts TestName
name ((AnnTestTree OptionSet -> b) -> [AnnTestTree OptionSet] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map AnnTestTree OptionSet -> b
go [AnnTestTree OptionSet]
trees)
AnnWithResource OptionSet
opts ResourceSpec a
res0 IO a -> AnnTestTree OptionSet
tree -> OptionSet -> ResourceSpec a -> (IO a -> b) -> b
forall a. OptionSet -> ResourceSpec a -> (IO a -> b) -> b
fResource OptionSet
opts ResourceSpec a
res0 ((IO a -> b) -> b) -> (IO a -> b) -> b
forall a b. (a -> b) -> a -> b
$ \IO a
res -> AnnTestTree OptionSet -> b
go (IO a -> AnnTestTree OptionSet
tree IO a
res)
AnnAfter OptionSet
opts DependencyType
deptype Expr
dep AnnTestTree OptionSet
tree -> OptionSet -> DependencyType -> Expr -> b -> b
fAfter OptionSet
opts DependencyType
deptype Expr
dep (AnnTestTree OptionSet -> b
go AnnTestTree OptionSet
tree)
data AnnTestTree ann
= AnnEmptyTestTree
| forall t . IsTest t => AnnSingleTest ann TestName t
| AnnTestGroup ann TestName [AnnTestTree ann]
| forall a . AnnWithResource ann (ResourceSpec a) (IO a -> AnnTestTree ann)
| AnnAfter ann DependencyType Expr (AnnTestTree ann)
evaluateOptions :: OptionSet -> TestTree -> AnnTestTree OptionSet
evaluateOptions :: OptionSet -> TestTree -> AnnTestTree OptionSet
evaluateOptions OptionSet
opts = \case
SingleTest TestName
name t
test ->
OptionSet -> TestName -> t -> AnnTestTree OptionSet
forall ann t. IsTest t => ann -> TestName -> t -> AnnTestTree ann
AnnSingleTest OptionSet
opts TestName
name t
test
TestGroup TestName
name [TestTree]
trees ->
OptionSet
-> TestName -> [AnnTestTree OptionSet] -> AnnTestTree OptionSet
forall ann. ann -> TestName -> [AnnTestTree ann] -> AnnTestTree ann
AnnTestGroup OptionSet
opts TestName
name ([AnnTestTree OptionSet] -> AnnTestTree OptionSet)
-> [AnnTestTree OptionSet] -> AnnTestTree OptionSet
forall a b. (a -> b) -> a -> b
$ (TestTree -> AnnTestTree OptionSet)
-> [TestTree] -> [AnnTestTree OptionSet]
forall a b. (a -> b) -> [a] -> [b]
map (OptionSet -> TestTree -> AnnTestTree OptionSet
evaluateOptions OptionSet
opts) [TestTree]
trees
PlusTestOptions OptionSet -> OptionSet
f TestTree
tree ->
OptionSet -> TestTree -> AnnTestTree OptionSet
evaluateOptions (OptionSet -> OptionSet
f OptionSet
opts) TestTree
tree
WithResource ResourceSpec a
res0 IO a -> TestTree
tree ->
OptionSet
-> ResourceSpec a
-> (IO a -> AnnTestTree OptionSet)
-> AnnTestTree OptionSet
forall ann a.
ann
-> ResourceSpec a -> (IO a -> AnnTestTree ann) -> AnnTestTree ann
AnnWithResource OptionSet
opts ResourceSpec a
res0 ((IO a -> AnnTestTree OptionSet) -> AnnTestTree OptionSet)
-> (IO a -> AnnTestTree OptionSet) -> AnnTestTree OptionSet
forall a b. (a -> b) -> a -> b
$ \IO a
res -> OptionSet -> TestTree -> AnnTestTree OptionSet
evaluateOptions OptionSet
opts (IO a -> TestTree
tree IO a
res)
AskOptions OptionSet -> TestTree
f ->
OptionSet -> TestTree -> AnnTestTree OptionSet
evaluateOptions OptionSet
opts (OptionSet -> TestTree
f OptionSet
opts)
After DependencyType
deptype Expr
dep TestTree
tree ->
OptionSet
-> DependencyType
-> Expr
-> AnnTestTree OptionSet
-> AnnTestTree OptionSet
forall ann.
ann -> DependencyType -> Expr -> AnnTestTree ann -> AnnTestTree ann
AnnAfter OptionSet
opts DependencyType
deptype Expr
dep (AnnTestTree OptionSet -> AnnTestTree OptionSet)
-> AnnTestTree OptionSet -> AnnTestTree OptionSet
forall a b. (a -> b) -> a -> b
$ OptionSet -> TestTree -> AnnTestTree OptionSet
evaluateOptions OptionSet
opts TestTree
tree
annotatePath :: AnnTestTree OptionSet -> AnnTestTree (OptionSet, Path)
annotatePath :: AnnTestTree OptionSet -> AnnTestTree (OptionSet, Seq TestName)
annotatePath = Seq TestName
-> AnnTestTree OptionSet -> AnnTestTree (OptionSet, Seq TestName)
go Seq TestName
forall a. Monoid a => a
mempty
where
go :: Seq.Seq TestName -> AnnTestTree OptionSet -> AnnTestTree (OptionSet, Path)
go :: Seq TestName
-> AnnTestTree OptionSet -> AnnTestTree (OptionSet, Seq TestName)
go Seq TestName
path = \case
AnnTestTree OptionSet
AnnEmptyTestTree -> AnnTestTree (OptionSet, Seq TestName)
forall ann. AnnTestTree ann
AnnEmptyTestTree
AnnSingleTest OptionSet
opts TestName
name t
tree ->
(OptionSet, Seq TestName)
-> TestName -> t -> AnnTestTree (OptionSet, Seq TestName)
forall ann t. IsTest t => ann -> TestName -> t -> AnnTestTree ann
AnnSingleTest (OptionSet
opts, Seq TestName
path Seq TestName -> TestName -> Seq TestName
forall a. Seq a -> a -> Seq a
|> TestName
name) TestName
name t
tree
AnnTestGroup OptionSet
opts TestName
name [AnnTestTree OptionSet]
trees ->
let newPath :: Seq TestName
newPath = Seq TestName
path Seq TestName -> TestName -> Seq TestName
forall a. Seq a -> a -> Seq a
|> TestName
name in
(OptionSet, Seq TestName)
-> TestName
-> [AnnTestTree (OptionSet, Seq TestName)]
-> AnnTestTree (OptionSet, Seq TestName)
forall ann. ann -> TestName -> [AnnTestTree ann] -> AnnTestTree ann
AnnTestGroup (OptionSet
opts, Seq TestName
newPath) TestName
name ((AnnTestTree OptionSet -> AnnTestTree (OptionSet, Seq TestName))
-> [AnnTestTree OptionSet]
-> [AnnTestTree (OptionSet, Seq TestName)]
forall a b. (a -> b) -> [a] -> [b]
map (Seq TestName
-> AnnTestTree OptionSet -> AnnTestTree (OptionSet, Seq TestName)
go Seq TestName
newPath) [AnnTestTree OptionSet]
trees)
AnnWithResource OptionSet
opts ResourceSpec a
res0 IO a -> AnnTestTree OptionSet
tree ->
(OptionSet, Seq TestName)
-> ResourceSpec a
-> (IO a -> AnnTestTree (OptionSet, Seq TestName))
-> AnnTestTree (OptionSet, Seq TestName)
forall ann a.
ann
-> ResourceSpec a -> (IO a -> AnnTestTree ann) -> AnnTestTree ann
AnnWithResource (OptionSet
opts, Seq TestName
path) ResourceSpec a
res0 ((IO a -> AnnTestTree (OptionSet, Seq TestName))
-> AnnTestTree (OptionSet, Seq TestName))
-> (IO a -> AnnTestTree (OptionSet, Seq TestName))
-> AnnTestTree (OptionSet, Seq TestName)
forall a b. (a -> b) -> a -> b
$ \IO a
res -> Seq TestName
-> AnnTestTree OptionSet -> AnnTestTree (OptionSet, Seq TestName)
go Seq TestName
path (IO a -> AnnTestTree OptionSet
tree IO a
res)
AnnAfter OptionSet
opts DependencyType
deptype Expr
dep AnnTestTree OptionSet
tree ->
(OptionSet, Seq TestName)
-> DependencyType
-> Expr
-> AnnTestTree (OptionSet, Seq TestName)
-> AnnTestTree (OptionSet, Seq TestName)
forall ann.
ann -> DependencyType -> Expr -> AnnTestTree ann -> AnnTestTree ann
AnnAfter (OptionSet
opts, Seq TestName
path) DependencyType
deptype Expr
dep (Seq TestName
-> AnnTestTree OptionSet -> AnnTestTree (OptionSet, Seq TestName)
go Seq TestName
path AnnTestTree OptionSet
tree)
filterByPattern :: AnnTestTree (OptionSet, Path) -> AnnTestTree OptionSet
filterByPattern :: AnnTestTree (OptionSet, Seq TestName) -> AnnTestTree OptionSet
filterByPattern = (TestMatched, AnnTestTree OptionSet) -> AnnTestTree OptionSet
forall a b. (a, b) -> b
snd ((TestMatched, AnnTestTree OptionSet) -> AnnTestTree OptionSet)
-> (AnnTestTree (OptionSet, Seq TestName)
-> (TestMatched, AnnTestTree OptionSet))
-> AnnTestTree (OptionSet, Seq TestName)
-> AnnTestTree OptionSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestMatched
-> AnnTestTree (OptionSet, Seq TestName)
-> (TestMatched, AnnTestTree OptionSet)
go (Bool -> TestMatched
Any Bool
False)
where
mkGroup :: ann -> TestName -> [AnnTestTree ann] -> AnnTestTree ann
mkGroup ann
opts TestName
name [AnnTestTree ann]
xs = case (AnnTestTree ann -> Bool) -> [AnnTestTree ann] -> [AnnTestTree ann]
forall a. (a -> Bool) -> [a] -> [a]
filter AnnTestTree ann -> Bool
forall {ann}. AnnTestTree ann -> Bool
isNonEmpty [AnnTestTree ann]
xs of
[] -> AnnTestTree ann
forall ann. AnnTestTree ann
AnnEmptyTestTree
[AnnTestTree ann]
ys -> ann -> TestName -> [AnnTestTree ann] -> AnnTestTree ann
forall ann. ann -> TestName -> [AnnTestTree ann] -> AnnTestTree ann
AnnTestGroup ann
opts TestName
name [AnnTestTree ann]
ys
isNonEmpty :: AnnTestTree ann -> Bool
isNonEmpty = \case
AnnTestTree ann
AnnEmptyTestTree -> Bool
False
AnnTestTree ann
_ -> Bool
True
go
:: ForceTestMatch
-> AnnTestTree (OptionSet, Path)
-> (TestMatched, AnnTestTree OptionSet)
go :: TestMatched
-> AnnTestTree (OptionSet, Seq TestName)
-> (TestMatched, AnnTestTree OptionSet)
go TestMatched
forceMatch = \case
AnnTestTree (OptionSet, Seq TestName)
AnnEmptyTestTree ->
(Bool -> TestMatched
Any Bool
False, AnnTestTree OptionSet
forall ann. AnnTestTree ann
AnnEmptyTestTree)
AnnSingleTest (OptionSet
opts, Seq TestName
path) TestName
name t
tree
| TestMatched -> Bool
getAny TestMatched
forceMatch Bool -> Bool -> Bool
|| TestPattern -> Seq TestName -> Bool
testPatternMatches (OptionSet -> TestPattern
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts) Seq TestName
path
-> (Bool -> TestMatched
Any Bool
True, OptionSet -> TestName -> t -> AnnTestTree OptionSet
forall ann t. IsTest t => ann -> TestName -> t -> AnnTestTree ann
AnnSingleTest OptionSet
opts TestName
name t
tree)
| Bool
otherwise
-> (Bool -> TestMatched
Any Bool
False, AnnTestTree OptionSet
forall ann. AnnTestTree ann
AnnEmptyTestTree)
AnnTestGroup (OptionSet, Seq TestName)
_ TestName
_ [] ->
(TestMatched
forceMatch, AnnTestTree OptionSet
forall ann. AnnTestTree ann
AnnEmptyTestTree)
AnnTestGroup (OptionSet
opts, Seq TestName
_) TestName
name [AnnTestTree (OptionSet, Seq TestName)]
trees ->
case OptionSet -> ExecutionMode
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts of
ExecutionMode
Parallel ->
([TestMatched] -> TestMatched)
-> ([AnnTestTree OptionSet] -> AnnTestTree OptionSet)
-> ([TestMatched], [AnnTestTree OptionSet])
-> (TestMatched, AnnTestTree OptionSet)
forall a b c d. (a -> b) -> (c -> d) -> (a, c) -> (b, d)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap
[TestMatched] -> TestMatched
forall a. Monoid a => [a] -> a
mconcat
(OptionSet
-> TestName -> [AnnTestTree OptionSet] -> AnnTestTree OptionSet
forall ann. ann -> TestName -> [AnnTestTree ann] -> AnnTestTree ann
mkGroup OptionSet
opts TestName
name)
([(TestMatched, AnnTestTree OptionSet)]
-> ([TestMatched], [AnnTestTree OptionSet])
forall a b. [(a, b)] -> ([a], [b])
unzip ((AnnTestTree (OptionSet, Seq TestName)
-> (TestMatched, AnnTestTree OptionSet))
-> [AnnTestTree (OptionSet, Seq TestName)]
-> [(TestMatched, AnnTestTree OptionSet)]
forall a b. (a -> b) -> [a] -> [b]
map (TestMatched
-> AnnTestTree (OptionSet, Seq TestName)
-> (TestMatched, AnnTestTree OptionSet)
go TestMatched
forceMatch) [AnnTestTree (OptionSet, Seq TestName)]
trees))
Sequential DependencyType
_ ->
([AnnTestTree OptionSet] -> AnnTestTree OptionSet)
-> (TestMatched, [AnnTestTree OptionSet])
-> (TestMatched, AnnTestTree OptionSet)
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second
(OptionSet
-> TestName -> [AnnTestTree OptionSet] -> AnnTestTree OptionSet
forall ann. ann -> TestName -> [AnnTestTree ann] -> AnnTestTree ann
mkGroup OptionSet
opts TestName
name)
((TestMatched
-> AnnTestTree (OptionSet, Seq TestName)
-> (TestMatched, AnnTestTree OptionSet))
-> TestMatched
-> [AnnTestTree (OptionSet, Seq TestName)]
-> (TestMatched, [AnnTestTree OptionSet])
forall (t :: * -> *) s a b.
Traversable t =>
(s -> a -> (s, b)) -> s -> t a -> (s, t b)
mapAccumR TestMatched
-> AnnTestTree (OptionSet, Seq TestName)
-> (TestMatched, AnnTestTree OptionSet)
go TestMatched
forceMatch [AnnTestTree (OptionSet, Seq TestName)]
trees)
AnnWithResource (OptionSet
opts, Seq TestName
_) ResourceSpec a
res0 IO a -> AnnTestTree (OptionSet, Seq TestName)
tree ->
( (TestMatched, AnnTestTree OptionSet) -> TestMatched
forall a b. (a, b) -> a
fst (TestMatched
-> AnnTestTree (OptionSet, Seq TestName)
-> (TestMatched, AnnTestTree OptionSet)
go TestMatched
forceMatch (IO a -> AnnTestTree (OptionSet, Seq TestName)
tree (ResourceError -> IO a
forall e a. Exception e => e -> IO a
throwIO ResourceError
NotRunningTests)))
, OptionSet
-> ResourceSpec a
-> (IO a -> AnnTestTree OptionSet)
-> AnnTestTree OptionSet
forall ann a.
ann
-> ResourceSpec a -> (IO a -> AnnTestTree ann) -> AnnTestTree ann
AnnWithResource OptionSet
opts ResourceSpec a
res0 ((IO a -> AnnTestTree OptionSet) -> AnnTestTree OptionSet)
-> (IO a -> AnnTestTree OptionSet) -> AnnTestTree OptionSet
forall a b. (a -> b) -> a -> b
$ \IO a
res -> (TestMatched, AnnTestTree OptionSet) -> AnnTestTree OptionSet
forall a b. (a, b) -> b
snd (TestMatched
-> AnnTestTree (OptionSet, Seq TestName)
-> (TestMatched, AnnTestTree OptionSet)
go TestMatched
forceMatch (IO a -> AnnTestTree (OptionSet, Seq TestName)
tree IO a
res))
)
AnnAfter (OptionSet
opts, Seq TestName
_) DependencyType
deptype Expr
dep AnnTestTree (OptionSet, Seq TestName)
tree ->
(AnnTestTree OptionSet -> AnnTestTree OptionSet)
-> (TestMatched, AnnTestTree OptionSet)
-> (TestMatched, AnnTestTree OptionSet)
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second
(OptionSet
-> DependencyType
-> Expr
-> AnnTestTree OptionSet
-> AnnTestTree OptionSet
forall ann.
ann -> DependencyType -> Expr -> AnnTestTree ann -> AnnTestTree ann
AnnAfter OptionSet
opts DependencyType
deptype Expr
dep)
(TestMatched
-> AnnTestTree (OptionSet, Seq TestName)
-> (TestMatched, AnnTestTree OptionSet)
go TestMatched
forceMatch AnnTestTree (OptionSet, Seq TestName)
tree)
treeOptions :: TestTree -> [OptionDescription]
treeOptions :: TestTree -> [OptionDescription]
treeOptions =
[[OptionDescription]] -> [OptionDescription]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Prelude.concat ([[OptionDescription]] -> [OptionDescription])
-> (TestTree -> [[OptionDescription]])
-> TestTree
-> [OptionDescription]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Map TypeRep [OptionDescription] -> [[OptionDescription]]
forall k a. Map k a -> [a]
Map.elems (Map TypeRep [OptionDescription] -> [[OptionDescription]])
-> (TestTree -> Map TypeRep [OptionDescription])
-> TestTree
-> [[OptionDescription]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
TreeFold (Map TypeRep [OptionDescription])
-> OptionSet -> TestTree -> Map TypeRep [OptionDescription]
forall b. Monoid b => TreeFold b -> OptionSet -> TestTree -> b
foldTestTree
TreeFold (Map TypeRep [OptionDescription])
forall b. Monoid b => TreeFold b
trivialFold { foldSingle = \OptionSet
_ TestName
_ -> t -> Map TypeRep [OptionDescription]
forall t. IsTest t => t -> Map TypeRep [OptionDescription]
getTestOptions }
OptionSet
forall a. Monoid a => a
mempty
where
getTestOptions
:: forall t . IsTest t
=> t -> Map.Map TypeRep [OptionDescription]
getTestOptions :: forall t. IsTest t => t -> Map TypeRep [OptionDescription]
getTestOptions t
t =
TypeRep -> [OptionDescription] -> Map TypeRep [OptionDescription]
forall k a. k -> a -> Map k a
Map.singleton (t -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf t
t) ([OptionDescription] -> Map TypeRep [OptionDescription])
-> [OptionDescription] -> Map TypeRep [OptionDescription]
forall a b. (a -> b) -> a -> b
$
Tagged t [OptionDescription] -> t -> [OptionDescription]
forall a b. Tagged a b -> a -> b
witness Tagged t [OptionDescription]
forall t. IsTest t => Tagged t [OptionDescription]
testOptions t
t