Copyright | (c) 2015-2020 Rudy Matela |
---|---|
License | 3-Clause BSD (see the file LICENSE) |
Maintainer | Rudy Matela <rudy@matela.com.br> |
Safe Haskell | None |
Language | Haskell2010 |
This module is part of LeanCheck, a simple enumerative property-based testing library.
Types to aid in property-based testing.
Synopsis
- newtype Int1 = Int1 {}
- newtype Int2 = Int2 {}
- newtype Int3 = Int3 {}
- newtype Int4 = Int4 {}
- newtype Word1 = Word1 {}
- newtype Word2 = Word2 {}
- newtype Word3 = Word3 {}
- newtype Word4 = Word4 {}
- newtype Nat = Nat {}
- newtype Nat1 = Nat1 {}
- newtype Nat2 = Nat2 {}
- newtype Nat3 = Nat3 {}
- newtype Nat4 = Nat4 {}
- newtype Nat5 = Nat5 {}
- newtype Nat6 = Nat6 {}
- newtype Nat7 = Nat7 {}
- newtype Natural = Natural {}
- type UInt1 = Word1
- type UInt2 = Word2
- type UInt3 = Word3
- type UInt4 = Word4
- newtype X a = X {
- unX :: a
- newtype Xs a = Xs [a]
- newtype NoDup a = NoDup [a]
- newtype Bag a = Bag [a]
- newtype Set a = Set [a]
- newtype Map a b = Map [(a, b)]
- data Space = Space {}
- data Lower = Lower {}
- data Upper = Upper {}
- data Alpha = Alpha {}
- data Digit = Digit {}
- data AlphaNum = AlphaNum {
- unAlphaNum :: Char
- data Letter = Letter {}
- data Spaces = Spaces {}
- data Lowers = Lowers {}
- data Uppers = Uppers {}
- data Alphas = Alphas {}
- data Digits = Digits {}
- data AlphaNums = AlphaNums {}
- data Letters = Letters {}
- data A
- data B
- data C
- data D
- data E
- data F
Integer types
Small-width integer types to aid in property-based testing. Sometimes it is useful to limit the possibilities of enumerated values when testing polymorphic functions, these types allow that.
The signed integer types IntN
are of limited bit width N
bounded by -2^(N-1)
to 2^(N-1)-1
.
The unsigned integer types WordN
are of limited bit width N
bounded by 0
to 2^N-1
.
Operations are closed and modulo 2^N
. e.g.:
maxBound + 1 = minBound read "2" = -2 :: Int2 abs minBound = minBound negate n = 2^N - n :: WordN
Single-bit signed integers: -1, 0
Instances
Bounded Int1 Source # | |
Enum Int1 Source # | |
Eq Int1 Source # | |
Integral Int1 Source # | |
Num Int1 Source # | |
Ord Int1 Source # | |
Read Int1 Source # | |
Real Int1 Source # | |
Defined in Test.LeanCheck.Utils.Types toRational :: Int1 -> Rational # | |
Show Int1 Source # | |
Ix Int1 Source # | |
Listable Int1 Source # | |
ShowFunction Int1 Source # | |
Two-bit signed integers: -2, -1, 0, 1
Instances
Bounded Int2 Source # | |
Enum Int2 Source # | |
Eq Int2 Source # | |
Integral Int2 Source # | |
Num Int2 Source # | |
Ord Int2 Source # | |
Read Int2 Source # | |
Real Int2 Source # | |
Defined in Test.LeanCheck.Utils.Types toRational :: Int2 -> Rational # | |
Show Int2 Source # | |
Ix Int2 Source # | |
Listable Int2 Source # | |
ShowFunction Int2 Source # | |
Three-bit signed integers: -4, -3, -2, -1, 0, 1, 2, 3
Instances
Bounded Int3 Source # | |
Enum Int3 Source # | |
Eq Int3 Source # | |
Integral Int3 Source # | |
Num Int3 Source # | |
Ord Int3 Source # | |
Read Int3 Source # | |
Real Int3 Source # | |
Defined in Test.LeanCheck.Utils.Types toRational :: Int3 -> Rational # | |
Show Int3 Source # | |
Ix Int3 Source # | |
Listable Int3 Source # | |
ShowFunction Int3 Source # | |
Four-bit signed integers: -8, -7, -6, -5, -4, -3, -2, -1, 0, 1, 2, 3, 4, 5, 6, 7
Instances
Bounded Int4 Source # | |
Enum Int4 Source # | |
Eq Int4 Source # | |
Integral Int4 Source # | |
Num Int4 Source # | |
Ord Int4 Source # | |
Read Int4 Source # | |
Real Int4 Source # | |
Defined in Test.LeanCheck.Utils.Types toRational :: Int4 -> Rational # | |
Show Int4 Source # | |
Ix Int4 Source # | |
Listable Int4 Source # | |
ShowFunction Int4 Source # | |
Single-bit unsigned integer: 0, 1
Instances
Bounded Word1 Source # | |
Enum Word1 Source # | |
Defined in Test.LeanCheck.Utils.Types | |
Eq Word1 Source # | |
Integral Word1 Source # | |
Num Word1 Source # | |
Ord Word1 Source # | |
Read Word1 Source # | |
Real Word1 Source # | |
Defined in Test.LeanCheck.Utils.Types toRational :: Word1 -> Rational # | |
Show Word1 Source # | |
Ix Word1 Source # | |
Listable Word1 Source # | |
ShowFunction Word1 Source # | |
Two-bit unsigned integers: 0, 1, 2, 3
Instances
Bounded Word2 Source # | |
Enum Word2 Source # | |
Defined in Test.LeanCheck.Utils.Types | |
Eq Word2 Source # | |
Integral Word2 Source # | |
Num Word2 Source # | |
Ord Word2 Source # | |
Read Word2 Source # | |
Real Word2 Source # | |
Defined in Test.LeanCheck.Utils.Types toRational :: Word2 -> Rational # | |
Show Word2 Source # | |
Ix Word2 Source # | |
Listable Word2 Source # | |
ShowFunction Word2 Source # | |
Three-bit unsigned integers: 0, 1, 2, 3, 4, 5, 6, 7
Instances
Bounded Word3 Source # | |
Enum Word3 Source # | |
Defined in Test.LeanCheck.Utils.Types | |
Eq Word3 Source # | |
Integral Word3 Source # | |
Num Word3 Source # | |
Ord Word3 Source # | |
Read Word3 Source # | |
Real Word3 Source # | |
Defined in Test.LeanCheck.Utils.Types toRational :: Word3 -> Rational # | |
Show Word3 Source # | |
Ix Word3 Source # | |
Listable Word3 Source # | |
ShowFunction Word3 Source # | |
Four-bit unsigned integers: 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15
Instances
Bounded Word4 Source # | |
Enum Word4 Source # | |
Defined in Test.LeanCheck.Utils.Types | |
Eq Word4 Source # | |
Integral Word4 Source # | |
Num Word4 Source # | |
Ord Word4 Source # | |
Read Word4 Source # | |
Real Word4 Source # | |
Defined in Test.LeanCheck.Utils.Types toRational :: Word4 -> Rational # | |
Show Word4 Source # | |
Ix Word4 Source # | |
Listable Word4 Source # | |
ShowFunction Word4 Source # | |
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
.
Its Enum
, Listable
and Num
instances only produce non-negative values.
When x < y
then x - y = 0
.
Instances
Natural numbers modulo 1: 0
Instances
Bounded Nat1 Source # | |
Enum Nat1 Source # | |
Eq Nat1 Source # | |
Integral Nat1 Source # | |
Num Nat1 Source # | |
Ord Nat1 Source # | |
Read Nat1 Source # | |
Real Nat1 Source # | |
Defined in Test.LeanCheck.Utils.Types toRational :: Nat1 -> Rational # | |
Show Nat1 Source # | |
Ix Nat1 Source # | |
Listable Nat1 Source # | |
ShowFunction Nat1 Source # | |
Natural numbers modulo 2: 0, 1
Instances
Bounded Nat2 Source # | |
Enum Nat2 Source # | |
Eq Nat2 Source # | |
Integral Nat2 Source # | |
Num Nat2 Source # | |
Ord Nat2 Source # | |
Read Nat2 Source # | |
Real Nat2 Source # | |
Defined in Test.LeanCheck.Utils.Types toRational :: Nat2 -> Rational # | |
Show Nat2 Source # | |
Ix Nat2 Source # | |
Listable Nat2 Source # | |
ShowFunction Nat2 Source # | |
Natural numbers modulo 3: 0, 1, 2
Instances
Bounded Nat3 Source # | |
Enum Nat3 Source # | |
Eq Nat3 Source # | |
Integral Nat3 Source # | |
Num Nat3 Source # | |
Ord Nat3 Source # | |
Read Nat3 Source # | |
Real Nat3 Source # | |
Defined in Test.LeanCheck.Utils.Types toRational :: Nat3 -> Rational # | |
Show Nat3 Source # | |
Ix Nat3 Source # | |
Listable Nat3 Source # | |
ShowFunction Nat3 Source # | |
Natural numbers modulo 4: 0, 1, 2, 3
Instances
Bounded Nat4 Source # | |
Enum Nat4 Source # | |
Eq Nat4 Source # | |
Integral Nat4 Source # | |
Num Nat4 Source # | |
Ord Nat4 Source # | |
Read Nat4 Source # | |
Real Nat4 Source # | |
Defined in Test.LeanCheck.Utils.Types toRational :: Nat4 -> Rational # | |
Show Nat4 Source # | |
Ix Nat4 Source # | |
Listable Nat4 Source # | |
ShowFunction Nat4 Source # | |
Natural numbers modulo 5: 0, 1, 2, 3, 4
Instances
Bounded Nat5 Source # | |
Enum Nat5 Source # | |
Eq Nat5 Source # | |
Integral Nat5 Source # | |
Num Nat5 Source # | |
Ord Nat5 Source # | |
Read Nat5 Source # | |
Real Nat5 Source # | |
Defined in Test.LeanCheck.Utils.Types toRational :: Nat5 -> Rational # | |
Show Nat5 Source # | |
Ix Nat5 Source # | |
Listable Nat5 Source # | |
ShowFunction Nat5 Source # | |
Natural numbers modulo 6: 0, 1, 2, 3, 4, 5
Instances
Bounded Nat6 Source # | |
Enum Nat6 Source # | |
Eq Nat6 Source # | |
Integral Nat6 Source # | |
Num Nat6 Source # | |
Ord Nat6 Source # | |
Read Nat6 Source # | |
Real Nat6 Source # | |
Defined in Test.LeanCheck.Utils.Types toRational :: Nat6 -> Rational # | |
Show Nat6 Source # | |
Ix Nat6 Source # | |
Listable Nat6 Source # | |
ShowFunction Nat6 Source # | |
Natural numbers modulo 7: 0, 1, 2, 3, 4, 5, 6
Instances
Bounded Nat7 Source # | |
Enum Nat7 Source # | |
Eq Nat7 Source # | |
Integral Nat7 Source # | |
Num Nat7 Source # | |
Ord Nat7 Source # | |
Read Nat7 Source # | |
Real Nat7 Source # | |
Defined in Test.LeanCheck.Utils.Types toRational :: Nat7 -> Rational # | |
Show Nat7 Source # | |
Ix Nat7 Source # | |
Listable Nat7 Source # | |
ShowFunction Nat7 Source # | |
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
, Listable
and Num
instances only produce non-negative values.
When x < y
then x - y = 0
.
Instances
Enum Natural Source # | |
Eq Natural Source # | |
Integral Natural Source # | |
Defined in Test.LeanCheck.Utils.Types | |
Num Natural Source # | |
Ord Natural Source # | |
Read Natural Source # | |
Real Natural Source # | |
Defined in Test.LeanCheck.Utils.Types toRational :: Natural -> Rational # | |
Show Natural Source # | |
Ix Natural Source # | |
Defined in Test.LeanCheck.Utils.Types | |
Listable Natural Source # | |
ShowFunction Natural Source # | |
Aliases to word types (deprecated)
Extreme Integers
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
Instances
Eq a => Eq (X a) Source # | |
Ord a => Ord (X a) Source # | |
Show a => Show (X a) Source # | |
(Integral a, Bounded a) => Listable (X a) Source # | 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 , ... ] |
Show a => ShowFunction (X a) Source # | |
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]
Xs [a] |
List-wrapper types
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.
NoDup [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]]
Bag [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]]
Set [a] |
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)]]
Map [(a, b)] |
Character types
Space characters.
list :: [Space] = " \t\n\r\f\v"
> check $ \(Space c) -> isSpace c +++ OK, passed 6 tests (exhausted).
Lowercase characters.
list :: [Lower] = "abcdef..."
> check $ \(Lower c) -> isLower c +++ OK, passed 26 tests (exhausted).
Uppercase characters.
list :: [Upper] = "ABCDEF..."
> check $ \(Upper c) -> isUpper c +++ OK, passed 26 tests (exhausted).
Alphabetic characters.
list :: [Alpha] = "aAbBcC..."
> check $ \(Alpha c) -> isAlpha c +++ OK, passed 52 tests (exhausted).
Equivalent to Letter
.
Digits.
list :: [Digit] = "0123456789"
> check $ \(Digit c) -> isDigit c +++ OK, passed 10 tests (exhausted).
Alphanumeric characters.
list :: [AlphaNum] = "0a1A2b3B4c..."
> check $ \(AlphaNum c) -> isAlphaNum c +++ OK, passed 62 tests (exhausted).
Alphabetic characters.
list :: [Letter] = "aAbBcC..."
> check $ \(Letter c) -> isLetter c +++ OK, passed 52 tests (exhausted).
Equivalent to Alpha
.
String types
Strings of spaces.
Strings of lowercase characters.
Strings of uppercase characters
Strings of alphabetic characters
Strings of digits.
Strings of alphanumeric characters
Strings of letters
Generic types
Generic type A
.
Can be used to test polymorphic functions with a type variable
such as take
or sort
:
take :: Int -> [a] -> [a] sort :: Ord a => [a] -> [a]
by binding them to the following types:
take :: Int -> [A] -> [A] sort :: [A] -> [A]
This type is homomorphic to Nat6
, B
, C
, D
, E
and F
.
It is instance to several typeclasses so that it can be used to test functions with type contexts.
Generic type B
.
Can be used to test polymorphic functions with two type variables
such as map
or foldr
:
map :: (a -> b) -> [a] -> [b] foldr :: (a -> b -> b) -> b -> [a] -> b
by binding them to the following types:
map :: (A -> B) -> [A] -> [B] foldr :: (A -> B -> B) -> B -> [A] -> B
Generic type C
.
Can be used to test polymorphic functions with three type variables
such as uncurry
or zipWith
:
uncurry :: (a -> b -> c) -> (a, b) -> c zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
by binding them to the following types:
uncurry :: (A -> B -> C) -> (A, B) -> C zipWith :: (A -> B -> C) -> [A] -> [B] -> [C]
Generic type D
.
Can be used to test polymorphic functions with four type variables.
Generic type E
.
Can be used to test polymorphic functions with five type variables.
Generic type F
.
Can be used to test polymorphic functions with five type variables.