Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
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.
Note: the contents of this module are re-exported by Test.QuickCheck. You do not need to import it directly.
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 offorAll
orderedList
prop_Sort (Ordered
(xs :: [OrdA
])) = sort xs == xs
Synopsis
- newtype Blind a = Blind {
- getBlind :: a
- newtype Fixed a = Fixed {
- getFixed :: a
- newtype OrderedList a = Ordered {
- getOrdered :: [a]
- newtype NonEmptyList a = NonEmpty {
- getNonEmpty :: [a]
- data InfiniteList a = InfiniteList {
- getInfiniteList :: [a]
- infiniteListInternalData :: InfiniteListInternalData a
- newtype SortedList a = Sorted {
- getSorted :: [a]
- newtype Positive a = Positive {
- getPositive :: a
- newtype Negative a = Negative {
- getNegative :: a
- newtype NonZero a = NonZero {
- getNonZero :: a
- newtype NonNegative a = NonNegative {
- getNonNegative :: a
- newtype NonPositive a = NonPositive {
- getNonPositive :: a
- newtype Large a = Large {
- getLarge :: a
- newtype Small a = Small {
- getSmall :: a
- data Smart a = Smart Int a
- newtype Shrink2 a = Shrink2 {
- getShrink2 :: a
- data Shrinking s a = Shrinking s a
- class ShrinkState s a where
- shrinkInit :: a -> s
- shrinkState :: a -> s -> [(a, s)]
- newtype ASCIIString = ASCIIString {}
- newtype UnicodeString = UnicodeString {}
- newtype PrintableString = PrintableString {}
Type-level modifiers for changing generator behavior
Blind x
: as x, but x does not have to be in the Show
class.
Instances
Functor Blind Source # | |
Arbitrary a => Arbitrary (Blind a) Source # | |
Enum a => Enum (Blind a) Source # | |
Num a => Num (Blind a) Source # | |
Integral a => Integral (Blind a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Real a => Real (Blind a) Source # | |
Defined in Test.QuickCheck.Modifiers toRational :: Blind a -> Rational # | |
Show (Blind a) Source # | |
Eq a => Eq (Blind a) Source # | |
Ord a => Ord (Blind a) Source # | |
Fixed x
: as x, but will not be shrunk.
Instances
Functor Fixed Source # | |
Arbitrary a => Arbitrary (Fixed a) Source # | |
Enum a => Enum (Fixed a) Source # | |
Num a => Num (Fixed a) Source # | |
Read a => Read (Fixed a) Source # | |
Integral a => Integral (Fixed a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Real a => Real (Fixed a) Source # | |
Defined in Test.QuickCheck.Modifiers toRational :: Fixed a -> Rational # | |
Show a => Show (Fixed a) Source # | |
Eq a => Eq (Fixed a) Source # | |
Ord a => Ord (Fixed a) Source # | |
newtype OrderedList a Source #
Ordered xs
: guarantees that xs is ordered.
Ordered | |
|
Instances
newtype NonEmptyList a Source #
NonEmpty xs
: guarantees that xs is non-empty.
NonEmpty | |
|
Instances
data InfiniteList a Source #
InfiniteList xs _
: guarantees that xs is an infinite list.
When a counterexample is found, only prints the prefix of xs
that was used by the program.
Here is a contrived example property:
prop_take_10 :: InfiniteList Char -> Bool prop_take_10 (InfiniteList xs _) = or [ x == 'a' | x <- take 10 xs ]
In the following counterexample, the list must start with "bbbbbbbbbb"
but
the remaining (infinite) part can contain anything:
>>>
quickCheck prop_take_10
*** Failed! Falsified (after 1 test and 14 shrinks): "bbbbbbbbbb" ++ ...
InfiniteList | |
|
Instances
Arbitrary a => Arbitrary (InfiniteList a) Source # | |
Defined in Test.QuickCheck.Modifiers arbitrary :: Gen (InfiniteList a) Source # shrink :: InfiniteList a -> [InfiniteList a] Source # | |
Show a => Show (InfiniteList a) Source # | |
Defined in Test.QuickCheck.Modifiers showsPrec :: Int -> InfiniteList a -> ShowS # show :: InfiniteList a -> String # showList :: [InfiniteList a] -> ShowS # |
newtype SortedList a Source #
Sorted xs
: guarantees that xs is sorted.
Instances
Positive x
: guarantees that x > 0
.
Positive | |
|
Instances
Functor Positive Source # | |
(Num a, Ord a, Arbitrary a) => Arbitrary (Positive a) Source # | |
Enum a => Enum (Positive a) Source # | |
Defined in Test.QuickCheck.Modifiers succ :: Positive a -> Positive a # pred :: Positive a -> Positive a # fromEnum :: Positive a -> Int # enumFrom :: Positive a -> [Positive a] # enumFromThen :: Positive a -> Positive a -> [Positive a] # enumFromTo :: Positive a -> Positive a -> [Positive a] # enumFromThenTo :: Positive a -> Positive a -> Positive a -> [Positive a] # | |
Read a => Read (Positive a) Source # | |
Show a => Show (Positive a) Source # | |
Eq a => Eq (Positive a) Source # | |
Ord a => Ord (Positive a) Source # | |
Negative x
: guarantees that x < 0
.
Negative | |
|
Instances
Functor Negative Source # | |
(Num a, Ord a, Arbitrary a) => Arbitrary (Negative a) Source # | |
Enum a => Enum (Negative a) Source # | |
Defined in Test.QuickCheck.Modifiers succ :: Negative a -> Negative a # pred :: Negative a -> Negative a # fromEnum :: Negative a -> Int # enumFrom :: Negative a -> [Negative a] # enumFromThen :: Negative a -> Negative a -> [Negative a] # enumFromTo :: Negative a -> Negative a -> [Negative a] # enumFromThenTo :: Negative a -> Negative a -> Negative a -> [Negative a] # | |
Read a => Read (Negative a) Source # | |
Show a => Show (Negative a) Source # | |
Eq a => Eq (Negative a) Source # | |
Ord a => Ord (Negative a) Source # | |
NonZero x
: guarantees that x /= 0
.
NonZero | |
|
Instances
Functor NonZero Source # | |
(Num a, Eq a, Arbitrary a) => Arbitrary (NonZero a) Source # | |
Enum a => Enum (NonZero a) Source # | |
Defined in Test.QuickCheck.Modifiers succ :: NonZero a -> NonZero a # pred :: NonZero a -> NonZero a # fromEnum :: NonZero a -> Int # enumFrom :: NonZero a -> [NonZero a] # enumFromThen :: NonZero a -> NonZero a -> [NonZero a] # enumFromTo :: NonZero a -> NonZero a -> [NonZero a] # enumFromThenTo :: NonZero a -> NonZero a -> NonZero a -> [NonZero a] # | |
Read a => Read (NonZero a) Source # | |
Show a => Show (NonZero a) Source # | |
Eq a => Eq (NonZero a) Source # | |
Ord a => Ord (NonZero a) Source # | |
Defined in Test.QuickCheck.Modifiers |
newtype NonNegative a Source #
NonNegative x
: guarantees that x >= 0
.
Instances
newtype NonPositive a Source #
NonPositive x
: guarantees that x <= 0
.
Instances
Large x
: by default, QuickCheck generates Int
s drawn from a small
range. Large Int
gives you values drawn from the entire range instead.
Instances
Functor Large Source # | |
(Integral a, Bounded a) => Arbitrary (Large a) Source # | |
Enum a => Enum (Large a) Source # | |
Ix a => Ix (Large a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Num a => Num (Large a) Source # | |
Read a => Read (Large a) Source # | |
Integral a => Integral (Large a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Real a => Real (Large a) Source # | |
Defined in Test.QuickCheck.Modifiers toRational :: Large a -> Rational # | |
Show a => Show (Large a) Source # | |
Eq a => Eq (Large a) Source # | |
Ord a => Ord (Large a) Source # | |
Small x
: generates values of x
drawn from a small range.
The opposite of Large
.
Instances
Functor Small Source # | |
Integral a => Arbitrary (Small a) Source # | |
Enum a => Enum (Small a) Source # | |
Ix a => Ix (Small a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Num a => Num (Small a) Source # | |
Read a => Read (Small a) Source # | |
Integral a => Integral (Small a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Real a => Real (Small a) Source # | |
Defined in Test.QuickCheck.Modifiers toRational :: Small a -> Rational # | |
Show a => Show (Small a) Source # | |
Eq a => Eq (Small a) Source # | |
Ord a => Ord (Small a) Source # | |
Smart _ x
: tries a different order when shrinking.
Shrink2 x
: allows 2 shrinking steps at the same time when shrinking x
Shrink2 | |
|
Instances
Functor Shrink2 Source # | |
Arbitrary a => Arbitrary (Shrink2 a) Source # | |
Enum a => Enum (Shrink2 a) Source # | |
Defined in Test.QuickCheck.Modifiers succ :: Shrink2 a -> Shrink2 a # pred :: Shrink2 a -> Shrink2 a # fromEnum :: Shrink2 a -> Int # enumFrom :: Shrink2 a -> [Shrink2 a] # enumFromThen :: Shrink2 a -> Shrink2 a -> [Shrink2 a] # enumFromTo :: Shrink2 a -> Shrink2 a -> [Shrink2 a] # enumFromThenTo :: Shrink2 a -> Shrink2 a -> Shrink2 a -> [Shrink2 a] # | |
Num a => Num (Shrink2 a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Read a => Read (Shrink2 a) Source # | |
Integral a => Integral (Shrink2 a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Real a => Real (Shrink2 a) Source # | |
Defined in Test.QuickCheck.Modifiers toRational :: Shrink2 a -> Rational # | |
Show a => Show (Shrink2 a) Source # | |
Eq a => Eq (Shrink2 a) Source # | |
Ord a => Ord (Shrink2 a) Source # | |
Defined in Test.QuickCheck.Modifiers |
Shrinking _ x
: allows for maintaining a state during shrinking.
Shrinking s a |
class ShrinkState s a where Source #
shrinkInit :: a -> s Source #
shrinkState :: a -> s -> [(a, s)] Source #
newtype ASCIIString Source #
ASCIIString
: generates an ASCII string.
Instances
newtype UnicodeString Source #
UnicodeString
: generates a unicode String.
The string will not contain surrogate pairs.
Instances
newtype PrintableString Source #
PrintableString
: generates a printable unicode String.
The string will not contain surrogate pairs.
Instances
Arbitrary PrintableString Source # | |
Defined in Test.QuickCheck.Modifiers | |
Read PrintableString Source # | |
Defined in Test.QuickCheck.Modifiers | |
Show PrintableString Source # | |
Defined in Test.QuickCheck.Modifiers showsPrec :: Int -> PrintableString -> ShowS # show :: PrintableString -> String # showList :: [PrintableString] -> ShowS # | |
Eq PrintableString Source # | |
Defined in Test.QuickCheck.Modifiers (==) :: PrintableString -> PrintableString -> Bool # (/=) :: PrintableString -> PrintableString -> Bool # | |
Ord PrintableString Source # | |
Defined in Test.QuickCheck.Modifiers compare :: PrintableString -> PrintableString -> Ordering # (<) :: PrintableString -> PrintableString -> Bool # (<=) :: PrintableString -> PrintableString -> Bool # (>) :: PrintableString -> PrintableString -> Bool # (>=) :: PrintableString -> PrintableString -> Bool # max :: PrintableString -> PrintableString -> PrintableString # min :: PrintableString -> PrintableString -> PrintableString # |