Reputation: 152707
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:
shrink0 f = []
f
when passing it in or curry the application shrinkX f
when applying it to a
, b
, and c
Upvotes: 9
Views: 324
Reputation: 12000
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.
Upvotes: 9
Reputation: 7140
I doubt you can avoid scary extensions in this case, but otherwise:
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, TypeFamilies,
UndecidableInstances, IncoherentInstances #-}
import Test.QuickCheck
class Shrinkable a r where
shrinkn :: a -> r
instance (Shrinkable [a -> b] r) => Shrinkable (a -> b) r where
shrinkn f = shrinkn [f]
instance (Arbitrary a, Shrinkable [b] r1, r ~ (a -> r1)) => Shrinkable [a -> b] r where
shrinkn fs@(f:_) a =
let fs' = [f a | f <- fs]
in shrinkn $ fs' ++ [f a' | a' <- shrink a]
instance (r ~ [a]) => Shrinkable [a] r where
shrinkn (_:vs) = vs
instance (r ~ [a]) => Shrinkable a r where
shrinkn e = []
Here are a few Quickcheck properties to test against your example functions:
prop0 a = shrinkn a == []
prop1 a = shrink1 not a == shrinkn not a
prop2 a b = shrink2 (++) a b == shrinkn (++) a b
f3 a b c = if a then b + c else b * c
prop3 a b c = shrink3 f3 a b c == shrinkn f3 a b c
Upvotes: 2