speculate-0.3.4: discovery of properties about Haskell functions

Copyright(c) 2016-2017 Rudy Matela
License3-Clause BSD (see the file LICENSE)
MaintainerRudy Matela <rudy@matela.com.br>
Safe HaskellNone
LanguageHaskell2010

Test.Speculate

Contents

Description

Speculate: discovery of properties by reasoning from test results

Speculate automatically discovers laws about Haskell functions. Those laws involve:

  • equations, such as id x == x ;
  • inequalities, such as 0 <= x * x ;
  • conditional equations, such as x <= 0 ==> x + abs x == 0 .

_Example:_ the following program prints laws about 0, 1, + and abs.

import Test.Speculate

main :: IO ()
main = speculate args
  { constants =
      [ showConstant (0::Int)
      , showConstant (1::Int)
      , constant "+"   ((+)  :: Int -> Int -> Int)
      , constant "abs" (abs  :: Int -> Int)
      , background
      , constant "<="  ((<=) :: Int -> Int -> Bool)
      ]
  }
Synopsis

Documentation

speculate :: Args -> IO () Source #

Calls Speculate. See the example above (at the top of the file). Its only argument is an Args structure.

data Args Source #

Arguments to Speculate

Constructors

Args 

Fields

args :: Args Source #

Default arguments to Speculate

The constants list

The following combinators are used to build the constants list from Args.

data Expr Source #

An encoded Haskell functional-application expression for use by Speculate.

Instances
Eq Expr Source # 
Instance details

Defined in Test.Speculate.Expr.Core

Methods

(==) :: Expr -> Expr -> Bool #

(/=) :: Expr -> Expr -> Bool #

Ord Expr Source # 
Instance details

Defined in Test.Speculate.Expr.Core

Methods

compare :: Expr -> Expr -> Ordering #

(<) :: Expr -> Expr -> Bool #

(<=) :: Expr -> Expr -> Bool #

(>) :: Expr -> Expr -> Bool #

(>=) :: Expr -> Expr -> Bool #

max :: Expr -> Expr -> Expr #

min :: Expr -> Expr -> Expr #

Show Expr Source # 
Instance details

Defined in Test.Speculate.Expr.Core

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

constant :: Typeable a => String -> a -> Expr Source #

Encode a constant Haskell expression for use by Speculate. It takes a string representation of a value and a value, returning an Expr. Examples:

constant "0" 0
constant "'a'" 'a'
constant "True" True
constant "id" (id :: Int -> Int)
constant "(+)" ((+) :: Int -> Int -> Int)
constant "sort" (sort :: [Bool] -> [Bool])

showConstant :: (Typeable a, Show a) => a -> Expr Source #

A shorthand for constant to be used on values that are Show instances. Examples:

showConstant 0     =  constant "0" 0
showConstant 'a'   =  constant "'a'" 'a' 
showConstant True  =  constant "True" True

hole :: (Listable a, Typeable a) => a -> Expr Source #

(intended for advanced users)

hole (undefined :: Ty) returns a hole of type Ty

By convention, a Hole is a variable named with the empty string.

foreground :: Expr Source #

A special Expr value. When provided on the constants list, makes all the following constants foreground constants.

background :: Expr Source #

A special Expr value. When provided on the constants list, makes all the following constants background constants. Background constants can appear in laws about other constants, but not by themselves.

The instances list

The following combinators are used to build the instances list from Args.

type Instances = [Instance] Source #

Type information needed to Speculate expressions.

ins :: (Typeable a, Listable a, Show a, Eq a, Ord a) => String -> a -> Instances Source #

eq :: (Typeable a, Eq a) => a -> Instances Source #

ord :: (Typeable a, Ord a) => a -> Instances Source #

eqWith :: (Typeable a, Eq a) => (a -> a -> Bool) -> Instances Source #

ordWith :: (Typeable a, Ord a) => (a -> a -> Bool) -> Instances Source #

Misc.

report :: Args -> IO () Source #

uint4 :: UInt4 #

Deprecated. Use word4.

uint3 :: UInt3 #

Deprecated. Use word3.

uint2 :: UInt2 #

Deprecated. Use word2.

uint1 :: UInt1 #

Deprecated. Use word1.

word4 :: Word4 #

Undefined Word4 value.

word3 :: Word3 #

Undefined Word3 value.

word2 :: Word2 #

Undefined Word2 value.

word1 :: Word1 #

Undefined Word1 value.

int4 :: Int4 #

Undefined Int4 value.

int3 :: Int3 #

Undefined Int3 value.

int2 :: Int2 #

Undefined Int2 value.

int1 :: Int1 #

Undefined Int1 value.

nat :: Nat #

Undefined Nat value.

natural :: Natural #

Undefined Natural value.

eith :: a -> b -> Either a b #

Undefined Either value. Uses the types of the given values as the argument types. For use with type binding operators.

mayb :: a -> Maybe a #

Undefined Maybe value. Uses the type of the given value as the argument type. For use with type binding operators.

To check a property with the first argument bound to Maybe Int, do:

check $ prop -:> mayb int

ordering :: Ordering #

Undefined Ordering value.

string :: String #

Undefined String value.

char :: Char #

Undefined Char value.

bool :: Bool #

Undefined Bool value.

rational :: Rational #

Undefined Rational value for use with type binding operators.

double :: Double #

Undefined Double value for use with type binding operators.

float :: Float #

Undefined Float value for use with type binding operators.

integer :: Integer #

Undefined Integer value for use with type binding operators.

check $ (\x y -> x + y == y + x) ->:> integer

int :: Int #

Undefined Int value for use with type binding operators.

check $ (\x y -> x + y == y + x) ->:> int

und :: a #

Shorthand for undefined

(>-) :: a -> b -> a -> b infixr 9 #

Returns an undefined functional value that takes an argument of the type of its first argument and return a value of the type of its second argument.

ty >- ty  =  (undefined :: Ty -> Ty)

Examples:

'a' >- 'b'  =  char >- char  =  (undefined :: Char -> Char)
int >- bool >- int  =  undefined :: Int -> Bool -> Int

(->>>>>>>>>>>>:) :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m) -> m -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m infixl 1 #

Forces the result type of a 12-argument function.

(->>>>>>>>>>>:>) :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m) -> m -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m infixl 1 #

Forces the type of the 12th argument.

(->>>>>>>>>>>:) :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l) -> l -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l infixl 1 #

Forces the result type of a 11-argument function.

(->>>>>>>>>>:>) :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l) -> k -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l infixl 1 #

Forces the type of the 11th argument.

(->>>>>>>>>>:) :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k) -> k -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k infixl 1 #

Forces the result type of a 10-argument function.

(->>>>>>>>>:>) :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k) -> j -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k infixl 1 #

Forces the type of the 10th argument.

