{-# LANGUAGE ScopedTypeVariables, ExistentialQuantification, RankNTypes,
FlexibleContexts, BangPatterns, CPP, DeriveDataTypeable #-}
module Test.Tasty.Run
( Status(..)
, StatusMap
, launchTestTree
, DependencyException(..)
) where
import qualified Data.IntMap as IntMap
import qualified Data.Sequence as Seq
import qualified Data.Foldable as F
import Data.Int (Int64)
import Data.Maybe
import Data.Graph (SCC(..), stronglyConnComp)
import Data.Typeable
import Control.Monad (forever, guard, join, liftM)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Reader (ReaderT(..), local, ask)
import Control.Monad.Trans.Writer (WriterT(..), execWriterT, mapWriterT, tell)
import Control.Concurrent
import Control.Concurrent.STM
import Control.Concurrent.Async
import Control.Exception as E
import Control.Applicative
import Control.Arrow
import Data.Monoid (First(..))
import GHC.Conc (labelThread)
import Prelude
#ifdef MIN_VERSION_unbounded_delays
import Control.Concurrent.Timeout (timeout)
#else
import System.Timeout (timeout)
#endif
import Test.Tasty.Core
import Test.Tasty.Parallel
import Test.Tasty.Patterns
import Test.Tasty.Patterns.Types
import Test.Tasty.Options
import Test.Tasty.Options.Core
import Test.Tasty.Runners.Reducers
import Test.Tasty.Runners.Utils (timed, forceElements)
import Test.Tasty.Providers.ConsoleFormat (noResultDetails)
data Status
= NotStarted
| Executing Progress
| Done Result
deriving Int -> Status -> ShowS
[Status] -> ShowS
Status -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Status] -> ShowS
$cshowList :: [Status] -> ShowS
show :: Status -> [Char]
$cshow :: Status -> [Char]
showsPrec :: Int -> Status -> ShowS
$cshowsPrec :: Int -> Status -> ShowS
Show
type StatusMap = IntMap.IntMap (TVar Status)
data Resource r
= NotCreated
| BeingCreated
| FailedToCreate SomeException
| Created r
| BeingDestroyed
| Destroyed
instance Show (Resource r) where
show :: Resource r -> [Char]
show Resource r
r = case Resource r
r of
Resource r
NotCreated -> [Char]
"NotCreated"
Resource r
BeingCreated -> [Char]
"BeingCreated"
FailedToCreate SomeException
exn -> [Char]
"FailedToCreate " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show SomeException
exn
Created {} -> [Char]
"Created"
Resource r
BeingDestroyed -> [Char]
"BeingDestroyed"
Resource r
Destroyed -> [Char]
"Destroyed"
data Initializer
= forall res . Initializer
(IO res)
(TVar (Resource res))
data Finalizer
= forall res . Finalizer
(res -> IO ())
(TVar (Resource res))
(TVar Int)
executeTest
:: ((Progress -> IO ()) -> IO Result)
-> TVar Status
-> Timeout
-> Seq.Seq Initializer
-> Seq.Seq Finalizer
-> IO ()
executeTest :: ((Progress -> IO ()) -> IO Result)
-> TVar Status
-> Timeout
-> Seq Initializer
-> Seq Finalizer
-> IO ()
executeTest (Progress -> IO ()) -> IO Result
action TVar Status
statusVar Timeout
timeoutOpt Seq Initializer
inits Seq Finalizer
fins = forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
mask forall a b. (a -> b) -> a -> b
$ \forall a. IO a -> IO a
restore -> do
Either SomeException (Time, Result)
resultOrExn <- forall e a. Exception e => IO a -> IO (Either e a)
try forall a b. (a -> b) -> a -> b
$ forall a. IO a -> IO a
restore forall a b. (a -> b) -> a -> b
$ do
IO ()
initResources
forall a b. IO a -> (Async a -> IO b) -> IO b
withAsync ((Progress -> IO ()) -> IO Result
action forall {m :: * -> *} {p}. Monad m => p -> m ()
yieldProgress) forall a b. (a -> b) -> a -> b
$ \Async Result
asy -> do
ThreadId -> [Char] -> IO ()
labelThread (forall a. Async a -> ThreadId
asyncThreadId Async Result
asy) [Char]
"tasty_test_execution_thread"
forall a. IO a -> IO (Time, a)
timed forall a b. (a -> b) -> a -> b
$ Timeout -> IO Result -> IO Result
applyTimeout Timeout
timeoutOpt forall a b. (a -> b) -> a -> b
$ do
Result
r <- forall a. Async a -> IO a
wait Async Result
asy
forall a. a -> IO a
evaluate forall a b. (a -> b) -> a -> b
$
Result -> Outcome
resultOutcome Result
r seq :: forall a b. a -> b -> b
`seq`
forall a. [a] -> ()
forceElements (Result -> [Char]
resultDescription Result
r) seq :: forall a b. a -> b -> b
`seq`
forall a. [a] -> ()
forceElements (Result -> [Char]
resultShortDescription Result
r)
forall (m :: * -> *) a. Monad m => a -> m a
return Result
r
Maybe SomeException
mbExn <- (forall a. IO a -> IO a) -> IO (Maybe SomeException)
destroyResources forall a. IO a -> IO a
restore
forall a. STM a -> IO a
atomically forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. TVar a -> a -> STM ()
writeTVar TVar Status
statusVar forall a b. (a -> b) -> a -> b
$ Result -> Status
Done forall a b. (a -> b) -> a -> b
$
case Either SomeException (Time, Result)
resultOrExn forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a b. b -> Either a b
Right ()) forall a b. a -> Either a b
Left Maybe SomeException
mbExn of
Left SomeException
ex -> SomeException -> Result
exceptionResult SomeException
ex
Right (Time
t,Result
r) -> Result
r { resultTime :: Time
resultTime = Time
t }
where
initResources :: IO ()
initResources :: IO ()
initResources =
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
F.forM_ Seq Initializer
inits forall a b. (a -> b) -> a -> b
$ \(Initializer IO res
doInit TVar (Resource res)
initVar) -> do
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join forall a b. (a -> b) -> a -> b
$ forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ do
Resource res
resStatus <- forall a. TVar a -> STM a
readTVar TVar (Resource res)
initVar
case Resource res
resStatus of
Resource res
NotCreated -> do
forall a. TVar a -> a -> STM ()
writeTVar TVar (Resource res)
initVar forall r. Resource r
BeingCreated
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
(do
res
res <- IO res
doInit
forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ forall a. TVar a -> a -> STM ()
writeTVar TVar (Resource res)
initVar forall a b. (a -> b) -> a -> b
$ forall r. r -> Resource r
Created res
res
) forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`E.catch` \SomeException
exn -> do
forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ forall a. TVar a -> a -> STM ()
writeTVar TVar (Resource res)
initVar forall a b. (a -> b) -> a -> b
$ forall r. SomeException -> Resource r
FailedToCreate SomeException
exn
forall e a. Exception e => e -> IO a
throwIO SomeException
exn
Resource res
BeingCreated -> forall a. STM a
retry
Created {} -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return ()
FailedToCreate SomeException
exn -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO SomeException
exn
Resource res
Destroyed -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ IO ()
sleepIndefinitely
Resource res
BeingDestroyed -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ IO ()
sleepIndefinitely
applyTimeout :: Timeout -> IO Result -> IO Result
applyTimeout :: Timeout -> IO Result -> IO Result
applyTimeout Timeout
NoTimeout IO Result
a = IO Result
a
applyTimeout (Timeout Integer
t [Char]
tstr) IO Result
a = do
let
timeoutResult :: Result
timeoutResult =
Result
{ resultOutcome :: Outcome
resultOutcome = FailureReason -> Outcome
Failure forall a b. (a -> b) -> a -> b
$ Integer -> FailureReason
TestTimedOut Integer
t
, resultDescription :: [Char]
resultDescription =
[Char]
"Timed out after " forall a. [a] -> [a] -> [a]
++ [Char]
tstr
, resultShortDescription :: [Char]
resultShortDescription = [Char]
"TIMEOUT"
, resultTime :: Time
resultTime = forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
t
, resultDetailsPrinter :: ResultDetailsPrinter
resultDetailsPrinter = ResultDetailsPrinter
noResultDetails
}
let t' :: Int
t' = forall a. Num a => Integer -> a
fromInteger (forall a. Ord a => a -> a -> a
min (forall a. Ord a => a -> a -> a
max Integer
0 Integer
t) (forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: Int64)))
forall a. a -> Maybe a -> a
fromMaybe Result
timeoutResult forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Int -> IO a -> IO (Maybe a)
timeout Int
t' IO Result
a
destroyResources :: (forall a . IO a -> IO a) -> IO (Maybe SomeException)
destroyResources :: (forall a. IO a -> IO a) -> IO (Maybe SomeException)
destroyResources forall a. IO a -> IO a
restore = do
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM forall a. First a -> Maybe a
getFirst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) w a. Monad m => WriterT w m a -> m w
execWriterT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *). Traversal f -> f ()
getTraversal forall a b. (a -> b) -> a -> b
$
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
F.foldMap Seq Finalizer
fins forall a b. (a -> b) -> a -> b
$ \fin :: Finalizer
fin@(Finalizer res -> IO ()
_ TVar (Resource res)
_ TVar Int
finishVar) ->
forall (f :: * -> *). f () -> Traversal f
Traversal forall a b. (a -> b) -> a -> b
$ do
Bool
iAmLast <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ do
Int
nUsers <- forall a. TVar a -> STM a
readTVar TVar Int
finishVar
let nUsers' :: Int
nUsers' = Int
nUsers forall a. Num a => a -> a -> a
- Int
1
forall a. TVar a -> a -> STM ()
writeTVar TVar Int
finishVar Int
nUsers'
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Int
nUsers' forall a. Eq a => a -> a -> Bool
== Int
0
Maybe SomeException
mbExcn <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
if Bool
iAmLast
then (forall a. IO a -> IO a) -> Finalizer -> IO (Maybe SomeException)
destroyResource forall a. IO a -> IO a
restore Finalizer
fin
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell forall a b. (a -> b) -> a -> b
$ forall a. Maybe a -> First a
First Maybe SomeException
mbExcn
yieldProgress :: p -> m ()
yieldProgress p
_ = forall (m :: * -> *) a. Monad m => a -> m a
return ()
type InitFinPair = (Seq.Seq Initializer, Seq.Seq Finalizer)
type Deps = [(DependencyType, Expr)]
type Tr = Traversal
(WriterT ([(InitFinPair -> IO (), (TVar Status, Path, Deps))], Seq.Seq Finalizer)
(ReaderT (Path, Deps)
IO))
data DependencyException
= DependencyLoop
deriving (Typeable)
instance Show DependencyException where
show :: DependencyException -> [Char]
show DependencyException
DependencyLoop = [Char]
"Test dependencies form a loop."
instance Exception DependencyException
createTestActions
:: OptionSet
-> TestTree
-> IO ([(Action, TVar Status)], Seq.Seq Finalizer)
createTestActions :: OptionSet
-> TestTree -> IO ([(Action, TVar Status)], Seq Finalizer)
createTestActions OptionSet
opts0 TestTree
tree = do
let
traversal :: Tr
traversal :: Tr
traversal =
forall b. Monoid b => TreeFold b -> OptionSet -> TestTree -> b
foldTestTree
(forall b. Monoid b => TreeFold b
trivialFold :: TreeFold Tr)
{ foldSingle :: forall t. IsTest t => OptionSet -> [Char] -> t -> Tr
foldSingle = forall t. IsTest t => OptionSet -> [Char] -> t -> Tr
runSingleTest
, foldResource :: forall a. OptionSet -> ResourceSpec a -> (IO a -> Tr) -> Tr
foldResource = forall a. OptionSet -> ResourceSpec a -> (IO a -> Tr) -> Tr
addInitAndRelease
, foldGroup :: OptionSet -> [Char] -> Tr -> Tr
foldGroup = \OptionSet
_opts [Char]
name (Traversal WriterT
([(InitFinPair -> IO (), (TVar Status, Path, Deps))],
Seq Finalizer)
(ReaderT (Path, Deps) IO)
()
a) ->
forall (f :: * -> *). f () -> Traversal f
Traversal forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a w (n :: * -> *) b w'.
(m (a, w) -> n (b, w')) -> WriterT w m a -> WriterT w' n b
mapWriterT (forall r (m :: * -> *) a.
(r -> r) -> ReaderT r m a -> ReaderT r m a
local (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first (forall a. Seq a -> a -> Seq a
Seq.|> [Char]
name))) WriterT
([(InitFinPair -> IO (), (TVar Status, Path, Deps))],
Seq Finalizer)
(ReaderT (Path, Deps) IO)
()
a
, foldAfter :: OptionSet -> DependencyType -> Expr -> Tr -> Tr
foldAfter = \OptionSet
_opts DependencyType
deptype Expr
pat (Traversal WriterT
([(InitFinPair -> IO (), (TVar Status, Path, Deps))],
Seq Finalizer)
(ReaderT (Path, Deps) IO)
()
a) ->
forall (f :: * -> *). f () -> Traversal f
Traversal forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a w (n :: * -> *) b w'.
(m (a, w) -> n (b, w')) -> WriterT w m a -> WriterT w' n b
mapWriterT (forall r (m :: * -> *) a.
(r -> r) -> ReaderT r m a -> ReaderT r m a
local (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second ((DependencyType
deptype, Expr
pat) forall a. a -> [a] -> [a]
:))) WriterT
([(InitFinPair -> IO (), (TVar Status, Path, Deps))],
Seq Finalizer)
(ReaderT (Path, Deps) IO)
()
a
}
OptionSet
opts0 TestTree
tree
([(InitFinPair -> IO (), (TVar Status, Path, Deps))]
tests, Seq Finalizer
fins) <- Path
-> Deps
-> Tr
-> IO
([(InitFinPair -> IO (), (TVar Status, Path, Deps))],
Seq Finalizer)
unwrap (forall a. Monoid a => a
mempty :: Path) (forall a. Monoid a => a
mempty :: Deps) Tr
traversal
let
mb_tests :: Maybe [(Action, TVar Status)]
mb_tests :: Maybe [(Action, TVar Status)]
mb_tests = [(IO (), (TVar Status, Path, Deps))]
-> Maybe [(Action, TVar Status)]
resolveDeps forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map
(\(InitFinPair -> IO ()
act, (TVar Status, Path, Deps)
testInfo) ->
(InitFinPair -> IO ()
act (forall a. Seq a
Seq.empty, forall a. Seq a
Seq.empty), (TVar Status, Path, Deps)
testInfo))
[(InitFinPair -> IO (), (TVar Status, Path, Deps))]
tests
case Maybe [(Action, TVar Status)]
mb_tests of
Just [(Action, TVar Status)]
tests' -> forall (m :: * -> *) a. Monad m => a -> m a
return ([(Action, TVar Status)]
tests', Seq Finalizer
fins)
Maybe [(Action, TVar Status)]
Nothing -> forall e a. Exception e => e -> IO a
throwIO DependencyException
DependencyLoop
where
runSingleTest :: IsTest t => OptionSet -> TestName -> t -> Tr
runSingleTest :: forall t. IsTest t => OptionSet -> [Char] -> t -> Tr
runSingleTest OptionSet
opts [Char]
name t
test = forall (f :: * -> *). f () -> Traversal f
Traversal forall a b. (a -> b) -> a -> b
$ do
TVar Status
statusVar <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ forall a. a -> STM (TVar a)
newTVar Status
NotStarted
(Path
parentPath, Deps
deps) <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall (m :: * -> *) r. Monad m => ReaderT r m r
ask
let
path :: Path
path = Path
parentPath forall a. Seq a -> a -> Seq a
Seq.|> [Char]
name
act :: InitFinPair -> IO ()
act (Seq Initializer
inits, Seq Finalizer
fins) =
((Progress -> IO ()) -> IO Result)
-> TVar Status
-> Timeout
-> Seq Initializer
-> Seq Finalizer
-> IO ()
executeTest (forall t.
IsTest t =>
OptionSet -> t -> (Progress -> IO ()) -> IO Result
run OptionSet
opts t
test) TVar Status
statusVar (forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts) Seq Initializer
inits Seq Finalizer
fins
forall (m :: * -> *) w. Monad m => w -> WriterT w m ()
tell ([(InitFinPair -> IO ()
act, (TVar Status
statusVar, Path
path, Deps
deps))], forall a. Monoid a => a
mempty)
addInitAndRelease :: OptionSet -> ResourceSpec a -> (IO a -> Tr) -> Tr
addInitAndRelease :: forall a. OptionSet -> ResourceSpec a -> (IO a -> Tr) -> Tr
addInitAndRelease OptionSet
_opts (ResourceSpec IO a
doInit a -> IO ()
doRelease) IO a -> Tr
a = (Path
-> Deps
-> IO
([(InitFinPair -> IO (), (TVar Status, Path, Deps))],
Seq Finalizer))
-> Tr
wrap forall a b. (a -> b) -> a -> b
$ \Path
path Deps
deps -> do
TVar (Resource a)
initVar <- forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ forall a. a -> STM (TVar a)
newTVar forall r. Resource r
NotCreated
([(InitFinPair -> IO (), (TVar Status, Path, Deps))]
tests, Seq Finalizer
fins) <- Path
-> Deps
-> Tr
-> IO
([(InitFinPair -> IO (), (TVar Status, Path, Deps))],
Seq Finalizer)
unwrap Path
path Deps
deps forall a b. (a -> b) -> a -> b
$ IO a -> Tr
a (forall r. TVar (Resource r) -> IO r
getResource TVar (Resource a)
initVar)
let ntests :: Int
ntests = forall (t :: * -> *) a. Foldable t => t a -> Int
length [(InitFinPair -> IO (), (TVar Status, Path, Deps))]
tests
TVar Int
finishVar <- forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ forall a. a -> STM (TVar a)
newTVar Int
ntests
let
ini :: Initializer
ini = forall res. IO res -> TVar (Resource res) -> Initializer
Initializer IO a
doInit TVar (Resource a)
initVar
fin :: Finalizer
fin = forall res.
(res -> IO ()) -> TVar (Resource res) -> TVar Int -> Finalizer
Finalizer a -> IO ()
doRelease TVar (Resource a)
initVar TVar Int
finishVar
tests' :: [(InitFinPair -> IO (), (TVar Status, Path, Deps))]
tests' = forall a b. (a -> b) -> [a] -> [b]
map (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first (\InitFinPair -> IO ()
f (Seq Initializer
x, Seq Finalizer
y) -> InitFinPair -> IO ()
f (Seq Initializer
x forall a. Seq a -> a -> Seq a
Seq.|> Initializer
ini, Finalizer
fin forall a. a -> Seq a -> Seq a
Seq.<| Seq Finalizer
y))) [(InitFinPair -> IO (), (TVar Status, Path, Deps))]
tests
forall (m :: * -> *) a. Monad m => a -> m a
return ([(InitFinPair -> IO (), (TVar Status, Path, Deps))]
tests', Seq Finalizer
fins forall a. Seq a -> a -> Seq a
Seq.|> Finalizer
fin)
wrap
:: (Path ->
Deps ->
IO ([(InitFinPair -> IO (), (TVar Status, Path, Deps))], Seq.Seq Finalizer))
-> Tr
wrap :: (Path
-> Deps
-> IO
([(InitFinPair -> IO (), (TVar Status, Path, Deps))],
Seq Finalizer))
-> Tr
wrap = forall (f :: * -> *). f () -> Traversal f
Traversal forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
WriterT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((,) ()) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry
unwrap
:: Path
-> Deps
-> Tr
-> IO ([(InitFinPair -> IO (), (TVar Status, Path, Deps))], Seq.Seq Finalizer)
unwrap :: Path
-> Deps
-> Tr
-> IO
([(InitFinPair -> IO (), (TVar Status, Path, Deps))],
Seq Finalizer)
unwrap Path
path Deps
deps = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (Path
path, Deps
deps) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) w a. Monad m => WriterT w m a -> m w
execWriterT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *). Traversal f -> f ()
getTraversal
resolveDeps :: [(IO (), (TVar Status, Path, Deps))] -> Maybe [(Action, TVar Status)]
resolveDeps :: [(IO (), (TVar Status, Path, Deps))]
-> Maybe [(Action, TVar Status)]
resolveDeps [(IO (), (TVar Status, Path, Deps))]
tests = forall b a. Ord b => [(a, (b, [b]))] -> Maybe [a]
checkCycles forall a b. (a -> b) -> a -> b
$ do
(IO ()
run_test, (TVar Status
statusVar, Path
path0, Deps
deps)) <- [(IO (), (TVar Status, Path, Deps))]
tests
let
deps' :: [(DependencyType, TVar Status, Path)]
deps' :: [(DependencyType, TVar Status, Path)]
deps' = do
(DependencyType
deptype, Expr
depexpr) <- Deps
deps
(IO ()
_, (TVar Status
statusVar1, Path
path, Deps
_)) <- [(IO (), (TVar Status, Path, Deps))]
tests
forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ Expr -> Path -> Bool
exprMatches Expr
depexpr Path
path
forall (m :: * -> *) a. Monad m => a -> m a
return (DependencyType
deptype, TVar Status
statusVar1, Path
path)
getStatus :: STM ActionStatus
getStatus :: STM ActionStatus
getStatus = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr
(\(DependencyType
deptype, TVar Status
statusvar, Path
_) STM ActionStatus
k -> do
Status
status <- forall a. TVar a -> STM a
readTVar TVar Status
statusvar
case Status
status of
Done Result
result
| DependencyType
deptype forall a. Eq a => a -> a -> Bool
== DependencyType
AllFinish Bool -> Bool -> Bool
|| Result -> Bool
resultSuccessful Result
result -> STM ActionStatus
k
| Bool
otherwise -> forall (m :: * -> *) a. Monad m => a -> m a
return ActionStatus
ActionSkip
Status
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return ActionStatus
ActionWait
)
(forall (m :: * -> *) a. Monad m => a -> m a
return ActionStatus
ActionReady)
[(DependencyType, TVar Status, Path)]
deps'
let
dep_paths :: [Path]
dep_paths = forall a b. (a -> b) -> [a] -> [b]
map (\(DependencyType
_, TVar Status
_, Path
path) -> Path
path) [(DependencyType, TVar Status, Path)]
deps'
action :: Action
action = Action
{ actionStatus :: STM ActionStatus
actionStatus = STM ActionStatus
getStatus
, actionRun :: IO ()
actionRun = IO ()
run_test
, actionSkip :: STM ()
actionSkip = forall a. TVar a -> a -> STM ()
writeTVar TVar Status
statusVar forall a b. (a -> b) -> a -> b
$ Result -> Status
Done forall a b. (a -> b) -> a -> b
$ Result
{ resultOutcome :: Outcome
resultOutcome = FailureReason -> Outcome
Failure FailureReason
TestDepFailed
, resultDescription :: [Char]
resultDescription = [Char]
""
, resultShortDescription :: [Char]
resultShortDescription = [Char]
"SKIP"
, resultTime :: Time
resultTime = Time
0
, resultDetailsPrinter :: ResultDetailsPrinter
resultDetailsPrinter = ResultDetailsPrinter
noResultDetails
}
}
forall (m :: * -> *) a. Monad m => a -> m a
return ((Action
action, TVar Status
statusVar), (Path
path0, [Path]
dep_paths))
checkCycles :: Ord b => [(a, (b, [b]))] -> Maybe [a]
checkCycles :: forall b a. Ord b => [(a, (b, [b]))] -> Maybe [a]
checkCycles [(a, (b, [b]))]
tests = do
let
result :: [a]
result = forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(a, (b, [b]))]
tests
graph :: [((), b, [b])]
graph = [ ((), b
v, [b]
vs) | (b
v, [b]
vs) <- forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(a, (b, [b]))]
tests ]
sccs :: [SCC ()]
sccs = forall key node. Ord key => [(node, key, [key])] -> [SCC node]
stronglyConnComp [((), b, [b])]
graph
not_cyclic :: Bool
not_cyclic = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\SCC ()
scc -> case SCC ()
scc of
AcyclicSCC{} -> Bool
True
CyclicSCC{} -> Bool
False)
[SCC ()]
sccs
forall (f :: * -> *). Alternative f => Bool -> f ()
guard Bool
not_cyclic
forall (m :: * -> *) a. Monad m => a -> m a
return [a]
result
getResource :: TVar (Resource r) -> IO r
getResource :: forall r. TVar (Resource r) -> IO r
getResource TVar (Resource r)
var =
forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ do
Resource r
rState <- forall a. TVar a -> STM a
readTVar TVar (Resource r)
var
case Resource r
rState of
Created r
r -> forall (m :: * -> *) a. Monad m => a -> m a
return r
r
Resource r
Destroyed -> forall e a. Exception e => e -> STM a
throwSTM ResourceError
UseOutsideOfTest
Resource r
_ -> forall e a. Exception e => e -> STM a
throwSTM forall a b. (a -> b) -> a -> b
$ forall r. [Char] -> Resource r -> SomeException
unexpectedState [Char]
"getResource" Resource r
rState
destroyResource :: (forall a . IO a -> IO a) -> Finalizer -> IO (Maybe SomeException)
destroyResource :: (forall a. IO a -> IO a) -> Finalizer -> IO (Maybe SomeException)
destroyResource forall a. IO a -> IO a
restore (Finalizer res -> IO ()
doRelease TVar (Resource res)
stateVar TVar Int
_) = forall (m :: * -> *) a. Monad m => m (m a) -> m a
join forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ do
Resource res
rState <- forall a. TVar a -> STM a
readTVar TVar (Resource res)
stateVar
case Resource res
rState of
Created res
res -> do
forall a. TVar a -> a -> STM ()
writeTVar TVar (Resource res)
stateVar forall r. Resource r
BeingDestroyed
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
(forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a. a -> Maybe a
Just (forall a b. a -> b -> a
const forall a. Maybe a
Nothing)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall e a. Exception e => IO a -> IO (Either e a)
try (forall a. IO a -> IO a
restore forall a b. (a -> b) -> a -> b
$ res -> IO ()
doRelease res
res))
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall a. STM a -> IO a
atomically (forall a. TVar a -> a -> STM ()
writeTVar TVar (Resource res)
stateVar forall r. Resource r
Destroyed)
Resource res
BeingCreated -> forall a. STM a
retry
Resource res
BeingDestroyed -> forall a. STM a
retry
Resource res
NotCreated -> do
forall a. TVar a -> a -> STM ()
writeTVar TVar (Resource res)
stateVar forall r. Resource r
Destroyed
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
FailedToCreate {} -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
Resource res
Destroyed -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
launchTestTree
:: OptionSet
-> TestTree
-> (StatusMap -> IO (Time -> IO a))
-> IO a
launchTestTree :: forall a.
OptionSet -> TestTree -> (StatusMap -> IO (Time -> IO a)) -> IO a
launchTestTree OptionSet
opts TestTree
tree StatusMap -> IO (Time -> IO a)
k0 = do
([(Action, TVar Status)]
testActions, Seq Finalizer
fins) <- OptionSet
-> TestTree -> IO ([(Action, TVar Status)], Seq Finalizer)
createTestActions OptionSet
opts TestTree
tree
let NumThreads Int
numTheads = forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
(Time
t,Time -> IO a
k1) <- forall a. IO a -> IO (Time, a)
timed forall a b. (a -> b) -> a -> b
$ do
IO ()
abortTests <- Int -> [Action] -> IO (IO ())
runInParallel Int
numTheads (forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Action, TVar Status)]
testActions)
(do let smap :: StatusMap
smap = forall a. [(Int, a)] -> IntMap a
IntMap.fromList forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..] (forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Action, TVar Status)]
testActions)
StatusMap -> IO (Time -> IO a)
k0 StatusMap
smap)
forall a b. IO a -> ((forall a. IO a -> IO a) -> IO b) -> IO a
`finallyRestore` \forall a. IO a -> IO a
restore -> do
IO ()
abortTests
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
F.mapM_ ((forall a. IO a -> IO a) -> Finalizer -> IO (Maybe SomeException)
destroyResource forall a. IO a -> IO a
restore) Seq Finalizer
fins
forall a. IO a -> IO a
restore forall a b. (a -> b) -> a -> b
$ forall {t :: * -> *}. Foldable t => t Finalizer -> IO ()
waitForResources Seq Finalizer
fins
Time -> IO a
k1 Time
t
where
alive :: Resource r -> Bool
alive :: forall r. Resource r -> Bool
alive Resource r
r = case Resource r
r of
Resource r
NotCreated -> Bool
False
Resource r
BeingCreated -> Bool
True
FailedToCreate {} -> Bool
False
Created {} -> Bool
True
Resource r
BeingDestroyed -> Bool
True
Resource r
Destroyed -> Bool
False
waitForResources :: t Finalizer -> IO ()
waitForResources t Finalizer
fins = forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
F.forM_ t Finalizer
fins forall a b. (a -> b) -> a -> b
$ \(Finalizer res -> IO ()
_ TVar (Resource res)
rvar TVar Int
_) -> do
Resource res
res <- forall a. TVar a -> STM a
readTVar TVar (Resource res)
rvar
Bool -> STM ()
check forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall r. Resource r -> Bool
alive Resource res
res
unexpectedState :: String -> Resource r -> SomeException
unexpectedState :: forall r. [Char] -> Resource r -> SomeException
unexpectedState [Char]
where_ Resource r
r = forall e. Exception e => e -> SomeException
toException forall a b. (a -> b) -> a -> b
$ [Char] -> [Char] -> ResourceError
UnexpectedState [Char]
where_ (forall a. Show a => a -> [Char]
show Resource r
r)
sleepIndefinitely :: IO ()
sleepIndefinitely :: IO ()
sleepIndefinitely = forall (f :: * -> *) a b. Applicative f => f a -> f b
forever forall a b. (a -> b) -> a -> b
$ Int -> IO ()
threadDelay (Int
10forall a b. (Num a, Integral b) => a -> b -> a
^(Int
7::Int))
finallyRestore
:: IO a
-> ((forall c . IO c -> IO c) -> IO b)
-> IO a
IO a
a finallyRestore :: forall a b. IO a -> ((forall a. IO a -> IO a) -> IO b) -> IO a
`finallyRestore` (forall a. IO a -> IO a) -> IO b
sequel =
forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
mask forall a b. (a -> b) -> a -> b
$ \forall a. IO a -> IO a
restore -> do
a
r <- forall a. IO a -> IO a
restore IO a
a forall a b. IO a -> IO b -> IO a
`onException` (forall a. IO a -> IO a) -> IO b
sequel forall a. IO a -> IO a
restore
b
_ <- (forall a. IO a -> IO a) -> IO b
sequel forall a. IO a -> IO a
restore
forall (m :: * -> *) a. Monad m => a -> m a
return a
r