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.
In my original question, I said,
I was on the right track with here:
I found what I was looking for reading the source code for the module
Test.QuickCheck.All:[gotta love that Haskell library source code is readily available like this <3]
Instead of
allPropertiesandquickCheckWith, what I needed wasforAllPropertiesandquickCheckWithResult. WithforAllPropertiesone need not manuallymapover the properties, as I tried to do. The function,quickCheckWithResultis needed for outputting the results.Thus,
is what I was looking for.