(->>>>>>>>>:) :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j) -> j -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j infixl 1 #

Forces the result type of a 9-argument function.

(->>>>>>>>:>) :: (a -> b -> c -> d -> e -> f -> g -> h -> i -> j) -> i -> a -> b -> c -> d -> e -> f -> g -> h -> i -> j infixl 1 #

Forces the 9th argument type.

(->>>>>>>>:) :: (a -> b -> c -> d -> e -> f -> g -> h -> i) -> i -> a -> b -> c -> d -> e -> f -> g -> h -> i infixl 1 #

Forces the result type of a 8-argument function.

(->>>>>>>:>) :: (a -> b -> c -> d -> e -> f -> g -> h -> i) -> h -> a -> b -> c -> d -> e -> f -> g -> h -> i infixl 1 #

Forces the 8th argument type.

(->>>>>>>:) :: (a -> b -> c -> d -> e -> f -> g -> h) -> h -> a -> b -> c -> d -> e -> f -> g -> h infixl 1 #

Forces the result type of a 7-argument function.

(->>>>>>:>) :: (a -> b -> c -> d -> e -> f -> g -> h) -> g -> a -> b -> c -> d -> e -> f -> g -> h infixl 1 #

Forces the 7th argument type.

(->>>>>>:) :: (a -> b -> c -> d -> e -> f -> g) -> g -> a -> b -> c -> d -> e -> f -> g infixl 1 #

Forces the result type of a 6-argument function.

(->>>>>:>) :: (a -> b -> c -> d -> e -> f -> g) -> f -> a -> b -> c -> d -> e -> f -> g infixl 1 #

Forces the 6th argument type.

(->>>>>:) :: (a -> b -> c -> d -> e -> f) -> f -> a -> b -> c -> d -> e -> f infixl 1 #

Forces the result type of a 5-argument function.

(->>>>:>) :: (a -> b -> c -> d -> e -> f) -> e -> a -> b -> c -> d -> e -> f infixl 1 #

Forces the 5th argument type.

(->>>>:) :: (a -> b -> c -> d -> e) -> e -> a -> b -> c -> d -> e infixl 1 #

Forces the result type of a 4-argument function.

(->>>:>) :: (a -> b -> c -> d -> e) -> d -> a -> b -> c -> d -> e infixl 1 #

Forces the 4th argument type.

(->>>:) :: (a -> b -> c -> d) -> d -> a -> b -> c -> d infixl 1 #

Type restricted version of const that forces the result of the result of the result of its first argument to have the same type as the second.

(->>:>) :: (a -> b -> c -> d) -> c -> a -> b -> c -> d infixl 1 #

Type restricted version of const that forces the third argument of its first argument to have the same type as the second.

(->>:) :: (a -> b -> c) -> c -> a -> b -> c infixl 1 #

Type restricted version of const that forces the result of the result of its first argument to have the same type as the second.

f ->>: ty   =  f -: und -> und -> ty  =  f :: a -> b -> Ty

(->:>) :: (a -> b -> c) -> b -> a -> b -> c infixl 1 #

Type restricted version of const that forces the second argument of its first argument to have the same type as the second.

f ->:> ty   =  f -: und -> ty -> und  =  f :: a -> Ty -> b

(->:) :: (a -> b) -> b -> a -> b infixl 1 #

Type restricted version of const that forces the result of its first argument to have the same type as the second.

 f ->: ty  =  f -: und >- ty  =  f :: a -> Ty

(-:>) :: (a -> b) -> a -> a -> b infixl 1 #

Type restricted version of const that forces the argument of its first argument to have the same type as the second:

 f -:> ty  =  f -: ty >- und  =  f :: Ty -> a

Example:

 abs -:> int   =  abs -: int >- und  =  abs :: Int -> Int

(-:) :: a -> a -> a infixl 1 #

Type restricted version of const that forces its first argument to have the same type as the second. A symnonym to asTypeOf:

 value -: ty  =  value :: Ty

Examples:

 10 -: int   =  10 :: Int
 undefined -: 'a' >- 'b'  =  undefined :: Char -> Char

newtype Int1 #

Single-bit signed integers: -1, 0

Constructors

Int1 

Fields

Instances
Bounded Int1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Enum Int1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: Int1 -> Int1 #

pred :: Int1 -> Int1 #

toEnum :: Int -> Int1 #

fromEnum :: Int1 -> Int #

enumFrom :: Int1 -> [Int1] #

enumFromThen :: Int1 -> Int1 -> [Int1] #

enumFromTo :: Int1 -> Int1 -> [Int1] #

enumFromThenTo :: Int1 -> Int1 -> Int1 -> [Int1] #

Eq Int1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Int1 -> Int1 -> Bool #

(/=) :: Int1 -> Int1 -> Bool #

Integral Int1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: Int1 -> Int1 -> Int1 #

rem :: Int1 -> Int1 -> Int1 #

div :: Int1 -> Int1 -> Int1 #

mod :: Int1 -> Int1 -> Int1 #

quotRem :: Int1 -> Int1 -> (Int1, Int1) #

divMod :: Int1 -> Int1 -> (Int1, Int1) #

toInteger :: Int1 -> Integer #

Num Int1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: Int1 -> Int1 -> Int1 #

(-) :: Int1 -> Int1 -> Int1 #

(*) :: Int1 -> Int1 -> Int1 #

negate :: Int1 -> Int1 #

abs :: Int1 -> Int1 #

signum :: Int1 -> Int1 #

fromInteger :: Integer -> Int1 #

Ord Int1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Int1 -> Int1 -> Ordering #

(<) :: Int1 -> Int1 -> Bool #

(<=) :: Int1 -> Int1 -> Bool #

(>) :: Int1 -> Int1 -> Bool #

(>=) :: Int1 -> Int1 -> Bool #

max :: Int1 -> Int1 -> Int1 #

min :: Int1 -> Int1 -> Int1 #

Read Int1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Int1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: Int1 -> Rational #

Show Int1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Int1 -> ShowS #

show :: Int1 -> String #

showList :: [Int1] -> ShowS #

Listable Int1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Int1]] #

list :: [Int1] #

newtype Int2 #

Two-bit signed integers: -2, -1, 0, 1

Constructors

Int2 

Fields

Instances
Bounded Int2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Enum Int2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: Int2 -> Int2 #

pred :: Int2 -> Int2 #

toEnum :: Int -> Int2 #

fromEnum :: Int2 -> Int #

enumFrom :: Int2 -> [Int2] #

enumFromThen :: Int2 -> Int2 -> [Int2] #

enumFromTo :: Int2 -> Int2 -> [Int2] #

enumFromThenTo :: Int2 -> Int2 -> Int2 -> [Int2] #

Eq Int2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Int2 -> Int2 -> Bool #

(/=) :: Int2 -> Int2 -> Bool #

