{-# 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
forall a.
(Int -> a -> ShowS) -> (a -> TestName) -> ([a] -> ShowS) -> Show a
showList :: [FailureReason] -> ShowS
$cshowList :: [FailureReason] -> ShowS
show :: FailureReason -> TestName
$cshow :: FailureReason -> TestName
showsPrec :: Int -> FailureReason -> ShowS
$cshowsPrec :: Int -> FailureReason -> ShowS
Show
data Outcome
= Success
| Failure FailureReason
deriving (Int -> Outcome -> ShowS
[Outcome] -> ShowS
Outcome -> TestName
forall a.
(Int -> a -> ShowS) -> (a -> TestName) -> ([a] -> ShowS) -> Show a
showList :: [Outcome] -> ShowS
$cshowList :: [Outcome] -> ShowS
show :: Outcome -> TestName
$cshow :: Outcome -> TestName
showsPrec :: Int -> Outcome -> ShowS
$cshowsPrec :: Int -> Outcome -> ShowS
Show, 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
$cto :: forall x. Rep Outcome x -> Outcome
$cfrom :: forall x. Outcome -> Rep Outcome x
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
forall a.
(Int -> a -> ShowS) -> (a -> TestName) -> ([a] -> ShowS) -> Show a
showList :: [Result] -> ShowS
$cshowList :: [Result] -> ShowS
show :: Result -> TestName
$cshow :: Result -> TestName
showsPrec :: Int -> Result -> ShowS
$cshowsPrec :: Int -> 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 forall a b. (a -> b) -> a -> b
$ SomeException -> FailureReason
TestThrewException SomeException
e
, resultDescription :: TestName
resultDescription = TestName
"Exception: " forall a. [a] -> [a] -> [a]
++ 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
forall a.
(Int -> a -> ShowS) -> (a -> TestName) -> ([a] -> ShowS) -> Show a
showList :: [Progress] -> ShowS
$cshowList :: [Progress] -> ShowS
show :: Progress -> TestName
$cshow :: Progress -> TestName
showsPrec :: Int -> Progress -> ShowS
$cshowsPrec :: Int -> Progress -> ShowS
Show
, Progress -> Progress -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Progress -> Progress -> Bool
$c/= :: Progress -> Progress -> Bool
== :: Progress -> Progress -> Bool
$c== :: Progress -> Progress -> Bool
Eq
)
emptyProgress :: Progress
emptyProgress :: Progress
emptyProgress = TestName -> Float -> Progress
Progress 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) =
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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DependencyType -> DependencyType -> Bool
$c/= :: DependencyType -> DependencyType -> Bool
== :: DependencyType -> DependencyType -> Bool
$c== :: DependencyType -> DependencyType -> Bool
Eq
, Int -> DependencyType -> ShowS
[DependencyType] -> ShowS
DependencyType -> TestName
forall a.
(Int -> a -> ShowS) -> (a -> TestName) -> ([a] -> ShowS) -> Show a
showList :: [DependencyType] -> ShowS
$cshowList :: [DependencyType] -> ShowS
show :: DependencyType -> TestName
$cshow :: DependencyType -> TestName
showsPrec :: Int -> DependencyType -> ShowS
$cshowsPrec :: Int -> DependencyType -> ShowS
Show
, ReadPrec [DependencyType]
ReadPrec DependencyType
Int -> ReadS DependencyType
ReadS [DependencyType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DependencyType]
$creadListPrec :: ReadPrec [DependencyType]
readPrec :: ReadPrec DependencyType
$creadPrec :: ReadPrec DependencyType
readList :: ReadS [DependencyType]
$creadList :: ReadS [DependencyType]
readsPrec :: Int -> ReadS DependencyType
$creadsPrec :: Int -> ReadS DependencyType
Read
)
data ExecutionMode
= Sequential DependencyType
| Parallel
deriving (Int -> ExecutionMode -> ShowS
[ExecutionMode] -> ShowS
ExecutionMode -> TestName
forall a.
(Int -> a -> ShowS) -> (a -> TestName) -> ([a] -> ShowS) -> Show a
showList :: [ExecutionMode] -> ShowS
$cshowList :: [ExecutionMode] -> ShowS
show :: ExecutionMode -> TestName
$cshow :: ExecutionMode -> TestName
showsPrec :: Int -> ExecutionMode -> ShowS
$cshowsPrec :: Int -> ExecutionMode -> ShowS
Show, ReadPrec [ExecutionMode]
ReadPrec ExecutionMode
Int -> ReadS ExecutionMode
ReadS [ExecutionMode]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExecutionMode]
$creadListPrec :: ReadPrec [ExecutionMode]
readPrec :: ReadPrec ExecutionMode
$creadPrec :: ReadPrec ExecutionMode
readList :: ReadS [ExecutionMode]
$creadList :: ReadS [ExecutionMode]
readsPrec :: Int -> ReadS ExecutionMode
$creadsPrec :: Int -> ReadS ExecutionMode
Read)
instance IsOption ExecutionMode where
defaultValue :: ExecutionMode
defaultValue = ExecutionMode
Parallel
parseValue :: TestName -> Maybe ExecutionMode
parseValue = forall a. Read a => TestName -> Maybe a
readMaybe
optionName :: Tagged ExecutionMode TestName
optionName = forall {k} (s :: k) b. b -> Tagged s b
Tagged TestName
"execution-mode"
optionHelp :: Tagged ExecutionMode TestName
optionHelp = forall {k} (s :: k) b. b -> Tagged s b
Tagged TestName
"Whether to execute tests sequentially or in parallel"
optionCLParser :: Parser ExecutionMode
optionCLParser = forall v. IsOption v => Mod OptionFields v -> Parser v
mkOptionCLParser 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestName -> [TestTree] -> TestTree
TestGroup TestName
nm forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map TestTree -> TestTree
setParallel
where
setParallel :: TestTree -> TestTree
setParallel = (OptionSet -> OptionSet) -> TestTree -> TestTree
PlusTestOptions (forall v. IsOption v => v -> OptionSet -> OptionSet
setOption ExecutionMode
Parallel)
setSequential :: TestTree -> TestTree
setSequential = (OptionSet -> OptionSet) -> TestTree -> TestTree
PlusTestOptions (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 -> forall a. HasCallStack => TestName -> a
error forall a b. (a -> b) -> a -> b
$ TestName
"Could not parse pattern " forall a. [a] -> [a] -> [a]
++ 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
_ -> forall a. Monoid a => a
mempty
, foldGroup :: OptionSet -> TestName -> [b] -> b
foldGroup = \OptionSet
_ TestName
_ [b]
bs -> 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 forall a b. (a -> b) -> a -> b
$ 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 = forall b. b -> TreeFold b -> OptionSet -> TestTree -> b
foldTestTree0 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 -> 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 (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 -> forall a. OptionSet -> ResourceSpec a -> (IO a -> b) -> b
fResource OptionSet
opts ResourceSpec a
res0 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 ->
forall ann t. IsTest t => ann -> TestName -> t -> AnnTestTree ann
AnnSingleTest OptionSet
opts TestName
name t
test
TestGroup TestName
name [TestTree]
trees ->
forall ann. ann -> TestName -> [AnnTestTree ann] -> AnnTestTree ann
AnnTestGroup OptionSet
opts TestName
name forall a b. (a -> b) -> a -> b
$ 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 ->
forall ann a.
ann
-> ResourceSpec a -> (IO a -> AnnTestTree ann) -> AnnTestTree ann
AnnWithResource OptionSet
opts ResourceSpec a
res0 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 ->
forall ann.
ann -> DependencyType -> Expr -> AnnTestTree ann -> AnnTestTree ann
AnnAfter OptionSet
opts DependencyType
deptype Expr
dep 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 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 -> forall ann. AnnTestTree ann
AnnEmptyTestTree
AnnSingleTest OptionSet
opts TestName
name t
tree ->
forall ann t. IsTest t => ann -> TestName -> t -> AnnTestTree ann
AnnSingleTest (OptionSet
opts, Seq TestName
path 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 forall a. Seq a -> a -> Seq a
|> TestName
name in
forall ann. ann -> TestName -> [AnnTestTree ann] -> AnnTestTree ann
AnnTestGroup (OptionSet
opts, Seq TestName
newPath) TestName
name (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 ->
forall ann a.
ann
-> ResourceSpec a -> (IO a -> AnnTestTree ann) -> AnnTestTree ann
AnnWithResource (OptionSet
opts, Seq TestName
path) ResourceSpec a
res0 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 ->
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 = forall a b. (a, b) -> b
snd 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
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, 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 (forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts) Seq TestName
path
-> (Bool -> TestMatched
Any Bool
True, forall ann t. IsTest t => ann -> TestName -> t -> AnnTestTree ann
AnnSingleTest OptionSet
opts TestName
name t
tree)
| Bool
otherwise
-> (Bool -> TestMatched
Any Bool
False, forall ann. AnnTestTree ann
AnnEmptyTestTree)
AnnTestGroup (OptionSet
opts, Seq TestName
_) TestName
name [] ->
(TestMatched
forceMatch, forall ann. ann -> TestName -> [AnnTestTree ann] -> AnnTestTree ann
AnnTestGroup OptionSet
opts TestName
name [])
AnnTestGroup (OptionSet
opts, Seq TestName
_) TestName
name [AnnTestTree (OptionSet, Seq TestName)]
trees ->
case forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts of
ExecutionMode
Parallel ->
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap
forall a. Monoid a => [a] -> a
mconcat
(forall ann. ann -> TestName -> [AnnTestTree ann] -> AnnTestTree ann
AnnTestGroup OptionSet
opts TestName
name)
(forall a b. [(a, b)] -> ([a], [b])
unzip (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
_ ->
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second
(forall ann. ann -> TestName -> [AnnTestTree ann] -> AnnTestTree ann
AnnTestGroup OptionSet
opts TestName
name)
(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 ->
( 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 (forall e a. Exception e => e -> IO a
throwIO ResourceError
NotRunningTests)))
, forall ann a.
ann
-> ResourceSpec a -> (IO a -> AnnTestTree ann) -> AnnTestTree ann
AnnWithResource OptionSet
opts ResourceSpec a
res0 forall a b. (a -> b) -> a -> b
$ \IO a
res -> 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 ->
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second
(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 =
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Prelude.concat forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall k a. Map k a -> [a]
Map.elems forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall b. Monoid b => TreeFold b -> OptionSet -> TestTree -> b
foldTestTree
forall b. Monoid b => TreeFold b
trivialFold { foldSingle :: forall t.
IsTest t =>
OptionSet -> TestName -> t -> Map TypeRep [OptionDescription]
foldSingle = \OptionSet
_ TestName
_ -> forall t. IsTest t => t -> Map TypeRep [OptionDescription]
getTestOptions }
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 =
forall k a. k -> a -> Map k a
Map.singleton (forall a. Typeable a => a -> TypeRep
typeOf t
t) forall a b. (a -> b) -> a -> b
$
forall a b. Tagged a b -> a -> b
witness forall t. IsTest t => Tagged t [OptionDescription]
testOptions t
t