Copyright | (c) 2015-2020 Rudy Matela |
---|---|
License | 3-Clause BSD (see the file LICENSE) |
Maintainer | Rudy Matela <rudy@matela.com.br> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module is part of LeanCheck, a simple enumerative property-based testing library.
This module exports Test.LeanCheck.Core along with:
- support for
Listable
6-tuples up to 12-tuples; tiers
constructors (consN
) with arities from 6 up to 12;- a
Listable
Word
instance; - a
Listable
Ratio
instance (consequentlyListable
Rational
); - a
Listable
Complex
instance; Listable
'Int81632/64' instances;Listable
'Word81632/64' instances;Listable
instances for Foreign.C types;- a
Listable
ExitCode
instance; - a
Listable
GeneralCategory
instance; Listable
'BufferIOSeekMode' instances;- the operators
addWeight
andofWeight
.
The above includes all types defined in the Haskell 2010 Report with the exception of Array, IO, Handle, HandlePosn, IOErrorType.
Test.LeanCheck already exports everything from this module. You are probably better off importing it.
You should only import Test.LeanCheck.Basic if you only want the above basic functionality.
Synopsis
- module Test.LeanCheck.Core
- cons6 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f) => (a -> b -> c -> d -> e -> f -> g) -> [[g]]
- cons7 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g) => (a -> b -> c -> d -> e -> f -> g -> h) -> [[h]]
- cons8 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h) => (a -> b -> c -> d -> e -> f -> g -> h -> i) -> [[i]]
- cons9 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h, Listable i) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j) -> [[j]]
- cons10 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h, Listable i, Listable j) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k) -> [[k]]
- cons11 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h, Listable i, Listable j, Listable k) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l) -> [[l]]
- cons12 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h, Listable i, Listable j, Listable k, Listable l) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m) -> [[m]]
- ofWeight :: [[a]] -> Int -> [[a]]
- addWeight :: [[a]] -> Int -> [[a]]
Documentation
module Test.LeanCheck.Core
cons6 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f) => (a -> b -> c -> d -> e -> f -> g) -> [[g]] Source #
Returns tiers of applications of a 6-argument constructor.
cons7 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g) => (a -> b -> c -> d -> e -> f -> g -> h) -> [[h]] Source #
Returns tiers of applications of a 7-argument constructor.
cons8 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h) => (a -> b -> c -> d -> e -> f -> g -> h -> i) -> [[i]] Source #
Returns tiers of applications of a 8-argument constructor.
cons9 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h, Listable i) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j) -> [[j]] Source #
Returns tiers of applications of a 9-argument constructor.
cons10 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h, Listable i, Listable j) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k) -> [[k]] Source #
Returns tiers of applications of a 10-argument constructor.
cons11 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h, Listable i, Listable j, Listable k) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l) -> [[l]] Source #
Returns tiers of applications of a 11-argument constructor.
cons12 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h, Listable i, Listable j, Listable k, Listable l) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m) -> [[m]] Source #
Returns tiers of applications of a 12-argument constructor.
ofWeight :: [[a]] -> Int -> [[a]] Source #
Resets the weight of a constructor or tiers.
> [ [], [], ..., xs, ys, zs, ... ] `ofWeight` 1 [ [], xs, ys, zs, ... ]
> [ xs, ys, zs, ... ] `ofWeight` 2 [ [], [], xs, ys, zs, ... ]
> [ [], xs, ys, zs, ... ] `ofWeight` 3 [ [], [], [], xs, ys, zs, ... ]
Typically used as an infix operator when defining Listable
instances:
instance Listable <Type> where tiers = ... \/ cons<N> <Cons> `ofWeight` <W> \/ ...
Warning: do not apply `ofWeight` 0
to recursive data structure
constructors. In general this will make the list of size 0 infinite,
breaking the tier invariant (each tier must be finite).
`ofWeight` n
is equivalent to reset
followed
by n
applications of delay
.
addWeight :: [[a]] -> Int -> [[a]] Source #
Adds to the weight of a constructor or tiers.
instance Listable <Type> where tiers = ... \/ cons<N> <Cons> `addWeight` <W> \/ ...
Typically used as an infix operator when defining Listable
instances:
> [ xs, ys, zs, ... ] `addWeight` 1 [ [], xs, ys, zs, ... ]
> [ xs, ys, zs, ... ] `addWeight` 2 [ [], [], xs, ys, zs, ... ]
> [ [], xs, ys, zs, ... ] `addWeight` 3 [ [], [], [], [], xs, ys, zs, ... ]
`addWeight` n
is equivalent to n
applications of delay
.