Integral Int2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: Int2 -> Int2 -> Int2 #

rem :: Int2 -> Int2 -> Int2 #

div :: Int2 -> Int2 -> Int2 #

mod :: Int2 -> Int2 -> Int2 #

quotRem :: Int2 -> Int2 -> (Int2, Int2) #

divMod :: Int2 -> Int2 -> (Int2, Int2) #

toInteger :: Int2 -> Integer #

Num Int2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: Int2 -> Int2 -> Int2 #

(-) :: Int2 -> Int2 -> Int2 #

(*) :: Int2 -> Int2 -> Int2 #

negate :: Int2 -> Int2 #

abs :: Int2 -> Int2 #

signum :: Int2 -> Int2 #

fromInteger :: Integer -> Int2 #

Ord Int2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Int2 -> Int2 -> Ordering #

(<) :: Int2 -> Int2 -> Bool #

(<=) :: Int2 -> Int2 -> Bool #

(>) :: Int2 -> Int2 -> Bool #

(>=) :: Int2 -> Int2 -> Bool #

max :: Int2 -> Int2 -> Int2 #

min :: Int2 -> Int2 -> Int2 #

Read Int2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Int2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: Int2 -> Rational #

Show Int2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Int2 -> ShowS #

show :: Int2 -> String #

showList :: [Int2] -> ShowS #

Listable Int2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Int2]] #

list :: [Int2] #

newtype Int3 #

Three-bit signed integers: -4, -3, -2, -1, 0, 1, 2, 3

Constructors

Int3 

Fields

Instances
Bounded Int3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Enum Int3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: Int3 -> Int3 #

pred :: Int3 -> Int3 #

toEnum :: Int -> Int3 #

fromEnum :: Int3 -> Int #

enumFrom :: Int3 -> [Int3] #

enumFromThen :: Int3 -> Int3 -> [Int3] #

enumFromTo :: Int3 -> Int3 -> [Int3] #

enumFromThenTo :: Int3 -> Int3 -> Int3 -> [Int3] #

Eq Int3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Int3 -> Int3 -> Bool #

(/=) :: Int3 -> Int3 -> Bool #

Integral Int3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: Int3 -> Int3 -> Int3 #

rem :: Int3 -> Int3 -> Int3 #

div :: Int3 -> Int3 -> Int3 #

mod :: Int3 -> Int3 -> Int3 #

quotRem :: Int3 -> Int3 -> (Int3, Int3) #

divMod :: Int3 -> Int3 -> (Int3, Int3) #

toInteger :: Int3 -> Integer #

Num Int3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: Int3 -> Int3 -> Int3 #

(-) :: Int3 -> Int3 -> Int3 #

(*) :: Int3 -> Int3 -> Int3 #

negate :: Int3 -> Int3 #

abs :: Int3 -> Int3 #

signum :: Int3 -> Int3 #

fromInteger :: Integer -> Int3 #

Ord Int3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Int3 -> Int3 -> Ordering #

(<) :: Int3 -> Int3 -> Bool #

(<=) :: Int3 -> Int3 -> Bool #

(>) :: Int3 -> Int3 -> Bool #

(>=) :: Int3 -> Int3 -> Bool #

max :: Int3 -> Int3 -> Int3 #

min :: Int3 -> Int3 -> Int3 #

Read Int3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Int3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: Int3 -> Rational #

Show Int3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Int3 -> ShowS #

show :: Int3 -> String #

showList :: [Int3] -> ShowS #

Listable Int3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Int3]] #

list :: [Int3] #

newtype Int4 #

Four-bit signed integers: -8, -7, -6, -5, -4, -3, -2, -1, 0, 1, 2, 3, 4, 5, 6, 7

Constructors

Int4 

Fields

Instances
Bounded Int4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Enum Int4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: Int4 -> Int4 #

pred :: Int4 -> Int4 #

toEnum :: Int -> Int4 #

fromEnum :: Int4 -> Int #

enumFrom :: Int4 -> [Int4] #

enumFromThen :: Int4 -> Int4 -> [Int4] #

enumFromTo :: Int4 -> Int4 -> [Int4] #

enumFromThenTo :: Int4 -> Int4 -> Int4 -> [Int4] #

Eq Int4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Int4 -> Int4 -> Bool #

(/=) :: Int4 -> Int4 -> Bool #

Integral Int4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: Int4 -> Int4 -> Int4 #

rem :: Int4 -> Int4 -> Int4 #

div :: Int4 -> Int4 -> Int4 #

mod :: Int4 -> Int4 -> Int4 #

quotRem :: Int4 -> Int4 -> (Int4, Int4) #

divMod :: Int4 -> Int4 -> (Int4, Int4) #

toInteger :: Int4 -> Integer #

Num Int4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: Int4 -> Int4 -> Int4 #

(-) :: Int4 -> Int4 -> Int4 #

(*) :: Int4 -> Int4 -> Int4 #

negate :: Int4 -> Int4 #

abs :: Int4 -> Int4 #

signum :: Int4 -> Int4 #

fromInteger :: Integer -> Int4 #

Ord Int4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Int4 -> Int4 -> Ordering #

(<) :: Int4 -> Int4 -> Bool #

(<=) :: Int4 -> Int4 -> Bool #

(>) :: Int4 -> Int4 -> Bool #

(>=) :: Int4 -> Int4 -> Bool #

max :: Int4 -> Int4 -> Int4 #

min :: Int4 -> Int4 -> Int4 #

Read Int4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Int4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: Int4 -> Rational #

Show Int4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Int4 -> ShowS #

show :: Int4 -> String #

showList :: [Int4] -> ShowS #

Listable Int4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Int4]] #

list :: [Int4] #

newtype Word1 #

Single-bit unsigned integer: 0, 1

Constructors

Word1 

Fields

Instances
Bounded Word1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Enum Word1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Eq Word1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Word1 -> Word1 -> Bool #

(/=) :: Word1 -> Word1 -> Bool #

Integral Word1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Num Word1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Ord Word1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Word1 -> Word1 -> Ordering #

(<) :: Word1 -> Word1 -> Bool #

(<=) :: Word1 -> Word1 -> Bool #

(>) :: Word1 -> Word1 -> Bool #

(>=) :: Word1 -> Word1 -> Bool #

max :: Word1 -> Word1 -> Word1 #

min :: Word1 -> Word1 -> Word1 #

Read Word1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Word1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: Word1 -> Rational #

Show Word1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Word1 -> ShowS #

show :: Word1 -> String #

showList :: [Word1] -> ShowS #

Listable Word1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Word1]] #

list :: [Word1] #

newtype Word2 #

Two-bit unsigned integers: 0, 1, 2, 3

Constructors

Word2 

Fields

Instances
Bounded Word2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Enum Word2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Eq Word2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Word2 -> Word2 -> Bool #

(/=) :: Word2 -> Word2 -> Bool #

