quickspec-2.2: Equational laws for free!
Safe HaskellSafe-Inferred
LanguageHaskell2010

QuickSpec

Description

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 quickSpec sig to test it and see the discovered equations.

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

Running QuickSpec

quickSpec :: Signature sig => sig -> IO () Source #

Run QuickSpec. See the documentation at the top of this file.

data Sig Source #

A signature.

Instances

Instances details
Monoid Sig Source # 
Instance details

Defined in QuickSpec.Internal

Methods

mempty :: Sig #

mappend :: Sig -> Sig -> Sig #

mconcat :: [Sig] -> Sig #

Semigroup Sig Source # 
Instance details

Defined in QuickSpec.Internal

Methods

(<>) :: Sig -> Sig -> Sig #

sconcat :: NonEmpty Sig -> Sig #

stimes :: Integral b => b -> Sig -> Sig #

Signature Sig Source # 
Instance details

Defined in QuickSpec.Internal

Methods

signature :: Sig -> Sig Source #

class Signature sig where Source #

A class of things that can be used as a QuickSpec signature.

Methods

signature :: sig -> Sig Source #

Convert the thing to a signature.

Instances

Instances details
Signature Sig Source # 
Instance details

Defined in QuickSpec.Internal

Methods

signature :: Sig -> Sig Source #

Signature sig => Signature [sig] Source # 
Instance details

Defined in QuickSpec.Internal

Methods

signature :: [sig] -> Sig Source #

Declaring functions and predicates

con :: Typeable a => String -> a -> Sig Source #

Declare a constant with a given name and value. If the constant you want to use is polymorphic, you can use the types A, B, C, D, E to monomorphise it, for example:

constant "reverse" (reverse :: [A] -> [A])

QuickSpec will then understand that the constant is really polymorphic.

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

data A Source #

data B Source #

data C Source #

data D Source #

data E Source #

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 #

Declare a new monomorphic type using observational equivalence. The type must implement Observe and Arbitrary.

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.

Minimal complete definition

Nothing

Methods

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.

default observe :: (test ~ (), outcome ~ a) => test -> a -> outcome Source #

Instances

Instances details
Observe () All All Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> All -> All Source #

Observe () Any Any Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Any -> Any Source #

Observe () Unique Unique Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Unique -> Unique Source #

Observe () Void Void Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Void -> Void Source #

Observe () Int16 Int16 Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Int16 -> Int16 Source #

Observe () Int32 Int32 Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Int32 -> Int32 Source #

Observe () Int64 Int64 Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Int64 -> Int64 Source #

Observe () Int8 Int8 Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Int8 -> Int8 Source #

Observe () Word16 Word16 Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Word16 -> Word16 Source #

Observe () Word32 Word32 Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Word32 -> Word32 Source #

Observe () Word64 Word64 Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Word64 -> Word64 Source #

Observe () Word8 Word8 Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Word8 -> Word8 Source #

Observe () Ordering Ordering Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Ordering -> Ordering Source #

Observe () Integer Integer Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Integer -> Integer Source #

Observe () Natural Natural Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Natural -> Natural Source #

Observe () () () Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> () -> () Source #

Observe () Bool Bool Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Bool -> Bool Source #

Observe () Char Char Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Char -> Char Source #

Observe () Double Double Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Double -> Double Source #

Observe () Float Float Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Float -> Float Source #

Observe () Int Int Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Int -> Int Source #

Observe () Word Word Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: () -> Word -> Word Source #

