StrictCheck-0.3.0: StrictCheck: Keep Your Laziness In Check

Safe HaskellNone
LanguageHaskell2010

Test.StrictCheck

Contents

Description

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?

  1. 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.
  2. 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.

Synopsis

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 of f's argument types in order,
  • an implicit representation of a demand on f's result (embedded in f'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 Specs, and see the documentation for Test.StrictCheck.Examples.Lists for more examples of writing specifications.

Constructors

Spec (forall r. (args ⋯-> r) -> result -> args ⋯-> r) 

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 of Shrink shrinkers, one for each argument of f
  • An NP n-ary product of Gen generators, one for each argument of f
  • A Gen generator for strictnesses to be tested
  • A predicate on Evaluations: if the Evaluation passes the predicate, it should return Nothing; otherwise, it should return Just some evidence representing the failure (when checking Specs, this evidence comes in the form of a Spec'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

newtype Shrink a Source #

Newtype allowing us to construct NP n-ary products of shrinkers

Constructors

Shrink (a -> [a]) 

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.

Constructors

Evaluation 

Fields

Instances
(All (Typeable :: Type -> Constraint) args, Typeable result) => Show (Evaluation args result) Source # 
Instance details

Defined in Test.StrictCheck

Methods

showsPrec :: Int -> Evaluation args result -> ShowS #

show :: Evaluation args result -> String #

showList :: [Evaluation args result] -> ShowS #

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

Constructors

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 (a :: k -> Type) (b :: [k]) :: forall k. (k -> Type) -> [k] -> Type 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 K a, 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.

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 ]

Constructors