Integral Word2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Num Word2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Ord Word2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Word2 -> Word2 -> Ordering #

(<) :: Word2 -> Word2 -> Bool #

(<=) :: Word2 -> Word2 -> Bool #

(>) :: Word2 -> Word2 -> Bool #

(>=) :: Word2 -> Word2 -> Bool #

max :: Word2 -> Word2 -> Word2 #

min :: Word2 -> Word2 -> Word2 #

Read Word2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Word2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: Word2 -> Rational #

Show Word2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Word2 -> ShowS #

show :: Word2 -> String #

showList :: [Word2] -> ShowS #

Listable Word2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Word2]] #

list :: [Word2] #

newtype Word3 #

Three-bit unsigned integers: 0, 1, 2, 3, 4, 5, 6, 7

Constructors

Word3 

Fields

Instances
Bounded Word3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Enum Word3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Eq Word3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Word3 -> Word3 -> Bool #

(/=) :: Word3 -> Word3 -> Bool #

Integral Word3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Num Word3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Ord Word3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Word3 -> Word3 -> Ordering #

(<) :: Word3 -> Word3 -> Bool #

(<=) :: Word3 -> Word3 -> Bool #

(>) :: Word3 -> Word3 -> Bool #

(>=) :: Word3 -> Word3 -> Bool #

max :: Word3 -> Word3 -> Word3 #

min :: Word3 -> Word3 -> Word3 #

Read Word3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Word3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: Word3 -> Rational #

Show Word3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Word3 -> ShowS #

show :: Word3 -> String #

showList :: [Word3] -> ShowS #

Listable Word3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Word3]] #

list :: [Word3] #

newtype Word4 #

Four-bit unsigned integers: 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15

Constructors

Word4 

Fields

Instances
Bounded Word4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Enum Word4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Eq Word4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Word4 -> Word4 -> Bool #

(/=) :: Word4 -> Word4 -> Bool #

Integral Word4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Num Word4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Ord Word4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Word4 -> Word4 -> Ordering #

(<) :: Word4 -> Word4 -> Bool #

(<=) :: Word4 -> Word4 -> Bool #

(>) :: Word4 -> Word4 -> Bool #

(>=) :: Word4 -> Word4 -> Bool #

max :: Word4 -> Word4 -> Word4 #

min :: Word4 -> Word4 -> Word4 #

Read Word4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Word4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: Word4 -> Rational #

Show Word4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Word4 -> ShowS #

show :: Word4 -> String #

showList :: [Word4] -> ShowS #

Listable Word4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Word4]] #

list :: [Word4] #

newtype Natural #

Natural numbers (including 0): 0, 1, 2, 3, 4, 5, 6, 7, ...

Internally, this type is represented as an Integer allowing for an infinity of possible values.

Its Enum and Listable instances only produce non-negative values. Negatives can still be generated by negate or subtraction.

Constructors

Natural 

Fields

Instances
Enum Natural 
Instance details

Defined in Test.LeanCheck.Utils.Types

Eq Natural 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Natural -> Natural -> Bool #

(/=) :: Natural -> Natural -> Bool #

Integral Natural 
Instance details

Defined in Test.LeanCheck.Utils.Types

Num Natural 
Instance details

Defined in Test.LeanCheck.Utils.Types

Ord Natural 
Instance details

Defined in Test.LeanCheck.Utils.Types

Read Natural 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Natural 
Instance details

Defined in Test.LeanCheck.Utils.Types

Show Natural 
Instance details

Defined in Test.LeanCheck.Utils.Types

Listable Natural 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Natural]] #

list :: [Natural] #

newtype Nat #

Natural numbers (including 0): 0, 1, 2, 3, 4, 5, 6, 7, ...

Internally, this type is represented as an Int. So, it is limited by the maxBound of Int.

Constructors

Nat 

Fields

Instances
Bounded Nat 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

minBound :: Nat #

maxBound :: Nat #

Enum Nat 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: Nat -> Nat #

pred :: Nat -> Nat #

toEnum :: Int -> Nat #

fromEnum :: Nat -> Int #

enumFrom :: Nat -> [Nat] #

enumFromThen :: Nat -> Nat -> [Nat] #

enumFromTo :: Nat -> Nat -> [Nat] #

enumFromThenTo :: Nat -> Nat -> Nat -> [Nat] #

Eq Nat 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Nat -> Nat -> Bool #

(/=) :: Nat -> Nat -> Bool #

Integral Nat 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: Nat -> Nat -> Nat #

rem :: Nat -> Nat -> Nat #

div :: Nat -> Nat -> Nat #

mod :: Nat -> Nat -> Nat #

quotRem :: Nat -> Nat -> (Nat, Nat) #

divMod :: Nat -> Nat -> (Nat, Nat) #

toInteger :: Nat -> Integer #

Num Nat 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: Nat -> Nat -> Nat #

(-) :: Nat -> Nat -> Nat #

(*) :: Nat -> Nat -> Nat #

negate :: Nat -> Nat #

abs :: Nat -> Nat #

signum :: Nat -> Nat #

fromInteger :: Integer -> Nat #

Ord Nat 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Nat -> Nat -> Ordering #

(<) :: Nat -> Nat -> Bool #

(<=) :: Nat -> Nat -> Bool #

(>) :: Nat -> Nat -> Bool #

(>=) :: Nat -> Nat -> Bool #

max :: Nat -> Nat -> Nat #

min :: Nat -> Nat -> Nat #

Read Nat 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Nat 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: Nat -> Rational #

Show Nat 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Nat -> ShowS #

show :: Nat -> String #

showList :: [Nat] -> ShowS #

Listable Nat 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat]] #

list :: [Nat] #

newtype Nat1 #

Natural numbers modulo 1: 0

Constructors

Nat1 

Fields

Instances
Bounded Nat1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Enum Nat1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: Nat1 -> Nat1 #

pred :: Nat1 -> Nat1 #

toEnum :: Int -> Nat1 #

fromEnum :: Nat1 -> Int #

enumFrom :: Nat1 -> [Nat1] #

enumFromThen :: Nat1 -> Nat1 -> [Nat1] #

enumFromTo :: Nat1 -> Nat1 -> [Nat1] #

enumFromThenTo :: Nat1 -> Nat1 -> Nat1 -> [Nat1] #

Eq Nat1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Nat1 -> Nat1 -> Bool #

(/=) :: Nat1 -> Nat1 -> Bool #

Integral Nat1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: Nat1 -> Nat1 -> Nat1 #

rem :: Nat1 -> Nat1 -> Nat1 #

div :: Nat1 -> Nat1 -> Nat1 #

mod :: Nat1 -> Nat1 -> Nat1 #

quotRem :: Nat1 -> Nat1 -> (Nat1, Nat1) #

