ChasingBottoms-1.3.0.5: For testing partial and infinite values.

Portabilitynon-portable (GHC-specific)
Stabilityexperimental
Maintainerhttp://www.cse.chalmers.se/~nad/
Safe HaskellNone

Test.ChasingBottoms.ContinuousFunctions

Contents

Description

Note: This module is unfinished and experimental. However, I do not think that I will ever finish it, so I have released it in its current state. The documentation below may not be completely correct. The source code lists some things which should be addressed.

A framework for generating possibly non-strict, partial, continuous functions.

The functions generated using the standard QuickCheck Arbitrary instances are all strict. In the presence of partial and infinite values testing using only strict functions leads to worse coverage than if more general functions are used, though.

Using isBottom it is relatively easy to generate possibly non-strict functions that are, in general, not monotone. For instance, using

 type Cogen a = forall b. a -> Gen b -> Gen b

 integer :: Gen Integer
 integer = frequency [ (1, return bottom), (10, arbitrary) ]

 coBool :: CoGen Bool
 coBool b | isBottom b = variant 0
 coBool False          = variant 1
 coBool True           = variant 2

 function :: Cogen a -> Gen b -> Gen (a -> b)
 function coGen gen = promote (\a -> coGen a gen)

we can generate possibly non-strict functions from Bool to Integer using function coBool integer. There is a high likelihood that the functions generated are not monotone, though. The reason that we can get non-monotone functions in a language like Haskell is that we are using the impure function isBottom.

Sometimes using possibly non-monotone functions is good enough, since that set of functions is a superset of the continuous functions. However, say that we want to test that x <=! y implies that f x <=! f y for all functions f (whenever the latter expression returns a total result). This property is not valid in the presence of non-monotone functions.

By avoiding isBottom and, unlike the standard coarbitrary functions, deferring some pattern matches, we can generate continuous, possibly non-strict functions. There are two steps involved in generating a continuous function using the framework defined here.

  1. First the argument to the function is turned into a PatternMatch. A PatternMatch wraps up the pattern match on the top-level constructor of the argument, plus all further pattern matches on the children of the argument. Just like when coarbitrary is used a pattern match is represented as a generator transformer. The difference here is that there is not just one transformation per input, but one transformation per constructor in the input. PatternMatches can be constructed generically using match.
  2. Then the result is generated, almost like for a normal Arbitrary instance. However, for each constructor generated a subset of the transformations from step 1 are applied. This transformation application is wrapped up in the function transform.

The net result of this is that some pattern matches are performed later, or not at all, so functions can be lazy.

Here is an example illustrating typical use of this framework:

 data Tree a
   = Branch (Tree a) (Tree a)
   | Leaf a
     deriving (Show, Typeable, Data)

 finiteTreeOf :: MakeResult a -> MakeResult (Tree a)
 finiteTreeOf makeResult = sized' tree
   where
   tree size = transform $
     if size == 0 then
       baseCase
      else
       frequency' [ (1, baseCase)
                  , (1, liftM2 Branch tree' tree')
                  ]
     where
     tree' = tree (size `div` 2)

     baseCase =
       frequency' [ (1, return bottom)
                  , (2, liftM Leaf makeResult)
                  ]

Note the use of transform. To use this function to generate functions of type Bool -> Tree Integer we can use

 forAll (functionTo (finiteTreeOf flat)) $
   \(f :: Bool -> Tree Integer) ->
     ...

Synopsis

Basic framework

function :: MakePM a -> MakeResult b -> Gen (a -> b)Source

Generator for continuous, not necessarily strict functions. Functions are generated by first generating pattern matches, and then generating a result.

data PatternMatch Source

PatternMatch packages up the possible outcomes of a pattern match in a style suitable for generating functions. A pattern match is a generator (Gen) transformer based on the top-level constructor, and a sequence (see http://www.soi.city.ac.uk/~ross/software/html/Data.Sequence.html) of PatternMatches based on the children of that constructor.

Constructors

PatternMatch 

Fields

apply :: GenTransformer

A generator transformer, in the style of coarbitrary.

more :: Seq PatternMatch

Further pattern matches made possible by this match.

type GenTransformer = forall a. Gen a -> Gen aSource

The type of a generator transformer.

type MakePM a = a -> PatternMatchSource

The type of a PatternMatch generator.

data MakeResult a Source

Monad for generating results given previously generated pattern matches.

A MakeResult a should be implemented almost as other generators for the type a, with the difference that transform should be used wherever the resulting function should be allowed to pattern match (typically for each constructor emitted). See example above.

transform :: MakeResult a -> MakeResult aSource

transform makes sure that the pattern matches get to influence the generated value. See MakeResult.

Liftings of some QuickCheck functionality

lift' :: Gen a -> MakeResult aSource

Lifting of a Gen.

choose' :: Random a => (a, a) -> MakeResult aSource

Lifting of choose.

elements' :: [a] -> MakeResult aSource

Lifting of elements.

oneof' :: [MakeResult a] -> MakeResult aSource

Lifting of oneof.

sized' :: (Int -> MakeResult a) -> MakeResult aSource

Lifting of sized.

resize' :: Int -> MakeResult a -> MakeResult aSource

Lifting of resize.

Generic MakePM

match :: forall a. Data a => MakePM aSource

Generic implementation of PatternMatch construction.

Some MakeResults

flat :: Arbitrary a => MakeResult aSource

An implementation of MakeResult a which is suitable when a is flat and has an Arbitrary instance. Yields bottoms around 10% of the time.

finiteListOf :: MakeResult a -> MakeResult [a]Source

This MakeResult yields finite partial lists.

infiniteListOf :: MakeResult a -> MakeResult [a]Source

This MakeResult yields infinite partial lists.

listOf :: MakeResult a -> MakeResult [a]Source

This MakeResult yields finite or infinite partial lists.