Observe t p a => Observe t p (Identity a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> Identity a -> p Source #

Observe t p a => Observe t p (First a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> First a -> p Source #

Observe t p a => Observe t p (Last a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> Last a -> p Source #

Observe t p a => Observe t p (Max a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> Max a -> p Source #

Observe t p a => Observe t p (Min a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> Min a -> p Source #

Observe t p a => Observe t p (WrappedMonoid a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> WrappedMonoid a -> p Source #

Observe t p a => Observe t p (Dual a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> Dual a -> p Source #

Observe t p a => Observe t p (Product a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> Product a -> p Source #

Observe t p a => Observe t p (Sum a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> Sum a -> p Source #

Observe t p (f a) => Observe t p (Ap f a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> Ap f a -> p Source #

Observe t p (f a) => Observe t p (Alt f a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> Alt f a -> p Source #

Observe t p (f (g a)) => Observe t p (Compose f g a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> Compose f g a -> p Source #

Observe t p a => Observe t (NonEmpty p) (NonEmpty a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> NonEmpty a -> NonEmpty p Source #

Observe t p a => Observe t (Maybe p) (First a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> First a -> Maybe p Source #

Observe t p a => Observe t (Maybe p) (Last a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> Last a -> Maybe p Source #

Observe t p a => Observe t (Maybe p) (Maybe a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> Maybe a -> Maybe p Source #

Observe t p a => Observe t [p] [a] Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: t -> [a] -> [p] Source #

(Arbitrary a, Observe t p a) => Observe (a, t) p (Endo a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: (a, t) -> Endo a -> p Source #

(Arbitrary a, Observe test outcome b) => Observe (a, test) outcome (a -> b) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: (a, test) -> (a -> b) -> outcome Source #

Observe t p a => Observe (t, t) (p, p) (Complex a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: (t, t) -> Complex a -> (p, p) Source #

Observe t p a => Observe (t, t) (p, p) (Ratio a) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: (t, t) -> Ratio a -> (p, p) Source #

(Observe at ao a, Observe bt bo b) => Observe (at, bt) (Either ao bo) (Either a b) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: (at, bt) -> Either a b -> Either ao bo Source #

(Observe xt xo x, Observe yt yo y) => Observe (xt, yt) (xo, yo) (x, y) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: (xt, yt) -> (x, y) -> (xo, yo) Source #

(Observe xt xo x, Observe yt yo y, Observe zt zo z) => Observe (xt, yt, zt) (xo, yo, zo) (x, y, z) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: (xt, yt, zt) -> (x, y, z) -> (xo, yo, zo) Source #

(Observe xt xo x, Observe yt yo y, Observe zt zo z, Observe wt wo w) => Observe (xt, yt, zt, wt) (xo, yo, zo, wo) (x, y, z, w) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

observe :: (xt, yt, zt, wt) -> (x, y, z, w) -> (xo, yo, zo, wo) Source #

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 Map k v, you will need to add the following two declarations to your signature:

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.

Constructors

UpTo Int

UpTo n: terms may contain up to n distinct variables of this type (in some cases, laws with more variables may still be found)

Linear

Each variable in the term must be distinct

Instances

Instances details
Show VariableUse Source # 
Instance details

Defined in QuickSpec.Internal.Explore.Schemas

Eq VariableUse Source # 
Instance details

Defined in QuickSpec.Internal.Explore.Schemas

Declaring types: TypeApplication-friendly variants

mono :: forall a. (Ord a, Arbitrary a, Typeable a) => Sig Source #

Like monoType, but designed to be used with TypeApplications directly.

For example, you can add Foo to your signature via:

mono @Foo

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.

lists :: Sig Source #

A signature containing list operations: [], (:), (++).

arith :: forall proxy a. (Typeable a, Ord a, Num a, Arbitrary a) => proxy a -> Sig Source #

A signature containing arithmetic operations: 0, 1, (+). Instantiate it with e.g. arith (Proxy :: Proxy Int).

funs :: Sig Source #

A signature containing higher-order functions: (.) and id. Useful for testing map and similar.

bools :: Sig Source #

A signature containing boolean functions: (||), (&&), not, True, False.

prelude :: Sig Source #

The QuickSpec prelude. Contains boolean, arithmetic and list functions, and function composition. For more precise control over what gets included, see bools, arith, lists, funs and without.

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)

type (==>) c t = Dict c -> t Source #

Type class constraints as first class citizens

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.

defaultTo :: Typeable a => proxy a -> Sig Source #

Set which type polymorphic terms are tested at.

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.

Constructors

ForHumans 
ForQuickCheck 

Instances

Instances details
Bounded PrintStyle Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Enum PrintStyle Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Read PrintStyle Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Show PrintStyle Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Eq PrintStyle Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Ord PrintStyle Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

withConsistencyCheck :: Sig Source #

(Experimental) Check that the discovered laws do not imply any false laws

Integrating with QuickCheck

(=~=) :: (Show test, Show outcome, Observe test outcome a) => a -> a -> Property infix 4 Source #

Like ===, but using the Observe typeclass instead of Eq.

Re-exported functionality

class Typeable (a :: k) #

The class Typeable allows a concrete representation of a type to be calculated.

Minimal complete definition

typeRep#

Instances

Instances details
HasDict (Typeable k, Typeable a) (TypeRep a) 
Instance details

Defined in Data.Constraint

Methods

evidence :: TypeRep a -> Dict (Typeable k, Typeable a) #

newtype a :- b infixr 9 #

This is the type of entailment.

a :- b is read as a "entails" b.

With this we can actually build a category for Constraint resolution.

e.g.

Because Eq a is a superclass of Ord a, we can show that Ord a entails Eq a.

Because instance Ord a => Ord [a] exists, we can show that Ord a entails Ord [a] as well.

This relationship is captured in the :- entailment type here.

Since p :- p and entailment composes, :- 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 Ord a :- Eq [a], 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".

What are the two ways?

Well, we can go from Ord a :- Eq a via the superclass relationship, and then from Eq a :- Eq [a] via the instance, or we can go from Ord a :- Ord [a] via the instance then from Ord [a] :- Eq [a] through the superclass relationship and this diagram by definition must "commute".

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.

Constructors

Sub (a => Dict b) 

Instances

Instances details
Category (:-)

Possible since GHC 7.8, when Category was made polykinded.

Instance details

Defined in Data.Constraint

Methods

id :: forall (a :: k). a :- a #

(.) :: forall (b :: k) (c :: k) (a :: k). (b :- c) -> (a :- b) -> a :- c #

() :=> (Show (a :- b)) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show (a :- b) #

() :=> (Eq (a :- b)) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Eq (a :- b) #

() :=> (Ord (a :- b)) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Ord (a :- b) #

a => HasDict b (a :- b) 
Instance details

Defined in Data.Constraint

Methods

evidence :: (a :- b) -> Dict b #

(Typeable p, Typeable q, p, q) => Data (p :- q) 
Instance details

Defined in Data.Constraint

Methods

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) 
Instance details

Defined in Data.Constraint

Methods

showsPrec :: Int -> (a :- b) -> ShowS #

show :: (a :- b) -> String #

showList :: [a :- b] -> ShowS #

a => NFData (a :- b) 
Instance details

Defined in Data.Constraint

Methods

rnf :: (a :- b) -> () #

Eq (a :- b)

Assumes IncoherentInstances doesn't exist.

Instance details

Defined in Data.Constraint

Methods

(==) :: (a :- b) -> (a :- b) -> Bool #

(/=) :: (a :- b) -> (a :- b) -> Bool #

Ord (a :- b)

Assumes IncoherentInstances doesn't exist.

Instance details

Defined in Data.Constraint

Methods

compare :: (a :- b) -> (a :- b) -> Ordering #

(<) :: (a :- b) -> (a :- b) -> Bool #

(<=) :: (a :- b) -> (a :- b) -> Bool #

(>) :: (a :- b) -> (a :- b) -> Bool #

(>=) :: (a :- b) -> (a :- b) -> Bool #

max :: (a :- b) -> (a :- b) -> a :- b #

min :: (a :- b) -> (a :- b) -> a :- b #

data Dict a where #

Values of type Dict p capture a dictionary for a constraint of type p.

e.g.

Dict :: Dict (Eq Int)

captures a dictionary that proves we have an:

instance Eq Int

Pattern matching on the Dict constructor will bring this instance into scope.

Constructors

Dict :: forall a. a => Dict a 

Instances

Instances details
() :=> (Semigroup (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Semigroup (Dict a) #

() :=> (Show (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show (Dict a) #

() :=> (Eq (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Eq (Dict a) #

() :=> (Ord (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Ord (Dict a) #

a :=> (Monoid (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: a :- Monoid (Dict a) #

a :=> (Bounded (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: a :- Bounded (Dict a) #

a :=> (Enum (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: a :- Enum (Dict a) #

a :=> (Read (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: a :- Read (Dict a) #

HasDict a (Dict a) 
Instance details

Defined in Data.Constraint

Methods

evidence :: Dict a -> Dict a #

c => Arbitrary (Dict c) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

arbitrary :: Gen (Dict c) #

shrink :: Dict c -> [Dict c] #

(Typeable p, p) => Data (Dict p) 
Instance details

Defined in Data.Constraint

Methods

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) 
Instance details

Defined in Data.Constraint

Methods

mempty :: Dict a #

mappend :: Dict a -> Dict a -> Dict a #

mconcat :: [Dict a] -> Dict a #

Semigroup (Dict a) 
Instance details

Defined in Data.Constraint

Methods

(<>) :: Dict a -> Dict a -> Dict a #

sconcat :: NonEmpty (Dict a) -> Dict a #

stimes :: Integral b => b -> Dict a -> Dict a #

a => Bounded (Dict a) 
Instance details

Defined in Data.Constraint

Methods

minBound :: Dict a #

maxBound :: Dict a #

a => Enum (Dict a) 
Instance details

Defined in Data.Constraint

Methods

succ :: Dict a -> Dict a #

pred :: Dict a -> Dict a #

toEnum :: Int -> Dict a #

fromEnum :: Dict a -> Int #

enumFrom :: Dict a -> [Dict a] #

enumFromThen :: Dict a -> Dict a -> [Dict a] #

enumFromTo :: Dict a -> Dict a -> [Dict a] #

enumFromThenTo :: Dict a -> Dict a -> Dict a -> [Dict a] #

a => Read (Dict a) 
Instance details

Defined in Data.Constraint

Show (Dict a) 
Instance details

Defined in Data.Constraint

Methods

showsPrec :: Int -> Dict a -> ShowS #

show :: Dict a -> String #

showList :: [Dict a] -> ShowS #

NFData (Dict c) 
Instance details

Defined in Data.Constraint

Methods

rnf :: Dict c -> () #

Eq (Dict a) 
Instance details

Defined in Data.Constraint

Methods

(==) :: Dict a -> Dict a -> Bool #

(/=) :: Dict a -> Dict a -> Bool #

Ord (Dict a) 
Instance details

Defined in Data.Constraint

Methods

compare :: Dict a -> Dict a -> Ordering #

(<) :: Dict a -> Dict a -> Bool #

(<=) :: Dict a -> Dict a -> Bool #

(>) :: Dict a -> Dict a -> Bool #

(>=) :: Dict a -> Dict a -> Bool #

max :: Dict a -> Dict a -> Dict a #

min :: Dict a -> Dict a -> Dict a #

data Proxy (t :: k) #

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, Proxy :: Proxy a is a safer alternative to the undefined :: a idiom.

>>> 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

Constructors

Proxy 

Instances

Instances details
Generic1 (Proxy :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type #

Methods

from1 :: forall (a :: k0). Proxy a -> Rep1 Proxy a #

to1 :: forall (a :: k0). Rep1 Proxy a -> Proxy a #

Foldable (Proxy :: TYPE LiftedRep -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

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 #

toList :: Proxy a -> [a] #

null :: Proxy a -> Bool #

length :: Proxy a -> Int #

elem :: Eq a => a -> Proxy a -> Bool #

maximum :: Ord a => Proxy a -> a #

minimum :: Ord a => Proxy a -> a #

sum :: Num a => Proxy a -> a #

product :: Num a => Proxy a -> a #

Eq1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Proxy a -> Proxy b -> Bool #

Ord1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Proxy a -> Proxy b -> Ordering #

Read1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a] #

Show1 (Proxy :: TYPE LiftedRep -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy a] -> ShowS #

Traversable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Proxy a -> f (Proxy b) #

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) #

mapM :: Monad m => (a -> m b) -> Proxy a -> m (Proxy b) #

sequence :: Monad m => Proxy (m a) -> m (Proxy a) #

Alternative (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

empty :: Proxy a #

(<|>) :: Proxy a -> Proxy a -> Proxy a #

some :: Proxy a -> Proxy [a] #

many :: Proxy a -> Proxy [a] #

Applicative (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure :: a -> Proxy a #

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b #

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c #

(*>) :: Proxy a -> Proxy b -> Proxy b #

(<*) :: Proxy a -> Proxy b -> Proxy a #

Functor (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

fmap :: (a -> b) -> Proxy a -> Proxy b #

(<$) :: a -> Proxy b -> Proxy a #

Monad (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b #

(>>) :: Proxy a -> Proxy b -> Proxy b #

return :: a -> Proxy a #

MonadPlus (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a #

mplus :: Proxy a -> Proxy a -> Proxy a #

Hashable1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Proxy a -> Int #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Bounded (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succ :: Proxy s -> Proxy s #

pred :: Proxy s -> Proxy s #

toEnum :: Int -> Proxy s #

fromEnum :: Proxy s -> Int #

enumFrom :: Proxy s -> [Proxy s] #

enumFromThen :: Proxy s -> Proxy s -> [Proxy s] #

enumFromTo :: Proxy s -> Proxy s -> [Proxy s] #

enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] #

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] #

index :: (Proxy s, Proxy s) -> Proxy s -> Int #

unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int #

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool #

rangeSize :: (Proxy s, Proxy s) -> Int #

unsafeRangeSize :: (Proxy s, Proxy s) -> Int #

Read (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(==) :: Proxy s -> Proxy s -> Bool #

(/=) :: Proxy s -> Proxy s -> Bool #

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering #

(<) :: Proxy s -> Proxy s -> Bool #

(<=) :: Proxy s -> Proxy s -> Bool #

(>) :: Proxy s -> Proxy s -> Bool #

(>=) :: Proxy s -> Proxy s -> Bool #

max :: Proxy s -> Proxy s -> Proxy s #

min :: Proxy s -> Proxy s -> Proxy s #

Hashable (Proxy a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Proxy a -> Int #

hash :: Proxy a -> Int #

type Rep1 (Proxy :: k -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type))
type Rep (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type))

class Arbitrary a #

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.

Minimal complete definition

arbitrary

Instances

Instances details
Arbitrary ASCIIString 
Instance details

Defined in Test.QuickCheck.Modifiers

Arbitrary PrintableString 
Instance details

Defined in Test.QuickCheck.Modifiers

Arbitrary UnicodeString 
Instance details

Defined in Test.QuickCheck.Modifiers

Arbitrary A 
Instance details

Defined in Test.QuickCheck.Poly

Methods

arbitrary :: Gen A #

shrink :: A -> [A] #

Arbitrary B 
Instance details

Defined in Test.QuickCheck.Poly

Methods

arbitrary :: Gen B #

shrink :: B -> [B] #

Arbitrary C 
Instance details

Defined in Test.QuickCheck.Poly

Methods

arbitrary :: Gen C #

shrink :: C -> [C] #

Arbitrary OrdA 
Instance details

Defined in Test.QuickCheck.Poly

Methods

arbitrary :: Gen OrdA #

shrink :: OrdA -> [OrdA] #

Arbitrary OrdB 
Instance details

Defined in Test.QuickCheck.Poly

Methods

arbitrary :: Gen OrdB #

shrink :: OrdB -> [OrdB] #

Arbitrary OrdC 
Instance details

Defined in Test.QuickCheck.Poly

Methods

arbitrary :: Gen OrdC #

shrink :: OrdC -> [OrdC] #

Arbitrary QCGen 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen QCGen #

shrink :: QCGen -> [QCGen] #

Arbitrary All 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen All #

shrink :: All -> [All] #

Arbitrary Any 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Any #

shrink :: Any -> [Any] #

Arbitrary Version

Generates Version with non-empty non-negative versionBranch, and empty versionTags

Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CChar 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen CChar #

shrink :: CChar -> [CChar] #

Arbitrary CClock 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CDouble 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CFloat 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CInt 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen CInt #

shrink :: CInt -> [CInt] #

Arbitrary CIntMax 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CIntPtr 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CLLong 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CLong 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen CLong #

shrink :: CLong -> [CLong] #

Arbitrary CPtrdiff 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CSChar 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CSUSeconds 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CShort 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CSigAtomic 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CSize 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen CSize #

shrink :: CSize -> [CSize] #

Arbitrary CTime 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen CTime #

shrink :: CTime -> [CTime] #

Arbitrary CUChar 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CUInt 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen CUInt #

shrink :: CUInt -> [CUInt] #

Arbitrary CUIntMax 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CUIntPtr 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CULLong 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CULong 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CUSeconds 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CUShort 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CWchar 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary ExitCode 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Newline 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary NewlineMode 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Int16 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Int16 #

shrink :: Int16 -> [Int16] #

Arbitrary Int32 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Int32 #

shrink :: Int32 -> [Int32] #

Arbitrary Int64 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Int64 #

shrink :: Int64 -> [Int64] #

Arbitrary Int8 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Int8 #

shrink :: Int8 -> [Int8] #

Arbitrary Word16 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Word32 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Word64 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Word8 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Word8 #

shrink :: Word8 -> [Word8] #

Arbitrary IntSet 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Ordering 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Integer 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary () 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen () #

shrink :: () -> [()] #

Arbitrary Bool 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Bool #

shrink :: Bool -> [Bool] #

Arbitrary Char 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Char #

shrink :: Char -> [Char] #

Arbitrary Double 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Float 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Float #

shrink :: Float -> [Float] #

Arbitrary Int 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Int #

shrink :: Int -> [Int] #

Arbitrary Word 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Word #

shrink :: Word -> [Word] #

Arbitrary a => Arbitrary (Blind a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Blind a) #

shrink :: Blind a -> [Blind a] #

Arbitrary a => Arbitrary (Fixed a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Fixed a) #

shrink :: Fixed a -> [Fixed a] #

Arbitrary a => Arbitrary (InfiniteList a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Arbitrary a => Arbitrary (InfiniteListInternalData a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (InfiniteListInternalData a) #

shrink :: InfiniteListInternalData a -> [InfiniteListInternalData a] #

(Integral a, Bounded a) => Arbitrary (Large a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Large a) #

shrink :: Large a -> [Large a] #

(Num a, Ord a, Arbitrary a) => Arbitrary (Negative a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Negative a) #

shrink :: Negative a -> [Negative a] #

Arbitrary a => Arbitrary (NonEmptyList a) 
Instance details

Defined in Test.QuickCheck.Modifiers

(Num a, Ord a, Arbitrary a) => Arbitrary (NonNegative a) 
Instance details

Defined in Test.QuickCheck.Modifiers

(Num a, Ord a, Arbitrary a) => Arbitrary (NonPositive a) 
Instance details

Defined in Test.QuickCheck.Modifiers

(Num a, Eq a, Arbitrary a) => Arbitrary (NonZero a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (NonZero a) #

shrink :: NonZero a -> [NonZero a] #

(Ord a, Arbitrary a) => Arbitrary (OrderedList a) 
Instance details

Defined in Test.QuickCheck.Modifiers

(Num a, Ord a, Arbitrary a) => Arbitrary (Positive a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Positive a) #

shrink :: Positive a -> [Positive a] #

Arbitrary a => Arbitrary (Shrink2 a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Shrink2 a) #

shrink :: Shrink2 a -> [Shrink2 a] #

Integral a => Arbitrary (Small a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Small a) #

shrink :: Small a -> [Small a] #

Arbitrary a => Arbitrary (Smart a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Smart a) #

shrink :: Smart a -> [Smart a] #

(Arbitrary a, Ord a) => Arbitrary (SortedList a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Arbitrary a => Arbitrary (ZipList a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (ZipList a) #

shrink :: ZipList a -> [ZipList a] #

Arbitrary a => Arbitrary (Complex a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Complex a) #

shrink :: Complex a -> [Complex a] #

Arbitrary a => Arbitrary (Identity a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Identity a) #

shrink :: Identity a -> [Identity a] #

Arbitrary a => Arbitrary (First a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (First a) #

shrink :: First a -> [First a] #

Arbitrary a => Arbitrary (Last a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Last a) #

shrink :: Last a -> [Last a] #

Arbitrary a => Arbitrary (Dual a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Dual a) #

shrink :: Dual a -> [Dual a] #

(Arbitrary a, CoArbitrary a) => Arbitrary (Endo a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Endo a) #

shrink :: Endo a -> [Endo a] #

Arbitrary a => Arbitrary (Product a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Product a) #

shrink :: Product a -> [Product a] #

Arbitrary a => Arbitrary (Sum a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Sum a) #

shrink :: Sum a -> [Sum a] #

Integral a => Arbitrary (Ratio a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Ratio a) #

shrink :: Ratio a -> [Ratio a] #

c => Arbitrary (Dict c) Source # 
Instance details

Defined in QuickSpec.Internal.Haskell

Methods

arbitrary :: Gen (Dict c) #

shrink :: Dict c -> [Dict c] #

Arbitrary a => Arbitrary (IntMap a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (IntMap a) #

shrink :: IntMap a -> [IntMap a] #

Arbitrary a => Arbitrary (Seq a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Seq a) #

shrink :: Seq a -> [Seq a] #

(Ord a, Arbitrary a) => Arbitrary (Set a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Set a) #

shrink :: Set a -> [Set a] #

Arbitrary a => Arbitrary (Tree a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Tree a) #

shrink :: Tree a -> [Tree a] #

Arbitrary a => Arbitrary (Maybe a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Maybe a) #

shrink :: Maybe a -> [Maybe a] #

Arbitrary a => Arbitrary [a] 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen [a] #

shrink :: [a] -> [[a]] #

(Function a, CoArbitrary a, Arbitrary b) => Arbitrary (a :-> b) 
Instance details

Defined in Test.QuickCheck.Function

Methods

arbitrary :: Gen (a :-> b) #

shrink :: (a :-> b) -> [a :-> b] #

(Function a, CoArbitrary a, Arbitrary b) => Arbitrary (Fun a b) 
Instance details

Defined in Test.QuickCheck.Function

Methods

arbitrary :: Gen (Fun a b) #

shrink :: Fun a b -> [Fun a b] #

(Arbitrary a, ShrinkState s a) => Arbitrary (Shrinking s a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Shrinking s a) #

shrink :: Shrinking s a -> [Shrinking s a] #

Arbitrary (m a) => Arbitrary (WrappedMonad m a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (WrappedMonad m a) #

shrink :: WrappedMonad m a -> [WrappedMonad m a] #

(Arbitrary a, Arbitrary b) => Arbitrary (Either a b) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Either a b) #

shrink :: Either a b -> [Either a b] #

HasResolution a => Arbitrary (Fixed a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Fixed a) #

shrink :: Fixed a -> [Fixed a] #

(Ord k, Arbitrary k, Arbitrary v) => Arbitrary (Map k v) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Map k v) #

shrink :: Map k v -> [Map k v] #

(CoArbitrary a, Arbitrary b) => Arbitrary (a -> b) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (a -> b) #

shrink :: (a -> b) -> [a -> b] #

(Arbitrary a, Arbitrary b) => Arbitrary (a, b) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (a, b) #

shrink :: (a, b) -> [(a, b)] #

Arbitrary (a b c) => Arbitrary (WrappedArrow a b c) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (WrappedArrow a b c) #

shrink :: WrappedArrow a b c -> [WrappedArrow a b c] #

Arbitrary a => Arbitrary (Const a b) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Const a b) #

shrink :: Const a b -> [Const a b] #

Arbitrary (f a) => Arbitrary (Alt f a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Alt f a) #

shrink :: Alt f a -> [Alt f a] #

Arbitrary a => Arbitrary (Constant a b) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Constant a b) #

shrink :: Constant a b -> [Constant a b] #

(Arbitrary a, Arbitrary b, Arbitrary c) => Arbitrary (a, b, c) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (a, b, c) #

shrink :: (a, b, c) -> [(a, b, c)] #

(Arbitrary1 f, Arbitrary1 g, Arbitrary a) => Arbitrary (Product f g a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Product f g a) #

shrink :: Product f g a -> [Product f g a] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => Arbitrary (a, b, c, d) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (a, b, c, d) #

shrink :: (a, b, c, d) -> [(a, b, c, d)] #

(Arbitrary1 f, Arbitrary1 g, Arbitrary a) => Arbitrary (Compose f g a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Compose f g a) #

shrink :: Compose f g a -> [Compose f g a] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e) => Arbitrary (a, b, c, d, e) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (a, b, c, d, e) #

shrink :: (a, b, c, d, e) -> [(a, b, c, d, e)] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f) => Arbitrary (a, b, c, d, e, f) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (a, b, c, d, e, f) #

shrink :: (a, b, c, d, e, f) -> [(a, b, c, d, e, f)] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g) => Arbitrary (a, b, c, d, e, f, g) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (a, b, c, d, e, f, g) #

shrink :: (a, b, c, d, e, f, g) -> [(a, b, c, d, e, f, g)] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h) => Arbitrary (a, b, c, d, e, f, g, h) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (a, b, c, d, e, f, g, h) #

shrink :: (a, b, c, d, e, f, g, h) -> [(a, b, c, d, e, f, g, h)] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h, Arbitrary i) => Arbitrary (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (a, b, c, d, e, f, g, h, i) #

shrink :: (a, b, c, d, e, f, g, h, i) -> [(a, b, c, d, e, f, g, h, i)] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h, Arbitrary i, Arbitrary j) => Arbitrary (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (a, b, c, d, e, f, g, h, i, j) #

shrink :: (a, b, c, d, e, f, g, h, i, j) -> [(a, b, c, d, e, f, g, h, i, j)] #