divMod :: Nat1 -> Nat1 -> (Nat1, Nat1) #

toInteger :: Nat1 -> Integer #

Num Nat1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: Nat1 -> Nat1 -> Nat1 #

(-) :: Nat1 -> Nat1 -> Nat1 #

(*) :: Nat1 -> Nat1 -> Nat1 #

negate :: Nat1 -> Nat1 #

abs :: Nat1 -> Nat1 #

signum :: Nat1 -> Nat1 #

fromInteger :: Integer -> Nat1 #

Ord Nat1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Nat1 -> Nat1 -> Ordering #

(<) :: Nat1 -> Nat1 -> Bool #

(<=) :: Nat1 -> Nat1 -> Bool #

(>) :: Nat1 -> Nat1 -> Bool #

(>=) :: Nat1 -> Nat1 -> Bool #

max :: Nat1 -> Nat1 -> Nat1 #

min :: Nat1 -> Nat1 -> Nat1 #

Read Nat1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Nat1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: Nat1 -> Rational #

Show Nat1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Nat1 -> ShowS #

show :: Nat1 -> String #

showList :: [Nat1] -> ShowS #

Listable Nat1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat1]] #

list :: [Nat1] #

newtype Nat2 #

Natural numbers modulo 2: 0, 1

Constructors

Nat2 

Fields

Instances
Bounded Nat2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Enum Nat2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: Nat2 -> Nat2 #

pred :: Nat2 -> Nat2 #

toEnum :: Int -> Nat2 #

fromEnum :: Nat2 -> Int #

enumFrom :: Nat2 -> [Nat2] #

enumFromThen :: Nat2 -> Nat2 -> [Nat2] #

enumFromTo :: Nat2 -> Nat2 -> [Nat2] #

enumFromThenTo :: Nat2 -> Nat2 -> Nat2 -> [Nat2] #

Eq Nat2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Nat2 -> Nat2 -> Bool #

(/=) :: Nat2 -> Nat2 -> Bool #

Integral Nat2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: Nat2 -> Nat2 -> Nat2 #

rem :: Nat2 -> Nat2 -> Nat2 #

div :: Nat2 -> Nat2 -> Nat2 #

mod :: Nat2 -> Nat2 -> Nat2 #

quotRem :: Nat2 -> Nat2 -> (Nat2, Nat2) #

divMod :: Nat2 -> Nat2 -> (Nat2, Nat2) #

toInteger :: Nat2 -> Integer #

Num Nat2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: Nat2 -> Nat2 -> Nat2 #

(-) :: Nat2 -> Nat2 -> Nat2 #

(*) :: Nat2 -> Nat2 -> Nat2 #

negate :: Nat2 -> Nat2 #

abs :: Nat2 -> Nat2 #

signum :: Nat2 -> Nat2 #

fromInteger :: Integer -> Nat2 #

Ord Nat2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Nat2 -> Nat2 -> Ordering #

(<) :: Nat2 -> Nat2 -> Bool #

(<=) :: Nat2 -> Nat2 -> Bool #

(>) :: Nat2 -> Nat2 -> Bool #

(>=) :: Nat2 -> Nat2 -> Bool #

max :: Nat2 -> Nat2 -> Nat2 #

min :: Nat2 -> Nat2 -> Nat2 #

Read Nat2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Nat2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: Nat2 -> Rational #

Show Nat2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Nat2 -> ShowS #

show :: Nat2 -> String #

showList :: [Nat2] -> ShowS #

Listable Nat2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat2]] #

list :: [Nat2] #

newtype Nat3 #

Natural numbers modulo 3: 0, 1, 2

Constructors

Nat3 

Fields

Instances
Bounded Nat3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Enum Nat3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: Nat3 -> Nat3 #

pred :: Nat3 -> Nat3 #

toEnum :: Int -> Nat3 #

fromEnum :: Nat3 -> Int #

enumFrom :: Nat3 -> [Nat3] #

enumFromThen :: Nat3 -> Nat3 -> [Nat3] #

enumFromTo :: Nat3 -> Nat3 -> [Nat3] #

enumFromThenTo :: Nat3 -> Nat3 -> Nat3 -> [Nat3] #

Eq Nat3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Nat3 -> Nat3 -> Bool #

(/=) :: Nat3 -> Nat3 -> Bool #

Integral Nat3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: Nat3 -> Nat3 -> Nat3 #

rem :: Nat3 -> Nat3 -> Nat3 #

div :: Nat3 -> Nat3 -> Nat3 #

mod :: Nat3 -> Nat3 -> Nat3 #

quotRem :: Nat3 -> Nat3 -> (Nat3, Nat3) #

divMod :: Nat3 -> Nat3 -> (Nat3, Nat3) #

toInteger :: Nat3 -> Integer #

Num Nat3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: Nat3 -> Nat3 -> Nat3 #

(-) :: Nat3 -> Nat3 -> Nat3 #

(*) :: Nat3 -> Nat3 -> Nat3 #

negate :: Nat3 -> Nat3 #

abs :: Nat3 -> Nat3 #

signum :: Nat3 -> Nat3 #

fromInteger :: Integer -> Nat3 #

Ord Nat3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Nat3 -> Nat3 -> Ordering #

(<) :: Nat3 -> Nat3 -> Bool #

(<=) :: Nat3 -> Nat3 -> Bool #

(>) :: Nat3 -> Nat3 -> Bool #

(>=) :: Nat3 -> Nat3 -> Bool #

max :: Nat3 -> Nat3 -> Nat3 #

min :: Nat3 -> Nat3 -> Nat3 #

Read Nat3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Nat3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: Nat3 -> Rational #

Show Nat3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Nat3 -> ShowS #

show :: Nat3 -> String #

showList :: [Nat3] -> ShowS #

Listable Nat3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat3]] #

list :: [Nat3] #

newtype Nat4 #

Natural numbers modulo 4: 0, 1, 2, 3

Constructors

Nat4 

Fields

Instances
Bounded Nat4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Enum Nat4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: Nat4 -> Nat4 #

pred :: Nat4 -> Nat4 #

toEnum :: Int -> Nat4 #

fromEnum :: Nat4 -> Int #

enumFrom :: Nat4 -> [Nat4] #

enumFromThen :: Nat4 -> Nat4 -> [Nat4] #

enumFromTo :: Nat4 -> Nat4 -> [Nat4] #

enumFromThenTo :: Nat4 -> Nat4 -> Nat4 -> [Nat4] #

Eq Nat4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Nat4 -> Nat4 -> Bool #

(/=) :: Nat4 -> Nat4 -> Bool #

Integral Nat4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: Nat4 -> Nat4 -> Nat4 #

rem :: Nat4 -> Nat4 -> Nat4 #

div :: Nat4 -> Nat4 -> Nat4 #

mod :: Nat4 -> Nat4 -> Nat4 #

