-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Automatic testing of Haskell programs -- -- QuickCheck is a library for random testing of program properties. -- -- The programmer provides a specification of the program, in the form of -- properties which functions should satisfy, and QuickCheck then tests -- that the properties hold in a large number of randomly generated -- cases. -- -- Specifications are expressed in Haskell, using combinators defined in -- the QuickCheck library. QuickCheck provides combinators to define -- properties, observe the distribution of test data, and define test -- data generators. @package QuickCheck @version 2.4.2 module Test.QuickCheck.Text newtype Str MkStr :: String -> Str ranges :: (Show a, Integral a) => a -> a -> Str number :: Int -> String -> String short :: Int -> String -> String showErr :: Show a => a -> String bold :: String -> String newTerminal :: Output -> Output -> IO Terminal newStdioTerminal :: IO Terminal newNullTerminal :: IO Terminal terminalOutput :: Terminal -> IO String handle :: Handle -> String -> IO () data Terminal putPart, putLine, putTemp :: Terminal -> String -> IO () instance Show Str module Test.QuickCheck.State -- | State represents QuickCheck's internal state while testing a property. -- The state is made visible to callback functions. data State MkState :: Terminal -> Int -> Int -> (Int -> Int -> Int) -> Int -> Int -> [[(String, Int)]] -> Bool -> StdGen -> Int -> Int -> State -- | the current terminal terminal :: State -> Terminal -- | maximum number of successful tests needed maxSuccessTests :: State -> Int -- | maximum number of tests that can be discarded maxDiscardedTests :: State -> Int -- | how to compute the size of test cases from discarded tests computeSize :: State -> Int -> Int -> Int -- | the current number of tests that have succeeded numSuccessTests :: State -> Int -- | the current number of discarded tests numDiscardedTests :: State -> Int -- | all labels that have been collected so far collected :: State -> [[(String, Int)]] -- | indicates if the property is expected to fail expectedFailure :: State -> Bool -- | the current random seed randomSeed :: State -> StdGen -- | number of successful shrinking steps so far numSuccessShrinks :: State -> Int -- | number of failed shrinking steps since the last successful shrink numTryShrinks :: State -> Int -- | Test case generation. module Test.QuickCheck.Gen newtype Gen a MkGen :: (StdGen -> Int -> a) -> Gen a unGen :: Gen a -> StdGen -> Int -> a -- | Modifies a generator using an integer seed. variant :: Integral n => n -> Gen a -> Gen a -- | Used to construct generators that depend on the size parameter. sized :: (Int -> Gen a) -> Gen a -- | Overrides the size parameter. Returns a generator which uses the given -- size instead of the runtime-size parameter. resize :: Int -> Gen a -> Gen a -- | Generates a random element in the given inclusive range. choose :: Random a => (a, a) -> Gen a -- | Promotes a monadic generator to a generator of monadic values. promote :: Monad m => m (Gen a) -> Gen (m a) -- | Generates some example values. sample' :: Gen a -> IO [a] -- | Generates some example values and prints them to stdout. sample :: Show a => Gen a -> IO () -- | Generates a value that satisfies a predicate. suchThat :: Gen a -> (a -> Bool) -> Gen a -- | Tries to generate a value that satisfies a predicate. suchThatMaybe :: Gen a -> (a -> Bool) -> Gen (Maybe a) -- | Randomly uses one of the given generators. The input list must be -- non-empty. oneof :: [Gen a] -> Gen a -- | Chooses one of the given generators, with a weighted random -- distribution. The input list must be non-empty. frequency :: [(Int, Gen a)] -> Gen a -- | Generates one of the given values. The input list must be non-empty. elements :: [a] -> Gen a -- | Takes a list of elements of increasing size, and chooses among an -- initial segment of the list. The size of this initial segment -- increases with the size parameter. The input list must be non-empty. growingElements :: [a] -> Gen a -- | Generates a list of random length. The maximum length depends on the -- size parameter. listOf :: Gen a -> Gen [a] -- | Generates a non-empty list of random length. The maximum length -- depends on the size parameter. listOf1 :: Gen a -> Gen [a] -- | Generates a list of the given length. vectorOf :: Int -> Gen a -> Gen [a] instance Monad Gen instance Applicative Gen instance Functor Gen module Test.QuickCheck.Arbitrary -- | Random generation and shrinking of values. class Arbitrary a where arbitrary = error "no default generator" shrink _ = [] arbitrary :: Arbitrary a => Gen a shrink :: Arbitrary a => a -> [a] -- | Used for random generation of functions. class CoArbitrary a coarbitrary :: CoArbitrary a => a -> Gen c -> Gen c -- | Generates an integral number. The number can be positive or negative -- and its maximum absolute value depends on the size parameter. arbitrarySizedIntegral :: Num a => Gen a -- | Generates an integral number. The number is chosen uniformly from the -- entire range of the type. You may want to use -- arbitrarySizedBoundedIntegral instead. arbitraryBoundedIntegral :: (Bounded a, Integral a) => Gen a -- | Generates an integral number from a bounded domain. The number is -- chosen from the entire range of the type, but small numbers are -- generated more often than big numbers. Inspired by demands from Phil -- Wadler. arbitrarySizedBoundedIntegral :: (Bounded a, Integral a) => Gen a -- | Generates a fractional number. The number can be positive or negative -- and its maximum absolute value depends on the size parameter. arbitrarySizedFractional :: Fractional a => Gen a -- | Generates an element of a bounded type. The element is chosen from the -- entire range of the type. arbitraryBoundedRandom :: (Bounded a, Random a) => Gen a -- | Returns no shrinking alternatives. shrinkNothing :: a -> [a] shrinkList :: (a -> [a]) -> [a] -> [[a]] -- | Shrink an integral number. shrinkIntegral :: Integral a => a -> [a] -- | Shrink a fraction. shrinkRealFrac :: RealFrac a => a -> [a] -- | Combine two generator perturbing functions, for example the results of -- calls to variant or coarbitrary. (><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> (Gen a -> Gen a) -- | A coarbitrary implementation for integral numbers. coarbitraryIntegral :: Integral a => a -> Gen b -> Gen b -- | A coarbitrary implementation for real numbers. coarbitraryReal :: Real a => a -> Gen b -> Gen b -- | coarbitrary helper for lazy people :-). coarbitraryShow :: Show a => a -> Gen b -> Gen b -- | Generates a list of a given length. vector :: Arbitrary a => Int -> Gen [a] -- | Generates an ordered list of a given length. orderedList :: (Ord a, Arbitrary a) => Gen [a] instance CoArbitrary Double instance CoArbitrary Float instance CoArbitrary Char instance CoArbitrary Word64 instance CoArbitrary Word32 instance CoArbitrary Word16 instance CoArbitrary Word8 instance CoArbitrary Word instance CoArbitrary Int64 instance CoArbitrary Int32 instance CoArbitrary Int16 instance CoArbitrary Int8 instance CoArbitrary Int instance CoArbitrary Integer instance (CoArbitrary a, CoArbitrary b, CoArbitrary c, CoArbitrary d, CoArbitrary e) => CoArbitrary (a, b, c, d, e) instance (CoArbitrary a, CoArbitrary b, CoArbitrary c, CoArbitrary d) => CoArbitrary (a, b, c, d) instance (CoArbitrary a, CoArbitrary b, CoArbitrary c) => CoArbitrary (a, b, c) instance (CoArbitrary a, CoArbitrary b) => CoArbitrary (a, b) instance (RealFloat a, CoArbitrary a) => CoArbitrary (Complex a) instance (Integral a, CoArbitrary a) => CoArbitrary (Ratio a) instance CoArbitrary a => CoArbitrary [a] instance (CoArbitrary a, CoArbitrary b) => CoArbitrary (Either a b) instance CoArbitrary a => CoArbitrary (Maybe a) instance CoArbitrary Bool instance CoArbitrary () instance (Arbitrary a, CoArbitrary b) => CoArbitrary (a -> b) instance Arbitrary Double instance Arbitrary Float instance Arbitrary Char instance Arbitrary Word64 instance Arbitrary Word32 instance Arbitrary Word16 instance Arbitrary Word8 instance Arbitrary Word instance Arbitrary Int64 instance Arbitrary Int32 instance Arbitrary Int16 instance Arbitrary Int8 instance Arbitrary Int instance Arbitrary Integer instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e) => Arbitrary (a, b, c, d, e) instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => Arbitrary (a, b, c, d) instance (Arbitrary a, Arbitrary b, Arbitrary c) => Arbitrary (a, b, c) instance (Arbitrary a, Arbitrary b) => Arbitrary (a, b) instance (RealFloat a, Arbitrary a) => Arbitrary (Complex a) instance (Integral a, Arbitrary a) => Arbitrary (Ratio a) instance Arbitrary a => Arbitrary [a] instance (Arbitrary a, Arbitrary b) => Arbitrary (Either a b) instance Arbitrary a => Arbitrary (Maybe a) instance Arbitrary Bool instance Arbitrary () instance (CoArbitrary a, Arbitrary b) => Arbitrary (a -> b) -- | Types to help with testing polymorphic properties. -- -- Types A, B and C are newtype wrappers -- around Integer that implement Eq, Show, -- Arbitrary and CoArbitrary. Types OrdA, -- OrdB and OrdC also implement Ord and Num. -- -- See also Test.QuickCheck.All for an experimental way of testing -- polymorphic properties. module Test.QuickCheck.Poly newtype A A :: Integer -> A unA :: A -> Integer newtype B B :: Integer -> B unB :: B -> Integer newtype C C :: Integer -> C unC :: C -> Integer newtype OrdA OrdA :: Integer -> OrdA unOrdA :: OrdA -> Integer newtype OrdB OrdB :: Integer -> OrdB unOrdB :: OrdB -> Integer newtype OrdC OrdC :: Integer -> OrdC unOrdC :: OrdC -> Integer instance Eq A instance Eq B instance Eq C instance Eq OrdA instance Ord OrdA instance Num OrdA instance Eq OrdB instance Ord OrdB instance Num OrdB instance Eq OrdC instance Ord OrdC instance Num OrdC instance CoArbitrary OrdC instance Arbitrary OrdC instance Show OrdC instance CoArbitrary OrdB instance Arbitrary OrdB instance Show OrdB instance CoArbitrary OrdA instance Arbitrary OrdA instance Show OrdA instance CoArbitrary C instance Arbitrary C instance Show C instance CoArbitrary B instance Arbitrary B instance Show B instance CoArbitrary A instance Arbitrary A instance Show A -- | Modifiers for test data. -- -- These types do things such as restricting the kind of test data that -- can be generated. They can be pattern-matched on in properties as a -- stylistic alternative to using explicit quantification. -- -- Examples: -- --
--   -- Functions cannot be shown (but see Test.QuickCheck.Function)
--   prop_TakeDropWhile (Blind p) (xs :: [A]) =
--     takeWhile p xs ++ dropWhile p xs == xs
--   
-- --
--   prop_TakeDrop (NonNegative n) (xs :: [A]) =
--     take n xs ++ drop n xs == xs
--   
-- --
--   -- cycle does not work for empty lists
--   prop_Cycle (NonNegative n) (NonEmpty (xs :: [A])) =
--     take n (cycle xs) == take n (xs ++ cycle xs)
--   
-- --
--   -- Instead of forAll orderedList
--   prop_Sort (Ordered (xs :: [OrdA])) =
--     sort xs == xs
--   
module Test.QuickCheck.Modifiers -- | Blind x: as x, but x does not have to be in the Show -- class. newtype Blind a Blind :: a -> Blind a -- | Fixed x: as x, but will not be shrunk. newtype Fixed a Fixed :: a -> Fixed a -- | Ordered xs: guarantees that xs is ordered. newtype OrderedList a Ordered :: [a] -> OrderedList a -- | NonEmpty xs: guarantees that xs is non-empty. newtype NonEmptyList a NonEmpty :: [a] -> NonEmptyList a -- | Positive x: guarantees that x > 0. newtype Positive a Positive :: a -> Positive a -- | NonZero x: guarantees that x /= 0. newtype NonZero a NonZero :: a -> NonZero a -- | NonNegative x: guarantees that x >= 0. newtype NonNegative a NonNegative :: a -> NonNegative a -- | Smart _ x: tries a different order when shrinking. data Smart a Smart :: Int -> a -> Smart a -- | Shrink2 x: allows 2 shrinking steps at the same time when -- shrinking x newtype Shrink2 a Shrink2 :: a -> Shrink2 a -- | Shrinking _ x: allows for maintaining a state during -- shrinking. data Shrinking s a Shrinking :: s -> a -> Shrinking s a class ShrinkState s a shrinkInit :: ShrinkState s a => a -> s shrinkState :: ShrinkState s a => a -> s -> [(a, s)] instance Eq a => Eq (Blind a) instance Ord a => Ord (Blind a) instance Num a => Num (Blind a) instance Integral a => Integral (Blind a) instance Real a => Real (Blind a) instance Enum a => Enum (Blind a) instance Eq a => Eq (Fixed a) instance Ord a => Ord (Fixed a) instance Show a => Show (Fixed a) instance Read a => Read (Fixed a) instance Num a => Num (Fixed a) instance Integral a => Integral (Fixed a) instance Real a => Real (Fixed a) instance Enum a => Enum (Fixed a) instance Eq a => Eq (OrderedList a) instance Ord a => Ord (OrderedList a) instance Show a => Show (OrderedList a) instance Read a => Read (OrderedList a) instance Eq a => Eq (NonEmptyList a) instance Ord a => Ord (NonEmptyList a) instance Show a => Show (NonEmptyList a) instance Read a => Read (NonEmptyList a) instance Eq a => Eq (Positive a) instance Ord a => Ord (Positive a) instance Show a => Show (Positive a) instance Read a => Read (Positive a) instance Num a => Num (Positive a) instance Integral a => Integral (Positive a) instance Real a => Real (Positive a) instance Enum a => Enum (Positive a) instance Eq a => Eq (NonZero a) instance Ord a => Ord (NonZero a) instance Show a => Show (NonZero a) instance Read a => Read (NonZero a) instance Num a => Num (NonZero a) instance Integral a => Integral (NonZero a) instance Real a => Real (NonZero a) instance Enum a => Enum (NonZero a) instance Eq a => Eq (NonNegative a) instance Ord a => Ord (NonNegative a) instance Show a => Show (NonNegative a) instance Read a => Read (NonNegative a) instance Num a => Num (NonNegative a) instance Integral a => Integral (NonNegative a) instance Real a => Real (NonNegative a) instance Enum a => Enum (NonNegative a) instance Eq a => Eq (Shrink2 a) instance Ord a => Ord (Shrink2 a) instance Show a => Show (Shrink2 a) instance Read a => Read (Shrink2 a) instance Num a => Num (Shrink2 a) instance Integral a => Integral (Shrink2 a) instance Real a => Real (Shrink2 a) instance Enum a => Enum (Shrink2 a) instance (Arbitrary a, ShrinkState s a) => Arbitrary (Shrinking s a) instance Show a => Show (Shrinking s a) instance Arbitrary a => Arbitrary (Smart a) instance Show a => Show (Smart a) instance Arbitrary a => Arbitrary (Shrink2 a) instance (Num a, Ord a, Arbitrary a) => Arbitrary (NonNegative a) instance (Num a, Ord a, Arbitrary a) => Arbitrary (NonZero a) instance (Num a, Ord a, Arbitrary a) => Arbitrary (Positive a) instance Arbitrary a => Arbitrary (NonEmptyList a) instance (Ord a, Arbitrary a) => Arbitrary (OrderedList a) instance Arbitrary a => Arbitrary (Fixed a) instance Arbitrary a => Arbitrary (Blind a) instance Show (Blind a) -- | Generation of random shrinkable, showable functions. Not really -- documented at the moment! -- -- Example of use: -- --
--   >>> :{
--   
--   >>> let prop :: Fun String Integer -> Bool
--   
--   >>> prop (Fun _ f) = f "monkey" == f "banana" || f "banana" == f "elephant"
--   
--   >>> :}
--   
--   >>> quickCheck prop
--   *** Failed! Falsifiable (after 3 tests and 134 shrinks):     
--   {"elephant"->1, "monkey"->1, _->0}
--   
-- -- To generate random values of type Fun a b, you must -- have an instance Function a. If your type has a -- Show instance, you can use functionShow to write the -- instance; otherwise, use functionMap to give a bijection -- between your type and a type that is already an instance of -- Function. See the Function [a] instance for an -- example of the latter. module Test.QuickCheck.Function data Fun a b Fun :: (a :-> b, b) -> (a -> b) -> Fun a b apply :: Fun a b -> (a -> b) data (:->) a c class Function a function :: Function a => (a -> b) -> (a :-> b) functionMap :: Function b => (a -> b) -> (b -> a) -> (a -> c) -> (a :-> c) functionShow :: (Show a, Read a) => (a -> c) -> (a :-> c) instance (Function a, CoArbitrary a, Arbitrary b) => Arbitrary (Fun a b) instance (Show a, Show b) => Show (Fun a b) instance (Function a, CoArbitrary a, Arbitrary b) => Arbitrary (a :-> b) instance Function OrdC instance Function OrdB instance Function OrdA instance Function C instance Function B instance Function A instance Function Char instance Function Int instance Function Integer instance Function Bool instance Function a => Function (Maybe a) instance Function a => Function [a] instance (Function a, Function b) => Function (Either a b) instance (Function a, Function b) => Function (a, b) instance Function Word8 instance Function () instance Monad Steps instance (Show a, Show b) => Show (a :-> b) instance Functor ((:->) a) module Test.QuickCheck.Property type Property = Gen Prop -- | The class of things which can be tested, i.e. turned into a property. class Testable prop property :: Testable prop => prop -> Property -- | Do I/O inside a property. This can obviously lead to unrepeatable -- testcases, so use with care. morallyDubiousIOProperty :: Testable prop => IO prop -> Property protect :: (AnException -> a) -> IO a -> IO a newtype Prop MkProp :: Rose Result -> Prop unProp :: Prop -> Rose Result data Rose a MkRose :: a -> [Rose a] -> Rose a IORose :: (IO (Rose a)) -> Rose a ioRose :: IO (Rose Result) -> Rose Result joinRose :: Rose (Rose a) -> Rose a reduceRose :: Rose Result -> IO (Rose Result) onRose :: (a -> [Rose a] -> Rose a) -> Rose a -> Rose a protectRose :: IO (Rose Result) -> IO (Rose Result) protectResults :: Rose Result -> Rose Result -- | Different kinds of callbacks data Callback -- | Called just after a test PostTest :: CallbackKind -> (State -> Result -> IO ()) -> Callback -- | Called with the final failing test-case PostFinalFailure :: CallbackKind -> (State -> Result -> IO ()) -> Callback data CallbackKind -- | Affected by the verbose combinator Counterexample :: CallbackKind -- | Not affected by the verbose combinator NotCounterexample :: CallbackKind -- | The result of a single test. data Result MkResult :: Maybe Bool -> Bool -> String -> Bool -> [(String, Int)] -> [Callback] -> Result -- | result of the test case; Nothing = discard ok :: Result -> Maybe Bool -- | indicates what the expected result of the property is expect :: Result -> Bool -- | a message indicating what went wrong reason :: Result -> String -- | indicates if the test case was cancelled by pressing ^C interrupted :: Result -> Bool -- | the collected values for this test case stamp :: Result -> [(String, Int)] -- | the callbacks for this test case callbacks :: Result -> [Callback] result :: Result exception :: String -> AnException -> Result protectResult :: IO Result -> IO Result succeeded :: Result failed :: Result rejected :: Result liftBool :: Bool -> Result mapResult :: Testable prop => (Result -> Result) -> prop -> Property mapTotalResult :: Testable prop => (Result -> Result) -> prop -> Property mapRoseResult :: Testable prop => (Rose Result -> Rose Result) -> prop -> Property mapProp :: Testable prop => (Prop -> Prop) -> prop -> Property -- | Changes the maximum test case size for a property. mapSize :: Testable prop => (Int -> Int) -> prop -> Property -- | Shrinks the argument to property if it fails. Shrinking is done -- automatically for most types. This is only needed when you want to -- override the default behavior. shrinking :: Testable prop => (a -> [a]) -> a -> (a -> prop) -> Property -- | Disables shrinking for a property altogether. noShrinking :: Testable prop => prop -> Property -- | Adds a callback callback :: Testable prop => Callback -> prop -> Property -- | Prints a message to the terminal as part of the counterexample. printTestCase :: Testable prop => String -> prop -> Property -- | Performs an IO action after the last failure of a property. whenFail :: Testable prop => IO () -> prop -> Property -- | Performs an IO action every time a property fails. Thus, if -- shrinking is done, this can be used to keep track of the failures -- along the way. whenFail' :: Testable prop => IO () -> prop -> Property -- | Prints out the generated testcase every time the property is tested, -- like verboseCheck from QuickCheck 1. Only variables -- quantified over inside the verbose are printed. verbose :: Testable prop => prop -> Property -- | Modifies a property so that it is expected to fail for some test -- cases. expectFailure :: Testable prop => prop -> Property -- | Attaches a label to a property. This is used for reporting test case -- distribution. label :: Testable prop => String -> prop -> Property -- | Labels a property with a value: -- --
--   collect x = label (show x)
--   
collect :: (Show a, Testable prop) => a -> prop -> Property -- | Conditionally labels test case. classify :: Testable prop => Bool -> String -> prop -> Property -- | Checks that at least the given proportion of the test cases belong to -- the given class. cover :: Testable prop => Bool -> Int -> String -> prop -> Property -- | Implication for properties: The resulting property holds if the first -- argument is False, or if the given property holds. (==>) :: Testable prop => Bool -> prop -> Property -- | Considers a property failed if it does not complete within the given -- number of microseconds. within :: Testable prop => Int -> prop -> Property -- | Explicit universal quantification: uses an explicitly given test case -- generator. forAll :: (Show a, Testable prop) => Gen a -> (a -> prop) -> Property -- | Like forAll, but tries to shrink the argument for failing test -- cases. forAllShrink :: (Show a, Testable prop) => Gen a -> (a -> [a]) -> (a -> prop) -> Property -- | Nondeterministic choice: p1 .&. p2 picks -- randomly one of p1 and p2 to test. If you test the -- property 100 times it makes 100 random choices. (.&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property -- | Conjunction: p1 .&&. p2 passes if -- both p1 and p2 pass. (.&&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property -- | Take the conjunction of several properties. conjoin :: Testable prop => [prop] -> Property -- | Disjunction: p1 .||. p2 passes unless -- p1 and p2 simultaneously fail. (.||.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property -- | Take the disjunction of several properties. disjoin :: Testable prop => [prop] -> Property instance Monad Rose instance Functor Rose instance (Arbitrary a, Show a, Testable prop) => Testable (a -> prop) instance Testable prop => Testable (Gen prop) instance Testable Prop instance Testable Result instance Testable Bool instance Testable () module Test.QuickCheck.Test -- | Args specifies arguments to the QuickCheck driver data Args Args :: Maybe (StdGen, Int) -> Int -> Int -> Int -> Bool -> Args -- | should we replay a previous test? replay :: Args -> Maybe (StdGen, Int) -- | maximum number of successful tests before succeeding maxSuccess :: Args -> Int -- | maximum number of discarded tests before giving up maxDiscard :: Args -> Int -- | size to use for the biggest test cases maxSize :: Args -> Int -- | whether to print anything chatty :: Args -> Bool -- | Result represents the test result data Result Success :: Int -> [(String, Int)] -> String -> Result -- | number of tests performed -- -- number of tests performed -- -- number of successful tests performed -- -- number of successful tests performed numTests :: Result -> Int -- | labels and frequencies found during all successful tests -- -- labels and frequencies found during all successful tests -- -- labels and frequencies found during all tests -- -- labels and frequencies found during all tests labels :: Result -> [(String, Int)] -- | printed output -- -- printed output -- -- printed output -- -- printed output output :: Result -> String GaveUp :: Int -> [(String, Int)] -> String -> Result -- | number of tests performed -- -- number of tests performed -- -- number of successful tests performed -- -- number of successful tests performed numTests :: Result -> Int -- | labels and frequencies found during all successful tests -- -- labels and frequencies found during all successful tests -- -- labels and frequencies found during all tests -- -- labels and frequencies found during all tests labels :: Result -> [(String, Int)] -- | printed output -- -- printed output -- -- printed output -- -- printed output output :: Result -> String Failure :: Int -> Int -> StdGen -> Int -> String -> [(String, Int)] -> String -> Result -- | number of tests performed -- -- number of tests performed -- -- number of successful tests performed -- -- number of successful tests performed numTests :: Result -> Int -- | number of successful shrinking steps performed numShrinks :: Result -> Int -- | what seed was used usedSeed :: Result -> StdGen -- | what was the test size usedSize :: Result -> Int -- | what was the reason reason :: Result -> String -- | labels and frequencies found during all successful tests -- -- labels and frequencies found during all successful tests -- -- labels and frequencies found during all tests -- -- labels and frequencies found during all tests labels :: Result -> [(String, Int)] -- | printed output -- -- printed output -- -- printed output -- -- printed output output :: Result -> String NoExpectedFailure :: Int -> [(String, Int)] -> String -> Result -- | number of tests performed -- -- number of tests performed -- -- number of successful tests performed -- -- number of successful tests performed numTests :: Result -> Int -- | labels and frequencies found during all successful tests -- -- labels and frequencies found during all successful tests -- -- labels and frequencies found during all tests -- -- labels and frequencies found during all tests labels :: Result -> [(String, Int)] -- | printed output -- -- printed output -- -- printed output -- -- printed output output :: Result -> String -- | isSuccess checks if the test run result was a success isSuccess :: Result -> Bool -- | stdArgs are the default test arguments used stdArgs :: Args -- | Tests a property and prints the results to stdout. quickCheck :: Testable prop => prop -> IO () -- | Tests a property, using test arguments, and prints the results to -- stdout. quickCheckWith :: Testable prop => Args -> prop -> IO () -- | Tests a property, produces a test result, and prints the results to -- stdout. quickCheckResult :: Testable prop => prop -> IO Result -- | Tests a property, using test arguments, produces a test result, and -- prints the results to stdout. quickCheckWithResult :: Testable prop => Args -> prop -> IO Result -- | Tests a property and prints the results and all test cases generated -- to stdout. This is just a convenience function that means the -- same as quickCheck . verbose. verboseCheck :: Testable prop => prop -> IO () -- | Tests a property, using test arguments, and prints the results and all -- test cases generated to stdout. This is just a convenience -- function that combines quickCheckWith and verbose. verboseCheckWith :: Testable prop => Args -> prop -> IO () -- | Tests a property, produces a test result, and prints the results and -- all test cases generated to stdout. This is just a -- convenience function that combines quickCheckResult and -- verbose. verboseCheckResult :: Testable prop => prop -> IO Result -- | Tests a property, using test arguments, produces a test result, and -- prints the results and all test cases generated to stdout. -- This is just a convenience function that combines -- quickCheckWithResult and verbose. verboseCheckWithResult :: Testable prop => Args -> prop -> IO Result test :: State -> (StdGen -> Int -> Prop) -> IO Result doneTesting :: State -> (StdGen -> Int -> Prop) -> IO Result giveUp :: State -> (StdGen -> Int -> Prop) -> IO Result runATest :: State -> (StdGen -> Int -> Prop) -> IO Result summary :: State -> [(String, Int)] success :: State -> IO () foundFailure :: State -> Result -> [Rose Result] -> IO Int localMin :: State -> Result -> [Rose Result] -> IO Int localMin' :: State -> Result -> [Rose Result] -> IO Int localMinFound :: State -> Result -> IO Int callbackPostTest :: State -> Result -> IO () callbackPostFinalFailure :: State -> Result -> IO () safely :: State -> IO () -> IO () instance Show Args instance Read Args instance Show Result instance Read Result -- | Allows testing of monadic values. See the paper "Testing Monadic Code -- with QuickCheck": -- http://www.cse.chalmers.se/~rjmh/Papers/QuickCheckST.ps. module Test.QuickCheck.Monadic newtype PropertyM m a MkPropertyM :: ((a -> Gen (m Property)) -> Gen (m Property)) -> PropertyM m a unPropertyM :: PropertyM m a -> (a -> Gen (m Property)) -> Gen (m Property) stop :: (Testable prop, Monad m) => prop -> PropertyM m a assert :: Monad m => Bool -> PropertyM m () pre :: Monad m => Bool -> PropertyM m () run :: Monad m => m a -> PropertyM m a pick :: (Monad m, Show a) => Gen a -> PropertyM m a wp :: Monad m => m a -> (a -> PropertyM m b) -> PropertyM m b forAllM :: (Monad m, Show a) => Gen a -> (a -> PropertyM m b) -> PropertyM m b monitor :: Monad m => (Property -> Property) -> PropertyM m () monadic :: Monad m => (m Property -> Property) -> PropertyM m a -> Property monadic' :: Monad m => PropertyM m a -> Gen (m Property) monadicIO :: PropertyM IO a -> Property monadicST :: (forall s. PropertyM (ST s) a) -> Property runSTGen :: (forall s. Gen (ST s a)) -> Gen a instance Monad m => Monad (PropertyM m) instance Functor (PropertyM m) -- | Experimental features using Template Haskell. You need to have a -- {-# LANGUAGE TemplateHaskell #-} pragma in your module for -- any of these to work. module Test.QuickCheck.All -- | Test all properties in the current module. The name of the property -- must begin with prop_. Polymorphic properties will be -- defaulted to Integer. Returns True if all tests -- succeeded, False otherwise. -- -- Using quickCheckAll interactively doesn't work. Instead, add a -- definition to your module along the lines of -- --
--   runTests = $quickCheckAll
--   
-- -- and then execute runTests. quickCheckAll :: Q Exp -- | Test all properties in the current module. This is just a convenience -- function that combines quickCheckAll and verbose. verboseCheckAll :: Q Exp -- | Test all properties in the current module, using a custom -- quickCheck function. The same caveats as with -- quickCheckAll apply. -- -- $forAllProperties has type (Property -> -- IO Result) -> IO Bool. An example -- invocation is $forAllProperties -- quickCheckResult, which does the same thing as -- $quickCheckAll. forAllProperties :: Q Exp -- | Test a polymorphic property, defaulting all type variables to -- Integer. -- -- Invoke as $(polyQuickCheck 'prop), where prop -- is a property. Note that just evaluating quickCheck -- prop in GHCi will seem to work, but will silently default all -- type variables to ()! polyQuickCheck :: Name -> ExpQ -- | Test a polymorphic property, defaulting all type variables to -- Integer. This is just a convenience function that combines -- polyQuickCheck and verbose. polyVerboseCheck :: Name -> ExpQ -- | Monomorphise an arbitrary name by defaulting all type variables to -- Integer. -- -- For example, if f has type Ord a => [a] -> -- [a] then $(mono 'f) has type [Integer] -- -> [Integer]. mono :: Name -> ExpQ module Test.QuickCheck -- | Tests a property and prints the results to stdout. quickCheck :: Testable prop => prop -> IO () -- | Args specifies arguments to the QuickCheck driver data Args Args :: Maybe (StdGen, Int) -> Int -> Int -> Int -> Bool -> Args -- | should we replay a previous test? replay :: Args -> Maybe (StdGen, Int) -- | maximum number of successful tests before succeeding maxSuccess :: Args -> Int -- | maximum number of discarded tests before giving up maxDiscard :: Args -> Int -- | size to use for the biggest test cases maxSize :: Args -> Int -- | whether to print anything chatty :: Args -> Bool -- | Result represents the test result data Result Success :: Int -> [(String, Int)] -> String -> Result -- | number of tests performed -- -- number of tests performed -- -- number of successful tests performed -- -- number of successful tests performed numTests :: Result -> Int -- | labels and frequencies found during all successful tests -- -- labels and frequencies found during all successful tests -- -- labels and frequencies found during all tests -- -- labels and frequencies found during all tests labels :: Result -> [(String, Int)] -- | printed output -- -- printed output -- -- printed output -- -- printed output output :: Result -> String GaveUp :: Int -> [(String, Int)] -> String -> Result -- | number of tests performed -- -- number of tests performed -- -- number of successful tests performed -- -- number of successful tests performed numTests :: Result -> Int -- | labels and frequencies found during all successful tests -- -- labels and frequencies found during all successful tests -- -- labels and frequencies found during all tests -- -- labels and frequencies found during all tests labels :: Result -> [(String, Int)] -- | printed output -- -- printed output -- -- printed output -- -- printed output output :: Result -> String Failure :: Int -> Int -> StdGen -> Int -> String -> [(String, Int)] -> String -> Result -- | number of tests performed -- -- number of tests performed -- -- number of successful tests performed -- -- number of successful tests performed numTests :: Result -> Int -- | number of successful shrinking steps performed numShrinks :: Result -> Int -- | what seed was used usedSeed :: Result -> StdGen -- | what was the test size usedSize :: Result -> Int -- | what was the reason reason :: Result -> String -- | labels and frequencies found during all successful tests -- -- labels and frequencies found during all successful tests -- -- labels and frequencies found during all tests -- -- labels and frequencies found during all tests labels :: Result -> [(String, Int)] -- | printed output -- -- printed output -- -- printed output -- -- printed output output :: Result -> String NoExpectedFailure :: Int -> [(String, Int)] -> String -> Result -- | number of tests performed -- -- number of tests performed -- -- number of successful tests performed -- -- number of successful tests performed numTests :: Result -> Int -- | labels and frequencies found during all successful tests -- -- labels and frequencies found during all successful tests -- -- labels and frequencies found during all tests -- -- labels and frequencies found during all tests labels :: Result -> [(String, Int)] -- | printed output -- -- printed output -- -- printed output -- -- printed output output :: Result -> String -- | stdArgs are the default test arguments used stdArgs :: Args -- | Tests a property, using test arguments, and prints the results to -- stdout. quickCheckWith :: Testable prop => Args -> prop -> IO () -- | Tests a property, using test arguments, produces a test result, and -- prints the results to stdout. quickCheckWithResult :: Testable prop => Args -> prop -> IO Result -- | Tests a property, produces a test result, and prints the results to -- stdout. quickCheckResult :: Testable prop => prop -> IO Result -- | Tests a property and prints the results and all test cases generated -- to stdout. This is just a convenience function that means the -- same as quickCheck . verbose. verboseCheck :: Testable prop => prop -> IO () -- | Tests a property, using test arguments, and prints the results and all -- test cases generated to stdout. This is just a convenience -- function that combines quickCheckWith and verbose. verboseCheckWith :: Testable prop => Args -> prop -> IO () -- | Tests a property, using test arguments, produces a test result, and -- prints the results and all test cases generated to stdout. -- This is just a convenience function that combines -- quickCheckWithResult and verbose. verboseCheckWithResult :: Testable prop => Args -> prop -> IO Result -- | Tests a property, produces a test result, and prints the results and -- all test cases generated to stdout. This is just a -- convenience function that combines quickCheckResult and -- verbose. verboseCheckResult :: Testable prop => prop -> IO Result -- | Prints out the generated testcase every time the property is tested, -- like verboseCheck from QuickCheck 1. Only variables -- quantified over inside the verbose are printed. verbose :: Testable prop => prop -> Property data Gen a -- | Used to construct generators that depend on the size parameter. sized :: (Int -> Gen a) -> Gen a -- | Overrides the size parameter. Returns a generator which uses the given -- size instead of the runtime-size parameter. resize :: Int -> Gen a -> Gen a -- | Generates a random element in the given inclusive range. choose :: Random a => (a, a) -> Gen a -- | Promotes a monadic generator to a generator of monadic values. promote :: Monad m => m (Gen a) -> Gen (m a) -- | Generates a value that satisfies a predicate. suchThat :: Gen a -> (a -> Bool) -> Gen a -- | Tries to generate a value that satisfies a predicate. suchThatMaybe :: Gen a -> (a -> Bool) -> Gen (Maybe a) -- | Randomly uses one of the given generators. The input list must be -- non-empty. oneof :: [Gen a] -> Gen a -- | Chooses one of the given generators, with a weighted random -- distribution. The input list must be non-empty. frequency :: [(Int, Gen a)] -> Gen a -- | Generates one of the given values. The input list must be non-empty. elements :: [a] -> Gen a -- | Takes a list of elements of increasing size, and chooses among an -- initial segment of the list. The size of this initial segment -- increases with the size parameter. The input list must be non-empty. growingElements :: [a] -> Gen a -- | Generates a list of random length. The maximum length depends on the -- size parameter. listOf :: Gen a -> Gen [a] -- | Generates a non-empty list of random length. The maximum length -- depends on the size parameter. listOf1 :: Gen a -> Gen [a] -- | Generates a list of the given length. vectorOf :: Int -> Gen a -> Gen [a] -- | Generates a list of a given length. vector :: Arbitrary a => Int -> Gen [a] -- | Generates an ordered list of a given length. orderedList :: (Ord a, Arbitrary a) => Gen [a] -- | Generates some example values and prints them to stdout. sample :: Show a => Gen a -> IO () -- | Generates some example values. sample' :: Gen a -> IO [a] -- | Random generation and shrinking of values. class Arbitrary a where arbitrary = error "no default generator" shrink _ = [] arbitrary :: Arbitrary a => Gen a shrink :: Arbitrary a => a -> [a] -- | Used for random generation of functions. class CoArbitrary a coarbitrary :: CoArbitrary a => a -> Gen c -> Gen c -- | Generates an integral number. The number can be positive or negative -- and its maximum absolute value depends on the size parameter. arbitrarySizedIntegral :: Num a => Gen a -- | Generates a fractional number. The number can be positive or negative -- and its maximum absolute value depends on the size parameter. arbitrarySizedFractional :: Fractional a => Gen a -- | Generates an integral number from a bounded domain. The number is -- chosen from the entire range of the type, but small numbers are -- generated more often than big numbers. Inspired by demands from Phil -- Wadler. arbitrarySizedBoundedIntegral :: (Bounded a, Integral a) => Gen a -- | Generates an integral number. The number is chosen uniformly from the -- entire range of the type. You may want to use -- arbitrarySizedBoundedIntegral instead. arbitraryBoundedIntegral :: (Bounded a, Integral a) => Gen a -- | Generates an element of a bounded type. The element is chosen from the -- entire range of the type. arbitraryBoundedRandom :: (Bounded a, Random a) => Gen a -- | Returns no shrinking alternatives. shrinkNothing :: a -> [a] -- | Shrink an integral number. shrinkIntegral :: Integral a => a -> [a] -- | Shrink a fraction. shrinkRealFrac :: RealFrac a => a -> [a] -- | Modifies a generator using an integer seed. variant :: Integral n => n -> Gen a -> Gen a -- | Combine two generator perturbing functions, for example the results of -- calls to variant or coarbitrary. (><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> (Gen a -> Gen a) -- | A coarbitrary implementation for integral numbers. coarbitraryIntegral :: Integral a => a -> Gen b -> Gen b -- | A coarbitrary implementation for real numbers. coarbitraryReal :: Real a => a -> Gen b -> Gen b -- | coarbitrary helper for lazy people :-). coarbitraryShow :: Show a => a -> Gen b -> Gen b -- | Blind x: as x, but x does not have to be in the Show -- class. newtype Blind a Blind :: a -> Blind a -- | Fixed x: as x, but will not be shrunk. newtype Fixed a Fixed :: a -> Fixed a -- | Ordered xs: guarantees that xs is ordered. newtype OrderedList a Ordered :: [a] -> OrderedList a -- | NonEmpty xs: guarantees that xs is non-empty. newtype NonEmptyList a NonEmpty :: [a] -> NonEmptyList a -- | Positive x: guarantees that x > 0. newtype Positive a Positive :: a -> Positive a -- | NonZero x: guarantees that x /= 0. newtype NonZero a NonZero :: a -> NonZero a -- | NonNegative x: guarantees that x >= 0. newtype NonNegative a NonNegative :: a -> NonNegative a -- | Smart _ x: tries a different order when shrinking. data Smart a Smart :: Int -> a -> Smart a -- | Shrink2 x: allows 2 shrinking steps at the same time when -- shrinking x newtype Shrink2 a Shrink2 :: a -> Shrink2 a -- | Shrinking _ x: allows for maintaining a state during -- shrinking. data Shrinking s a Shrinking :: s -> a -> Shrinking s a class ShrinkState s a shrinkInit :: ShrinkState s a => a -> s shrinkState :: ShrinkState s a => a -> s -> [(a, s)] type Property = Gen Prop data Prop -- | The class of things which can be tested, i.e. turned into a property. class Testable prop property :: Testable prop => prop -> Property -- | Changes the maximum test case size for a property. mapSize :: Testable prop => (Int -> Int) -> prop -> Property -- | Shrinks the argument to property if it fails. Shrinking is done -- automatically for most types. This is only needed when you want to -- override the default behavior. shrinking :: Testable prop => (a -> [a]) -> a -> (a -> prop) -> Property -- | Implication for properties: The resulting property holds if the first -- argument is False, or if the given property holds. (==>) :: Testable prop => Bool -> prop -> Property -- | Explicit universal quantification: uses an explicitly given test case -- generator. forAll :: (Show a, Testable prop) => Gen a -> (a -> prop) -> Property -- | Like forAll, but tries to shrink the argument for failing test -- cases. forAllShrink :: (Show a, Testable prop) => Gen a -> (a -> [a]) -> (a -> prop) -> Property -- | Nondeterministic choice: p1 .&. p2 picks -- randomly one of p1 and p2 to test. If you test the -- property 100 times it makes 100 random choices. (.&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property -- | Conjunction: p1 .&&. p2 passes if -- both p1 and p2 pass. (.&&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property -- | Take the conjunction of several properties. conjoin :: Testable prop => [prop] -> Property -- | Disjunction: p1 .||. p2 passes unless -- p1 and p2 simultaneously fail. (.||.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property -- | Take the disjunction of several properties. disjoin :: Testable prop => [prop] -> Property -- | Performs an IO action after the last failure of a property. whenFail :: Testable prop => IO () -> prop -> Property -- | Prints a message to the terminal as part of the counterexample. printTestCase :: Testable prop => String -> prop -> Property -- | Performs an IO action every time a property fails. Thus, if -- shrinking is done, this can be used to keep track of the failures -- along the way. whenFail' :: Testable prop => IO () -> prop -> Property -- | Modifies a property so that it is expected to fail for some test -- cases. expectFailure :: Testable prop => prop -> Property -- | Considers a property failed if it does not complete within the given -- number of microseconds. within :: Testable prop => Int -> prop -> Property -- | Attaches a label to a property. This is used for reporting test case -- distribution. label :: Testable prop => String -> prop -> Property -- | Labels a property with a value: -- --
--   collect x = label (show x)
--   
collect :: (Show a, Testable prop) => a -> prop -> Property -- | Conditionally labels test case. classify :: Testable prop => Bool -> String -> prop -> Property -- | Checks that at least the given proportion of the test cases belong to -- the given class. cover :: Testable prop => Bool -> Int -> String -> prop -> Property newtype Str MkStr :: String -> Str ranges :: (Show a, Integral a) => a -> a -> Str