{-# LANGUAGE BangPatterns #-}
module Test.Tasty.Runners.Utils where
import Control.Exception
import Control.Applicative
#ifndef VERSION_clock
import Data.Time.Clock.POSIX (getPOSIXTime)
#endif
import Data.Typeable (Typeable)
import Prelude
import Text.Printf
import Foreign.C (CInt)
#ifdef VERSION_clock
import qualified System.Clock as Clock
#endif
import Test.Tasty.Core (Time)
#define INSTALL_HANDLERS defined __UNIX__ && MIN_VERSION_base(4,6,0)
#if INSTALL_HANDLERS
import Control.Concurrent (mkWeakThreadId, myThreadId)
import Control.Exception (Exception(..), throwTo)
import Control.Monad (forM_)
import System.Posix.Signals
import System.Mem.Weak (deRefWeak)
#endif
formatMessage :: String -> IO String
formatMessage = go 3
where
go :: Int -> String -> IO String
go 0 _ = return "exceptions keep throwing other exceptions!"
go recLimit msg = do
mbStr <- try $ evaluate $ forceElements msg
case mbStr of
Right () -> return msg
Left e' -> printf "message threw an exception: %s" <$> go (recLimit-1) (show (e' :: SomeException))
forceElements :: [a] -> ()
forceElements = foldr seq ()
installSignalHandlers :: IO ()
installSignalHandlers = do
#if INSTALL_HANDLERS
main_thread_id <- myThreadId
weak_tid <- mkWeakThreadId main_thread_id
forM_ [ sigABRT, sigBUS, sigFPE, sigHUP, sigILL, sigQUIT, sigSEGV,
sigSYS, sigTERM, sigUSR1, sigUSR2, sigXCPU, sigXFSZ ] $ \sig ->
installHandler sig (Catch $ send_exception weak_tid sig) Nothing
where
send_exception weak_tid sig = do
m <- deRefWeak weak_tid
case m of
Nothing -> return ()
Just tid -> throwTo tid (toException $ SignalException sig)
#else
return ()
#endif
newtype SignalException = SignalException CInt
deriving (Show, Typeable)
instance Exception SignalException
timed :: IO a -> IO (Time, a)
timed t = do
start <- getTime
!r <- t
end <- getTime
return (end-start, r)
#ifdef VERSION_clock
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)
#else
getTime :: IO Time
getTime = realToFrac <$> getPOSIXTime
#endif