quotRem :: Nat4 -> Nat4 -> (Nat4, Nat4) #

divMod :: Nat4 -> Nat4 -> (Nat4, Nat4) #

toInteger :: Nat4 -> Integer #

Num Nat4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: Nat4 -> Nat4 -> Nat4 #

(-) :: Nat4 -> Nat4 -> Nat4 #

(*) :: Nat4 -> Nat4 -> Nat4 #

negate :: Nat4 -> Nat4 #

abs :: Nat4 -> Nat4 #

signum :: Nat4 -> Nat4 #

fromInteger :: Integer -> Nat4 #

Ord Nat4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Nat4 -> Nat4 -> Ordering #

(<) :: Nat4 -> Nat4 -> Bool #

(<=) :: Nat4 -> Nat4 -> Bool #

(>) :: Nat4 -> Nat4 -> Bool #

(>=) :: Nat4 -> Nat4 -> Bool #

max :: Nat4 -> Nat4 -> Nat4 #

min :: Nat4 -> Nat4 -> Nat4 #

Read Nat4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Nat4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: Nat4 -> Rational #

Show Nat4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Nat4 -> ShowS #

show :: Nat4 -> String #

showList :: [Nat4] -> ShowS #

Listable Nat4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat4]] #

list :: [Nat4] #

newtype Nat5 #

Natural numbers modulo 5: 0, 1, 2, 3, 4

Constructors

Nat5 

Fields

Instances
Bounded Nat5 
Instance details

Defined in Test.LeanCheck.Utils.Types

Enum Nat5 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: Nat5 -> Nat5 #

pred :: Nat5 -> Nat5 #

toEnum :: Int -> Nat5 #

fromEnum :: Nat5 -> Int #

enumFrom :: Nat5 -> [Nat5] #

enumFromThen :: Nat5 -> Nat5 -> [Nat5] #

enumFromTo :: Nat5 -> Nat5 -> [Nat5] #

enumFromThenTo :: Nat5 -> Nat5 -> Nat5 -> [Nat5] #

Eq Nat5 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Nat5 -> Nat5 -> Bool #

(/=) :: Nat5 -> Nat5 -> Bool #

Integral Nat5 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: Nat5 -> Nat5 -> Nat5 #

rem :: Nat5 -> Nat5 -> Nat5 #

div :: Nat5 -> Nat5 -> Nat5 #

mod :: Nat5 -> Nat5 -> Nat5 #

quotRem :: Nat5 -> Nat5 -> (Nat5, Nat5) #

divMod :: Nat5 -> Nat5 -> (Nat5, Nat5) #

toInteger :: Nat5 -> Integer #

Num Nat5 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: Nat5 -> Nat5 -> Nat5 #

(-) :: Nat5 -> Nat5 -> Nat5 #

(*) :: Nat5 -> Nat5 -> Nat5 #

negate :: Nat5 -> Nat5 #

abs :: Nat5 -> Nat5 #

signum :: Nat5 -> Nat5 #

fromInteger :: Integer -> Nat5 #

Ord Nat5 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Nat5 -> Nat5 -> Ordering #

(<) :: Nat5 -> Nat5 -> Bool #

(<=) :: Nat5 -> Nat5 -> Bool #

(>) :: Nat5 -> Nat5 -> Bool #

(>=) :: Nat5 -> Nat5 -> Bool #

max :: Nat5 -> Nat5 -> Nat5 #

min :: Nat5 -> Nat5 -> Nat5 #

Read Nat5 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Nat5 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: Nat5 -> Rational #

Show Nat5 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Nat5 -> ShowS #

show :: Nat5 -> String #

showList :: [Nat5] -> ShowS #

Listable Nat5 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat5]] #

list :: [Nat5] #

newtype Nat6 #

Natural numbers modulo 6: 0, 1, 2, 3, 4, 5

Constructors

Nat6 

Fields

Instances
Bounded Nat6 
Instance details

Defined in Test.LeanCheck.Utils.Types

Enum Nat6 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: Nat6 -> Nat6 #

pred :: Nat6 -> Nat6 #

toEnum :: Int -> Nat6 #

fromEnum :: Nat6 -> Int #

enumFrom :: Nat6 -> [Nat6] #

enumFromThen :: Nat6 -> Nat6 -> [Nat6] #

enumFromTo :: Nat6 -> Nat6 -> [Nat6] #

enumFromThenTo :: Nat6 -> Nat6 -> Nat6 -> [Nat6] #

Eq Nat6 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Nat6 -> Nat6 -> Bool #

(/=) :: Nat6 -> Nat6 -> Bool #

Integral Nat6 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: Nat6 -> Nat6 -> Nat6 #

rem :: Nat6 -> Nat6 -> Nat6 #

div :: Nat6 -> Nat6 -> Nat6 #

mod :: Nat6 -> Nat6 -> Nat6 #

quotRem :: Nat6 -> Nat6 -> (Nat6, Nat6) #

divMod :: Nat6 -> Nat6 -> (Nat6, Nat6) #

toInteger :: Nat6 -> Integer #

Num Nat6 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: Nat6 -> Nat6 -> Nat6 #

(-) :: Nat6 -> Nat6 -> Nat6 #

(*) :: Nat6 -> Nat6 -> Nat6 #

negate :: Nat6 -> Nat6 #

abs :: Nat6 -> Nat6 #

signum :: Nat6 -> Nat6 #

fromInteger :: Integer -> Nat6 #

Ord Nat6 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Nat6 -> Nat6 -> Ordering #

(<) :: Nat6 -> Nat6 -> Bool #

(<=) :: Nat6 -> Nat6 -> Bool #

(>) :: Nat6 -> Nat6 -> Bool #

(>=) :: Nat6 -> Nat6 -> Bool #

max :: Nat6 -> Nat6 -> Nat6 #

min :: Nat6 -> Nat6 -> Nat6 #

Read Nat6 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Nat6 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: Nat6 -> Rational #

Show Nat6 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Nat6 -> ShowS #

show :: Nat6 -> String #

showList :: [Nat6] -> ShowS #

Listable Nat6 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat6]] #

list :: [Nat6] #

newtype Nat7 #

Natural numbers modulo 7: 0, 1, 2, 3, 4, 5, 6

Constructors

Nat7 

Fields

Instances
Bounded Nat7 
Instance details

Defined in Test.LeanCheck.Utils.Types

Enum Nat7 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: Nat7 -> Nat7 #

pred :: Nat7 -> Nat7 #

toEnum :: Int -> Nat7 #

fromEnum :: Nat7 -> Int #

enumFrom :: Nat7 -> [Nat7] #

enumFromThen :: Nat7 -> Nat7 -> [Nat7] #

enumFromTo :: Nat7 -> Nat7 -> [Nat7] #

enumFromThenTo :: Nat7 -> Nat7 -> Nat7 -> [Nat7] #

