module Test.HUnit.Tools (assertRaises, mapassertEqual,
runVerbTestText, runVerboseTests, qccheck, qctest,
qc2hu, tl)
where
import Test.QuickCheck as QC
import Test.QuickCheck.Text
import Test.QuickCheck.Test
import Test.QuickCheck.Gen
import Test.QuickCheck.State
import qualified Test.QuickCheck.Property as P
import Test.QuickCheck.Property hiding (Result(reason))
import qualified Control.Exception
import qualified Test.HUnit as HU
#if MIN_VERSION_QuickCheck(2,7,0)
import Test.QuickCheck.Random (newQCGen, QCGen(..))
import System.Random (split)
#else
import System.Random (newStdGen, StdGen(..), split)
#define newStdGen newQCGen
#define StdGen QCGen
#endif
import System.IO
import Text.Printf
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 610
assertRaises :: (Show a, Control.Exception.Exception e, Show e, Eq e) =>
String -> e -> IO a -> IO ()
#else
assertRaises :: Show a => String -> Control.Exception.Exception -> IO a -> IO ()
#endif
assertRaises msg selector action =
let thetest e = if e == selector then return ()
else HU.assertFailure $ msg ++ "\nReceived unexpected exception: "
++ (show e) ++ "\ninstead of exception: " ++ (show selector)
in do
r <- Control.Exception.try action
case r of
Left e -> thetest e
Right _ -> HU.assertFailure $ msg ++ "\nReceived no exception, but was expecting exception: " ++ (show selector)
mapassertEqual :: (Show b, Eq b) => String -> (a -> b) -> [(a, b)] -> [HU.Test]
mapassertEqual _ _ [] = []
mapassertEqual descrip func ((inp,result):xs) =
(HU.TestCase $ HU.assertEqual descrip result (func inp)) : mapassertEqual descrip func xs
qccheck :: (QC.Testable a) =>
QC.Args
-> String
-> a
-> HU.Test
qccheck config lbl property =
HU.TestLabel lbl $ HU.TestCase $
do result <- localquickCheckWithResult config property
case result of
#if MIN_VERSION_QuickCheck(2,3,0)
Success _ _ _ -> return ()
#else
Success _ -> return ()
#endif
_ -> HU.assertFailure (show result)
runVerbTestText :: HU.PutText st -> HU.Test -> IO (HU.Counts, st)
runVerbTestText (HU.PutText put us) t = do
hSetBuffering stdout LineBuffering
hSetBuffering stderr LineBuffering
(counts, us') <- HU.performTest reportStart reportError reportFailure us t
us'' <- put (HU.showCounts counts) True us'
return (counts, us'')
where
reportStart ss us = do hFlush stderr
hPrintf stdout "\rTesting %-70s\n"
(HU.showPath (HU.path ss))
hFlush stdout
put (HU.showCounts (HU.counts ss)) False us
reportError = reportProblem "Error:" "Error in: "
reportFailure = reportProblem "Failure:" "Failure in: "
reportProblem p0 p1 msg ss us = put line True us
where line = "### " ++ kind ++ path' ++ '\n' : msg
kind = if null path' then p0 else p1
path' = HU.showPath (HU.path ss)
qctest :: (QC.Testable a) => String -> a -> HU.Test
qctest lbl = qccheck stdArgs lbl
qc2hu :: QC.Testable a => Int -> String -> a -> HU.Test
qc2hu maxTest = qccheck (stdArgs {maxSuccess = maxTest,
#if MIN_VERSION_QuickCheck(2,5,0)
maxDiscardRatio = if maxTest /= 0 then 20000 `div` maxTest else 10
#else
maxDiscard = 20000
#endif
})
runVerboseTests :: HU.Test -> IO (HU.Counts, Int)
runVerboseTests tests =
runVerbTestText (myPutText stderr True) $ tests
where myPutText h b =
case HU.putTextToHandle h b of
HU.PutText putf st -> HU.PutText (myputf h putf) st
myputf h putf x y z = do r <- putf x y z
hFlush h
return r
tl :: String -> [HU.Test] -> HU.Test
tl msg t = HU.TestLabel msg $ HU.TestList t
localquickCheckWithResult :: Testable prop => Args -> prop -> IO Result
localquickCheckWithResult args p =
#if MIN_VERSION_QuickCheck(2,3,0)
#if MIN_VERSION_QuickCheck(2,6,0)
(if chatty args then withStdioTerminal else withNullTerminal) $ \tm -> do
#else
do
tm <- if chatty args then newStdioTerminal else newNullTerminal
#endif
#else
do
tm <- newTerminal
#endif
rnd <- case replay args of
Nothing -> newQCGen
Just (rnd,_) -> return rnd
test MkState{ terminal = tm
, maxSuccessTests = maxSuccess args
, maxDiscardedTests =
#if MIN_VERSION_QuickCheck(2,5,0)
maxDiscardRatio args * maxSuccess args
#else
maxDiscard args
#endif
, computeSize = case replay args of
Nothing -> \n d -> (n * maxSize args)
`div` maxSuccess args
+ (d `div` 10)
Just (_,s) -> \_ _ -> s
, numSuccessTests = 0
, numDiscardedTests = 0
, collected = []
, expectedFailure = False
, randomSeed = rnd
#if !(MIN_VERSION_QuickCheck(2,3,0))
, isShrinking = False
#endif
, numSuccessShrinks = 0
, numTryShrinks = 0
#if MIN_VERSION_QuickCheck(2,7,0)
, numRecentlyDiscardedTests = 0
, numTotTryShrinks = 0
} (unGen (unProperty (property p)))
#else
} (unGen (property p))
#endif
where
test :: State -> (QCGen -> Int -> Prop) -> IO Result
test st f
| numSuccessTests st >= maxSuccessTests st = doneTesting st f
| numDiscardedTests st >= maxDiscardedTests st = giveUp st f
| otherwise = runATest st f
doneTesting :: State -> (QCGen -> Int -> Prop) -> IO Result
doneTesting st f =
do
#if MIN_VERSION_QuickCheck(2,3,0)
theOutput <- terminalOutput (terminal st)
#endif
if expectedFailure st then
return Success{ labels = summary st
#if MIN_VERSION_QuickCheck(2,3,0)
, numTests = numSuccessTests st
, output = theOutput
#endif
}
else
return NoExpectedFailure{ labels = summary st
#if MIN_VERSION_QuickCheck(2,3,0)
, numTests = numSuccessTests st
, output = theOutput
#endif
}
giveUp :: State -> (QCGen -> Int -> Prop) -> IO Result
giveUp st f =
do
#if MIN_VERSION_QuickCheck(2,3,0)
theOutput <- terminalOutput (terminal st)
#endif
return GaveUp{ numTests = numSuccessTests st
, labels = summary st
#if MIN_VERSION_QuickCheck(2,3,0)
, output = theOutput
#endif
}
runATest :: State -> (QCGen -> Int -> Prop) -> IO Result
runATest st f =
do
let size = computeSize st (numSuccessTests st) (numDiscardedTests st)
#if MIN_VERSION_QuickCheck(2,4,0)
MkRose res ts <- protectRose (reduceRose (unProp (f rnd1 size)))
#elif MIN_VERSION_QuickCheck(2,3,0)
(mres, ts) <- unpackRose (unProp (f rnd1 size))
res <- mres
#elif MIN_VERSION_QuickCheck(2,1,0)
MkRose mres ts <- protectRose (unProp (f rnd1 size))
res <- mres
#endif
callbackPostTest st res
case ok res of
Just True ->
do test st{ numSuccessTests = numSuccessTests st + 1
, randomSeed = rnd2
, collected = stamp res : collected st
, expectedFailure = expect res
} f
Nothing ->
do test st{ numDiscardedTests = numDiscardedTests st + 1
, randomSeed = rnd2
, expectedFailure = expect res
} f
Just False ->
do
#if MIN_VERSION_QuickCheck(2,3,0)
#if MIN_VERSION_QuickCheck(2,3,0)
(numShrinks, totFailed, lastFailed) <- foundFailure st res ts
#else
numShrinks <- foundFailure st res ts
#endif
theOutput <- terminalOutput (terminal st)
#else
foundFailure st res ts
#endif
if not (expect res) then
return Success{ labels = summary st
#if MIN_VERSION_QuickCheck(2,3,0)
, numTests = numSuccessTests st+1
, output = theOutput
#endif
}
else
return Failure{ usedSeed = randomSeed st
, usedSize = size
, reason = P.reason res
, labels = summary st
#if MIN_VERSION_QuickCheck(2,3,0)
, numTests = numSuccessTests st + 1
, numShrinks = numShrinks
, output = theOutput
#endif
#if MIN_VERSION_QuickCheck(2,7,0)
, numShrinkTries = totFailed
, numShrinkFinal = lastFailed
#endif
}
where (rnd1,rnd2) = split (randomSeed st)