Nil :: forall k (a :: k -> Type) (b :: [k]). NP a ([] :: [k]) 
(:*) :: forall k (a :: k -> Type) (b :: [k]) (x :: k) (xs :: [k]). a x -> NP a xs -> NP a (x ': xs) infixr 5 
Instances
HTrans (NP :: (k1 -> Type) -> [k1] -> Type) (NP :: (k2 -> Type) -> [k2] -> Type) 
Instance details

Defined in Generics.SOP.NP

Methods

htrans :: AllZipN (Prod NP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NP f xs -> NP g ys #

hcoerce :: (AllZipN (Prod NP) (LiftedCoercible f g) xs ys, HTrans NP NP) => NP f xs -> NP g ys #

HPure (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Generics.SOP.NP

Methods

hpure :: SListIN NP xs => (forall (a :: k0). f a) -> NP f xs #

hcpure :: AllN NP c xs => proxy c -> (forall (a :: k0). c a => f a) -> NP f xs #

HAp (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Generics.SOP.NP

Methods

hap :: Prod NP (f -.-> g) xs -> NP f xs -> NP g xs #

HCollapse (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Generics.SOP.NP

Methods

hcollapse :: SListIN NP xs => NP (K a) xs -> CollapseTo NP a #

HTraverse_ (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Generics.SOP.NP

Methods

hctraverse_ :: (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NP f xs -> g () #

htraverse_ :: (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NP f xs -> g () #

HSequence (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Generics.SOP.NP

Methods

hsequence' :: (SListIN NP xs, Applicative f) => NP (f :.: g) xs -> f (NP g xs) #

hctraverse' :: (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NP f xs -> g (NP f' xs) #

htraverse' :: (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NP f xs -> g (NP f' xs) #

List (NP I) Source # 
Instance details

Defined in Test.StrictCheck.Curry

Methods

nil :: NP I [] Source #

cons :: x -> NP I xs -> NP I (x ': xs) Source #

uncons :: NP I (x ': xs) -> (x, NP I xs) Source #

All (Compose Eq f) xs => Eq (NP f xs) 
Instance details

Defined in Generics.SOP.NP

Methods

(==) :: NP f xs -> NP f xs -> Bool #

(/=) :: NP f xs -> NP f xs -> Bool #

(All (Compose Eq f) xs, All (Compose Ord f) xs) => Ord (NP f xs) 
Instance details

Defined in Generics.SOP.NP

Methods

compare :: NP f xs -> NP f xs -> Ordering #

(<) :: NP f xs -> NP f xs -> Bool #

(<=) :: NP f xs -> NP f xs -> Bool #

(>) :: NP f xs -> NP f xs -> Bool #

(>=) :: NP f xs -> NP f xs -> Bool #

max :: NP f xs -> NP f xs -> NP f xs #

min :: NP f xs -> NP f xs -> NP f xs #

All (Compose Show f) xs => Show (NP f xs) 
Instance details

Defined in Generics.SOP.NP

Methods

showsPrec :: Int -> NP f xs -> ShowS #

show :: NP f xs -> String #

showList :: [NP f xs] -> ShowS #

All (Compose NFData f) xs => NFData (NP f xs)

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.NP

Methods

rnf :: NP f xs -> () #

type Same (NP :: (k1 -> Type) -> [k1] -> Type) 
Instance details

Defined in Generics.SOP.NP

type Same (NP :: (k1 -> Type) -> [k1] -> Type) = (NP :: (k2 -> Type) -> [k2] -> Type)
type Prod (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Generics.SOP.NP

type Prod (NP :: (k -> Type) -> [k] -> Type) = (NP :: (k -> Type) -> [k] -> Type)
type UnProd (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Generics.SOP.NS

type UnProd (NP :: (k -> Type) -> [k] -> Type) = (NS :: (k -> Type) -> [k] -> Type)
type CollapseTo (NP :: (k -> Type) -> [k] -> Type) a 
Instance details

Defined in Generics.SOP.NP

type CollapseTo (NP :: (k -> Type) -> [k] -> Type) a = [a]
type SListIN (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Generics.SOP.NP

type SListIN (NP :: (k -> Type) -> [k] -> Type) = (SListI :: [k] -> Constraint)
type AllN (NP :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) 
Instance details

Defined in Generics.SOP.NP

type AllN (NP :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) = All c
type AllZipN (NP :: (k -> Type) -> [k] -> Type) (c :: a -> b -> Constraint) 
Instance details

Defined in Generics.SOP.NP

type AllZipN (NP :: (k -> Type) -> [k] -> Type) (c :: a -> b -> Constraint) = AllZip c

newtype I a #

The identity type functor.

Like Identity, but with a shorter name.

Constructors

I a 
Instances
Monad I 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

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

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

return :: a -> I a #

fail :: String -> I a #

Functor I 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

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

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

Applicative I 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

pure :: a -> I a #

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

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

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

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

Foldable I 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

fold :: Monoid m => I m -> m #

foldMap :: Monoid m => (a -> m) -> I a -> m #

foldr :: (a -> b -> b) -> b -> I a -> b #

foldr' :: (a -> b -> b) -> b -> I a -> b #

foldl :: (b -> a -> b) -> b -> I a -> b #

foldl' :: (b -> a -> b) -> b -> I a -> b #

foldr1 :: (a -> a -> a) -> I a -> a #

foldl1 :: (a -> a -> a) -> I a -> a #

toList :: I a -> [a] #

null :: I a -> Bool #

length :: I a -> Int #

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

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

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

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

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

Traversable I 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

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

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

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

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

Eq1 I

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

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

Ord1 I

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

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

Read1 I

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

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

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

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

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

Show1 I

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

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

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

NFData1 I

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftRnf :: (a -> ()) -> I a -> () #

Eq a => Eq (I a) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

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

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

Ord a => Ord (I a) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

compare :: I a -> I a -> Ordering #

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

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

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

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

max :: I a -> I a -> I a #

min :: I a -> I a -> I a #

Read a => Read (I a) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

readsPrec :: Int -> ReadS (I a) #

readList :: ReadS [I a] #

readPrec :: ReadPrec (I a) #

readListPrec :: ReadPrec [I a] #

Show a => Show (I a) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

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

show :: I a -> String #

showList :: [I a] -> ShowS #

Generic (I a) 
Instance details

Defined in Generics.SOP.BasicFunctors

Associated Types

type Rep (I a) :: Type -> Type #

Methods

from :: I a -> Rep (I a) x #

to :: Rep (I a) x -> I a #

NFData a => NFData (I a)

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

rnf :: I a -> () #

List (NP I) Source # 
Instance details

Defined in Test.StrictCheck.Curry

Methods

nil :: NP I [] Source #

cons :: x -> NP I xs -> NP I (x ': xs) Source #

uncons :: NP I (x ': xs) -> (x, NP I xs) Source #

type Rep (I a) 
Instance details

Defined in Generics.SOP.BasicFunctors

type Rep (I a) = D1 (MetaData "I" "Generics.SOP.BasicFunctors" "generics-sop-0.3.2.0-1LIoMWx8QIZINcf2OfoAby" True) (C1 (MetaCons "I" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Code (I a) 
Instance details

Defined in Generics.SOP.Instances

type Code (I a) = (a ': ([] :: [Type])) ': ([] :: [[Type]])
type DatatypeInfoOf (I a) 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf (I a) = Newtype "Generics.SOP.BasicFunctors" "I" (Constructor "I")

class (AllF f xs, SListI xs) => All (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.

Instances
(AllF f xs, SListI xs) => All (f :: k -> Constraint) (xs :: [k]) 
Instance details

Defined in Generics.SOP.Constraint

Re-exports of the rest of the library