Eq Nat7 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: Nat7 -> Nat7 -> Bool #

(/=) :: Nat7 -> Nat7 -> Bool #

Integral Nat7 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: Nat7 -> Nat7 -> Nat7 #

rem :: Nat7 -> Nat7 -> Nat7 #

div :: Nat7 -> Nat7 -> Nat7 #

mod :: Nat7 -> Nat7 -> Nat7 #

quotRem :: Nat7 -> Nat7 -> (Nat7, Nat7) #

divMod :: Nat7 -> Nat7 -> (Nat7, Nat7) #

toInteger :: Nat7 -> Integer #

Num Nat7 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: Nat7 -> Nat7 -> Nat7 #

(-) :: Nat7 -> Nat7 -> Nat7 #

(*) :: Nat7 -> Nat7 -> Nat7 #

negate :: Nat7 -> Nat7 #

abs :: Nat7 -> Nat7 #

signum :: Nat7 -> Nat7 #

fromInteger :: Integer -> Nat7 #

Ord Nat7 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Nat7 -> Nat7 -> Ordering #

(<) :: Nat7 -> Nat7 -> Bool #

(<=) :: Nat7 -> Nat7 -> Bool #

(>) :: Nat7 -> Nat7 -> Bool #

(>=) :: Nat7 -> Nat7 -> Bool #

max :: Nat7 -> Nat7 -> Nat7 #

min :: Nat7 -> Nat7 -> Nat7 #

Read Nat7 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real Nat7 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: Nat7 -> Rational #

Show Nat7 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Nat7 -> ShowS #

show :: Nat7 -> String #

showList :: [Nat7] -> ShowS #

Listable Nat7 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat7]] #

list :: [Nat7] #

type UInt1 = Word1 #

Deprecated. Use Word1.

type UInt2 = Word2 #

Deprecated. Use Word2.

type UInt3 = Word3 #

Deprecated. Use Word3.

type UInt4 = Word4 #

Deprecated. Use Word4.

newtype NoDup a #

Lists without repeated elements.

> take 6 $ list :: [NoDup Nat]
[NoDup [],NoDup [0],NoDup [1],NoDup [0,1],NoDup [1,0],NoDup [2]]

Example, checking the property that nub is an identity:

import Data.List (nub)
> check $ \xs -> nub xs == (xs :: [Int])
*** Failed! Falsifiable (after 3 tests):
[0,0]
> check $ \(NoDup xs) -> nub xs == (xs :: [Int])
+++ OK, passed 200 tests.

Constructors

