module Test.Tasty.Run
( Status(..)
, StatusMap
, launchTestTree
) where
import qualified Data.IntMap as IntMap
import qualified Data.Sequence as Seq
import qualified Data.Foldable as F
import Data.Maybe
import Control.Monad.State
import Control.Monad.Writer
import Control.Monad.Reader
import Control.Concurrent.STM
import Control.Concurrent.Timeout (timeout)
import Control.Concurrent.Async
import Control.Exception as E
import Control.Applicative
import Control.Arrow
import GHC.Conc (labelThread)
import Prelude
import qualified System.Clock as Clock
import Test.Tasty.Core
import Test.Tasty.Parallel
import Test.Tasty.Options
import Test.Tasty.Options.Core
import Test.Tasty.Runners.Reducers
data Status
= NotStarted
| Executing Progress
| Done Result
type StatusMap = IntMap.IntMap (TVar Status)
data Resource r
= NotCreated
| BeingCreated
| FailedToCreate SomeException
| Created r
| Destroyed
instance Show (Resource r) where
show r = case r of
NotCreated -> "NotCreated"
BeingCreated -> "BeingCreated"
FailedToCreate exn -> "FailedToCreate " ++ show exn
Created {} -> "Created"
Destroyed -> "Destroyed"
data ResourceVar = forall r . ResourceVar (TVar (Resource r))
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 action statusVar timeoutOpt inits fins = mask $ \restore -> do
resultOrExn <- try $ restore $ do
initResources
withAsync (action yieldProgress) $ \asy -> do
labelThread (asyncThreadId asy) "tasty_test_execution_thread"
timed $ applyTimeout timeoutOpt $ wait asy
mbExn <- destroyResources restore
atomically . writeTVar statusVar $ Done $
case resultOrExn <* maybe (Right ()) Left mbExn of
Left ex -> exceptionResult ex
Right (t,r) -> r { resultTime = t }
where
initResources :: IO ()
initResources =
F.forM_ inits $ \(Initializer doInit initVar) -> do
join $ atomically $ do
resStatus <- readTVar initVar
case resStatus of
NotCreated -> do
writeTVar initVar BeingCreated
return $
(do
res <- doInit
atomically $ writeTVar initVar $ Created res
) `E.catch` \exn -> do
atomically $ writeTVar initVar $ FailedToCreate exn
throwIO exn
BeingCreated -> retry
Created {} -> return $ return ()
FailedToCreate exn -> return $ throwIO exn
_ -> return $ throwIO $
unexpectedState "initResources" resStatus
applyTimeout :: Timeout -> IO Result -> IO Result
applyTimeout NoTimeout a = a
applyTimeout (Timeout t tstr) a = do
let
timeoutResult =
Result
{ resultOutcome = Failure $ TestTimedOut t
, resultDescription =
"Timed out after " ++ tstr
, resultShortDescription = "TIMEOUT"
, resultTime = fromIntegral t
}
fromMaybe timeoutResult <$> timeout t a
destroyResources :: (forall a . IO a -> IO a) -> IO (Maybe SomeException)
destroyResources restore = do
liftM getFirst . execWriterT . getTraversal $
flip F.foldMap fins $ \(Finalizer doRelease initVar finishVar) ->
Traversal $ do
iAmLast <- liftIO $ atomically $ do
nUsers <- readTVar finishVar
let nUsers' = nUsers 1
writeTVar finishVar nUsers'
return $ nUsers' == 0
mbExcn <- liftIO $
if iAmLast
then join $ atomically $ do
resStatus <- readTVar initVar
case resStatus of
Created res -> do
return $
(either Just (const Nothing)
<$> try (restore $ doRelease res))
<* atomically (writeTVar initVar Destroyed)
FailedToCreate {} -> return $ return Nothing
_ -> return $ return $ Just $
unexpectedState "destroyResources" resStatus
else return Nothing
tell $ First mbExcn
yieldProgress _ = return ()
type InitFinPair = (Seq.Seq Initializer, Seq.Seq Finalizer)
createTestActions :: OptionSet -> TestTree -> IO ([(IO (), TVar Status)], [ResourceVar])
createTestActions opts0 tree = do
let
traversal ::
Traversal (WriterT ([(InitFinPair -> IO (), TVar Status)], [ResourceVar]) IO)
traversal =
foldTestTree
trivialFold
{ foldSingle = runSingleTest
, foldResource = addInitAndRelease
}
opts0 tree
(tests, rvars) <- unwrap traversal
let tests' = map (first ($ (Seq.empty, Seq.empty))) tests
return (tests', rvars)
where
runSingleTest opts _ test = Traversal $ do
statusVar <- liftIO $ atomically $ newTVar NotStarted
let
act (inits, fins) =
executeTest (run opts test) statusVar (lookupOption opts) inits fins
tell ([(act, statusVar)], mempty)
addInitAndRelease (ResourceSpec doInit doRelease) a = wrap $ do
initVar <- atomically $ newTVar NotCreated
(tests, rvars) <- unwrap $ a (getResource initVar)
let ntests = length tests
finishVar <- atomically $ newTVar ntests
let
ini = Initializer doInit initVar
fin = Finalizer doRelease initVar finishVar
tests' = map (first $ local $ (Seq.|> ini) *** (fin Seq.<|)) tests
return (tests', ResourceVar initVar : rvars)
wrap = Traversal . WriterT . fmap ((,) ())
unwrap = execWriterT . getTraversal
getResource :: TVar (Resource r) -> IO r
getResource var =
atomically $ do
rState <- readTVar var
case rState of
Created r -> return r
Destroyed -> throwSTM UseOutsideOfTest
_ -> throwSTM $ unexpectedState "getResource" rState
launchTestTree
:: OptionSet
-> TestTree
-> (StatusMap -> IO (Time -> IO a))
-> IO a
launchTestTree opts tree k0 = do
(testActions, rvars) <- createTestActions opts tree
let NumThreads numTheads = lookupOption opts
(t,k1) <- timed $ do
abortTests <- runInParallel numTheads (fst <$> testActions)
(do let smap = IntMap.fromList $ zip [0..] (snd <$> testActions)
k0 smap)
`finally` do
abortTests
waitForResources rvars
k1 t
where
alive :: Resource r -> Bool
alive r = case r of
NotCreated -> False
BeingCreated -> True
FailedToCreate {} -> False
Created {} -> True
Destroyed -> False
waitForResources rvars = atomically $
forM_ rvars $ \(ResourceVar rvar) -> do
res <- readTVar rvar
check $ not $ alive res
unexpectedState :: String -> Resource r -> SomeException
unexpectedState where_ r = toException $ UnexpectedState where_ (show r)
timed :: IO a -> IO (Time, a)
timed t = do
start <- getTime
!r <- t
end <- getTime
return (endstart, r)
getTime :: IO Time
getTime = do
t <- Clock.getTime Clock.Monotonic
let ns = realToFrac $
#if MIN_VERSION_clock(0,7,1)
Clock.toNanoSecs t
#else
Clock.timeSpecAsNanoSecs t
#endif
return $ ns / 10 ^ (9 :: Int)