-- 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.7.6 -- | A wrapper around the system random number generator. Internal -- QuickCheck module. module Test.QuickCheck.Random newTheGen :: IO TFGen bits :: Integral a => a doneBit :: Integral a => a mask :: Integral a => a chip :: Bool -> Word32 -> TFGen -> TFGen chop :: Integer -> Integer stop :: Integral a => a -> Bool mkTheGen :: Int -> TFGen -- | The standard QuickCheck random number generator. A wrapper -- around either TFGen on GHC, or StdGen on other Haskell -- systems. newtype QCGen QCGen :: TFGen -> QCGen newQCGen :: IO QCGen mkQCGen :: Int -> QCGen bigNatVariant :: Integer -> TFGen -> TFGen natVariant :: Integral a => a -> TFGen -> TFGen variantTheGen :: Integral a => a -> TFGen -> TFGen boolVariant :: Bool -> TFGen -> TFGen variantQCGen :: Integral a => a -> QCGen -> QCGen instance RandomGen QCGen instance Read QCGen instance Show QCGen -- | Throwing and catching exceptions. Internal QuickCheck module. module Test.QuickCheck.Exception type AnException = SomeException tryEvaluate :: a -> IO (Either AnException a) tryEvaluateIO :: IO a -> IO (Either AnException a) isInterrupt :: AnException -> Bool -- | A special exception that makes QuickCheck discard the test case. -- Normally you should use ==>, but if for some reason this -- isn't possible (e.g. you are deep inside a generator), use -- discard instead. discard :: a isDiscard :: AnException -> Bool finally :: IO a -> IO b -> IO a -- | Terminal control. Internal QuickCheck module. 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 oneLine :: String -> String isOneLine :: String -> Bool bold :: String -> String newTerminal :: Output -> Output -> IO Terminal withStdioTerminal :: (Terminal -> IO a) -> IO a withNullTerminal :: (Terminal -> IO a) -> IO a terminalOutput :: Terminal -> IO String handle :: Handle -> String -> IO () data Terminal putTemp :: Terminal -> String -> IO () putPart :: Terminal -> String -> IO () putLine :: Terminal -> String -> IO () instance Show Str -- | QuickCheck's internal state. Internal QuickCheck module. 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 -> Int -> [[(String, Int)]] -> Bool -> QCGen -> Int -> 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 -- | the number of discarded tests since the last successful test numRecentlyDiscardedTests :: 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 -> QCGen -- | number of successful shrinking steps so far numSuccessShrinks :: State -> Int -- | number of failed shrinking steps since the last successful shrink numTryShrinks :: State -> Int -- | total number of failed shrinking steps numTotTryShrinks :: State -> Int -- | Test case generation. module Test.QuickCheck.Gen -- | A generator for values of type a. newtype Gen a MkGen :: (QCGen -> Int -> a) -> Gen a -- | Run the generator on a particular seed. If you just want to get a -- random value out, consider using generate. unGen :: Gen a -> QCGen -> 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 -- | Run a generator. generate :: Gen a -> IO 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] -- | Generates an infinite list. infiniteListOf :: Gen a -> Gen [a] instance Monad Gen instance Applicative Gen instance Functor Gen -- | Unsafe combinators for the Gen monad. -- -- Gen is only morally a monad: two generators that are supposed -- to be equal will give the same probability distribution, but they -- might be different as functions from random number seeds to values. -- QuickCheck maintains the illusion that a Gen is a probability -- distribution and does not allow you to distinguish two generators that -- have the same distribution. -- -- The functions in this module allow you to break this illusion by -- reusing the same random number seed twice. This is unsafe because by -- applying the same seed to two morally equal generators, you can see -- whether they are really equal or not. module Test.QuickCheck.Gen.Unsafe -- | Promotes a monadic generator to a generator of monadic values. promote :: Monad m => m (Gen a) -> Gen (m a) -- | Randomly generates a function of type Gen a -> a, -- which you can then use to evaluate generators. Mostly useful in -- implementing promote. delay :: Gen (Gen a -> a) -- | A variant of delay that returns a polymorphic evaluation -- function. Can be used in a pinch to generate polymorphic (rank-2) -- values: -- --
--   genSelector :: Gen (a -> a -> a)
--   genSelector = elements [\x y -> x, \x y -> y]
--   
--   data Selector = Selector (forall a. a -> a -> a)
--   genPolySelector :: Gen Selector
--   genPolySelector = do
--     Capture eval <- capture
--     return (Selector (eval genSelector))
--   
capture :: Gen Capture newtype Capture Capture :: (forall a. Gen a -> a) -> Capture -- | Type classes for random generation of values. 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 b -> Gen b -- | Generates an integral number. The number can be positive or negative -- and its maximum absolute value depends on the size parameter. arbitrarySizedIntegral :: 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 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 -- | Generates an element of a bounded enumeration. arbitraryBoundedEnum :: (Bounded a, Enum a) => Gen a -- | Shrink a term to any of its immediate subterms, and also recursively -- shrink all subterms. genericShrink :: (Generic a, Typeable a, RecursivelyShrink (Rep a), Subterms (Rep a)) => a -> [a] -- | All immediate subterms of a term. subterms :: (Generic a, Typeable a, Subterms (Rep a)) => a -> [a] -- | Recursively shrink all immediate subterms. recursivelyShrink :: (Generic a, RecursivelyShrink (Rep a)) => a -> [a] -- | Returns no shrinking alternatives. shrinkNothing :: a -> [a] -- | Shrink a list of values given a shrinking function for individual -- values. shrinkList :: (a -> [a]) -> [a] -> [[a]] -- | Shrink an integral number. shrinkIntegral :: Integral a => a -> [a] -- | Shrink a fraction. shrinkRealFrac :: RealFrac a => a -> [a] -- | Shrink a fraction, but only shrink to integral values. shrinkRealFracToInteger :: RealFrac a => a -> [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 -- | A coarbitrary implementation for enums. coarbitraryEnum :: Enum a => a -> Gen b -> Gen b -- | Combine two generator perturbing functions, for example the results of -- calls to variant or coarbitrary. -- | Deprecated: Use ordinary function composition instead (><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> (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] -- | Generate an infinite list. infiniteList :: 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 HasResolution a => CoArbitrary (Fixed 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 Ordering 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 HasResolution a => Arbitrary (Fixed a) 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 Ordering instance Arbitrary Bool instance Arbitrary () instance (CoArbitrary a, Arbitrary b) => Arbitrary (a -> b) instance Subterms U1 instance Typeable a => Subterms (K1 i a) instance Subterms f => Subterms (M1 i c f) instance (Subterms f, Subterms g) => Subterms (f :+: g) instance (Subterms f, Subterms g) => Subterms (f :*: g) instance RecursivelyShrink U1 instance Arbitrary a => RecursivelyShrink (K1 i a) instance RecursivelyShrink f => RecursivelyShrink (M1 i c f) instance (RecursivelyShrink f, RecursivelyShrink g) => RecursivelyShrink (f :+: g) instance (RecursivelyShrink f, RecursivelyShrink g) => RecursivelyShrink (f :*: g) -- | 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 getBlind :: Blind a -> a -- | Fixed x: as x, but will not be shrunk. newtype Fixed a Fixed :: a -> Fixed a getFixed :: Fixed a -> a -- | Ordered xs: guarantees that xs is ordered. newtype OrderedList a Ordered :: [a] -> OrderedList a getOrdered :: OrderedList a -> [a] -- | NonEmpty xs: guarantees that xs is non-empty. newtype NonEmptyList a NonEmpty :: [a] -> NonEmptyList a getNonEmpty :: NonEmptyList a -> [a] -- | Positive x: guarantees that x > 0. newtype Positive a Positive :: a -> Positive a getPositive :: Positive a -> a -- | NonZero x: guarantees that x /= 0. newtype NonZero a NonZero :: a -> NonZero a getNonZero :: NonZero a -> a -- | NonNegative x: guarantees that x >= 0. newtype NonNegative a NonNegative :: a -> NonNegative a getNonNegative :: NonNegative a -> a -- | Large x: by default, QuickCheck generates Ints drawn -- from a small range. Large Int gives you values drawn from the -- entire range instead. newtype Large a Large :: a -> Large a getLarge :: Large a -> a -- | Small x: generates values of x drawn from a small -- range. The opposite of Large. newtype Small a Small :: a -> Small a getSmall :: Small a -> 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 getShrink2 :: Shrink2 a -> 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 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 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 Enum a => Enum (NonNegative a) instance Eq a => Eq (Large a) instance Ord a => Ord (Large a) instance Show a => Show (Large a) instance Read a => Read (Large a) instance Num a => Num (Large a) instance Integral a => Integral (Large a) instance Real a => Real (Large a) instance Enum a => Enum (Large a) instance Eq a => Eq (Small a) instance Ord a => Ord (Small a) instance Show a => Show (Small a) instance Read a => Read (Small a) instance Num a => Num (Small a) instance Integral a => Integral (Small a) instance Real a => Real (Small a) instance Enum a => Enum (Small 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 Functor (Shrinking s) instance Arbitrary a => Arbitrary (Smart a) instance Show a => Show (Smart a) instance Functor Smart instance Arbitrary a => Arbitrary (Shrink2 a) instance Functor Shrink2 instance Integral a => Arbitrary (Small a) instance Functor Small instance (Integral a, Bounded a) => Arbitrary (Large a) instance Functor Large instance (Num a, Ord a, Arbitrary a) => Arbitrary (NonNegative a) instance Functor NonNegative instance (Num a, Ord a, Arbitrary a) => Arbitrary (NonZero a) instance Functor NonZero instance (Num a, Ord a, Arbitrary a) => Arbitrary (Positive a) instance Functor Positive instance Arbitrary a => Arbitrary (NonEmptyList a) instance Functor NonEmptyList instance (Ord a, Arbitrary a) => Arbitrary (OrderedList a) instance Functor OrderedList instance Arbitrary a => Arbitrary (Fixed a) instance Functor Fixed instance Arbitrary a => Arbitrary (Blind a) instance Show (Blind a) instance Functor Blind -- | 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 automatic 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 -- | Generation of random shrinkable, showable functions. See the paper -- "Shrinking and showing functions" by Koen Claessen. -- -- 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 c, Function d, Function e, Function f, Function g) => Function (a, b, c, d, e, f, g) instance (Function a, Function b, Function c, Function d, Function e, Function f) => Function (a, b, c, d, e, f) instance (Function a, Function b, Function c, Function d, Function e) => Function (a, b, c, d, e) instance (Function a, Function b, Function c, Function d) => Function (a, b, c, d) instance (Function a, Function b, Function c) => Function (a, b, c) instance (Function a, Function b) => Function (Either a b) instance (Function a, Function b) => Function (a, b) instance Function Word8 instance Function () instance (Show a, Show b) => Show (a :-> b) instance Functor ((:->) a) -- | Combinators for constructing properties. module Test.QuickCheck.Property -- | The type of properties. -- -- Backwards combatibility note: in older versions of QuickCheck -- Property was a type synonym for Gen -- Prop, so you could mix and match property combinators and -- Gen monad operations. Code that does this will no longer -- typecheck. However, it is easy to fix: because of the Testable -- typeclass, any combinator that expects a Property will also -- accept a Gen Property. If you have a -- Property where you need a Gen a, -- simply wrap the property combinator inside a return to get a -- Gen Property, and all should be well. newtype Property MkProperty :: Gen Prop -> Property unProperty :: Property -> Gen Prop -- | The class of things which can be tested, i.e. turned into a property. class Testable prop where exhaustive _ = False property :: Testable prop => prop -> Property exhaustive :: Testable prop => prop -> Bool -- | If a property returns Discard, the current test case is -- discarded, the same as if a precondition was false. data Discard Discard :: Discard -- | Do I/O inside a property. This can obviously lead to unrepeatable -- testcases, so use with care. -- | Deprecated: Use ioProperty instead morallyDubiousIOProperty :: Testable prop => IO prop -> Property -- | Do I/O inside a property. This can obviously lead to unrepeatable -- testcases, so use with care. -- -- For more advanced monadic testing you may want to look at -- Test.QuickCheck.Monadic. ioProperty :: 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 -> Maybe AnException -> 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 -- | the exception thrown, if any theException :: Result -> Maybe AnException -- | if True, the test should not be repeated abort :: 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 formatException :: String -> AnException -> String 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 -- | Adds the given string to the counterexample. counterexample :: Testable prop => String -> prop -> Property -- | Adds the given string to the counterexample. -- | Deprecated: Use counterexample instead 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. -- Only variables quantified over inside the verbose are -- printed. verbose :: Testable prop => prop -> Property -- | Indicates that a property is supposed to fail. QuickCheck will report -- an error if it does not fail. expectFailure :: Testable prop => prop -> Property -- | Modifies a property so that it only will be tested once. once :: 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 (in which case the test case is discarded), -- 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 -- | Like ==, but prints a counterexample when it fails. (===) :: (Eq a, Show a) => a -> a -> Property instance [safe] Monad Rose instance [safe] Applicative Rose instance [safe] Functor Rose instance [safe] (Arbitrary a, Show a, Testable prop) => Testable (a -> prop) instance [safe] Testable Property instance [safe] Testable prop => Testable (Gen prop) instance [safe] Testable Prop instance [safe] Testable Result instance [safe] Testable Bool instance [safe] Testable Discard -- | The main test loop. module Test.QuickCheck.Test -- | Args specifies arguments to the QuickCheck driver data Args Args :: Maybe (QCGen, Int) -> Int -> Int -> Int -> Bool -> Args -- | Should we replay a previous test? replay :: Args -> Maybe (QCGen, Int) -- | Maximum number of successful tests before succeeding maxSuccess :: Args -> Int -- | Maximum number of discarded tests per successful test before giving up maxDiscardRatio :: 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 -- | A successful test run Success :: Int -> [(String, Int)] -> String -> Result -- | Number of tests performed numTests :: Result -> Int -- | Labels and frequencies found during all successful tests labels :: Result -> [(String, Int)] -- | Printed output output :: Result -> String -- | Given up GaveUp :: Int -> [(String, Int)] -> String -> Result -- | Number of tests performed numTests :: Result -> Int -- | Labels and frequencies found during all successful tests labels :: Result -> [(String, Int)] -- | Printed output output :: Result -> String -- | A failed test run Failure :: Int -> Int -> Int -> Int -> QCGen -> Int -> String -> Maybe AnException -> [(String, Int)] -> String -> Result -- | Number of tests performed numTests :: Result -> Int -- | Number of successful shrinking steps performed numShrinks :: Result -> Int -- | Number of unsuccessful shrinking steps performed numShrinkTries :: Result -> Int -- | Number of unsuccessful shrinking steps performed since last successful -- shrink numShrinkFinal :: Result -> Int -- | What seed was used usedSeed :: Result -> QCGen -- | What was the test size usedSize :: Result -> Int -- | Why did the property fail reason :: Result -> String -- | The exception the property threw, if any theException :: Result -> Maybe AnException -- | Labels and frequencies found during all successful tests labels :: Result -> [(String, Int)] -- | Printed output output :: Result -> String -- | A property that should have failed did not NoExpectedFailure :: Int -> [(String, Int)] -> String -> Result -- | Number of tests performed numTests :: Result -> Int -- | Labels and frequencies found during all successful tests labels :: Result -> [(String, Int)] -- | Printed output output :: Result -> String -- | Check if the test run result was a success isSuccess :: Result -> Bool -- | The default test arguments 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 -> (QCGen -> Int -> Prop) -> IO Result doneTesting :: State -> (QCGen -> Int -> Prop) -> IO Result giveUp :: State -> (QCGen -> Int -> Prop) -> IO Result runATest :: State -> (QCGen -> Int -> Prop) -> IO Result summary :: State -> [(String, Int)] success :: State -> IO () foundFailure :: State -> Result -> [Rose Result] -> IO (Int, Int, Int) localMin :: State -> Result -> Result -> [Rose Result] -> IO (Int, Int, Int) localMin' :: State -> Result -> [Rose Result] -> IO (Int, Int, Int) localMinFound :: State -> Result -> IO (Int, Int, Int) callbackPostTest :: State -> Result -> IO () callbackPostFinalFailure :: State -> Result -> IO () safely :: State -> IO () -> IO () instance [safe] Show Args instance [safe] Read Args instance [safe] Show Result -- | Test all properties in the current module, 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. -- -- To use quickCheckAll, add a definition to your module along the -- lines of -- --
--   return []
--   runTests = $quickCheckAll
--   
-- -- and then execute runTests. -- -- Note: the bizarre return [] in the example above is needed on -- GHC 7.8; without it, quickCheckAll will not be able to find any -- of the properties. For the curious, the return [] is a -- Template Haskell splice that makes GHC insert the empty list of -- declarations at that point in the program; GHC typechecks everything -- before the return [] before it starts on the rest of the -- module, which means that the later call to quickCheckAll can -- see everything that was defined before the return []. Yikes! quickCheckAll :: Q Exp -- | Test all properties in the current module. This is just a convenience -- function that combines quickCheckAll and verbose. -- -- verboseCheckAll has the same issue with scoping as -- quickCheckAll: see the note there about return []. 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 has the same issue with scoping as -- quickCheckAll: see the note there about return []. 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 'prop) means the same as -- quickCheck $(monomorphic 'prop). If you want to -- supply custom arguments to polyQuickCheck, you will have to -- combine quickCheckWith and monomorphic yourself. -- -- If you want to use polyQuickCheck in the same file where you -- defined the property, the same scoping problems pop up as in -- quickCheckAll: see the note there about return []. polyQuickCheck :: Name -> ExpQ -- | Test a polymorphic property, defaulting all type variables to -- Integer. This is just a convenience function that combines -- verboseCheck and monomorphic. -- -- If you want to use polyVerboseCheck in the same file where you -- defined the property, the same scoping problems pop up as in -- quickCheckAll: see the note there about return []. polyVerboseCheck :: Name -> ExpQ -- | Monomorphise an arbitrary property by defaulting all type variables to -- Integer. -- -- For example, if f has type Ord a => [a] -> -- [a] then $(monomorphic 'f) has type -- [Integer] -> [Integer]. -- -- If you want to use monomorphic in the same file where you -- defined the property, the same scoping problems pop up as in -- quickCheckAll: see the note there about return []. monomorphic :: Name -> ExpQ -- | 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 MonadIO m => MonadIO (PropertyM m) instance MonadTrans PropertyM instance Monad m => Monad (PropertyM m) instance Monad m => Applicative (PropertyM m) instance Functor (PropertyM m) 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 (QCGen, Int) -> Int -> Int -> Int -> Bool -> Args -- | Should we replay a previous test? replay :: Args -> Maybe (QCGen, Int) -- | Maximum number of successful tests before succeeding maxSuccess :: Args -> Int -- | Maximum number of discarded tests per successful test before giving up maxDiscardRatio :: 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 -- | A successful test run Success :: Int -> [(String, Int)] -> String -> Result -- | Number of tests performed numTests :: Result -> Int -- | Labels and frequencies found during all successful tests labels :: Result -> [(String, Int)] -- | Printed output output :: Result -> String -- | Given up GaveUp :: Int -> [(String, Int)] -> String -> Result -- | Number of tests performed numTests :: Result -> Int -- | Labels and frequencies found during all successful tests labels :: Result -> [(String, Int)] -- | Printed output output :: Result -> String -- | A failed test run Failure :: Int -> Int -> Int -> Int -> QCGen -> Int -> String -> Maybe AnException -> [(String, Int)] -> String -> Result -- | Number of tests performed numTests :: Result -> Int -- | Number of successful shrinking steps performed numShrinks :: Result -> Int -- | Number of unsuccessful shrinking steps performed numShrinkTries :: Result -> Int -- | Number of unsuccessful shrinking steps performed since last successful -- shrink numShrinkFinal :: Result -> Int -- | What seed was used usedSeed :: Result -> QCGen -- | What was the test size usedSize :: Result -> Int -- | Why did the property fail reason :: Result -> String -- | The exception the property threw, if any theException :: Result -> Maybe AnException -- | Labels and frequencies found during all successful tests labels :: Result -> [(String, Int)] -- | Printed output output :: Result -> String -- | A property that should have failed did not NoExpectedFailure :: Int -> [(String, Int)] -> String -> Result -- | Number of tests performed numTests :: Result -> Int -- | Labels and frequencies found during all successful tests labels :: Result -> [(String, Int)] -- | Printed output output :: Result -> String -- | The default test arguments 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 -- | 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. -- -- To use quickCheckAll, add a definition to your module along the -- lines of -- --
--   return []
--   runTests = $quickCheckAll
--   
-- -- and then execute runTests. -- -- Note: the bizarre return [] in the example above is needed on -- GHC 7.8; without it, quickCheckAll will not be able to find any -- of the properties. For the curious, the return [] is a -- Template Haskell splice that makes GHC insert the empty list of -- declarations at that point in the program; GHC typechecks everything -- before the return [] before it starts on the rest of the -- module, which means that the later call to quickCheckAll can -- see everything that was defined before the return []. Yikes! quickCheckAll :: Q Exp -- | Test all properties in the current module. This is just a convenience -- function that combines quickCheckAll and verbose. -- -- verboseCheckAll has the same issue with scoping as -- quickCheckAll: see the note there about return []. 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 has the same issue with scoping as -- quickCheckAll: see the note there about return []. 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 'prop) means the same as -- quickCheck $(monomorphic 'prop). If you want to -- supply custom arguments to polyQuickCheck, you will have to -- combine quickCheckWith and monomorphic yourself. -- -- If you want to use polyQuickCheck in the same file where you -- defined the property, the same scoping problems pop up as in -- quickCheckAll: see the note there about return []. polyQuickCheck :: Name -> ExpQ -- | Test a polymorphic property, defaulting all type variables to -- Integer. This is just a convenience function that combines -- verboseCheck and monomorphic. -- -- If you want to use polyVerboseCheck in the same file where you -- defined the property, the same scoping problems pop up as in -- quickCheckAll: see the note there about return []. polyVerboseCheck :: Name -> ExpQ -- | Monomorphise an arbitrary property by defaulting all type variables to -- Integer. -- -- For example, if f has type Ord a => [a] -> -- [a] then $(monomorphic 'f) has type -- [Integer] -> [Integer]. -- -- If you want to use monomorphic in the same file where you -- defined the property, the same scoping problems pop up as in -- quickCheckAll: see the note there about return []. monomorphic :: Name -> ExpQ -- | A generator for values of type a. data Gen a -- | Generates a random element in the given inclusive range. choose :: Random a => (a, a) -> Gen 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 -- | 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 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) -- | 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 an infinite list. infiniteListOf :: 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] -- | Generate an infinite list. infiniteList :: Arbitrary a => Gen [a] -- | Run a generator. generate :: Gen a -> IO 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 b -> Gen b -- | Generates an integral number. The number can be positive or negative -- and its maximum absolute value depends on the size parameter. arbitrarySizedIntegral :: 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 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 -- | Generates an element of a bounded enumeration. arbitraryBoundedEnum :: (Bounded a, Enum a) => Gen a -- | Shrink a term to any of its immediate subterms, and also recursively -- shrink all subterms. genericShrink :: (Generic a, Typeable a, RecursivelyShrink (Rep a), Subterms (Rep a)) => a -> [a] -- | All immediate subterms of a term. subterms :: (Generic a, Typeable a, Subterms (Rep a)) => a -> [a] -- | Recursively shrink all immediate subterms. recursivelyShrink :: (Generic a, RecursivelyShrink (Rep a)) => a -> [a] -- | Returns no shrinking alternatives. shrinkNothing :: a -> [a] -- | Shrink a list of values given a shrinking function for individual -- values. shrinkList :: (a -> [a]) -> [a] -> [[a]] -- | Shrink an integral number. shrinkIntegral :: Integral a => a -> [a] -- | Shrink a fraction. shrinkRealFrac :: RealFrac a => a -> [a] -- | Shrink a fraction, but only shrink to integral values. shrinkRealFracToInteger :: RealFrac a => a -> [a] -- | Modifies a generator using an integer seed. variant :: Integral n => n -> 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 -- | A coarbitrary implementation for enums. coarbitraryEnum :: Enum a => a -> Gen b -> Gen b -- | Combine two generator perturbing functions, for example the results of -- calls to variant or coarbitrary. -- | Deprecated: Use ordinary function composition instead (><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> (Gen a -> Gen a) -- | Blind x: as x, but x does not have to be in the Show -- class. newtype Blind a Blind :: a -> Blind a getBlind :: Blind a -> a -- | Fixed x: as x, but will not be shrunk. newtype Fixed a Fixed :: a -> Fixed a getFixed :: Fixed a -> a -- | Ordered xs: guarantees that xs is ordered. newtype OrderedList a Ordered :: [a] -> OrderedList a getOrdered :: OrderedList a -> [a] -- | NonEmpty xs: guarantees that xs is non-empty. newtype NonEmptyList a NonEmpty :: [a] -> NonEmptyList a getNonEmpty :: NonEmptyList a -> [a] -- | Positive x: guarantees that x > 0. newtype Positive a Positive :: a -> Positive a getPositive :: Positive a -> a -- | NonZero x: guarantees that x /= 0. newtype NonZero a NonZero :: a -> NonZero a getNonZero :: NonZero a -> a -- | NonNegative x: guarantees that x >= 0. newtype NonNegative a NonNegative :: a -> NonNegative a getNonNegative :: NonNegative a -> a -- | Large x: by default, QuickCheck generates Ints drawn -- from a small range. Large Int gives you values drawn from the -- entire range instead. newtype Large a Large :: a -> Large a getLarge :: Large a -> a -- | Small x: generates values of x drawn from a small -- range. The opposite of Large. newtype Small a Small :: a -> Small a getSmall :: Small a -> 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 getShrink2 :: Shrink2 a -> 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)] -- | The type of properties. -- -- Backwards combatibility note: in older versions of QuickCheck -- Property was a type synonym for Gen -- Prop, so you could mix and match property combinators and -- Gen monad operations. Code that does this will no longer -- typecheck. However, it is easy to fix: because of the Testable -- typeclass, any combinator that expects a Property will also -- accept a Gen Property. If you have a -- Property where you need a Gen a, -- simply wrap the property combinator inside a return to get a -- Gen Property, and all should be well. data Property -- | The class of things which can be tested, i.e. turned into a property. class Testable prop where exhaustive _ = False property :: Testable prop => prop -> Property exhaustive :: Testable prop => prop -> Bool -- | 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 -- | 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 (in which case the test case is discarded), -- or if the given property holds. (==>) :: Testable prop => Bool -> prop -> Property -- | Like ==, but prints a counterexample when it fails. (===) :: (Eq a, Show a) => a -> a -> Property -- | Do I/O inside a property. This can obviously lead to unrepeatable -- testcases, so use with care. -- -- For more advanced monadic testing you may want to look at -- Test.QuickCheck.Monadic. ioProperty :: Testable prop => IO prop -> Property -- | Prints out the generated testcase every time the property is tested. -- Only variables quantified over inside the verbose are -- printed. verbose :: Testable prop => prop -> Property -- | Modifies a property so that it only will be tested once. once :: 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 -- | Disables shrinking for a property altogether. noShrinking :: Testable prop => 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 -- | Adds the given string to the counterexample. counterexample :: Testable prop => String -> prop -> Property -- | Adds the given string to the counterexample. -- | Deprecated: Use counterexample instead 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 -- | Indicates that a property is supposed to fail. QuickCheck will report -- an error if it does not fail. 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 -- | If a property returns Discard, the current test case is -- discarded, the same as if a precondition was false. data Discard Discard :: Discard -- | A special exception that makes QuickCheck discard the test case. -- Normally you should use ==>, but if for some reason this -- isn't possible (e.g. you are deep inside a generator), use -- discard instead. discard :: a -- | Changes the maximum test case size for a property. mapSize :: Testable prop => (Int -> Int) -> prop -> Property