NoDup [a] 
Instances
Eq a => Eq (NoDup a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

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

Ord a => Ord (NoDup a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: NoDup a -> NoDup a -> Ordering #

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

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

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

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

max :: NoDup a -> NoDup a -> NoDup a #

min :: NoDup a -> NoDup a -> NoDup a #

Read a => Read (NoDup a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Show a => Show (NoDup a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

show :: NoDup a -> String #

showList :: [NoDup a] -> ShowS #

Listable a => Listable (NoDup a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[NoDup a]] #

list :: [NoDup a] #

newtype Bag a #

Lists representing bags (multisets). The Listable tiers enumeration will not have repeated bags.

> take 6 (list :: [Bag Nat])
[Bag [],Bag [0],Bag [0,0],Bag [1],Bag [0,0,0],Bag [0,1]]

See also: bagsOf and bagCons.

Constructors

Bag [a] 
Instances
Eq a => Eq (Bag a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

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

Ord a => Ord (Bag a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Bag a -> Bag a -> Ordering #

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

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

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

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

max :: Bag a -> Bag a -> Bag a #

min :: Bag a -> Bag a -> Bag a #

Read a => Read (Bag a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Show a => Show (Bag a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

show :: Bag a -> String #

showList :: [Bag a] -> ShowS #

Listable a => Listable (Bag a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Bag a]] #

list :: [Bag a] #

newtype Set a #

Lists representing sets. The Listable tiers enumeration will not have repeated sets.

> take 6 (list :: [Set Nat])
[Set [],Set [0],Set [1],Set [0,1],Set [2],Set [0,2]]

Constructors

Set [a] 
Instances
Eq a => Eq (Set a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

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

Ord a => Ord (Set a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Set a -> Set a -> Ordering #

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

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

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

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

max :: Set a -> Set a -> Set a #

min :: Set a -> Set a -> Set a #

Read a => Read (Set a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Show a => Show (Set a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

show :: Set a -> String #

showList :: [Set a] -> ShowS #

Listable a => Listable (Set a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Set a]] #

list :: [Set a] #

newtype Map a b #

Lists of pairs representing maps. The Listable tiers enumeration will not have repeated maps.

> take 6 (list :: [Map Nat Nat])
[Map [],Map [(0,0)],Map [(0,1)],Map [(1,0)],Map [(0,2)],Map [(1,1)]]

Constructors

Map [(a, b)] 
Instances
(Eq a, Eq b) => Eq (Map a b) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

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

(Ord a, Ord b) => Ord (Map a b) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Map a b -> Map a b -> Ordering #

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

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

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

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

max :: Map a b -> Map a b -> Map a b #

min :: Map a b -> Map a b -> Map a b #

(Read a, Read b) => Read (Map a b) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

readsPrec :: Int -> ReadS (Map a b) #

readList :: ReadS [Map a b] #

readPrec :: ReadPrec (Map a b) #

readListPrec :: ReadPrec [Map a b] #

(Show a, Show b) => Show (Map a b) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> Map a b -> ShowS #

show :: Map a b -> String #

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

(Listable a, Listable b) => Listable (Map a b) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Map a b]] #

list :: [Map a b] #

newtype X a #

X type to be wrapped around integer types for an e-X-treme integer enumeration. See the Listable instance for X. Use X when testing properties about overflows and the like:

> check $ \x -> x + 1 > (x :: Int)
+++ OK, passed 200 tests.
> check $ \(X x) -> x + 1 > (x :: Int)
+++ Failed! Falsifiable (after 4 tests):
9223372036854775807

Constructors

X 

Fields

Instances
Eq a => Eq (X a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

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

Ord a => Ord (X a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: X a -> X a -> Ordering #

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

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

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

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

max :: X a -> X a -> X a #

min :: X a -> X a -> X a #

Show a => Show (X a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

show :: X a -> String #

showList :: [X a] -> ShowS #

(Integral a, Bounded a) => Listable (X a)

Extremily large integers are intercalated with small integers.

list :: [X Int] = map X
  [ 0, 1, -1, maxBound,   minBound
     , 2, -2, maxBound-1, minBound+1
     , 3, -3, maxBound-2, minBound+2
     , ... ]
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[X a]] #

list :: [X a] #

newtype Xs a #

Wrap around lists of integers for an enumeration containing e-X-treme integer values.

> check $ \xs -> all (>=0) xs ==> sum (take 1 xs :: [Int]) <= sum xs
+++ OK, passed 200 tests.
> check $ \(Xs xs) -> all (>=0) xs ==> sum (take 1 xs :: [Int]) <= sum xs
*** Failed! Falsifiable (after 56 tests):
[1,9223372036854775807]

Constructors

Xs [a] 
Instances
Eq a => Eq (Xs a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

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

Ord a => Ord (Xs a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: Xs a -> Xs a -> Ordering #

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

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

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

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

max :: Xs a -> Xs a -> Xs a #

min :: Xs a -> Xs a -> Xs a #

Read a => Read (Xs a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Show a => Show (Xs a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

show :: Xs a -> String #

showList :: [Xs a] -> ShowS #

(Integral a, Bounded a) => Listable (Xs a)

Lists with elements of the X type.

Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Xs a]] #

list :: [Xs a] #

(|=) :: (a -> Bool) -> a -> Bool infixl 4 #

See =|

(=|) :: Eq a => [a] -> Int -> [a] -> Bool infixl 4 #

Check if two lists are equal for n values. This operator has the same fixity of ==.

xs =| n |= ys  =  take n xs == take n ys
[1,2,3,4,5] =| 2 |= [1,2,4,8,16] -- > True
[1,2,3,4,5] =| 3 |= [1,2,4,8,16] -- > False

($=) :: (a -> Bool) -> a -> Bool infixl 4 #

See =$

(=$) :: Eq b => a -> (a -> b) -> a -> Bool infixl 4 #

Equal under, a ternary operator with the same fixity as ==.

x =$ f $= y  =  f x = f y
[1,2,3,4,5] =$  take 2    $= [1,2,4,8,16] -- > True
[1,2,3,4,5] =$  take 3    $= [1,2,4,8,16] -- > False
    [1,2,3] =$    sort    $= [3,2,1]      -- > True
         42 =$ (`mod` 10) $= 16842        -- > True
         42 =$ (`mod`  9) $= 16842        -- > False
        'a' =$  isLetter  $= 'b'          -- > True
        'a' =$  isLetter  $= '1'          -- > False

okNum :: (Eq a, Num a) => a -> a -> a -> Bool #

okEqOrd :: (Eq a, Ord a) => a -> a -> a -> Bool #

okOrd :: Ord a => a -> a -> a -> Bool #

okEq :: Eq a => a -> a -> a -> Bool #

neverIdentity :: Eq a => (a -> a) -> a -> Bool #

Is the given function never an identity? f x /= x

holds n $ neverIdentity not
fails n $ neverIdentity negate   -- yes, fails: negate 0 == 0, hah!

Note: this is not the same as not being an identity.

identity :: Eq a => (a -> a) -> a -> Bool #

Is the given function an identity? f x == x

holds n $ identity (+0)
holds n $ identity (sort :: [()])
holds n $ identity (not . not)

idempotent :: Eq a => (a -> a) -> a -> Bool #

Is the given function idempotent? f (f x) == x

holds n $ idempotent abs
holds n $ idempotent sort
fails n $ idempotent negate

strictTotalOrder :: Eq a => (a -> a -> Bool) -> a -> a -> a -> Bool #

Is the given binary relation a strict total order?

totalOrder :: Eq a => (a -> a -> Bool) -> a -> a -> a -> Bool #

Is the given binary relation a total order?

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

Is the given binary relation a strict partial order? Is the given relation irreflexive, asymmetric and transitive?

partialOrder :: Eq a => (a -> a -> Bool) -> a -> a -> a -> Bool #

Is the given binary relation a partial order? Is the given relation reflexive, antisymmetric and transitive?

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

Is the given binary relation an equivalence? Is the given relation reflexive, symmetric and transitive?

> check (equivalence (==) :: Int -> Int -> Int -> Bool)
+++ OK, passed 200 tests.
> check (equivalence (<=) :: Int -> Int -> Int -> Bool)
*** Failed! Falsifiable (after 3 tests):
0 1 0

Or, using Test.LeanCheck.Utils.TypeBinding:

> check $ equivalence (<=) -:> int
*** Failed! Falsifiable (after 3 tests):
0 1 0

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

Is a given relation asymmetric? Not to be confused with "not symmetric" and "antissymetric".

antisymmetric :: Eq a => (a -> a -> Bool) -> a -> a -> Bool #

Is a given relation antisymmetric? Not to be confused with "not symmetric" and "assymetric".

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

Is a given relation symmetric? This is a type-restricted version of commutative.

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

An element is never related to itself.

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

An element is always related to itself.

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

Is a given relation transitive?

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

Are two operators flipped versions of each other?

holds n $ (<)  `symmetric2` (>)  -:> int
holds n $ (<=) `symmetric2` (>=) -:> int
fails n $ (<)  `symmetric2` (>=) -:> int
fails n $ (<=) `symmetric2` (>)  -:> int

distributive :: Eq a => (a -> a -> a) -> (a -> a -> a) -> a -> a -> a -> Bool #

Does the first operator, distributes over the second?

associative :: Eq a => (a -> a -> a) -> a -> a -> a -> Bool #

Is a given operator associative? x + (y + z) = (x + y) + z

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

Is a given operator commutative? x + y = y + x

holds n $ commutative (+)
fails n $ commutative union  -- union [] [0,0] = [0]

(||||) :: (a -> b -> Bool) -> (a -> b -> Bool) -> a -> b -> Bool infixr 2 #

(|||) :: (a -> Bool) -> (a -> Bool) -> a -> Bool infixr 2 #

(&&&&) :: (a -> b -> Bool) -> (a -> b -> Bool) -> a -> b -> Bool infixr 3 #

(&&&) :: (a -> Bool) -> (a -> Bool) -> a -> Bool infixr 3 #

(====) :: Eq c => (a -> b -> c) -> (a -> b -> c) -> a -> b -> Bool infix 4 #

(===) :: Eq b => (a -> b) -> (a -> b) -> a -> Bool infix 4 #

countsOn :: Eq b => (a -> b) -> [a] -> [(b, Int)] #

countsBy :: (a -> a -> Bool) -> [a] -> [(a, Int)] #

counts :: Eq a => [a] -> [(a, Int)] #

classifyOn :: Eq b => (a -> b) -> [a] -> [[a]] #

classifyBy :: (a -> a -> Bool) -> [a] -> [[a]] #

classify :: Eq a => [a] -> [[a]] #

conditionStatsT :: Listable a => Int -> [(String, a -> Bool)] -> IO () #

conditionStats :: Listable a => Int -> [(String, a -> Bool)] -> IO () #

classStatsT :: (Listable a, Show b) => Int -> (a -> b) -> IO () #

classStats :: (Listable a, Show b) => Int -> (a -> b) -> IO () #