Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
- Running QuickSpec
- Declaring functions and predicates
- Declaring types
- Declaring types:
TypeApplication
-friendly variants - Standard signatures
- Exploring functions in series
- Including type class constraints (experimental, subject to change)
- Customising QuickSpec
- Integrating with QuickCheck
- Re-exported functionality
The main QuickSpec module. Everything you need to run QuickSpec lives here.
To run QuickSpec, you need to tell it which functions to test. We call the
list of functions the signature. Here is an example signature, which tells
QuickSpec to test the ++
, reverse
and []
functions:
sig = [con
"++" ((++) :: [A
] -> [A
] -> [A
]),con
"reverse" (reverse :: [A
] -> [A
]),con
"[]" ([] :: [A
]) ]
The con
function, used above, adds a function to the signature, given its
name and its value. When declaring polymorphic functions in the signature,
we use the types A
to E
to represent type variables.
Having defined this signature, we can say
to test it and
see the discovered equations.quickSpec
sig
If you want to test functions over your own datatypes, those types need to
implement Arbitrary
and Ord
(if the Ord
instance is a problem, see Observe
).
You must also declare those instances to QuickSpec, by including them in the
signature. For monomorphic types you can do this using monoType
:
data T = ...
main = quickSpec [
...,
monoType
(Proxy :: Proxy T)]
You can only declare monomorphic types with monoType
. If you want to test
your own polymorphic types, you must explicitly declare Arbitrary
and Ord
instances using the inst
function. You can also use the generator
function
to use a custom generator instead of the Arbitrary
instance for a given type.
You can also use QuickSpec to find conditional equations. To do so, you need
to include some predicates in the signature. These are functions returning
Bool
which can appear as conditions in other equations. Declaring a predicate
works just like declaring a function, except that you declare it using
predicate
instead of con
.
You can also put certain options in the signature. The most useful is
withMaxTermSize
, which you can use to tell QuickSpec to generate larger
equations.
The examples
directory contains many examples. Here are some interesting ones:
Arith.hs
: a simple arithmetic example. Demonstrates basic use of QuickSpec.Lists.hs
: list functions. Demonstrates testing polymorphic functions.Sorted.hs
: sorting. Demonstrates finding conditional equations.IntSet.hs
: a few functions from Data.IntSet. Demonstrates testing user-defined datatypes and finding conditional equations.PrettyPrinting.hs
: pretty printing combinators. Demonstrates testing user-defined datatypes and using observational equality.Parsing.hs
: parser combinators. Demonstrates testing polymorphic datatypes and using observational equality.
You can also find some larger case studies in our paper, Quick specifications for the busy programmer.
Synopsis
- quickSpec :: Signature sig => sig -> IO ()
- data Sig
- class Signature sig where
- con :: Typeable a => String -> a -> Sig
- predicate :: (Predicateable a, PredicateResult a ~ Bool, Typeable a, Typeable (PredicateTestCase a)) => String -> a -> Sig
- predicateGen :: (Predicateable a, Typeable a, Typeable (PredicateTestCase a), HasFriendly (PredicateTestCase a)) => String -> a -> Gen (FriendlyPredicateTestCase a) -> Sig
- data A
- data B
- data C
- data D
- data E
- monoType :: forall proxy a. (Ord a, Arbitrary a, Typeable a) => proxy a -> Sig
- monoTypeObserve :: forall proxy test outcome a. (Observe test outcome a, Arbitrary test, Ord outcome, Arbitrary a, Typeable test, Typeable outcome, Typeable a) => proxy a -> Sig
- class (Arbitrary test, Ord outcome) => Observe test outcome a | a -> test outcome where
- observe :: test -> a -> outcome
- inst :: (Typeable c1, Typeable c2) => (c1 :- c2) -> Sig
- generator :: Typeable a => Gen a -> Sig
- vars :: forall proxy a. Typeable a => [String] -> proxy a -> Sig
- monoTypeWithVars :: forall proxy a. (Ord a, Arbitrary a, Typeable a) => [String] -> proxy a -> Sig
- monoTypeObserveWithVars :: forall proxy test outcome a. (Observe test outcome a, Arbitrary test, Ord outcome, Arbitrary a, Typeable test, Typeable outcome, Typeable a) => [String] -> proxy a -> Sig
- variableUse :: forall proxy a. Typeable a => VariableUse -> proxy a -> Sig
- data VariableUse
- mono :: forall a. (Ord a, Arbitrary a, Typeable a) => Sig
- monoObserve :: forall a test outcome. (Observe test outcome a, Arbitrary test, Ord outcome, Arbitrary a, Typeable test, Typeable outcome, Typeable a) => Sig
- monoVars :: forall a. (Ord a, Arbitrary a, Typeable a) => [String] -> Sig
- monoObserveVars :: forall a test outcome. (Observe test outcome a, Arbitrary test, Ord outcome, Arbitrary a, Typeable test, Typeable outcome, Typeable a) => [String] -> Sig
- lists :: Sig
- arith :: forall proxy a. (Typeable a, Ord a, Num a, Arbitrary a) => proxy a -> Sig
- funs :: Sig
- bools :: Sig
- prelude :: Sig
- without :: Signature sig => sig -> [String] -> Sig
- background :: Signature sig => sig -> Sig
- series :: Signature sig => [sig] -> Sig
- type (==>) c t = Dict c -> t
- liftC :: (c => a) -> c ==> a
- instanceOf :: forall c. (Typeable c, c) => Sig
- withMaxTermSize :: Int -> Sig
- withMaxTests :: Int -> Sig
- withMaxTestSize :: Int -> Sig
- withMaxFunctions :: Int -> Sig
- defaultTo :: Typeable a => proxy a -> Sig
- withPruningDepth :: Int -> Sig
- withPruningTermSize :: Int -> Sig
- withFixedSeed :: Int -> Sig
- withInferInstanceTypes :: Sig
- withPrintStyle :: PrintStyle -> Sig
- data PrintStyle
- withConsistencyCheck :: Sig
- (=~=) :: (Show test, Show outcome, Observe test outcome a) => a -> a -> Property
- class Typeable (a :: k)
- newtype a :- b = Sub (a => Dict b)
- data Dict a where
- data Proxy (t :: k) = Proxy
- class Arbitrary a
Running QuickSpec
quickSpec :: Signature sig => sig -> IO () Source #
Run QuickSpec. See the documentation at the top of this file.
Declaring functions and predicates
predicate :: (Predicateable a, PredicateResult a ~ Bool, Typeable a, Typeable (PredicateTestCase a)) => String -> a -> Sig Source #
Declare a predicate with a given name and value.
The predicate should be a function which returns Bool
.
It will appear in equations just like any other constant,
but will also be allowed to appear as a condition.
Warning: if the predicate is unlikely to be true for a
randomly-generated value, you will get bad-quality test data.
In that case, use predicateGen
instead.
For example:
sig = [con
"delete" (delete
:: Int -> [Int] -> [Int]),con
"insert" (insert
:: Int -> [Int] -> [Int]), predicate "member" (member :: Int -> [Int] -> Bool) ]
predicateGen :: (Predicateable a, Typeable a, Typeable (PredicateTestCase a), HasFriendly (PredicateTestCase a)) => String -> a -> Gen (FriendlyPredicateTestCase a) -> Sig Source #
Declare a predicate with a given name and value.
The predicate should be a function which returns Bool
.
It will appear in equations just like any other constant,
but will also be allowed to appear as a condition.
The third argument is a generator for values satisfying the predicate.
For example, this declares a predicate that checks if a list is sorted:
predicateGen "sorted" sorted genSortedList
where
sorted :: [a] -> Bool sorted xs = sort xs == xs genSortedList :: Gen [a] genSortedList = sort <$> arbitrary
Type variables for polymorphic functions
Declaring types
monoType :: forall proxy a. (Ord a, Arbitrary a, Typeable a) => proxy a -> Sig Source #
Declare a new monomorphic type.
The type must implement Ord
and Arbitrary
.
If the type does not implement Ord
, you can use monoTypeObserve
to declare an observational equivalence function. If the type does
not implement Arbitrary
, you can use generator
to declare a
custom QuickCheck generator.
You do not necessarily need Ord
and Arbitrary
instances for
every type. If there is no Ord
(or Observe
instance) for a
type, you will not get equations between terms of that type. If
there is no Arbitrary
instance (or generator), you will not get
variables of that type.
monoTypeObserve :: forall proxy test outcome a. (Observe test outcome a, Arbitrary test, Ord outcome, Arbitrary a, Typeable test, Typeable outcome, Typeable a) => proxy a -> Sig Source #
class (Arbitrary test, Ord outcome) => Observe test outcome a | a -> test outcome where Source #
A typeclass for types which support observational equality, typically used
for types that have no Ord
instance.
An instance Observe test outcome a
declares that values of type a
can be
tested for equality by random testing. You supply a function
observe :: test -> outcome -> a
. Then, two values x
and y
are considered
equal, if for many random values of type test
, observe test x == observe test y
.
The function monoTypeObserve
declares a monomorphic
type with an observation function. For polymorphic types, use
inst
to declare the Observe
instance.
For an example of using observational equality, see PrettyPrinting.hs
.
Nothing
observe :: test -> a -> outcome Source #
Make an observation on a value. Should satisfy the following law: if
x /= y
, then there exists a value of test
such that observe test x /= observe test y
.
Instances
inst :: (Typeable c1, Typeable c2) => (c1 :- c2) -> Sig Source #
Declare a typeclass instance. QuickSpec needs to have an Ord
and
Arbitrary
instance for each type you want it to test.
For example, if you are testing
, you will need to add
the following two declarations to your signature:Map
k v
inst
(Sub
Dict
:: (Ord A, Ord B):-
Ord (Map A B))inst
(Sub
Dict
:: (Arbitrary A, Arbitrary B):-
Arbitrary (Map A B))
For a monomorphic type T
, you can use monoType
instead, but if you
want to use inst
, you can do it like this:
inst
(Sub
Dict
:: ():-
Ord T)inst
(Sub
Dict
:: ():-
Arbitrary T)
generator :: Typeable a => Gen a -> Sig Source #
Declare a generator to be used to produce random values of a
given type. This will take precedence over any Arbitrary
instance.
vars :: forall proxy a. Typeable a => [String] -> proxy a -> Sig Source #
Customize how variables of a particular type are named.
monoTypeWithVars :: forall proxy a. (Ord a, Arbitrary a, Typeable a) => [String] -> proxy a -> Sig Source #
Declare a new monomorphic type, saying how you want variables of that type to be named.
monoTypeObserveWithVars :: forall proxy test outcome a. (Observe test outcome a, Arbitrary test, Ord outcome, Arbitrary a, Typeable test, Typeable outcome, Typeable a) => [String] -> proxy a -> Sig Source #
Declare a new monomorphic type using observational equivalence, saying how you want variables of that type to be named.
variableUse :: forall proxy a. Typeable a => VariableUse -> proxy a -> Sig Source #
Constrain how variables of a particular type may occur in a term.
The default value is
.UpTo
4
data VariableUse Source #
Constrains how variables of a particular type may occur in a term.
UpTo Int |
|
Linear | Each variable in the term must be distinct |
Instances
Show VariableUse Source # | |
Defined in QuickSpec.Internal.Explore.Schemas showsPrec :: Int -> VariableUse -> ShowS # show :: VariableUse -> String # showList :: [VariableUse] -> ShowS # | |
Eq VariableUse Source # | |
Defined in QuickSpec.Internal.Explore.Schemas (==) :: VariableUse -> VariableUse -> Bool # (/=) :: VariableUse -> VariableUse -> Bool # |
Declaring types: TypeApplication
-friendly variants
monoObserve :: forall a test outcome. (Observe test outcome a, Arbitrary test, Ord outcome, Arbitrary a, Typeable test, Typeable outcome, Typeable a) => Sig Source #
Like monoTypeObserve
, but designed to be used with TypeApplications directly.
For example, you can add Foo
to your signature via:
monoObserve
@Foo
monoVars :: forall a. (Ord a, Arbitrary a, Typeable a) => [String] -> Sig Source #
Like monoTypeWithVars
designed to be used with TypeApplications directly.
For example, you can add Foo
to your signature via:
monoVars
@Foo ["foo"]
monoObserveVars :: forall a test outcome. (Observe test outcome a, Arbitrary test, Ord outcome, Arbitrary a, Typeable test, Typeable outcome, Typeable a) => [String] -> Sig Source #
Like monoTypeObserveWithVars
, but designed to be used with TypeApplications directly.
For example, you can add Foo
to your signature via:
monoObserveVars
@Foo ["foo"]
Standard signatures
The "prelude": a standard signature containing useful functions
like ++
, which can be used as background theory.
without :: Signature sig => sig -> [String] -> Sig Source #
Remove a function or predicate from the signature.
Useful in combination with prelude
and friends.
Exploring functions in series
background :: Signature sig => sig -> Sig Source #
Declare some functions as being background functions. These are functions which are not interesting on their own, but which may appear in interesting laws with non-background functions. Declaring background functions may improve the laws you get out.
Here is an example, which tests ++
and length
, giving 0
and +
as
background functions:
main = quickSpec [ con "++" ((++) :: [A] -> [A] -> [A]), con "length" (length :: [A] -> Int), background [ con "0" (0 :: Int), con "+" ((+) :: Int -> Int -> Int) ] ]
series :: Signature sig => [sig] -> Sig Source #
Run QuickCheck on a series of signatures. Tests the functions in the first signature, then adds the functions in the second signature, then adds the functions in the third signature, and so on.
This can be useful when you have a core API you want to test first, and a larger API you want to test later. The laws for the core API will be printed separately from the laws for the larger API.
Here is an example which first tests 0
and +
and then adds ++
and length
:
main = quickSpec (series [sig1, sig2]) where sig1 = [ con "0" (0 :: Int), con "+" ((+) :: Int -> Int -> Int) ] sig2 = [ con "++" ((++) :: [A] -> [A] -> [A]), con "length" (length :: [A] -> Int) ]
Including type class constraints (experimental, subject to change)
liftC :: (c => a) -> c ==> a Source #
Lift a constrained type to a ==>
type which QuickSpec
can work with
instanceOf :: forall c. (Typeable c, c) => Sig Source #
Add an instance of a type class to the signature
Customising QuickSpec
withMaxTermSize :: Int -> Sig Source #
Set the maximum size of terms to explore (default: 7).
withMaxTests :: Int -> Sig Source #
Set how many times to test each discovered law (default: 1000).
withMaxTestSize :: Int -> Sig Source #
Set the maximum value for QuickCheck's size parameter when generating test data (default: 20).
withMaxFunctions :: Int -> Sig Source #
Limit how many different function symbols can occur in a term.
withPruningDepth :: Int -> Sig Source #
Set how hard QuickSpec tries to filter out redundant equations (default: no limit).
If you experience long pauses when running QuickSpec, try setting this number to 2 or 3.
withPruningTermSize :: Int -> Sig Source #
Set the maximum term size QuickSpec will reason about when it filters out redundant equations (default: same as maximum term size).
If you get laws you believe are redundant, try increasing this number to 1 or 2 more than the maximum term size.
withFixedSeed :: Int -> Sig Source #
Set the random number seed used for test case generation. Useful if you want repeatable results.
withInferInstanceTypes :: Sig Source #
Automatically infer types to add to the universe from available type class instances
withPrintStyle :: PrintStyle -> Sig Source #
Set how QuickSpec should display its discovered equations (default: ForHumans
).
If you'd instead like to turn QuickSpec's output into QuickCheck tests, set
this to ForQuickCheck
.
data PrintStyle Source #
How QuickSpec should style equations.
Instances
withConsistencyCheck :: Sig Source #
(Experimental) Check that the discovered laws do not imply any false laws
Integrating with QuickCheck
Re-exported functionality
The class Typeable
allows a concrete representation of a type to
be calculated.
typeRep#
This is the type of entailment.
a
is read as :-
ba
"entails" b
.
With this we can actually build a category for Constraint
resolution.
e.g.
Because
is a superclass of Eq
a
, we can show that Ord
a
entails Ord
a
.Eq
a
Because instance
exists, we can show that Ord
a => Ord
[a]
entails Ord
a
as well.Ord
[a]
This relationship is captured in the :-
entailment type here.
Since p
and entailment composes, :-
p:-
forms the arrows of a
Category
of constraints. However, Category
only became sufficiently
general to support this instance in GHC 7.8, so prior to 7.8 this instance
is unavailable.
But due to the coherence of instance resolution in Haskell, this Category
has some very interesting properties. Notably, in the absence of
IncoherentInstances
, this category is "thin", which is to say that
between any two objects (constraints) there is at most one distinguishable
arrow.
This means that for instance, even though there are two ways to derive
, the answers from these two paths _must_ by
construction be equal. This is a property that Haskell offers that is
pretty much unique in the space of languages with things they call "type
classes".Ord
a :-
Eq
[a]
What are the two ways?
Well, we can go from
via the
superclass relationship, and then from Ord
a :-
Eq
a
via the
instance, or we can go from Eq
a :-
Eq
[a]
via the instance
then from Ord
a :-
Ord
[a]
through the superclass relationship
and this diagram by definition must "commute".Ord
[a] :-
Eq
[a]
Diagrammatically,
Ord a ins / \ cls v v Ord [a] Eq a cls \ / ins v v Eq [a]
This safety net ensures that pretty much anything you can write with this library is sensible and can't break any assumptions on the behalf of library authors.
Instances
Category (:-) | Possible since GHC 7.8, when |
() :=> (Show (a :- b)) | |
() :=> (Eq (a :- b)) | |
() :=> (Ord (a :- b)) | |
a => HasDict b (a :- b) | |
Defined in Data.Constraint | |
(Typeable p, Typeable q, p, q) => Data (p :- q) | |
Defined in Data.Constraint gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> (p :- q) -> c (p :- q) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (p :- q) # toConstr :: (p :- q) -> Constr # dataTypeOf :: (p :- q) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (p :- q)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (p :- q)) # gmapT :: (forall b. Data b => b -> b) -> (p :- q) -> p :- q # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (p :- q) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (p :- q) -> r # gmapQ :: (forall d. Data d => d -> u) -> (p :- q) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> (p :- q) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (p :- q) -> m (p :- q) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (p :- q) -> m (p :- q) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (p :- q) -> m (p :- q) # | |
Show (a :- b) | |
a => NFData (a :- b) | |
Defined in Data.Constraint | |
Eq (a :- b) | Assumes |
Ord (a :- b) | Assumes |
Defined in Data.Constraint |
Values of type
capture a dictionary for a constraint of type Dict
pp
.
e.g.
Dict
::Dict
(Eq
Int
)
captures a dictionary that proves we have an:
instanceEq
Int
Pattern matching on the Dict
constructor will bring this instance into scope.
Instances
() :=> (Semigroup (Dict a)) | |
() :=> (Show (Dict a)) | |
() :=> (Eq (Dict a)) | |
() :=> (Ord (Dict a)) | |
a :=> (Monoid (Dict a)) | |
a :=> (Bounded (Dict a)) | |
a :=> (Enum (Dict a)) | |
a :=> (Read (Dict a)) | |
HasDict a (Dict a) | |
Defined in Data.Constraint | |
c => Arbitrary (Dict c) Source # | |
(Typeable p, p) => Data (Dict p) | |
Defined in Data.Constraint gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dict p -> c (Dict p) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dict p) # toConstr :: Dict p -> Constr # dataTypeOf :: Dict p -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Dict p)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Dict p)) # gmapT :: (forall b. Data b => b -> b) -> Dict p -> Dict p # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dict p -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dict p -> r # gmapQ :: (forall d. Data d => d -> u) -> Dict p -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dict p -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) # | |
a => Monoid (Dict a) | |
Semigroup (Dict a) | |
a => Bounded (Dict a) | |
a => Enum (Dict a) | |
Defined in Data.Constraint | |
a => Read (Dict a) | |
Show (Dict a) | |
NFData (Dict c) | |
Defined in Data.Constraint | |
Eq (Dict a) | |
Ord (Dict a) | |
Proxy
is a type that holds no data, but has a phantom parameter of
arbitrary type (or even kind). Its use is to provide type information, even
though there is no value available of that type (or it may be too costly to
create one).
Historically,
is a safer alternative to the
Proxy
:: Proxy
a
idiom.undefined
:: a
>>>
Proxy :: Proxy (Void, Int -> Int)
Proxy
Proxy can even hold types of higher kinds,
>>>
Proxy :: Proxy Either
Proxy
>>>
Proxy :: Proxy Functor
Proxy
>>>
Proxy :: Proxy complicatedStructure
Proxy
Instances
Generic1 (Proxy :: k -> Type) | |
Foldable (Proxy :: TYPE LiftedRep -> Type) | Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> m # foldMap' :: Monoid m => (a -> m) -> Proxy a -> m # foldr :: (a -> b -> b) -> b -> Proxy a -> b # foldr' :: (a -> b -> b) -> b -> Proxy a -> b # foldl :: (b -> a -> b) -> b -> Proxy a -> b # foldl' :: (b -> a -> b) -> b -> Proxy a -> b # foldr1 :: (a -> a -> a) -> Proxy a -> a # foldl1 :: (a -> a -> a) -> Proxy a -> a # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
Eq1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Ord1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 (Proxy :: TYPE LiftedRep -> Type) | Since: base-4.9.0.0 |
Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Hashable1 (Proxy :: Type -> Type) | |
Defined in Data.Hashable.Class | |
Monoid (Proxy s) | Since: base-4.7.0.0 |
Semigroup (Proxy s) | Since: base-4.9.0.0 |
Bounded (Proxy t) | Since: base-4.7.0.0 |
Enum (Proxy s) | Since: base-4.7.0.0 |
Generic (Proxy t) | |
Ix (Proxy s) | Since: base-4.7.0.0 |
Defined in Data.Proxy | |
Read (Proxy t) | Since: base-4.7.0.0 |
Show (Proxy s) | Since: base-4.7.0.0 |
Eq (Proxy s) | Since: base-4.7.0.0 |
Ord (Proxy s) | Since: base-4.7.0.0 |
Hashable (Proxy a) | |
Defined in Data.Hashable.Class | |
type Rep1 (Proxy :: k -> Type) | Since: base-4.6.0.0 |
type Rep (Proxy t) | Since: base-4.6.0.0 |
Random generation and shrinking of values.
QuickCheck provides Arbitrary
instances for most types in base
,
except those which incur extra dependencies.
For a wider range of Arbitrary
instances see the
quickcheck-instances
package.