[Haskell-cafe] Testing polymorphic properties with QuickCheck

Stuart Hungerford stuart.hungerford at gmail.com
Wed Feb 18 20:41:25 UTC 2015


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


More information about the Haskell-Cafe mailing list