[Haskell-cafe] Testing polymorphic properties with QuickCheck

Mike Izbicki mike at izbicki.me
Wed Feb 18 21:04:54 UTC 2015


I agree that this is a huge pain.  I've been working on an alternative
numeric hierarchy, and as part of that I've wanted a completely
automated test suite.  What I've done is use template haskell to write
boilerplate code for me.  Currently, I am verifying around 1000
quickcheck properties, all of which are automatically generated.  I
suspect that by the time I finish the final number of properties will
be between 10000-100000, so full automation for this is a must!

Here's a file-by-file breakdown of how it works:

----

https://github.com/mikeizbicki/subhask/blob/master/test/TestSuite.hs

This file defines the actual tests.  You specify a type to test, and
then the template haskell figures out all of the classes it's an
instance of and runs the appropriate tests on that type.  Eventually,
I'd like to automate this a bit more so that you don't have to
manually specify types to test, and the template haskell will
determine that as well.

----

https://github.com/mikeizbicki/subhask/blob/master/src/SubHask/Algebra.hs

Here's the code for the classes.  Notice that for each class I've
created functions beginning with law_, defn_ or theorem_ that define
the required properties of the class.  These are the tests that will
get automatically run on an instance of that class to verify it obeys
the laws.  The prefix differences don't mean anything special to my
generating code yet.  Eventually, I'd like to create a "fast" test
suite for quick development and a "thorough" test suite to run before
releases, in which case there would be a difference between these
prefixes.

----

https://github.com/mikeizbicki/subhask/blob/master/src/SubHask/TemplateHaskell/Test.hs

Then I have a bunch of template haskell code to generate test cases
automatically from the law_/defn_/theorem_ functions.  The `testmap`
variable contains all the tests that apply to each class.  In theory,
this can be generated automatically, however, template haskell isn't
yet powerful enough to do this
(https://ghc.haskell.org/trac/ghc/ticket/9699).

On Wed, Feb 18, 2015 at 12:41 PM, Stuart Hungerford
<stuart.hungerford at gmail.com> wrote:
> Hi,
>
> I'd like to use QuickCheck to test polymorphic properties and I'm
> wondering if there's any community consenus on how to do this while
> avoiding creating large amounts of boilerplate test code.
>
> As an example, suppose I have this simple simplistic Monoid typeclass:
>
> class Monoid a where
>   zero  :: a
>   (|+|) :: a -> a -> a
>
> And suppose I make these types Monoid instances:
>
>
> instance Monoid Integer where
>   zero  = 0
>   (|+|) = (+)
>
> instance Monoid Rational where
>   zero  = 0
>   (|+|) = (+)
>
> instance (Monoid a, Monoid b) => Monoid (a, b) where
>   zero = (zero, zero)
>   (|+|) (x, y) (u, v) = (x |+| u, y |+| v)
>
>
> Using QuickCheck and the Tasty test framework I'd like to test the
> Monoid laws across the relevant types (I'm only showing one part of
> one law here) as QuickCheck properties:
>
>
> prop_left_add_id :: (Eq a, Monoid a) => a -> Bool
> prop_left_add_id x = zero |+| x == x
>
> monoid_suite :: TestTree
> monoid_suite = testGroup "monoid" [
>   testProperty "left additive identity (Integer)"
>     (prop_left_add_id :: Integer -> Bool),
>
>   testProperty "left additive identity (Rational)"
>     (prop_left_add_id :: Rational -> Bool),
>
>   testProperty "left additive identity ((Integer, Integer))"
>     (prop_left_add_id :: (Integer, Integer) -> Bool),
>   -- ...]
>
>
> And this is where I start creating a lot of essentially boilerplate
> code. I'm wondering if there's any consensus on the way to go about
> this kind of testing?
>
> Researching this issue I've found ways of combining various GHC
> extensions and the type system to (I think) write the properties more
> at the type level. There are QuickCheck and Tasty modules that aim to
> find all properties in a module and test them, but polymorphic
> properties are automatically defaulted to Integer arguments. I'm also
> tempted by Template Haskell to write what's essentially code
> generation templates.
>
> Is there a better way to go about this?
>
> Thanks,
>
> Stu
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list