Geoffrey Warne
Geoffrey Warne

Reputation: 162

Haskell: Using quickCheckAll with a size constraint (e.g. quickCheckWith (stdArgs {maxSize = n}))

I want to be able to use quickCheckAll to run a number of tests together. At the same time, I need to specify size constraints on my tests.

In the following program, there are two tests that are impractical without size constraints. Getting all the partitions of a very large integer is beyond the computational power of this algorithm, and testing a random list of strictly positive integers would require too many lists to be discarded.

{-# LANGUAGE TemplateHaskell #-}
module Partitions where

import Test.QuickCheck
import Test.QuickCheck.All
import Data.List (sort)

sizeCheck n = quickCheckWith (stdArgs {maxSize = n})

partitions :: Int -> [[Int]]
partitions 0 = [[]]
partitions n | n > 0
     = [k:xs | k <- [1..n], xs <- partitions (n - k), all (k <=) xs]

-- "adding up all of the numbers in each partition should give 𝑛"
prop_partitions :: Int -> Property
prop_partitions n =
  n >= 0 ==> all ((== n) . sum) (partitions n)

-- "sorting any list of strictly positive integers gives one of the
--  partitions of its sum"
prop_partitions' :: [Int] -> Property
prop_partitions' xs =
  all (>0) xs ==> sort xs `elem` partitions (sum xs)

return []
runTests = $quickCheckAll

Normally I will use quickCheckAll to run all the tests using the pragma {-# LANGUAGE TemplateHaskell #-}, naming all the tests of type Property to start with prop_, concluding the program with return [] and runTests = $quickCheckAll, then running runTests.

The textbook that I am using gives a convenient way to specify size constraints with quickCheckWith: sizeCheck n = quickCheckWith (stdArgs {maxSize = n}) (Introduction to Computation: Haskell, Logic and Automata; Sanella, Fourman, Peng, and Wadler; p. 272).

I do not see a way to combine quickCheckAll with quickCheckWith.

I tried using $allProperties (from the QuickCheck module) to collect the tests, then map over them with quickCheckWith (runTests n = map (quickCheckWith (stdArgs {maxSize=n}) . snd) $allProperties), but that did not work.

I suppose that I could use arbitrary to define test cases, but that seems to be going significantly out of the way.

Upvotes: 1

Views: 104

Answers (2)

effectfully
effectfully

Reputation: 12715

Answering your question directly, you can use the

mapSize :: Testable prop => (Int -> Int) -> prop -> Property

function and set the size via, say, mapSize (min 10) like this:

prop_partitions :: Property
prop_partitions = mapSize (min 10) $ \n ->
  n >= 0 ==> all ((== n) . sum) (partitions n)

But it wouldn't be a good solution, because generally size should be adjustable, so that you can for example run compute-intensive tests overnight. So it would be better to use mapSize (`div` 10) or something of this sort (you probably don't want to generate 0 in 10% of cases, so you could make the logic fancier).

Note that you shouldn't introduce cond ==> prop unless you really have to, because throwing away generated cases is just wasted compute. And in your case it's trivial to avoid the conditional:

prop_partitions :: Property
prop_partitions = mapSize (`div` 10) $ \nPre ->
  let n = abs nPre
  in all ((== n) . sum) (partitions n)

Similarly for prop_partitions' you can use map abs to handle negative numbers and/or map (`rem` 10) to handle large numbers.

Upvotes: 2

Geoffrey Warne
Geoffrey Warne

Reputation: 162

In my original question, I said,

I do not see a way to combine quickCheckAll with quickCheckWith.

I was on the right track with here:

I tried using $allProperties (from the QuickCheck module) to collect the tests, then map over them with quickCheckWith (runTests n = map (quickCheckWith (stdArgs {maxSize=n}) . snd) $allProperties), but that did not work.

I found what I was looking for reading the source code for the module Test.QuickCheck.All:

-- | Test all properties in the current module, using a custom
-- 'quickCheck' function. The same caveats as with 'quickCheckAll'
-- apply.
--
-- @$'forAllProperties'@ has type @('Property' -> 'IO' 'Result') -> 'IO' 'Bool'@.
-- An example invocation is @$'forAllProperties' 'quickCheckResult'@,
-- which does the same thing as @$'quickCheckAll'@.
--
-- 'forAllProperties' has the same issue with scoping as 'quickCheckAll':
-- see the note there about @return []@.
forAllProperties :: Q Exp -- :: (Property -> IO Result) -> IO Bool
forAllProperties = [| runQuickCheckAll |] `appE` allProperties

[gotta love that Haskell library source code is readily available like this <3]

Instead of allProperties and quickCheckWith, what I needed was forAllProperties and quickCheckWithResult. With forAllProperties one need not manually map over the properties, as I tried to do. The function, quickCheckWithResult is needed for outputting the results.

Thus,

runTests2 = $forAllProperties (quickCheckWithResult (stdArgs {maxSize = 9}))

is what I was looking for.

Upvotes: 1

Related Questions