module Test.Framework.Providers.QuickCheck2 (
testProperty
) where
import Test.Framework.Providers.API
import Test.QuickCheck.Property (Testable, Callback(PostTest), CallbackKind(NotCounterexample), callback)
import Test.QuickCheck.State (numSuccessTests)
import Test.QuickCheck.Test
#if MIN_VERSION_QuickCheck(2,7,0)
import Test.QuickCheck.Random (QCGen, mkQCGen)
#endif
import System.Random
import Data.Typeable
testProperty :: Testable a => TestName -> a -> Test
testProperty name = Test name . Property
instance TestResultlike PropertyTestCount PropertyResult where
testSucceeded = propertySucceeded
type PropertyTestCount = Int
data PropertyResult = PropertyResult {
pr_status :: PropertyStatus,
pr_used_seed :: Int,
pr_tests_run :: Maybe PropertyTestCount
}
data PropertyStatus = PropertyOK
| PropertyArgumentsExhausted
| PropertyFalsifiable String String
| PropertyNoExpectedFailure
| PropertyTimedOut
#if MIN_VERSION_QuickCheck(2,8,0)
| PropertyInsufficientCoverage
#endif
instance Show PropertyResult where
show (PropertyResult { pr_status = status, pr_used_seed = used_seed, pr_tests_run = mb_tests_run })
= case status of
PropertyOK -> "OK, passed " ++ tests_run_str ++ " tests"
PropertyArgumentsExhausted -> "Arguments exhausted after " ++ tests_run_str ++ " tests"
PropertyFalsifiable _rsn otpt -> otpt ++ "(used seed " ++ show used_seed ++ ")"
PropertyNoExpectedFailure -> "No expected failure with seed " ++ show used_seed ++ ", after " ++ tests_run_str ++ " tests"
PropertyTimedOut -> "Timed out after " ++ tests_run_str ++ " tests"
#if MIN_VERSION_QuickCheck(2,8,0)
PropertyInsufficientCoverage -> "Insufficient coverage after " ++ tests_run_str ++ " tests"
#endif
where
tests_run_str = fmap show mb_tests_run `orElse` "an unknown number of"
propertySucceeded :: PropertyResult -> Bool
propertySucceeded (PropertyResult { pr_status = status, pr_tests_run = mb_n }) = case status of
PropertyOK -> True
PropertyArgumentsExhausted -> maybe False (/= 0) mb_n
_ -> False
data Property = forall a. Testable a => Property a
deriving Typeable
instance Testlike PropertyTestCount PropertyResult Property where
runTest topts (Property testable) = runProperty topts testable
testTypeName _ = "Properties"
#if MIN_VERSION_QuickCheck(2,7,0)
newSeededQCGen :: Seed -> IO (QCGen, Int)
newSeededQCGen (FixedSeed seed) = return $ (mkQCGen seed, seed)
newSeededQCGen RandomSeed = do
seed <- randomIO
return (mkQCGen seed, seed)
#else
newSeededQCGen :: Seed -> IO (StdGen, Int)
newSeededQCGen = newSeededStdGen
#endif
runProperty :: Testable a => CompleteTestOptions -> a -> IO (PropertyTestCount :~> PropertyResult, IO ())
runProperty topts testable = do
(gen, seed) <- newSeededQCGen (unK $ topt_seed topts)
let max_success = unK $ topt_maximum_generated_tests topts
max_discard = unK $ topt_maximum_unsuitable_generated_tests topts
args = stdArgs { replay = Just (gen, 0)
, maxSuccess = max_success
#if MIN_VERSION_QuickCheck(2,5,0)
, maxDiscardRatio = (max_discard `div` max_success) + 1
#else
, maxDiscard = max_discard
#endif
, maxSize = unK $ topt_maximum_test_size topts
, chatty = False }
runImprovingIO $ do
tunnel <- tunnelImprovingIO
mb_result <- maybeTimeoutImprovingIO (unK (topt_timeout topts)) $
liftIO $ quickCheckWithResult args (callback (PostTest NotCounterexample (\s _r -> tunnel $ yieldImprovement $ numSuccessTests s)) testable)
return $ case mb_result of
Nothing -> PropertyResult { pr_status = PropertyTimedOut, pr_used_seed = seed, pr_tests_run = Nothing }
Just result -> PropertyResult {
pr_status = toPropertyStatus result,
pr_used_seed = seed,
pr_tests_run = Just (numTests result)
}
where
toPropertyStatus (Success {}) = PropertyOK
toPropertyStatus (GaveUp {}) = PropertyArgumentsExhausted
toPropertyStatus (Failure { reason = rsn, output = otpt }) = PropertyFalsifiable rsn otpt
toPropertyStatus (NoExpectedFailure {}) = PropertyNoExpectedFailure
#if MIN_VERSION_QuickCheck(2,8,0)
toPropertyStatus (InsufficientCoverage _ _ _) = PropertyInsufficientCoverage
#endif