#if defined(__NHC__) && __NHC__ > 120
#define BASE4 1
#endif
module Test.QuickCheck.Batch
( run
, runTests
, defOpt
, TestOptions (..)
, TestResult (..)
, isBottom
, bottom
) where
import Prelude
import System.Random
#ifdef __GLASGOW_HASKELL__
import Control.Concurrent
#endif
import Control.Exception hiding (catch, evaluate)
#if BASE4
import qualified Control.Exception as Exception
#else
import qualified Control.Exception as Exception (catch, evaluate)
#endif
import Test.QuickCheck
import System.IO.Unsafe
data TestOptions = TestOptions {
no_of_tests :: Int,
length_of_tests :: Int,
debug_tests :: Bool }
defOpt :: TestOptions
defOpt = TestOptions
{ no_of_tests = 100
, length_of_tests = 1
, debug_tests = False
}
data TestResult = TestOk String Int [[String]]
| TestExausted String Int [[String]]
| TestFailed [String] Int
#if BASE4
| TestAborted SomeException
#else
| TestAborted Exception
#endif
tests :: Config -> Gen Result -> StdGen -> Int -> Int -> [[String]]
-> IO TestResult
tests config gen rnd0 ntest nfail stamps
| ntest == configMaxTest config = return (TestOk "OK, passed" ntest stamps)
| nfail == configMaxFail config = return (TestExausted "Arguments exhausted after"
ntest stamps)
| otherwise =
do (if not (null txt) then putStr txt else return ())
case ok result of
Nothing ->
tests config gen rnd1 ntest (nfail+1) stamps
Just True ->
tests config gen rnd1 (ntest+1) nfail (stamp result:stamps)
Just False ->
do return (TestFailed (arguments result) ntest)
where
txt = configEvery config ntest (arguments result)
result = generate (configSize config ntest) rnd2 gen
(rnd1,rnd2) = split rnd0
batch n v = Config
{ configMaxTest = n
, configMaxFail = n * 10
, configSize = (+ 3) . (`div` 2)
, configEvery = \n args -> if v then show n ++ ":\n" ++ unlines args else ""
}
run :: Testable a => a -> TestOptions -> IO TestResult
run a TestOptions { no_of_tests = n, length_of_tests = len, debug_tests = debug } =
#ifdef __GLASGOW_HASKELL__
do me <- myThreadId
ready <- newEmptyMVar
r <- if len == 0
then try theTest
else try (do
watcher <- forkIO (Exception.catch
(do threadDelay (len * 1000 * 1000)
takeMVar ready
throwTo me NonTermination
return ())
#if BASE4
(\ e -> case e of
Exception.ThreadKilled -> return ()
_ -> throw e))
#else
(\ _ -> return ()))
#endif
putMVar ready ()
r <- theTest
killThread watcher
return r)
case r of
Right r -> return r
Left e -> return (TestAborted e)
#else
Exception.catch theTest $ \ e -> return (TestAborted e)
#endif
where
theTest = tests (batch n debug) (evaluate a) (mkStdGen 0) 0 0 []
runTests :: String -> TestOptions -> [TestOptions -> IO TestResult] -> IO ()
runTests name scale actions =
do putStr (rjustify 25 name ++ " : ")
f <- tr 1 actions [] 0
mapM fa f
return ()
where
rjustify n s = replicate (max 0 (n length s)) ' ' ++ s
tr n [] xs c = do
putStr (rjustify (max 0 (35n)) " (" ++ show c ++ ")\n")
return xs
tr n (action:actions) others c =
do r <- action scale
case r of
(TestOk _ m _)
-> do { putStr "." ;
tr (n+1) actions others (c+m) }
(TestExausted s m ss)
-> do { putStr "?" ;
tr (n+1) actions others (c+m) }
(TestAborted e)
-> do { putStr "*" ;
tr (n+1) actions others c }
(TestFailed f num)
-> do { putStr "#" ;
tr (n+1) actions ((f,n,num):others) (c+num) }
fa :: ([String],Int,Int) -> IO ()
fa (f,n,no) =
do putStr "\n"
putStr (" ** test "
++ show (n :: Int)
++ " of "
++ name
++ " failed with the binding(s)\n")
sequence_ [putStr (" ** " ++ v ++ "\n")
| v <- f ]
putStr "\n"
bottom :: a
bottom = error "_|_"
isBottom :: a -> Bool
isBottom a = unsafePerformIO (do
a' <- try (Exception.evaluate a)
case a' of
#if BASE4
Left e -> let _ = e :: SomeException
in return True
#else
Left _ -> return True
#endif
Right _ -> return False)