{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveDataTypeable, NamedFieldPuns #-}
module Test.Tasty.QuickCheck
( testProperty
, testProperties
, QuickCheckTests(..)
, QuickCheckReplay(..)
, QuickCheckShowReplay(..)
, QuickCheckMaxSize(..)
, QuickCheckMaxRatio(..)
, QuickCheckVerbose(..)
, QuickCheckMaxShrinks(..)
, module Test.QuickCheck
, QC(..)
, optionSetToArgs
) where
import Test.Tasty ( testGroup )
import Test.Tasty.Providers
import Test.Tasty.Options
import qualified Test.QuickCheck as QC
import qualified Test.QuickCheck.Property as QCP
import qualified Test.QuickCheck.State as QC
import Test.Tasty.Runners (formatMessage, emptyProgress)
import Test.QuickCheck hiding
( quickCheck
, Args(..)
, Result
, stdArgs
, quickCheckWith
, quickCheckWithResult
, quickCheckResult
, verboseCheck
, verboseCheckWith
, verboseCheckWithResult
, verboseCheckResult
, verbose
#if MIN_VERSION_QuickCheck(2,11,0)
, allProperties
#endif
, forAllProperties
, quickCheckAll
, verboseCheckAll
)
import Control.Applicative
import Data.Typeable
import Data.List
import Text.Printf
import Test.QuickCheck.Random (QCGen, mkQCGen)
import Options.Applicative (metavar)
import System.Random (getStdRandom, randomR)
#if !MIN_VERSION_base(4,9,0)
import Data.Monoid
#endif
newtype QC = QC QC.Property
deriving Typeable
testProperty :: QC.Testable a => TestName -> a -> TestTree
testProperty :: forall a. Testable a => String -> a -> TestTree
testProperty String
name a
prop = String -> QC -> TestTree
forall t. IsTest t => String -> t -> TestTree
singleTest String
name (QC -> TestTree) -> QC -> TestTree
forall a b. (a -> b) -> a -> b
$ Property -> QC
QC (Property -> QC) -> Property -> QC
forall a b. (a -> b) -> a -> b
$ a -> Property
forall prop. Testable prop => prop -> Property
QC.property a
prop
testProperties :: TestName -> [(String, Property)] -> TestTree
testProperties :: String -> [(String, Property)] -> TestTree
testProperties String
name = String -> [TestTree] -> TestTree
testGroup String
name ([TestTree] -> TestTree)
-> ([(String, Property)] -> [TestTree])
-> [(String, Property)]
-> TestTree
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((String, Property) -> TestTree)
-> [(String, Property)] -> [TestTree]
forall a b. (a -> b) -> [a] -> [b]
map ((String -> Property -> TestTree) -> (String, Property) -> TestTree
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry String -> Property -> TestTree
forall a. Testable a => String -> a -> TestTree
testProperty)
newtype QuickCheckTests = QuickCheckTests Int
deriving (Integer -> QuickCheckTests
QuickCheckTests -> QuickCheckTests
QuickCheckTests -> QuickCheckTests -> QuickCheckTests
(QuickCheckTests -> QuickCheckTests -> QuickCheckTests)
-> (QuickCheckTests -> QuickCheckTests -> QuickCheckTests)
-> (QuickCheckTests -> QuickCheckTests -> QuickCheckTests)
-> (QuickCheckTests -> QuickCheckTests)
-> (QuickCheckTests -> QuickCheckTests)
-> (QuickCheckTests -> QuickCheckTests)
-> (Integer -> QuickCheckTests)
-> Num QuickCheckTests
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
+ :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
$c- :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
- :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
$c* :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
* :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
$cnegate :: QuickCheckTests -> QuickCheckTests
negate :: QuickCheckTests -> QuickCheckTests
$cabs :: QuickCheckTests -> QuickCheckTests
abs :: QuickCheckTests -> QuickCheckTests
$csignum :: QuickCheckTests -> QuickCheckTests
signum :: QuickCheckTests -> QuickCheckTests
$cfromInteger :: Integer -> QuickCheckTests
fromInteger :: Integer -> QuickCheckTests
Num, Eq QuickCheckTests
Eq QuickCheckTests =>
(QuickCheckTests -> QuickCheckTests -> Ordering)
-> (QuickCheckTests -> QuickCheckTests -> Bool)
-> (QuickCheckTests -> QuickCheckTests -> Bool)
-> (QuickCheckTests -> QuickCheckTests -> Bool)
-> (QuickCheckTests -> QuickCheckTests -> Bool)
-> (QuickCheckTests -> QuickCheckTests -> QuickCheckTests)
-> (QuickCheckTests -> QuickCheckTests -> QuickCheckTests)
-> Ord QuickCheckTests
QuickCheckTests -> QuickCheckTests -> Bool
QuickCheckTests -> QuickCheckTests -> Ordering
QuickCheckTests -> QuickCheckTests -> QuickCheckTests
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: QuickCheckTests -> QuickCheckTests -> Ordering
compare :: QuickCheckTests -> QuickCheckTests -> Ordering
$c< :: QuickCheckTests -> QuickCheckTests -> Bool
< :: QuickCheckTests -> QuickCheckTests -> Bool
$c<= :: QuickCheckTests -> QuickCheckTests -> Bool
<= :: QuickCheckTests -> QuickCheckTests -> Bool
$c> :: QuickCheckTests -> QuickCheckTests -> Bool
> :: QuickCheckTests -> QuickCheckTests -> Bool
$c>= :: QuickCheckTests -> QuickCheckTests -> Bool
>= :: QuickCheckTests -> QuickCheckTests -> Bool
$cmax :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
max :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
$cmin :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
min :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
Ord, QuickCheckTests -> QuickCheckTests -> Bool
(QuickCheckTests -> QuickCheckTests -> Bool)
-> (QuickCheckTests -> QuickCheckTests -> Bool)
-> Eq QuickCheckTests
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QuickCheckTests -> QuickCheckTests -> Bool
== :: QuickCheckTests -> QuickCheckTests -> Bool
$c/= :: QuickCheckTests -> QuickCheckTests -> Bool
/= :: QuickCheckTests -> QuickCheckTests -> Bool
Eq, Num QuickCheckTests
Ord QuickCheckTests
(Num QuickCheckTests, Ord QuickCheckTests) =>
(QuickCheckTests -> Rational) -> Real QuickCheckTests
QuickCheckTests -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: QuickCheckTests -> Rational
toRational :: QuickCheckTests -> Rational
Real, Int -> QuickCheckTests
QuickCheckTests -> Int
QuickCheckTests -> [QuickCheckTests]
QuickCheckTests -> QuickCheckTests
QuickCheckTests -> QuickCheckTests -> [QuickCheckTests]
QuickCheckTests
-> QuickCheckTests -> QuickCheckTests -> [QuickCheckTests]
(QuickCheckTests -> QuickCheckTests)
-> (QuickCheckTests -> QuickCheckTests)
-> (Int -> QuickCheckTests)
-> (QuickCheckTests -> Int)
-> (QuickCheckTests -> [QuickCheckTests])
-> (QuickCheckTests -> QuickCheckTests -> [QuickCheckTests])
-> (QuickCheckTests -> QuickCheckTests -> [QuickCheckTests])
-> (QuickCheckTests
-> QuickCheckTests -> QuickCheckTests -> [QuickCheckTests])
-> Enum QuickCheckTests
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: QuickCheckTests -> QuickCheckTests
succ :: QuickCheckTests -> QuickCheckTests
$cpred :: QuickCheckTests -> QuickCheckTests
pred :: QuickCheckTests -> QuickCheckTests
$ctoEnum :: Int -> QuickCheckTests
toEnum :: Int -> QuickCheckTests
$cfromEnum :: QuickCheckTests -> Int
fromEnum :: QuickCheckTests -> Int
$cenumFrom :: QuickCheckTests -> [QuickCheckTests]
enumFrom :: QuickCheckTests -> [QuickCheckTests]
$cenumFromThen :: QuickCheckTests -> QuickCheckTests -> [QuickCheckTests]
enumFromThen :: QuickCheckTests -> QuickCheckTests -> [QuickCheckTests]
$cenumFromTo :: QuickCheckTests -> QuickCheckTests -> [QuickCheckTests]
enumFromTo :: QuickCheckTests -> QuickCheckTests -> [QuickCheckTests]
$cenumFromThenTo :: QuickCheckTests
-> QuickCheckTests -> QuickCheckTests -> [QuickCheckTests]
enumFromThenTo :: QuickCheckTests
-> QuickCheckTests -> QuickCheckTests -> [QuickCheckTests]
Enum, Enum QuickCheckTests
Real QuickCheckTests
(Real QuickCheckTests, Enum QuickCheckTests) =>
(QuickCheckTests -> QuickCheckTests -> QuickCheckTests)
-> (QuickCheckTests -> QuickCheckTests -> QuickCheckTests)
-> (QuickCheckTests -> QuickCheckTests -> QuickCheckTests)
-> (QuickCheckTests -> QuickCheckTests -> QuickCheckTests)
-> (QuickCheckTests
-> QuickCheckTests -> (QuickCheckTests, QuickCheckTests))
-> (QuickCheckTests
-> QuickCheckTests -> (QuickCheckTests, QuickCheckTests))
-> (QuickCheckTests -> Integer)
-> Integral QuickCheckTests
QuickCheckTests -> Integer
QuickCheckTests
-> QuickCheckTests -> (QuickCheckTests, QuickCheckTests)
QuickCheckTests -> QuickCheckTests -> QuickCheckTests
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
quot :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
$crem :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
rem :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
$cdiv :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
div :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
$cmod :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
mod :: QuickCheckTests -> QuickCheckTests -> QuickCheckTests
$cquotRem :: QuickCheckTests
-> QuickCheckTests -> (QuickCheckTests, QuickCheckTests)
quotRem :: QuickCheckTests
-> QuickCheckTests -> (QuickCheckTests, QuickCheckTests)
$cdivMod :: QuickCheckTests
-> QuickCheckTests -> (QuickCheckTests, QuickCheckTests)
divMod :: QuickCheckTests
-> QuickCheckTests -> (QuickCheckTests, QuickCheckTests)
$ctoInteger :: QuickCheckTests -> Integer
toInteger :: QuickCheckTests -> Integer
Integral, Typeable)
data QuickCheckReplay
=
QuickCheckReplayNone
|
QuickCheckReplayLegacy Int
|
QuickCheckReplay (QCGen, Int)
deriving (Typeable)
newtype QuickCheckShowReplay = QuickCheckShowReplay Bool
deriving (Typeable)
newtype QuickCheckMaxSize = QuickCheckMaxSize Int
deriving (Integer -> QuickCheckMaxSize
QuickCheckMaxSize -> QuickCheckMaxSize
QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
(QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize)
-> (QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize)
-> (QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize)
-> (QuickCheckMaxSize -> QuickCheckMaxSize)
-> (QuickCheckMaxSize -> QuickCheckMaxSize)
-> (QuickCheckMaxSize -> QuickCheckMaxSize)
-> (Integer -> QuickCheckMaxSize)
-> Num QuickCheckMaxSize
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
+ :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
$c- :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
- :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
$c* :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
* :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
$cnegate :: QuickCheckMaxSize -> QuickCheckMaxSize
negate :: QuickCheckMaxSize -> QuickCheckMaxSize
$cabs :: QuickCheckMaxSize -> QuickCheckMaxSize
abs :: QuickCheckMaxSize -> QuickCheckMaxSize
$csignum :: QuickCheckMaxSize -> QuickCheckMaxSize
signum :: QuickCheckMaxSize -> QuickCheckMaxSize
$cfromInteger :: Integer -> QuickCheckMaxSize
fromInteger :: Integer -> QuickCheckMaxSize
Num, Eq QuickCheckMaxSize
Eq QuickCheckMaxSize =>
(QuickCheckMaxSize -> QuickCheckMaxSize -> Ordering)
-> (QuickCheckMaxSize -> QuickCheckMaxSize -> Bool)
-> (QuickCheckMaxSize -> QuickCheckMaxSize -> Bool)
-> (QuickCheckMaxSize -> QuickCheckMaxSize -> Bool)
-> (QuickCheckMaxSize -> QuickCheckMaxSize -> Bool)
-> (QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize)
-> (QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize)
-> Ord QuickCheckMaxSize
QuickCheckMaxSize -> QuickCheckMaxSize -> Bool
QuickCheckMaxSize -> QuickCheckMaxSize -> Ordering
QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: QuickCheckMaxSize -> QuickCheckMaxSize -> Ordering
compare :: QuickCheckMaxSize -> QuickCheckMaxSize -> Ordering
$c< :: QuickCheckMaxSize -> QuickCheckMaxSize -> Bool
< :: QuickCheckMaxSize -> QuickCheckMaxSize -> Bool
$c<= :: QuickCheckMaxSize -> QuickCheckMaxSize -> Bool
<= :: QuickCheckMaxSize -> QuickCheckMaxSize -> Bool
$c> :: QuickCheckMaxSize -> QuickCheckMaxSize -> Bool
> :: QuickCheckMaxSize -> QuickCheckMaxSize -> Bool
$c>= :: QuickCheckMaxSize -> QuickCheckMaxSize -> Bool
>= :: QuickCheckMaxSize -> QuickCheckMaxSize -> Bool
$cmax :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
max :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
$cmin :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
min :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
Ord, QuickCheckMaxSize -> QuickCheckMaxSize -> Bool
(QuickCheckMaxSize -> QuickCheckMaxSize -> Bool)
-> (QuickCheckMaxSize -> QuickCheckMaxSize -> Bool)
-> Eq QuickCheckMaxSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QuickCheckMaxSize -> QuickCheckMaxSize -> Bool
== :: QuickCheckMaxSize -> QuickCheckMaxSize -> Bool
$c/= :: QuickCheckMaxSize -> QuickCheckMaxSize -> Bool
/= :: QuickCheckMaxSize -> QuickCheckMaxSize -> Bool
Eq, Num QuickCheckMaxSize
Ord QuickCheckMaxSize
(Num QuickCheckMaxSize, Ord QuickCheckMaxSize) =>
(QuickCheckMaxSize -> Rational) -> Real QuickCheckMaxSize
QuickCheckMaxSize -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: QuickCheckMaxSize -> Rational
toRational :: QuickCheckMaxSize -> Rational
Real, Int -> QuickCheckMaxSize
QuickCheckMaxSize -> Int
QuickCheckMaxSize -> [QuickCheckMaxSize]
QuickCheckMaxSize -> QuickCheckMaxSize
QuickCheckMaxSize -> QuickCheckMaxSize -> [QuickCheckMaxSize]
QuickCheckMaxSize
-> QuickCheckMaxSize -> QuickCheckMaxSize -> [QuickCheckMaxSize]
(QuickCheckMaxSize -> QuickCheckMaxSize)
-> (QuickCheckMaxSize -> QuickCheckMaxSize)
-> (Int -> QuickCheckMaxSize)
-> (QuickCheckMaxSize -> Int)
-> (QuickCheckMaxSize -> [QuickCheckMaxSize])
-> (QuickCheckMaxSize -> QuickCheckMaxSize -> [QuickCheckMaxSize])
-> (QuickCheckMaxSize -> QuickCheckMaxSize -> [QuickCheckMaxSize])
-> (QuickCheckMaxSize
-> QuickCheckMaxSize -> QuickCheckMaxSize -> [QuickCheckMaxSize])
-> Enum QuickCheckMaxSize
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: QuickCheckMaxSize -> QuickCheckMaxSize
succ :: QuickCheckMaxSize -> QuickCheckMaxSize
$cpred :: QuickCheckMaxSize -> QuickCheckMaxSize
pred :: QuickCheckMaxSize -> QuickCheckMaxSize
$ctoEnum :: Int -> QuickCheckMaxSize
toEnum :: Int -> QuickCheckMaxSize
$cfromEnum :: QuickCheckMaxSize -> Int
fromEnum :: QuickCheckMaxSize -> Int
$cenumFrom :: QuickCheckMaxSize -> [QuickCheckMaxSize]
enumFrom :: QuickCheckMaxSize -> [QuickCheckMaxSize]
$cenumFromThen :: QuickCheckMaxSize -> QuickCheckMaxSize -> [QuickCheckMaxSize]
enumFromThen :: QuickCheckMaxSize -> QuickCheckMaxSize -> [QuickCheckMaxSize]
$cenumFromTo :: QuickCheckMaxSize -> QuickCheckMaxSize -> [QuickCheckMaxSize]
enumFromTo :: QuickCheckMaxSize -> QuickCheckMaxSize -> [QuickCheckMaxSize]
$cenumFromThenTo :: QuickCheckMaxSize
-> QuickCheckMaxSize -> QuickCheckMaxSize -> [QuickCheckMaxSize]
enumFromThenTo :: QuickCheckMaxSize
-> QuickCheckMaxSize -> QuickCheckMaxSize -> [QuickCheckMaxSize]
Enum, Enum QuickCheckMaxSize
Real QuickCheckMaxSize
(Real QuickCheckMaxSize, Enum QuickCheckMaxSize) =>
(QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize)
-> (QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize)
-> (QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize)
-> (QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize)
-> (QuickCheckMaxSize
-> QuickCheckMaxSize -> (QuickCheckMaxSize, QuickCheckMaxSize))
-> (QuickCheckMaxSize
-> QuickCheckMaxSize -> (QuickCheckMaxSize, QuickCheckMaxSize))
-> (QuickCheckMaxSize -> Integer)
-> Integral QuickCheckMaxSize
QuickCheckMaxSize -> Integer
QuickCheckMaxSize
-> QuickCheckMaxSize -> (QuickCheckMaxSize, QuickCheckMaxSize)
QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
quot :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
$crem :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
rem :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
$cdiv :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
div :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
$cmod :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
mod :: QuickCheckMaxSize -> QuickCheckMaxSize -> QuickCheckMaxSize
$cquotRem :: QuickCheckMaxSize
-> QuickCheckMaxSize -> (QuickCheckMaxSize, QuickCheckMaxSize)
quotRem :: QuickCheckMaxSize
-> QuickCheckMaxSize -> (QuickCheckMaxSize, QuickCheckMaxSize)
$cdivMod :: QuickCheckMaxSize
-> QuickCheckMaxSize -> (QuickCheckMaxSize, QuickCheckMaxSize)
divMod :: QuickCheckMaxSize
-> QuickCheckMaxSize -> (QuickCheckMaxSize, QuickCheckMaxSize)
$ctoInteger :: QuickCheckMaxSize -> Integer
toInteger :: QuickCheckMaxSize -> Integer
Integral, Typeable)
newtype QuickCheckMaxRatio = QuickCheckMaxRatio Int
deriving (Integer -> QuickCheckMaxRatio
QuickCheckMaxRatio -> QuickCheckMaxRatio
QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
(QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio)
-> (QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio)
-> (QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio)
-> (QuickCheckMaxRatio -> QuickCheckMaxRatio)
-> (QuickCheckMaxRatio -> QuickCheckMaxRatio)
-> (QuickCheckMaxRatio -> QuickCheckMaxRatio)
-> (Integer -> QuickCheckMaxRatio)
-> Num QuickCheckMaxRatio
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
+ :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
$c- :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
- :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
$c* :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
* :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
$cnegate :: QuickCheckMaxRatio -> QuickCheckMaxRatio
negate :: QuickCheckMaxRatio -> QuickCheckMaxRatio
$cabs :: QuickCheckMaxRatio -> QuickCheckMaxRatio
abs :: QuickCheckMaxRatio -> QuickCheckMaxRatio
$csignum :: QuickCheckMaxRatio -> QuickCheckMaxRatio
signum :: QuickCheckMaxRatio -> QuickCheckMaxRatio
$cfromInteger :: Integer -> QuickCheckMaxRatio
fromInteger :: Integer -> QuickCheckMaxRatio
Num, Eq QuickCheckMaxRatio
Eq QuickCheckMaxRatio =>
(QuickCheckMaxRatio -> QuickCheckMaxRatio -> Ordering)
-> (QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool)
-> (QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool)
-> (QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool)
-> (QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool)
-> (QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio)
-> (QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio)
-> Ord QuickCheckMaxRatio
QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool
QuickCheckMaxRatio -> QuickCheckMaxRatio -> Ordering
QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> Ordering
compare :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> Ordering
$c< :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool
< :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool
$c<= :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool
<= :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool
$c> :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool
> :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool
$c>= :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool
>= :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool
$cmax :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
max :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
$cmin :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
min :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
Ord, QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool
(QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool)
-> (QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool)
-> Eq QuickCheckMaxRatio
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool
== :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool
$c/= :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool
/= :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> Bool
Eq, Num QuickCheckMaxRatio
Ord QuickCheckMaxRatio
(Num QuickCheckMaxRatio, Ord QuickCheckMaxRatio) =>
(QuickCheckMaxRatio -> Rational) -> Real QuickCheckMaxRatio
QuickCheckMaxRatio -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: QuickCheckMaxRatio -> Rational
toRational :: QuickCheckMaxRatio -> Rational
Real, Int -> QuickCheckMaxRatio
QuickCheckMaxRatio -> Int
QuickCheckMaxRatio -> [QuickCheckMaxRatio]
QuickCheckMaxRatio -> QuickCheckMaxRatio
QuickCheckMaxRatio -> QuickCheckMaxRatio -> [QuickCheckMaxRatio]
QuickCheckMaxRatio
-> QuickCheckMaxRatio -> QuickCheckMaxRatio -> [QuickCheckMaxRatio]
(QuickCheckMaxRatio -> QuickCheckMaxRatio)
-> (QuickCheckMaxRatio -> QuickCheckMaxRatio)
-> (Int -> QuickCheckMaxRatio)
-> (QuickCheckMaxRatio -> Int)
-> (QuickCheckMaxRatio -> [QuickCheckMaxRatio])
-> (QuickCheckMaxRatio
-> QuickCheckMaxRatio -> [QuickCheckMaxRatio])
-> (QuickCheckMaxRatio
-> QuickCheckMaxRatio -> [QuickCheckMaxRatio])
-> (QuickCheckMaxRatio
-> QuickCheckMaxRatio
-> QuickCheckMaxRatio
-> [QuickCheckMaxRatio])
-> Enum QuickCheckMaxRatio
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: QuickCheckMaxRatio -> QuickCheckMaxRatio
succ :: QuickCheckMaxRatio -> QuickCheckMaxRatio
$cpred :: QuickCheckMaxRatio -> QuickCheckMaxRatio
pred :: QuickCheckMaxRatio -> QuickCheckMaxRatio
$ctoEnum :: Int -> QuickCheckMaxRatio
toEnum :: Int -> QuickCheckMaxRatio
$cfromEnum :: QuickCheckMaxRatio -> Int
fromEnum :: QuickCheckMaxRatio -> Int
$cenumFrom :: QuickCheckMaxRatio -> [QuickCheckMaxRatio]
enumFrom :: QuickCheckMaxRatio -> [QuickCheckMaxRatio]
$cenumFromThen :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> [QuickCheckMaxRatio]
enumFromThen :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> [QuickCheckMaxRatio]
$cenumFromTo :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> [QuickCheckMaxRatio]
enumFromTo :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> [QuickCheckMaxRatio]
$cenumFromThenTo :: QuickCheckMaxRatio
-> QuickCheckMaxRatio -> QuickCheckMaxRatio -> [QuickCheckMaxRatio]
enumFromThenTo :: QuickCheckMaxRatio
-> QuickCheckMaxRatio -> QuickCheckMaxRatio -> [QuickCheckMaxRatio]
Enum, Enum QuickCheckMaxRatio
Real QuickCheckMaxRatio
(Real QuickCheckMaxRatio, Enum QuickCheckMaxRatio) =>
(QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio)
-> (QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio)
-> (QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio)
-> (QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio)
-> (QuickCheckMaxRatio
-> QuickCheckMaxRatio -> (QuickCheckMaxRatio, QuickCheckMaxRatio))
-> (QuickCheckMaxRatio
-> QuickCheckMaxRatio -> (QuickCheckMaxRatio, QuickCheckMaxRatio))
-> (QuickCheckMaxRatio -> Integer)
-> Integral QuickCheckMaxRatio
QuickCheckMaxRatio -> Integer
QuickCheckMaxRatio
-> QuickCheckMaxRatio -> (QuickCheckMaxRatio, QuickCheckMaxRatio)
QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
quot :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
$crem :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
rem :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
$cdiv :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
div :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
$cmod :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
mod :: QuickCheckMaxRatio -> QuickCheckMaxRatio -> QuickCheckMaxRatio
$cquotRem :: QuickCheckMaxRatio
-> QuickCheckMaxRatio -> (QuickCheckMaxRatio, QuickCheckMaxRatio)
quotRem :: QuickCheckMaxRatio
-> QuickCheckMaxRatio -> (QuickCheckMaxRatio, QuickCheckMaxRatio)
$cdivMod :: QuickCheckMaxRatio
-> QuickCheckMaxRatio -> (QuickCheckMaxRatio, QuickCheckMaxRatio)
divMod :: QuickCheckMaxRatio
-> QuickCheckMaxRatio -> (QuickCheckMaxRatio, QuickCheckMaxRatio)
$ctoInteger :: QuickCheckMaxRatio -> Integer
toInteger :: QuickCheckMaxRatio -> Integer
Integral, Typeable)
newtype QuickCheckVerbose = QuickCheckVerbose Bool
deriving (Typeable)
newtype QuickCheckMaxShrinks = QuickCheckMaxShrinks Int
deriving (Integer -> QuickCheckMaxShrinks
QuickCheckMaxShrinks -> QuickCheckMaxShrinks
QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
(QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks)
-> (QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks)
-> (QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks)
-> (QuickCheckMaxShrinks -> QuickCheckMaxShrinks)
-> (QuickCheckMaxShrinks -> QuickCheckMaxShrinks)
-> (QuickCheckMaxShrinks -> QuickCheckMaxShrinks)
-> (Integer -> QuickCheckMaxShrinks)
-> Num QuickCheckMaxShrinks
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
+ :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
$c- :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
- :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
$c* :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
* :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
$cnegate :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks
negate :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks
$cabs :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks
abs :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks
$csignum :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks
signum :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks
$cfromInteger :: Integer -> QuickCheckMaxShrinks
fromInteger :: Integer -> QuickCheckMaxShrinks
Num, Eq QuickCheckMaxShrinks
Eq QuickCheckMaxShrinks =>
(QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Ordering)
-> (QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool)
-> (QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool)
-> (QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool)
-> (QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool)
-> (QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks)
-> (QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks)
-> Ord QuickCheckMaxShrinks
QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool
QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Ordering
QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Ordering
compare :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Ordering
$c< :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool
< :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool
$c<= :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool
<= :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool
$c> :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool
> :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool
$c>= :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool
>= :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool
$cmax :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
max :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
$cmin :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
min :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
Ord, QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool
(QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool)
-> (QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool)
-> Eq QuickCheckMaxShrinks
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool
== :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool
$c/= :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool
/= :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks -> Bool
Eq, Num QuickCheckMaxShrinks
Ord QuickCheckMaxShrinks
(Num QuickCheckMaxShrinks, Ord QuickCheckMaxShrinks) =>
(QuickCheckMaxShrinks -> Rational) -> Real QuickCheckMaxShrinks
QuickCheckMaxShrinks -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: QuickCheckMaxShrinks -> Rational
toRational :: QuickCheckMaxShrinks -> Rational
Real, Int -> QuickCheckMaxShrinks
QuickCheckMaxShrinks -> Int
QuickCheckMaxShrinks -> [QuickCheckMaxShrinks]
QuickCheckMaxShrinks -> QuickCheckMaxShrinks
QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> [QuickCheckMaxShrinks]
QuickCheckMaxShrinks
-> QuickCheckMaxShrinks
-> QuickCheckMaxShrinks
-> [QuickCheckMaxShrinks]
(QuickCheckMaxShrinks -> QuickCheckMaxShrinks)
-> (QuickCheckMaxShrinks -> QuickCheckMaxShrinks)
-> (Int -> QuickCheckMaxShrinks)
-> (QuickCheckMaxShrinks -> Int)
-> (QuickCheckMaxShrinks -> [QuickCheckMaxShrinks])
-> (QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> [QuickCheckMaxShrinks])
-> (QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> [QuickCheckMaxShrinks])
-> (QuickCheckMaxShrinks
-> QuickCheckMaxShrinks
-> QuickCheckMaxShrinks
-> [QuickCheckMaxShrinks])
-> Enum QuickCheckMaxShrinks
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks
succ :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks
$cpred :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks
pred :: QuickCheckMaxShrinks -> QuickCheckMaxShrinks
$ctoEnum :: Int -> QuickCheckMaxShrinks
toEnum :: Int -> QuickCheckMaxShrinks
$cfromEnum :: QuickCheckMaxShrinks -> Int
fromEnum :: QuickCheckMaxShrinks -> Int
$cenumFrom :: QuickCheckMaxShrinks -> [QuickCheckMaxShrinks]
enumFrom :: QuickCheckMaxShrinks -> [QuickCheckMaxShrinks]
$cenumFromThen :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> [QuickCheckMaxShrinks]
enumFromThen :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> [QuickCheckMaxShrinks]
$cenumFromTo :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> [QuickCheckMaxShrinks]
enumFromTo :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> [QuickCheckMaxShrinks]
$cenumFromThenTo :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks
-> QuickCheckMaxShrinks
-> [QuickCheckMaxShrinks]
enumFromThenTo :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks
-> QuickCheckMaxShrinks
-> [QuickCheckMaxShrinks]
Enum, Enum QuickCheckMaxShrinks
Real QuickCheckMaxShrinks
(Real QuickCheckMaxShrinks, Enum QuickCheckMaxShrinks) =>
(QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks)
-> (QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks)
-> (QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks)
-> (QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks)
-> (QuickCheckMaxShrinks
-> QuickCheckMaxShrinks
-> (QuickCheckMaxShrinks, QuickCheckMaxShrinks))
-> (QuickCheckMaxShrinks
-> QuickCheckMaxShrinks
-> (QuickCheckMaxShrinks, QuickCheckMaxShrinks))
-> (QuickCheckMaxShrinks -> Integer)
-> Integral QuickCheckMaxShrinks
QuickCheckMaxShrinks -> Integer
QuickCheckMaxShrinks
-> QuickCheckMaxShrinks
-> (QuickCheckMaxShrinks, QuickCheckMaxShrinks)
QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
quot :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
$crem :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
rem :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
$cdiv :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
div :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
$cmod :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
mod :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks -> QuickCheckMaxShrinks
$cquotRem :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks
-> (QuickCheckMaxShrinks, QuickCheckMaxShrinks)
quotRem :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks
-> (QuickCheckMaxShrinks, QuickCheckMaxShrinks)
$cdivMod :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks
-> (QuickCheckMaxShrinks, QuickCheckMaxShrinks)
divMod :: QuickCheckMaxShrinks
-> QuickCheckMaxShrinks
-> (QuickCheckMaxShrinks, QuickCheckMaxShrinks)
$ctoInteger :: QuickCheckMaxShrinks -> Integer
toInteger :: QuickCheckMaxShrinks -> Integer
Integral, Typeable)
instance IsOption QuickCheckTests where
defaultValue :: QuickCheckTests
defaultValue = QuickCheckTests
100
parseValue :: String -> Maybe QuickCheckTests
parseValue =
(Int -> QuickCheckTests) -> Maybe Int -> Maybe QuickCheckTests
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> QuickCheckTests
QuickCheckTests (Maybe Int -> Maybe QuickCheckTests)
-> (String -> Maybe Int) -> String -> Maybe QuickCheckTests
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe Int
forall a. Read a => String -> Maybe a
safeRead (String -> Maybe Int) -> (String -> String) -> String -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
filter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'_')
optionName :: Tagged QuickCheckTests String
optionName = String -> Tagged QuickCheckTests String
forall a. a -> Tagged QuickCheckTests a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"quickcheck-tests"
optionHelp :: Tagged QuickCheckTests String
optionHelp = String -> Tagged QuickCheckTests String
forall a. a -> Tagged QuickCheckTests a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"Number of test cases for QuickCheck to generate. Underscores accepted: e.g. 10_000_000"
optionCLParser :: Parser QuickCheckTests
optionCLParser = Mod OptionFields QuickCheckTests -> Parser QuickCheckTests
forall v. IsOption v => Mod OptionFields v -> Parser v
mkOptionCLParser (Mod OptionFields QuickCheckTests -> Parser QuickCheckTests)
-> Mod OptionFields QuickCheckTests -> Parser QuickCheckTests
forall a b. (a -> b) -> a -> b
$ String -> Mod OptionFields QuickCheckTests
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"NUMBER"
instance IsOption QuickCheckReplay where
defaultValue :: QuickCheckReplay
defaultValue = QuickCheckReplay
QuickCheckReplayNone
parseValue :: String -> Maybe QuickCheckReplay
parseValue String
v =
(Int -> QuickCheckReplay
QuickCheckReplayLegacy (Int -> QuickCheckReplay) -> Maybe Int -> Maybe QuickCheckReplay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Maybe Int
forall a. Read a => String -> Maybe a
safeRead String
v) Maybe QuickCheckReplay
-> Maybe QuickCheckReplay -> Maybe QuickCheckReplay
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ((QCGen, Int) -> QuickCheckReplay
QuickCheckReplay ((QCGen, Int) -> QuickCheckReplay)
-> Maybe (QCGen, Int) -> Maybe QuickCheckReplay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Maybe (QCGen, Int)
forall a. Read a => String -> Maybe a
safeRead String
v)
optionName :: Tagged QuickCheckReplay String
optionName = String -> Tagged QuickCheckReplay String
forall a. a -> Tagged QuickCheckReplay a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"quickcheck-replay"
optionHelp :: Tagged QuickCheckReplay String
optionHelp = String -> Tagged QuickCheckReplay String
forall a. a -> Tagged QuickCheckReplay a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"Random seed to use for replaying a previous test run"
optionCLParser :: Parser QuickCheckReplay
optionCLParser = Mod OptionFields QuickCheckReplay -> Parser QuickCheckReplay
forall v. IsOption v => Mod OptionFields v -> Parser v
mkOptionCLParser (Mod OptionFields QuickCheckReplay -> Parser QuickCheckReplay)
-> Mod OptionFields QuickCheckReplay -> Parser QuickCheckReplay
forall a b. (a -> b) -> a -> b
$ String -> Mod OptionFields QuickCheckReplay
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"SEED"
instance IsOption QuickCheckShowReplay where
defaultValue :: QuickCheckShowReplay
defaultValue = Bool -> QuickCheckShowReplay
QuickCheckShowReplay Bool
False
parseValue :: String -> Maybe QuickCheckShowReplay
parseValue = (Bool -> QuickCheckShowReplay)
-> Maybe Bool -> Maybe QuickCheckShowReplay
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> QuickCheckShowReplay
QuickCheckShowReplay (Maybe Bool -> Maybe QuickCheckShowReplay)
-> (String -> Maybe Bool) -> String -> Maybe QuickCheckShowReplay
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe Bool
safeReadBool
optionName :: Tagged QuickCheckShowReplay String
optionName = String -> Tagged QuickCheckShowReplay String
forall a. a -> Tagged QuickCheckShowReplay a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"quickcheck-show-replay"
optionHelp :: Tagged QuickCheckShowReplay String
optionHelp = String -> Tagged QuickCheckShowReplay String
forall a. a -> Tagged QuickCheckShowReplay a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"Show a replay token for replaying tests"
optionCLParser :: Parser QuickCheckShowReplay
optionCLParser = Maybe Char -> QuickCheckShowReplay -> Parser QuickCheckShowReplay
forall v. IsOption v => Maybe Char -> v -> Parser v
flagCLParser Maybe Char
forall a. Maybe a
Nothing (Bool -> QuickCheckShowReplay
QuickCheckShowReplay Bool
True)
defaultMaxSize :: Int
defaultMaxSize :: Int
defaultMaxSize = Args -> Int
QC.maxSize Args
QC.stdArgs
instance IsOption QuickCheckMaxSize where
defaultValue :: QuickCheckMaxSize
defaultValue = Int -> QuickCheckMaxSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
defaultMaxSize
parseValue :: String -> Maybe QuickCheckMaxSize
parseValue = (Int -> QuickCheckMaxSize) -> Maybe Int -> Maybe QuickCheckMaxSize
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> QuickCheckMaxSize
QuickCheckMaxSize (Maybe Int -> Maybe QuickCheckMaxSize)
-> (String -> Maybe Int) -> String -> Maybe QuickCheckMaxSize
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe Int
forall a. Read a => String -> Maybe a
safeRead
optionName :: Tagged QuickCheckMaxSize String
optionName = String -> Tagged QuickCheckMaxSize String
forall a. a -> Tagged QuickCheckMaxSize a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"quickcheck-max-size"
optionHelp :: Tagged QuickCheckMaxSize String
optionHelp = String -> Tagged QuickCheckMaxSize String
forall a. a -> Tagged QuickCheckMaxSize a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"Size of the biggest test cases quickcheck generates"
optionCLParser :: Parser QuickCheckMaxSize
optionCLParser = Mod OptionFields QuickCheckMaxSize -> Parser QuickCheckMaxSize
forall v. IsOption v => Mod OptionFields v -> Parser v
mkOptionCLParser (Mod OptionFields QuickCheckMaxSize -> Parser QuickCheckMaxSize)
-> Mod OptionFields QuickCheckMaxSize -> Parser QuickCheckMaxSize
forall a b. (a -> b) -> a -> b
$ String -> Mod OptionFields QuickCheckMaxSize
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"NUMBER"
instance IsOption QuickCheckMaxRatio where
defaultValue :: QuickCheckMaxRatio
defaultValue = Int -> QuickCheckMaxRatio
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> QuickCheckMaxRatio) -> Int -> QuickCheckMaxRatio
forall a b. (a -> b) -> a -> b
$ Args -> Int
QC.maxDiscardRatio Args
QC.stdArgs
parseValue :: String -> Maybe QuickCheckMaxRatio
parseValue = (Int -> QuickCheckMaxRatio)
-> Maybe Int -> Maybe QuickCheckMaxRatio
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> QuickCheckMaxRatio
QuickCheckMaxRatio (Maybe Int -> Maybe QuickCheckMaxRatio)
-> (String -> Maybe Int) -> String -> Maybe QuickCheckMaxRatio
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe Int
forall a. Read a => String -> Maybe a
safeRead
optionName :: Tagged QuickCheckMaxRatio String
optionName = String -> Tagged QuickCheckMaxRatio String
forall a. a -> Tagged QuickCheckMaxRatio a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"quickcheck-max-ratio"
optionHelp :: Tagged QuickCheckMaxRatio String
optionHelp = String -> Tagged QuickCheckMaxRatio String
forall a. a -> Tagged QuickCheckMaxRatio a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"Maximum number of discared tests per successful test before giving up"
optionCLParser :: Parser QuickCheckMaxRatio
optionCLParser = Mod OptionFields QuickCheckMaxRatio -> Parser QuickCheckMaxRatio
forall v. IsOption v => Mod OptionFields v -> Parser v
mkOptionCLParser (Mod OptionFields QuickCheckMaxRatio -> Parser QuickCheckMaxRatio)
-> Mod OptionFields QuickCheckMaxRatio -> Parser QuickCheckMaxRatio
forall a b. (a -> b) -> a -> b
$ String -> Mod OptionFields QuickCheckMaxRatio
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"NUMBER"
instance IsOption QuickCheckVerbose where
defaultValue :: QuickCheckVerbose
defaultValue = Bool -> QuickCheckVerbose
QuickCheckVerbose Bool
False
parseValue :: String -> Maybe QuickCheckVerbose
parseValue = (Bool -> QuickCheckVerbose)
-> Maybe Bool -> Maybe QuickCheckVerbose
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> QuickCheckVerbose
QuickCheckVerbose (Maybe Bool -> Maybe QuickCheckVerbose)
-> (String -> Maybe Bool) -> String -> Maybe QuickCheckVerbose
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe Bool
safeReadBool
optionName :: Tagged QuickCheckVerbose String
optionName = String -> Tagged QuickCheckVerbose String
forall a. a -> Tagged QuickCheckVerbose a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"quickcheck-verbose"
optionHelp :: Tagged QuickCheckVerbose String
optionHelp = String -> Tagged QuickCheckVerbose String
forall a. a -> Tagged QuickCheckVerbose a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"Show the generated test cases"
optionCLParser :: Parser QuickCheckVerbose
optionCLParser = Mod FlagFields QuickCheckVerbose
-> QuickCheckVerbose -> Parser QuickCheckVerbose
forall v. IsOption v => Mod FlagFields v -> v -> Parser v
mkFlagCLParser Mod FlagFields QuickCheckVerbose
forall a. Monoid a => a
mempty (Bool -> QuickCheckVerbose
QuickCheckVerbose Bool
True)
instance IsOption QuickCheckMaxShrinks where
defaultValue :: QuickCheckMaxShrinks
defaultValue = Int -> QuickCheckMaxShrinks
QuickCheckMaxShrinks (Args -> Int
QC.maxShrinks Args
QC.stdArgs)
parseValue :: String -> Maybe QuickCheckMaxShrinks
parseValue = (Int -> QuickCheckMaxShrinks)
-> Maybe Int -> Maybe QuickCheckMaxShrinks
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> QuickCheckMaxShrinks
QuickCheckMaxShrinks (Maybe Int -> Maybe QuickCheckMaxShrinks)
-> (String -> Maybe Int) -> String -> Maybe QuickCheckMaxShrinks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe Int
forall a. Read a => String -> Maybe a
safeRead
optionName :: Tagged QuickCheckMaxShrinks String
optionName = String -> Tagged QuickCheckMaxShrinks String
forall a. a -> Tagged QuickCheckMaxShrinks a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"quickcheck-shrinks"
optionHelp :: Tagged QuickCheckMaxShrinks String
optionHelp = String -> Tagged QuickCheckMaxShrinks String
forall a. a -> Tagged QuickCheckMaxShrinks a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"Number of shrinks allowed before QuickCheck will fail a test"
optionCLParser :: Parser QuickCheckMaxShrinks
optionCLParser = Mod OptionFields QuickCheckMaxShrinks
-> Parser QuickCheckMaxShrinks
forall v. IsOption v => Mod OptionFields v -> Parser v
mkOptionCLParser (Mod OptionFields QuickCheckMaxShrinks
-> Parser QuickCheckMaxShrinks)
-> Mod OptionFields QuickCheckMaxShrinks
-> Parser QuickCheckMaxShrinks
forall a b. (a -> b) -> a -> b
$ String -> Mod OptionFields QuickCheckMaxShrinks
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"NUMBER"
optionSetToArgs :: OptionSet -> IO (Int, QC.Args)
optionSetToArgs :: OptionSet -> IO (Int, Args)
optionSetToArgs OptionSet
opts = do
(Int
intSeed, (QCGen, Int)
replaySeed) <- case QuickCheckReplay
quickCheckReplay of
QuickCheckReplay
QuickCheckReplayNone -> do
Int
intSeed <- (StdGen -> (Int, StdGen)) -> IO Int
forall (m :: * -> *) a. MonadIO m => (StdGen -> (a, StdGen)) -> m a
getStdRandom ((Int, Int) -> StdGen -> (Int, StdGen)
forall g. RandomGen g => (Int, Int) -> g -> (Int, g)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
randomR (Int
1,Int
999999))
(Int, (QCGen, Int)) -> IO (Int, (QCGen, Int))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
intSeed, (Int -> QCGen
mkQCGen Int
intSeed, Int
0))
QuickCheckReplayLegacy Int
intSeed -> (Int, (QCGen, Int)) -> IO (Int, (QCGen, Int))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
intSeed, (Int -> QCGen
mkQCGen Int
intSeed, Int
0))
QuickCheckReplay (QCGen, Int)
replaySeed -> (Int, (QCGen, Int)) -> IO (Int, (QCGen, Int))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
0, (QCGen, Int)
replaySeed)
let args :: Args
args = Args
QC.stdArgs
{ QC.chatty = False
, QC.maxSuccess = nTests
, QC.maxSize = maxSize
, QC.replay = Just replaySeed
, QC.maxDiscardRatio = maxRatio
, QC.maxShrinks = maxShrinks
}
(Int, Args) -> IO (Int, Args)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
intSeed, Args
args)
where
QuickCheckTests Int
nTests = OptionSet -> QuickCheckTests
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
quickCheckReplay :: QuickCheckReplay
quickCheckReplay = OptionSet -> QuickCheckReplay
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
QuickCheckMaxSize Int
maxSize = OptionSet -> QuickCheckMaxSize
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
QuickCheckMaxRatio Int
maxRatio = OptionSet -> QuickCheckMaxRatio
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
QuickCheckMaxShrinks Int
maxShrinks = OptionSet -> QuickCheckMaxShrinks
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
instance IsTest QC where
testOptions :: Tagged QC [OptionDescription]
testOptions = [OptionDescription] -> Tagged QC [OptionDescription]
forall a. a -> Tagged QC a
forall (m :: * -> *) a. Monad m => a -> m a
return
[ Proxy QuickCheckTests -> OptionDescription
forall v. IsOption v => Proxy v -> OptionDescription
Option (Proxy QuickCheckTests
forall {k} (t :: k). Proxy t
Proxy :: Proxy QuickCheckTests)
, Proxy QuickCheckReplay -> OptionDescription
forall v. IsOption v => Proxy v -> OptionDescription
Option (Proxy QuickCheckReplay
forall {k} (t :: k). Proxy t
Proxy :: Proxy QuickCheckReplay)
, Proxy QuickCheckShowReplay -> OptionDescription
forall v. IsOption v => Proxy v -> OptionDescription
Option (Proxy QuickCheckShowReplay
forall {k} (t :: k). Proxy t
Proxy :: Proxy QuickCheckShowReplay)
, Proxy QuickCheckMaxSize -> OptionDescription
forall v. IsOption v => Proxy v -> OptionDescription
Option (Proxy QuickCheckMaxSize
forall {k} (t :: k). Proxy t
Proxy :: Proxy QuickCheckMaxSize)
, Proxy QuickCheckMaxRatio -> OptionDescription
forall v. IsOption v => Proxy v -> OptionDescription
Option (Proxy QuickCheckMaxRatio
forall {k} (t :: k). Proxy t
Proxy :: Proxy QuickCheckMaxRatio)
, Proxy QuickCheckVerbose -> OptionDescription
forall v. IsOption v => Proxy v -> OptionDescription
Option (Proxy QuickCheckVerbose
forall {k} (t :: k). Proxy t
Proxy :: Proxy QuickCheckVerbose)
, Proxy QuickCheckMaxShrinks -> OptionDescription
forall v. IsOption v => Proxy v -> OptionDescription
Option (Proxy QuickCheckMaxShrinks
forall {k} (t :: k). Proxy t
Proxy :: Proxy QuickCheckMaxShrinks)
]
run :: OptionSet -> QC -> (Progress -> IO ()) -> IO Result
run OptionSet
opts (QC Property
prop) Progress -> IO ()
yieldProgress = do
(Int
_, Args
args) <- OptionSet -> IO (Int, Args)
optionSetToArgs OptionSet
opts
let
QuickCheckShowReplay Bool
showReplay = OptionSet -> QuickCheckShowReplay
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
QuickCheckVerbose Bool
verbose = OptionSet -> QuickCheckVerbose
forall v. IsOption v => OptionSet -> v
lookupOption OptionSet
opts
Result
r <- (Progress -> IO ()) -> Args -> Property -> IO Result
quickCheck Progress -> IO ()
yieldProgress
Args
args
(if Bool
verbose then Property -> Property
forall prop. Testable prop => prop -> Property
QC.verbose Property
prop else Property
prop)
String
qcOutput <- String -> IO String
formatMessage (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ Result -> String
QC.output Result
r
let qcOutputNl :: String
qcOutputNl =
if String
"\n" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` String
qcOutput
then String
qcOutput
else String
qcOutput String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
testSuccessful :: Bool
testSuccessful = Result -> Bool
successful Result
r
putReplayInDesc :: Bool
putReplayInDesc = (Bool -> Bool
not Bool
testSuccessful) Bool -> Bool -> Bool
|| Bool
showReplay
Just (QCGen, Int)
seedSz <- Maybe (QCGen, Int) -> IO (Maybe (QCGen, Int))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (QCGen, Int) -> IO (Maybe (QCGen, Int)))
-> Maybe (QCGen, Int) -> IO (Maybe (QCGen, Int))
forall a b. (a -> b) -> a -> b
$ Result -> Maybe (QCGen, Int)
replayFromResult Result
r Maybe (QCGen, Int) -> Maybe (QCGen, Int) -> Maybe (QCGen, Int)
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Args -> Maybe (QCGen, Int)
QC.replay Args
args
let replayMsg :: String
replayMsg = (QCGen, Int) -> String
makeReplayMsg (QCGen, Int)
seedSz
Result -> IO Result
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Result -> IO Result) -> Result -> IO Result
forall a b. (a -> b) -> a -> b
$
(if Bool
testSuccessful then String -> Result
testPassed else String -> Result
testFailed)
(String
qcOutputNl String -> String -> String
forall a. [a] -> [a] -> [a]
++
(if Bool
putReplayInDesc then String
replayMsg else String
""))
quickCheck :: (Progress -> IO ())
-> QC.Args
-> QC.Property
-> IO QC.Result
quickCheck :: (Progress -> IO ()) -> Args -> Property -> IO Result
quickCheck Progress -> IO ()
yieldProgress Args
args
= (Property -> IO Result)
-> (Property -> Property) -> Property -> IO Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) (Args -> Property -> IO Result
forall prop. Testable prop => Args -> prop -> IO Result
QC.quickCheckWithResult Args
args)
((Property -> Property) -> Property -> IO Result)
-> (Property -> Property) -> Property -> IO Result
forall a b. (a -> b) -> a -> b
$ Callback -> Property -> Property
forall prop. Testable prop => Callback -> prop -> Property
QCP.callback
(Callback -> Property -> Property)
-> Callback -> Property -> Property
forall a b. (a -> b) -> a -> b
$ CallbackKind -> (State -> Result -> IO ()) -> Callback
QCP.PostTest CallbackKind
QCP.NotCounterexample
((State -> Result -> IO ()) -> Callback)
-> (State -> Result -> IO ()) -> Callback
forall a b. (a -> b) -> a -> b
$ \QC.MkState {Int
maxSuccessTests :: Int
maxSuccessTests :: State -> Int
QC.maxSuccessTests, Int
numSuccessTests :: Int
numSuccessTests :: State -> Int
QC.numSuccessTests} Result
_ ->
Progress -> IO ()
yieldProgress (Progress -> IO ()) -> Progress -> IO ()
forall a b. (a -> b) -> a -> b
$ Progress
emptyProgress {progressPercent = fromIntegral numSuccessTests / fromIntegral maxSuccessTests}
successful :: QC.Result -> Bool
successful :: Result -> Bool
successful Result
r =
case Result
r of
QC.Success {} -> Bool
True
Result
_ -> Bool
False
makeReplayMsg :: (QCGen, Int) -> String
makeReplayMsg :: (QCGen, Int) -> String
makeReplayMsg (QCGen, Int)
seedSz =
String -> String -> String
forall r. PrintfType r => String -> r
printf String
"Use --quickcheck-replay=\"%s\" to reproduce." ((QCGen, Int) -> String
forall a. Show a => a -> String
show (QCGen, Int)
seedSz)
replayFromResult :: QC.Result -> Maybe (QCGen, Int)
replayFromResult :: Result -> Maybe (QCGen, Int)
replayFromResult Result
r =
case Result
r of
Failure{} -> (QCGen, Int) -> Maybe (QCGen, Int)
forall a. a -> Maybe a
Just (Result -> QCGen
QC.usedSeed Result
r, Result -> Int
QC.usedSize Result
r)
Result
_ -> Maybe (QCGen, Int)
forall a. Maybe a
Nothing