Safe Haskell | None |
---|---|
Language | Haskell2010 |
The top-level interface to the StrictCheck library for random strictness testing.
Quick Start:
Want to explore the strictness of functions before you write specifications?
Go to Test.StrictCheck.Observe and look at the functions observe1
and
observe
.
Want to check the strictness of a function against a specification of its strictness?
- Write a
Spec
describing your expectation of the function's behavior. See Test.StrictCheck.Demand for more on working with demands, and Test.StrictCheck.Examples.Lists for examples of some specifications of functions on lists. - Check your function using
strictCheckSpecExact
, like so:
strictCheckSpecExact spec function
If your function passes testing, you'll get a success message just like in Test.QuickCheck; if a counterexample to your specification is found, you will see a pretty Unicode box diagram describing the mismatch.
Hint: StrictCheck, just like QuickCheck, doesn't work with polymorphic functions. If you get baffling type errors, first make sure that all your types are totally concrete.
- newtype Spec (args :: [*]) (result :: *) = Spec (forall r. (args ⋯-> r) -> result -> args ⋯-> r)
- getSpec :: forall r args result. Spec args result -> (args ⋯-> r) -> result -> args ⋯-> r
- type StrictCheck function = (Shaped (Result function), Consume (Result function), Curry (Args function), All Typeable (Args function), All Shaped (Args function))
- strictCheckSpecExact :: forall function. (StrictCheck function, All Arbitrary (Args function), All Produce (Args function)) => Spec (Args function) (Result function) -> function -> IO ()
- strictCheckWithResults :: forall function evidence. StrictCheck function => Args -> NP Shrink (Args function) -> NP Gen (Args function) -> Gen Strictness -> (Evaluation (Args function) (Result function) -> Maybe evidence) -> function -> IO (Maybe (Evaluation (Args function) (Result function), evidence), Result)
- genViaProduce :: All Produce xs => NP Gen xs
- newtype Shrink a = Shrink (a -> [a])
- shrinkViaArbitrary :: All Arbitrary xs => NP Shrink xs
- data Strictness
- strictnessViaSized :: Gen Strictness
- data Evaluation args result = Evaluation {
- inputs :: NP I args
- inputDemands :: NP Demand args
- resultDemand :: PosDemand result
- evaluationForall :: forall f. (Curry (Args f), Consume (Result f), Shaped (Result f), All Shaped (Args f)) => NP Gen (Args f) -> Gen Strictness -> f -> Gen (Evaluation (Args f) (Result f))
- shrinkEvalWith :: forall f. (Curry (Args f), Shaped (Result f), All Shaped (Args f)) => NP Shrink (Args f) -> f -> Evaluation (Args f) (Result f) -> [Evaluation (Args f) (Result f)]
- newtype DemandComparison a = DemandComparison (Demand a -> Demand a -> Bool)
- compareToSpecWith :: forall args result. (All Shaped args, Curry args, Shaped result) => NP DemandComparison args -> Spec args result -> Evaluation args result -> Maybe (NP Demand args)
- equalToSpec :: forall args result. (All Shaped args, Shaped result, Curry args) => Spec args result -> Evaluation args result -> Maybe (NP Demand args)
- data NP k (a :: k -> *) (b :: [k]) :: forall k. (k -> *) -> [k] -> * where
- newtype I a :: * -> * = I a
- class (AllF k f xs, SListI k xs) => All k (f :: k -> Constraint) (xs :: [k])
- module Test.StrictCheck.Demand
- module Test.StrictCheck.Observe
- module Test.StrictCheck.Produce
- module Test.StrictCheck.Consume
- module Test.StrictCheck.Shaped
Specifying demand behavior
newtype Spec (args :: [*]) (result :: *) Source #
A demand specification for some function f
is itself a function which
manipulates demand values for some function's arguments and results
A Spec
for f
wraps a function which takes, in order:
- a continuation
predict
which accepts all off
's argument types in order, - an implicit representation of a demand on
f
's result (embedded inf
's actual result type using special bottom values, see the documentation for Test.StrictCheck.Demand for details), and - all of
f
's original arguments in order
The intention is that the Spec
will call predict
on some set of demands
representing the demands it predicts that f
will exert on its inputs,
given the provided demand on f
's outputs.
For example, here is a correct Spec
for take
:
take_spec :: Spec '[Int, [a]] [a] take_spec = Spec $ \predict d n xs -> predict n (if n > length xs then d else d ++ thunk)
See the documentation for Test.StrictCheck.Demand for information about how
to manipulate these implicit demand representations when writing Spec
s, and
see the documentation for Test.StrictCheck.Examples.Lists for more examples
of writing specifications.
getSpec :: forall r args result. Spec args result -> (args ⋯-> r) -> result -> args ⋯-> r Source #
Unwrap a Spec
constructor, returning the contained CPS-ed specification
Conceptually, this is the inverse to the Spec
constructor, but because
Spec
is variadic, getSpec . Spec
and Spec . getSpec
don't typecheck
without additional type annotation.
Checking specifications
type StrictCheck function = (Shaped (Result function), Consume (Result function), Curry (Args function), All Typeable (Args function), All Shaped (Args function)) Source #
A function can be checked against a specification if it meets the
StrictCheck
constraint
strictCheckSpecExact :: forall function. (StrictCheck function, All Arbitrary (Args function), All Produce (Args function)) => Spec (Args function) (Result function) -> function -> IO () Source #
Check a function to see whether it exactly meets a strictness specification
If the function fails to meet the specification, a counterexample is pretty-printed in a box-drawn diagram illustrating how the specification failed to match the real observed behavior of the function.
strictCheckWithResults :: forall function evidence. StrictCheck function => Args -> NP Shrink (Args function) -> NP Gen (Args function) -> Gen Strictness -> (Evaluation (Args function) (Result function) -> Maybe evidence) -> function -> IO (Maybe (Evaluation (Args function) (Result function), evidence), Result) Source #
The most general function for random strictness testing: all of the more convenient such functions can be derived from this one
Given some function f
, this takes as arguments:
- A
Args
record describing arguments to pass to the underlying QuickCheck engine - An
NP
n-ary product ofShrink
shrinkers, one for each argument off
- An
NP
n-ary product ofGen
generators, one for each argument off
- A
Gen
generator for strictnesses to be tested - A predicate on
Evaluation
s: if theEvaluation
passes the predicate, it should returnNothing
; otherwise, it should returnJust
someevidence
representing the failure (when checkingSpec
s, this evidence comes in the form of aSpec
's (incorrect) prediction) - the function
f
to be tested
If all tests succeed, (Nothing, result)
is returned, where result
is the
underlying Result
type from Test.QuickCheck. If there is a test
failure, it also returns Just
the failed Evaluation
as well as whatever
evidence
was produced by the predicate.
Providing arguments for strictCheckWithResults
genViaProduce :: All Produce xs => NP Gen xs Source #
The default way to generate inputs: via Produce
shrinkViaArbitrary :: All Arbitrary xs => NP Shrink xs Source #
The default way to shrink inputs: via shrink
(from Test.QuickCheck's
Arbitrary
typeclass)
data Strictness Source #
A Strictness
represents (roughly) how strict a randomly generated
function or evaluation context should be
An evaluation context generated with some strictness s
(i.e. through
evaluationForall
) will consume at most s
constructors of its input,
although it might consume fewer.
strictnessViaSized :: Gen Strictness Source #
The default way to generate random strictnesses: uniformly choose between
1 and the test configuration's size
parameter
Representing individual evaluations of functions
data Evaluation args result Source #
A snapshot of the observed strictness behavior of a function
An Evaluation
contains the inputs
at which a function was called, the
inputDemands
which were induced upon those inputs, and the resultDemand
which induced that demand on the inputs.
Evaluation | |
|
evaluationForall :: forall f. (Curry (Args f), Consume (Result f), Shaped (Result f), All Shaped (Args f)) => NP Gen (Args f) -> Gen Strictness -> f -> Gen (Evaluation (Args f) (Result f)) Source #
Given a list of generators for a function's arguments and a generator for
random strictnesses (measured in number of constructors evaluated), create
a generator for random Evaluation
s of that function in random contexts
shrinkEvalWith :: forall f. (Curry (Args f), Shaped (Result f), All Shaped (Args f)) => NP Shrink (Args f) -> f -> Evaluation (Args f) (Result f) -> [Evaluation (Args f) (Result f)] Source #
Given a shrinker for each of the arguments of a function, the function
itself, and some Evaluation
of that function, produce a list of smaller
Evaluation
s of that function
Comparing demands
newtype DemandComparison a Source #
A newtype for wrapping a comparison on demands
This is useful when constructing an NP
n-ary product of such comparisons.
DemandComparison (Demand a -> Demand a -> Bool) |
compareToSpecWith :: forall args result. (All Shaped args, Curry args, Shaped result) => NP DemandComparison args -> Spec args result -> Evaluation args result -> Maybe (NP Demand args) Source #
Given a list of ways to compare demands, a demand specification, and an evaluation of a particular function, determine if the function met the specification, as decided by the comparisons. If so, return the prediction of the specification.
equalToSpec :: forall args result. (All Shaped args, Shaped result, Curry args) => Spec args result -> Evaluation args result -> Maybe (NP Demand args) Source #
Checks if a given Evaluation
exactly matches the prediction of a given
Spec
, returning the prediction of that Spec
if not
Note: In the case of success this returns Nothing
; in the case of
failure this returns Just
the incorrect prediction.
Re-exported n-ary products from Generics.SOP
data NP k (a :: k -> *) (b :: [k]) :: forall k. (k -> *) -> [k] -> * where #
An n-ary product.
The product is parameterized by a type constructor f
and
indexed by a type-level list xs
. The length of the list
determines the number of elements in the product, and if the
i
-th element of the list is of type x
, then the i
-th
element of the product is of type f x
.
The constructor names are chosen to resemble the names of the list constructors.
Two common instantiations of f
are the identity functor I
and the constant functor K
. For I
, the product becomes a
heterogeneous list, where the type-level list describes the
types of its components. For
, the product becomes a
homogeneous list, where the contents of the type-level list are
ignored, but its length still specifies the number of elements.K
a
In the context of the SOP approach to generic programming, an n-ary product describes the structure of the arguments of a single data constructor.
Examples:
I 'x' :* I True :* Nil :: NP I '[ Char, Bool ] K 0 :* K 1 :* Nil :: NP (K Int) '[ Char, Bool ] Just 'x' :* Nothing :* Nil :: NP Maybe '[ Char, Bool ]
HTrans k1 [k1] k2 [k2] (NP k1) (NP k2) | |
HPure k [k] (NP k) | |
HAp k [k] (NP k) | |
HCollapse k [k] (NP k) | |
HTraverse_ k [k] (NP k) | |
HSequence k [k] (NP k) | |
List (NP * I) Source # | |
All k (Compose * k Eq f) xs => Eq (NP k f xs) | |
(All k (Compose * k Eq f) xs, All k (Compose * k Ord f) xs) => Ord (NP k f xs) | |
All k (Compose * k Show f) xs => Show (NP k f xs) | |
All k (Compose * k NFData f) xs => NFData (NP k f xs) | Since: 0.2.5.0 |
type AllZipN k [k] a b [a] [b] (NP k) c | |
type Same k1 [k1] k2 [k2] (NP k1) | |
type Prod k [k] (NP k) | |
type UnProd k [k] (NP k) | |
type SListIN k [k] (NP k) | |
type CollapseTo k [k] (NP k) a | |
type AllN k [k] (NP k) c | |
The identity type functor.
Like Identity
, but with a shorter name.
I a |
Monad I | |
Functor I | |
Applicative I | |
Foldable I | |
Traversable I | |
Eq1 I | Since: 0.2.4.0 |
Ord1 I | Since: 0.2.4.0 |
Read1 I | Since: 0.2.4.0 |
Show1 I | Since: 0.2.4.0 |
NFData1 I | Since: 0.2.5.0 |
Eq a => Eq (I a) | |
Ord a => Ord (I a) | |
Read a => Read (I a) | |
Show a => Show (I a) | |
Generic (I a) | |
NFData a => NFData (I a) | Since: 0.2.5.0 |
List (NP * I) Source # | |
type Rep (I a) | |
type Code (I a) | |
type DatatypeInfoOf (I a) | |
class (AllF k f xs, SListI k xs) => All k (f :: k -> Constraint) (xs :: [k]) #
Require a constraint for every element of a list.
If you have a datatype that is indexed over a type-level
list, then you can use All
to indicate that all elements
of that type-level list must satisfy a given constraint.
Example: The constraint
All Eq '[ Int, Bool, Char ]
is equivalent to the constraint
(Eq Int, Eq Bool, Eq Char)
Example: A type signature such as
f :: All Eq xs => NP I xs -> ...
means that f
can assume that all elements of the n-ary
product satisfy Eq
.
Re-exports of the rest of the library
module Test.StrictCheck.Demand
module Test.StrictCheck.Observe
module Test.StrictCheck.Produce
module Test.StrictCheck.Consume
module Test.StrictCheck.Shaped