Search code examples
haskelltypeclassquickcheck

typeclass challenge: having both variadic arguments and results


While writing some Arbitrary instances, I implemented a couple of functions with the following quite mechanical pattern:

type A = Arbitrary -- to cut down on the size of the annotations below
shrink1 :: (A a          ) => (a           -> r) -> (a           -> [r])
shrink2 :: (A a, A b     ) => (a -> b      -> r) -> (a -> b      -> [r])
shrink3 :: (A a, A b, A c) => (a -> b -> c -> r) -> (a -> b -> c -> [r])

shrink1 f a     = [f a'     | a' <- shrink a]
shrink2 f a b   = [f a' b   | a' <- shrink a] ++ [f a b'   | b' <- shrink b]
shrink3 f a b c = [f a' b c | a' <- shrink a] ++ [f a b' c | b' <- shrink b] ++ [f a b c' | c' <- shrink c]

I wrote out these functions by hand up to shrink7, and that seems to be sufficient for my needs. But I can't help but wonder: can this reasonably be automated? Bonus points for a solution that:

  • allows for shrink0 f = []
  • generates all the shrinkers
  • has loads of typeclass hackery, I love that
  • skips the scary extensions like incoherent/undecidable/overlapping instances
  • lets me have my cake and eat it, too: doesn't require me to uncurry f when passing it in or curry the application shrinkX f when applying it to a, b, and c

Solution

  • This compiles, I hope it works:

    {-# LANGUAGE TypeFamilies #-}
    import Test.QuickCheck
    
    class Shrink t where
      type Inp t :: *
      shrinkn :: Inp t -> t
      (++*) :: [Inp t] -> t -> t
    
    instance Shrink [r] where
      type Inp [r] = r
      shrinkn _ = []
      (++*) = (++) 
    
    instance (Arbitrary a, Shrink s) => Shrink (a -> s) where
      type Inp (a -> s) = a -> Inp s
      shrinkn f a = [ f a' | a' <- shrink a ] ++* shrinkn (f a)
      l ++* f = \b -> map ($ b) l ++* f b
    

    (++*) is only for implementing shrinkn.

    Sorry for the relative lack of typeclass hackery. The [r] provides a nice stop condition for the type recursion, so hackery isn't needed.