{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ConstraintKinds #-}
module Test.Hspec.Core.Runner.Eval (
EvalConfig(..)
, ColorMode(..)
, EvalTree
, Tree(..)
, EvalItem(..)
, Concurrency(..)
, runFormatter
#ifdef TEST
, mergeResults
#endif
) where
import Prelude ()
import Test.Hspec.Core.Compat hiding (Monad)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.Reader
import Control.Monad.Trans.Class
import Test.Hspec.Core.Util
import Test.Hspec.Core.Spec (Progress, FailureReason(..), Result(..), ResultStatus(..), ProgressCallback)
import Test.Hspec.Core.Timer
import Test.Hspec.Core.Format (Format)
import qualified Test.Hspec.Core.Format as Format
import Test.Hspec.Core.Clock
import Test.Hspec.Core.Example.Location
import Test.Hspec.Core.Example (safeEvaluateResultStatus, exceptionToResultStatus)
import qualified NonEmpty
import NonEmpty (NonEmpty(..))
import Test.Hspec.Core.Runner.JobQueue
data Tree c a =
Node String (NonEmpty (Tree c a))
| NodeWithCleanup (Maybe (String, Location)) c (NonEmpty (Tree c a))
| Leaf a
deriving (Tree c a -> Tree c a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall c a. (Eq c, Eq a) => Tree c a -> Tree c a -> Bool
/= :: Tree c a -> Tree c a -> Bool
$c/= :: forall c a. (Eq c, Eq a) => Tree c a -> Tree c a -> Bool
== :: Tree c a -> Tree c a -> Bool
$c== :: forall c a. (Eq c, Eq a) => Tree c a -> Tree c a -> Bool
Eq, Int -> Tree c a -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall c a. (Show c, Show a) => Int -> Tree c a -> ShowS
forall c a. (Show c, Show a) => [Tree c a] -> ShowS
forall c a. (Show c, Show a) => Tree c a -> String
showList :: [Tree c a] -> ShowS
$cshowList :: forall c a. (Show c, Show a) => [Tree c a] -> ShowS
show :: Tree c a -> String
$cshow :: forall c a. (Show c, Show a) => Tree c a -> String
showsPrec :: Int -> Tree c a -> ShowS
$cshowsPrec :: forall c a. (Show c, Show a) => Int -> Tree c a -> ShowS
Show, forall a b. a -> Tree c b -> Tree c a
forall a b. (a -> b) -> Tree c a -> Tree c b
forall c a b. a -> Tree c b -> Tree c a
forall c a b. (a -> b) -> Tree c a -> Tree c b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Tree c b -> Tree c a
$c<$ :: forall c a b. a -> Tree c b -> Tree c a
fmap :: forall a b. (a -> b) -> Tree c a -> Tree c b
$cfmap :: forall c a b. (a -> b) -> Tree c a -> Tree c b
Functor, forall a. Tree c a -> Bool
forall c a. Eq a => a -> Tree c a -> Bool
forall c a. Num a => Tree c a -> a
forall c a. Ord a => Tree c a -> a
forall m a. Monoid m => (a -> m) -> Tree c a -> m
forall c m. Monoid m => Tree c m -> m
forall c a. Tree c a -> Bool
forall c a. Tree c a -> Int
forall c a. Tree c a -> [a]
forall a b. (a -> b -> b) -> b -> Tree c a -> b
forall c a. (a -> a -> a) -> Tree c a -> a
forall c m a. Monoid m => (a -> m) -> Tree c a -> m
forall c b a. (b -> a -> b) -> b -> Tree c a -> b
forall c a b. (a -> b -> b) -> b -> Tree c a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => Tree c a -> a
$cproduct :: forall c a. Num a => Tree c a -> a
sum :: forall a. Num a => Tree c a -> a
$csum :: forall c a. Num a => Tree c a -> a
minimum :: forall a. Ord a => Tree c a -> a
$cminimum :: forall c a. Ord a => Tree c a -> a
maximum :: forall a. Ord a => Tree c a -> a
$cmaximum :: forall c a. Ord a => Tree c a -> a
elem :: forall a. Eq a => a -> Tree c a -> Bool
$celem :: forall c a. Eq a => a -> Tree c a -> Bool
length :: forall a. Tree c a -> Int
$clength :: forall c a. Tree c a -> Int
null :: forall a. Tree c a -> Bool
$cnull :: forall c a. Tree c a -> Bool
toList :: forall a. Tree c a -> [a]
$ctoList :: forall c a. Tree c a -> [a]
foldl1 :: forall a. (a -> a -> a) -> Tree c a -> a
$cfoldl1 :: forall c a. (a -> a -> a) -> Tree c a -> a
foldr1 :: forall a. (a -> a -> a) -> Tree c a -> a
$cfoldr1 :: forall c a. (a -> a -> a) -> Tree c a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> Tree c a -> b
$cfoldl' :: forall c b a. (b -> a -> b) -> b -> Tree c a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Tree c a -> b
$cfoldl :: forall c b a. (b -> a -> b) -> b -> Tree c a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Tree c a -> b
$cfoldr' :: forall c a b. (a -> b -> b) -> b -> Tree c a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Tree c a -> b
$cfoldr :: forall c a b. (a -> b -> b) -> b -> Tree c a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> Tree c a -> m
$cfoldMap' :: forall c m a. Monoid m => (a -> m) -> Tree c a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Tree c a -> m
$cfoldMap :: forall c m a. Monoid m => (a -> m) -> Tree c a -> m
fold :: forall m. Monoid m => Tree c m -> m
$cfold :: forall c m. Monoid m => Tree c m -> m
Foldable, forall c. Functor (Tree c)
forall c. Foldable (Tree c)
forall c (m :: * -> *) a. Monad m => Tree c (m a) -> m (Tree c a)
forall c (f :: * -> *) a.
Applicative f =>
Tree c (f a) -> f (Tree c a)
forall c (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Tree c a -> m (Tree c b)
forall c (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Tree c a -> f (Tree c b)
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 (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Tree c a -> f (Tree c b)
sequence :: forall (m :: * -> *) a. Monad m => Tree c (m a) -> m (Tree c a)
$csequence :: forall c (m :: * -> *) a. Monad m => Tree c (m a) -> m (Tree c a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Tree c a -> m (Tree c b)
$cmapM :: forall c (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Tree c a -> m (Tree c b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Tree c (f a) -> f (Tree c a)
$csequenceA :: forall c (f :: * -> *) a.
Applicative f =>
Tree c (f a) -> f (Tree c a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Tree c a -> f (Tree c b)
$ctraverse :: forall c (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Tree c a -> f (Tree c b)
Traversable)
data EvalConfig = EvalConfig {
EvalConfig -> Format
evalConfigFormat :: Format
, EvalConfig -> Int
evalConfigConcurrentJobs :: Int
, EvalConfig -> Bool
evalConfigFailFast :: Bool
, EvalConfig -> ColorMode
evalConfigColorMode :: ColorMode
}
data ColorMode = ColorDisabled | ColorEnabled
data Env = Env {
Env -> EvalConfig
envConfig :: EvalConfig
, Env -> IORef Bool
envFailed :: IORef Bool
, Env -> IORef [(Path, Item)]
envResults :: IORef [(Path, Format.Item)]
}
formatEvent :: Format.Event -> EvalM ()
formatEvent :: Event -> EvalM ()
formatEvent Event
event = do
Format
format <- forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks forall a b. (a -> b) -> a -> b
$ EvalConfig -> Format
evalConfigFormat forall b c a. (b -> c) -> (a -> b) -> a -> c
. Env -> EvalConfig
envConfig
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Format
format Event
event
type EvalM = ReaderT Env IO
setFailed :: EvalM ()
setFailed :: EvalM ()
setFailed = do
IORef Bool
ref <- forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks Env -> IORef Bool
envFailed
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. IORef a -> a -> IO ()
writeIORef IORef Bool
ref Bool
True
hasFailed :: EvalM Bool
hasFailed :: EvalM Bool
hasFailed = do
IORef Bool
ref <- forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks Env -> IORef Bool
envFailed
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. IORef a -> IO a
readIORef IORef Bool
ref
addResult :: Path -> Format.Item -> EvalM ()
addResult :: Path -> Item -> EvalM ()
addResult Path
path Item
item = do
IORef [(Path, Item)]
ref <- forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks Env -> IORef [(Path, Item)]
envResults
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. IORef a -> (a -> a) -> IO ()
modifyIORef IORef [(Path, Item)]
ref ((Path
path, Item
item) forall a. a -> [a] -> [a]
:)
reportItem :: Path -> Maybe Location -> EvalM (Seconds, Result) -> EvalM ()
reportItem :: Path -> Maybe Location -> EvalM (Seconds, Result) -> EvalM ()
reportItem Path
path Maybe Location
loc EvalM (Seconds, Result)
action = do
Path -> EvalM ()
reportItemStarted Path
path
EvalM (Seconds, Result)
action forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Path -> Maybe Location -> (Seconds, Result) -> EvalM ()
reportResult Path
path Maybe Location
loc
reportItemStarted :: Path -> EvalM ()
reportItemStarted :: Path -> EvalM ()
reportItemStarted = Event -> EvalM ()
formatEvent forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path -> Event
Format.ItemStarted
reportItemDone :: Path -> Format.Item -> EvalM ()
reportItemDone :: Path -> Item -> EvalM ()
reportItemDone Path
path Item
item = do
let
isFailure :: Bool
isFailure = case Item -> Result
Format.itemResult Item
item of
Format.Success{} -> Bool
False
Format.Pending{} -> Bool
False
Format.Failure{} -> Bool
True
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
isFailure EvalM ()
setFailed
Path -> Item -> EvalM ()
addResult Path
path Item
item
Event -> EvalM ()
formatEvent forall a b. (a -> b) -> a -> b
$ Path -> Item -> Event
Format.ItemDone Path
path Item
item
reportResult :: Path -> Maybe Location -> (Seconds, Result) -> EvalM ()
reportResult :: Path -> Maybe Location -> (Seconds, Result) -> EvalM ()
reportResult Path
path Maybe Location
loc (Seconds
duration, Result
result) = do
ColorMode
mode <- forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks (EvalConfig -> ColorMode
evalConfigColorMode forall b c a. (b -> c) -> (a -> b) -> a -> c
. Env -> EvalConfig
envConfig)
case Result
result of
Result String
info ResultStatus
status -> Path -> Item -> EvalM ()
reportItemDone Path
path forall a b. (a -> b) -> a -> b
$ Maybe Location -> Seconds -> String -> Result -> Item
Format.Item Maybe Location
loc Seconds
duration String
info forall a b. (a -> b) -> a -> b
$ case ResultStatus
status of
ResultStatus
Success -> Result
Format.Success
Pending Maybe Location
loc_ Maybe String
reason -> Maybe Location -> Maybe String -> Result
Format.Pending Maybe Location
loc_ Maybe String
reason
Failure Maybe Location
loc_ err :: FailureReason
err@(Error Maybe String
_ SomeException
e) -> Maybe Location -> FailureReason -> Result
Format.Failure (Maybe Location
loc_ forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> SomeException -> Maybe Location
extractLocation SomeException
e) FailureReason
err
Failure Maybe Location
loc_ FailureReason
err -> Maybe Location -> FailureReason -> Result
Format.Failure Maybe Location
loc_ forall a b. (a -> b) -> a -> b
$ case ColorMode
mode of
ColorMode
ColorEnabled -> FailureReason
err
ColorMode
ColorDisabled -> case FailureReason
err of
FailureReason
NoReason -> FailureReason
err
Reason String
_ -> FailureReason
err
ExpectedButGot Maybe String
_ String
_ String
_ -> FailureReason
err
ColorizedReason String
r -> String -> FailureReason
Reason (ShowS
stripAnsi String
r)
#if __GLASGOW_HASKELL__ < 900
Error _ _ -> err
#endif
groupStarted :: Path -> EvalM ()
groupStarted :: Path -> EvalM ()
groupStarted = Event -> EvalM ()
formatEvent forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path -> Event
Format.GroupStarted
groupDone :: Path -> EvalM ()
groupDone :: Path -> EvalM ()
groupDone = Event -> EvalM ()
formatEvent forall b c a. (b -> c) -> (a -> b) -> a -> c
. Path -> Event
Format.GroupDone
data EvalItem = EvalItem {
EvalItem -> String
evalItemDescription :: String
, EvalItem -> Maybe Location
evalItemLocation :: Maybe Location
, EvalItem -> Concurrency
evalItemConcurrency :: Concurrency
, EvalItem -> ProgressCallback -> IO (Seconds, Result)
evalItemAction :: ProgressCallback -> IO (Seconds, Result)
}
type EvalTree = Tree (IO ()) EvalItem
runFormatter :: EvalConfig -> [EvalTree] -> IO [(Path, Format.Item)]
runFormatter :: EvalConfig -> [EvalTree] -> IO [(Path, Item)]
runFormatter EvalConfig
config [EvalTree]
specs = do
forall a. Int -> (JobQueue -> IO a) -> IO a
withJobQueue (EvalConfig -> Int
evalConfigConcurrentJobs EvalConfig
config) forall a b. (a -> b) -> a -> b
$ \ JobQueue
queue -> do
forall a. Seconds -> (IO Bool -> IO a) -> IO a
withTimer Seconds
0.05 forall a b. (a -> b) -> a -> b
$ \ IO Bool
timer -> do
Env
env <- IO Env
mkEnv
[RunningTree_ IO]
runningSpecs_ <- forall (m :: * -> *).
MonadIO m =>
JobQueue -> [EvalTree] -> IO [RunningTree_ m]
enqueueItems JobQueue
queue [EvalTree]
specs
let
applyReportProgress :: RunningItem_ IO -> RunningItem
applyReportProgress :: RunningItem_ IO -> RunningItem
applyReportProgress RunningItem_ IO
item = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO Bool -> Path -> ProgressCallback
reportProgress IO Bool
timer) RunningItem_ IO
item
runningSpecs :: [RunningTree ()]
runningSpecs :: [RunningTree ()]
runningSpecs = [RunningTree (IO ())] -> [RunningTree ()]
applyCleanup forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap RunningItem_ IO -> RunningItem
applyReportProgress) [RunningTree_ IO]
runningSpecs_
getResults :: IO [(Path, Format.Item)]
getResults :: IO [(Path, Item)]
getResults = forall a. [a] -> [a]
reverse forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. IORef a -> IO a
readIORef (Env -> IORef [(Path, Item)]
envResults Env
env)
formatItems :: IO ()
formatItems :: IO ()
formatItems = forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ([RunningTree ()] -> EvalM ()
eval [RunningTree ()]
runningSpecs) Env
env
formatDone :: IO ()
formatDone :: IO ()
formatDone = IO [(Path, Item)]
getResults forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Format
format forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Path, Item)] -> Event
Format.Done
Format
format Event
Format.Started
IO ()
formatItems forall a b. IO a -> IO b -> IO a
`finally` IO ()
formatDone
IO [(Path, Item)]
getResults
where
mkEnv :: IO Env
mkEnv :: IO Env
mkEnv = EvalConfig -> IORef Bool -> IORef [(Path, Item)] -> Env
Env EvalConfig
config forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. a -> IO (IORef a)
newIORef Bool
False forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. a -> IO (IORef a)
newIORef []
format :: Format
format :: Format
format = EvalConfig -> Format
evalConfigFormat EvalConfig
config
reportProgress :: IO Bool -> Path -> Progress -> IO ()
reportProgress :: IO Bool -> Path -> ProgressCallback
reportProgress IO Bool
timer Path
path Progress
progress = do
Bool
r <- IO Bool
timer
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
r forall a b. (a -> b) -> a -> b
$ do
Format
format (Path -> Progress -> Event
Format.Progress Path
path Progress
progress)
data Item a = Item {
forall a. Item a -> String
itemDescription :: String
, forall a. Item a -> Maybe Location
itemLocation :: Maybe Location
, forall a. Item a -> a
itemAction :: a
} deriving forall a b. a -> Item b -> Item a
forall a b. (a -> b) -> Item a -> Item b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Item b -> Item a
$c<$ :: forall a b. a -> Item b -> Item a
fmap :: forall a b. (a -> b) -> Item a -> Item b
$cfmap :: forall a b. (a -> b) -> Item a -> Item b
Functor
type RunningItem = Item (Path -> IO (Seconds, Result))
type RunningTree c = Tree c RunningItem
type RunningItem_ m = Item (Job m Progress (Seconds, Result))
type RunningTree_ m = Tree (IO ()) (RunningItem_ m)
applyCleanup :: [RunningTree (IO ())] -> [RunningTree ()]
applyCleanup :: [RunningTree (IO ())] -> [RunningTree ()]
applyCleanup = forall a b. (a -> b) -> [a] -> [b]
map RunningTree (IO ()) -> RunningTree ()
go
where
go :: RunningTree (IO ()) -> RunningTree ()
go RunningTree (IO ())
t = case RunningTree (IO ())
t of
Node String
label NonEmpty (RunningTree (IO ()))
xs -> forall c a. String -> NonEmpty (Tree c a) -> Tree c a
Node String
label (RunningTree (IO ()) -> RunningTree ()
go forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty (RunningTree (IO ()))
xs)
NodeWithCleanup Maybe (String, Location)
loc IO ()
cleanup NonEmpty (RunningTree (IO ()))
xs -> forall c a.
Maybe (String, Location) -> c -> NonEmpty (Tree c a) -> Tree c a
NodeWithCleanup Maybe (String, Location)
loc () (Maybe (String, Location)
-> IO () -> NonEmpty (RunningTree ()) -> NonEmpty (RunningTree ())
addCleanupToLastLeaf Maybe (String, Location)
loc IO ()
cleanup forall a b. (a -> b) -> a -> b
$ RunningTree (IO ()) -> RunningTree ()
go forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty (RunningTree (IO ()))
xs)
Leaf RunningItem
a -> forall c a. a -> Tree c a
Leaf RunningItem
a
addCleanupToLastLeaf :: Maybe (String, Location) -> IO () -> NonEmpty (RunningTree ()) -> NonEmpty (RunningTree ())
addCleanupToLastLeaf :: Maybe (String, Location)
-> IO () -> NonEmpty (RunningTree ()) -> NonEmpty (RunningTree ())
addCleanupToLastLeaf Maybe (String, Location)
loc IO ()
cleanup = NonEmpty (RunningTree ()) -> NonEmpty (RunningTree ())
go
where
go :: NonEmpty (RunningTree ()) -> NonEmpty (RunningTree ())
go = forall a. NonEmpty a -> NonEmpty a
NonEmpty.reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> a) -> NonEmpty a -> NonEmpty a
mapHead RunningTree () -> RunningTree ()
goNode forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NonEmpty a -> NonEmpty a
NonEmpty.reverse
goNode :: RunningTree () -> RunningTree ()
goNode RunningTree ()
node = case RunningTree ()
node of
Node String
description NonEmpty (RunningTree ())
xs -> forall c a. String -> NonEmpty (Tree c a) -> Tree c a
Node String
description (NonEmpty (RunningTree ()) -> NonEmpty (RunningTree ())
go NonEmpty (RunningTree ())
xs)
NodeWithCleanup Maybe (String, Location)
loc_ () NonEmpty (RunningTree ())
xs -> forall c a.
Maybe (String, Location) -> c -> NonEmpty (Tree c a) -> Tree c a
NodeWithCleanup Maybe (String, Location)
loc_ () (NonEmpty (RunningTree ()) -> NonEmpty (RunningTree ())
go NonEmpty (RunningTree ())
xs)
Leaf RunningItem
item -> forall c a. a -> Tree c a
Leaf (Maybe (String, Location) -> IO () -> RunningItem -> RunningItem
addCleanupToItem Maybe (String, Location)
loc IO ()
cleanup RunningItem
item)
mapHead :: (a -> a) -> NonEmpty a -> NonEmpty a
mapHead :: forall a. (a -> a) -> NonEmpty a -> NonEmpty a
mapHead a -> a
f NonEmpty a
xs = case NonEmpty a
xs of
a
y :| [a]
ys -> a -> a
f a
y forall a. a -> [a] -> NonEmpty a
:| [a]
ys
addCleanupToItem :: Maybe (String, Location) -> IO () -> RunningItem -> RunningItem
addCleanupToItem :: Maybe (String, Location) -> IO () -> RunningItem -> RunningItem
addCleanupToItem Maybe (String, Location)
loc IO ()
cleanup RunningItem
item = RunningItem
item {
itemAction :: Path -> IO (Seconds, Result)
itemAction = \ Path
path -> do
(Seconds
t1, Result
r1) <- forall a. Item a -> a
itemAction RunningItem
item Path
path
(Seconds
t2, ResultStatus
r2) <- forall a. IO a -> IO (Seconds, a)
measure forall a b. (a -> b) -> a -> b
$ IO ResultStatus -> IO ResultStatus
safeEvaluateResultStatus (IO ()
cleanup forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ResultStatus
Success)
let t :: Seconds
t = Seconds
t1 forall a. Num a => a -> a -> a
+ Seconds
t2
forall (m :: * -> *) a. Monad m => a -> m a
return (Seconds
t, Maybe (String, Location) -> Result -> ResultStatus -> Result
mergeResults Maybe (String, Location)
loc Result
r1 ResultStatus
r2)
}
mergeResults :: Maybe (String, Location) -> Result -> ResultStatus -> Result
mergeResults :: Maybe (String, Location) -> Result -> ResultStatus -> Result
mergeResults Maybe (String, Location)
mCallSite (Result String
info ResultStatus
r1) ResultStatus
r2 = String -> ResultStatus -> Result
Result String
info forall a b. (a -> b) -> a -> b
$ case (ResultStatus
r1, ResultStatus
r2) of
(ResultStatus
_, ResultStatus
Success) -> ResultStatus
r1
(Failure{}, ResultStatus
_) -> ResultStatus
r1
(Pending{}, Pending{}) -> ResultStatus
r1
(ResultStatus
Success, Pending{}) -> ResultStatus
r2
(ResultStatus
_, Failure Maybe Location
mLoc FailureReason
err) -> Maybe Location -> FailureReason -> ResultStatus
Failure (Maybe Location
mLoc forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Location
hookLoc) forall a b. (a -> b) -> a -> b
$ case FailureReason
err of
Error Maybe String
message SomeException
e -> Maybe String -> SomeException -> FailureReason
Error (Maybe String
message forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe String
hookFailed) SomeException
e
FailureReason
_ -> FailureReason
err
where
hookLoc :: Maybe Location
hookLoc = forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (String, Location)
mCallSite
hookFailed :: Maybe String
hookFailed = case Maybe (String, Location)
mCallSite of
Just (String
name, Location
_) -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ String
"in " forall a. [a] -> [a] -> [a]
++ String
name forall a. [a] -> [a] -> [a]
++ String
"-hook:"
Maybe (String, Location)
Nothing -> forall a. Maybe a
Nothing
enqueueItems :: MonadIO m => JobQueue -> [EvalTree] -> IO [RunningTree_ m]
enqueueItems :: forall (m :: * -> *).
MonadIO m =>
JobQueue -> [EvalTree] -> IO [RunningTree_ m]
enqueueItems JobQueue
queue = forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *).
MonadIO m =>
JobQueue -> EvalItem -> IO (RunningItem_ m)
enqueueItem JobQueue
queue)
enqueueItem :: MonadIO m => JobQueue -> EvalItem -> IO (RunningItem_ m)
enqueueItem :: forall (m :: * -> *).
MonadIO m =>
JobQueue -> EvalItem -> IO (RunningItem_ m)
enqueueItem JobQueue
queue EvalItem{String
Maybe Location
Concurrency
ProgressCallback -> IO (Seconds, Result)
evalItemAction :: ProgressCallback -> IO (Seconds, Result)
evalItemConcurrency :: Concurrency
evalItemLocation :: Maybe Location
evalItemDescription :: String
evalItemAction :: EvalItem -> ProgressCallback -> IO (Seconds, Result)
evalItemConcurrency :: EvalItem -> Concurrency
evalItemLocation :: EvalItem -> Maybe Location
evalItemDescription :: EvalItem -> String
..} = do
Job m Progress (Either SomeException (Seconds, Result))
job <- forall (m :: * -> *) progress a.
MonadIO m =>
JobQueue
-> Concurrency
-> Job IO progress a
-> IO (Job m progress (Either SomeException a))
enqueueJob JobQueue
queue Concurrency
evalItemConcurrency ProgressCallback -> IO (Seconds, Result)
evalItemAction
forall (m :: * -> *) a. Monad m => a -> m a
return Item {
itemDescription :: String
itemDescription = String
evalItemDescription
, itemLocation :: Maybe Location
itemLocation = Maybe Location
evalItemLocation
, itemAction :: (Progress -> m ()) -> m (Seconds, Result)
itemAction = Job m Progress (Either SomeException (Seconds, Result))
job forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either SomeException -> IO (Seconds, Result)
exceptionToResult forall (m :: * -> *) a. Monad m => a -> m a
return
}
where
exceptionToResult :: SomeException -> IO (Seconds, Result)
exceptionToResult :: SomeException -> IO (Seconds, Result)
exceptionToResult SomeException
err = (,) Seconds
0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ResultStatus -> Result
Result String
"" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SomeException -> IO ResultStatus
exceptionToResultStatus SomeException
err
eval :: [RunningTree ()] -> EvalM ()
eval :: [RunningTree ()] -> EvalM ()
eval [RunningTree ()]
specs = do
Bool
failFast <- forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks (EvalConfig -> Bool
evalConfigFailFast forall b c a. (b -> c) -> (a -> b) -> a -> c
. Env -> EvalConfig
envConfig)
Bool -> [EvalM ()] -> EvalM ()
sequenceActions Bool
failFast (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap RunningTree () -> [EvalM ()]
foldSpec [RunningTree ()]
specs)
where
foldSpec :: RunningTree () -> [EvalM ()]
foldSpec :: RunningTree () -> [EvalM ()]
foldSpec = forall c a r. FoldTree c a r -> Tree c a -> [r]
foldTree FoldTree {
onGroupStarted :: Path -> EvalM ()
onGroupStarted = Path -> EvalM ()
groupStarted
, onGroupDone :: Path -> EvalM ()
onGroupDone = Path -> EvalM ()
groupDone
, onCleanup :: Maybe (String, Location) -> [String] -> () -> EvalM ()
onCleanup = Maybe (String, Location) -> [String] -> () -> EvalM ()
runCleanup
, onLeafe :: [String] -> RunningItem -> EvalM ()
onLeafe = [String] -> RunningItem -> EvalM ()
evalItem
}
runCleanup :: Maybe (String, Location) -> [String] -> () -> EvalM ()
runCleanup :: Maybe (String, Location) -> [String] -> () -> EvalM ()
runCleanup Maybe (String, Location)
_loc [String]
_groups = forall (m :: * -> *) a. Monad m => a -> m a
return
evalItem :: [String] -> RunningItem -> EvalM ()
evalItem :: [String] -> RunningItem -> EvalM ()
evalItem [String]
groups (Item String
requirement Maybe Location
loc Path -> IO (Seconds, Result)
action) = do
Path -> Maybe Location -> EvalM (Seconds, Result) -> EvalM ()
reportItem Path
path Maybe Location
loc forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (Path -> IO (Seconds, Result)
action Path
path)
where
path :: Path
path :: Path
path = ([String]
groups, String
requirement)
data FoldTree c a r = FoldTree {
forall c a r. FoldTree c a r -> Path -> r
onGroupStarted :: Path -> r
, forall c a r. FoldTree c a r -> Path -> r
onGroupDone :: Path -> r
, forall c a r.
FoldTree c a r -> Maybe (String, Location) -> [String] -> c -> r
onCleanup :: Maybe (String, Location) -> [String] -> c -> r
, forall c a r. FoldTree c a r -> [String] -> a -> r
onLeafe :: [String] -> a -> r
}
foldTree :: FoldTree c a r -> Tree c a -> [r]
foldTree :: forall c a r. FoldTree c a r -> Tree c a -> [r]
foldTree FoldTree{[String] -> a -> r
Maybe (String, Location) -> [String] -> c -> r
Path -> r
onLeafe :: [String] -> a -> r
onCleanup :: Maybe (String, Location) -> [String] -> c -> r
onGroupDone :: Path -> r
onGroupStarted :: Path -> r
onLeafe :: forall c a r. FoldTree c a r -> [String] -> a -> r
onCleanup :: forall c a r.
FoldTree c a r -> Maybe (String, Location) -> [String] -> c -> r
onGroupDone :: forall c a r. FoldTree c a r -> Path -> r
onGroupStarted :: forall c a r. FoldTree c a r -> Path -> r
..} = [String] -> Tree c a -> [r]
go []
where
go :: [String] -> Tree c a -> [r]
go [String]
rGroups (Node String
group NonEmpty (Tree c a)
xs) = r
start forall a. a -> [a] -> [a]
: [r]
children forall a. [a] -> [a] -> [a]
++ [r
done]
where
path :: Path
path = (forall a. [a] -> [a]
reverse [String]
rGroups, String
group)
start :: r
start = Path -> r
onGroupStarted Path
path
children :: [r]
children = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ([String] -> Tree c a -> [r]
go (String
group forall a. a -> [a] -> [a]
: [String]
rGroups)) NonEmpty (Tree c a)
xs
done :: r
done = Path -> r
onGroupDone Path
path
go [String]
rGroups (NodeWithCleanup Maybe (String, Location)
loc c
action NonEmpty (Tree c a)
xs) = [r]
children forall a. [a] -> [a] -> [a]
++ [r
cleanup]
where
children :: [r]
children = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ([String] -> Tree c a -> [r]
go [String]
rGroups) NonEmpty (Tree c a)
xs
cleanup :: r
cleanup = Maybe (String, Location) -> [String] -> c -> r
onCleanup Maybe (String, Location)
loc (forall a. [a] -> [a]
reverse [String]
rGroups) c
action
go [String]
rGroups (Leaf a
a) = [[String] -> a -> r
onLeafe (forall a. [a] -> [a]
reverse [String]
rGroups) a
a]
sequenceActions :: Bool -> [EvalM ()] -> EvalM ()
sequenceActions :: Bool -> [EvalM ()] -> EvalM ()
sequenceActions Bool
failFast = [EvalM ()] -> EvalM ()
go
where
go :: [EvalM ()] -> EvalM ()
go :: [EvalM ()] -> EvalM ()
go [] = forall (m :: * -> *). Applicative m => m ()
pass
go (EvalM ()
action : [EvalM ()]
actions) = do
EvalM ()
action
Bool
stopNow <- case Bool
failFast of
Bool
False -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
Bool
True -> EvalM Bool
hasFailed
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
stopNow ([EvalM ()] -> EvalM ()
go [EvalM ()]
actions)