[Haskell-cafe] [QuickCheck] Fwd: an idea for improving 'shrink'

Petr Pudlák petr.mvd at gmail.com
Wed Sep 17 09:51:28 UTC 2014


Hi Nick,

you're right, this example is indeed problematic. I'll try to think about
it how to get around that, keeping backward compatibility.

  Petr
Dne 11. 9. 2014 21:37 "Nick Smallbone" <nicsma at chalmers.se> napsal(a):

> Hi Petr,
>
> My attitude has always been "just use the shrink instance for tuples".
> I don't think there's all that much difference between:
>   shrink (C x y) = [ C x' y' | (x', y') <- shrink (x, y) ]
> and:
>   shrink (C x y) = C <$> shrink x <*> shrink y
> The second is certainly nicer, but neither way is really very painful.
>
> However, your shrinkOne example shows a case where shrinking tuples
> doesn't work and you really need a shrinking Applicative.
> So this is a good reason to add a shrinking Applicative to QuickCheck
> and I would probably like to do it at some point.
>
> There is a problem with your current patch, though. Namely the default
> implementation of shrinkA:
>   shrinkA = pure
> If someone defines shrink but not shrinkA, then shrinkA will not
> shrink! In fact, one of your examples exhibits this bug:
>   shrinkA (Branch x l r) =
>     Branch <$> shrinkA x <*> shrinkA l <*> shrinkA r
> If the Arbitrary instance for whatever x is defines shrink but not
> shrinkA, then this will do the wrong thing.
>
> So we can't provide a default implementation for shrink in terms of
> shrinkA, or vice versa, because we want the user to be able to define
> either. We can't even define both in terms of the other because then
> the default implementation will loop instead of returning [].
>
> Probably we would just have to move shrinkA outside of the Arbitrary
> class. This does make using the Applicative more cumbersome, e.g.:
>   shrink (C x y) = fromShrink (C <$> shrinkA x <*> shrinkA y)
>   shrinkOne shr = fromShrink . traverse (Shrink . shr)
> but maybe this would still be useful for defining trickier shrink
> functions.
>
> Anyway, this is the only worry I have - how to integrate the
> traditional and applicative-based shrinking without too much syntactic
> overhead. If we can come up with a good solution for that then I'd be
> very eager to add this to QuickCheck. Or maybe calling fromShrink
> isn't so painful and we should add it anyway. I will think it over a
> bit...
>
> Nick
>
> On Saturday 06 September, 2014 at 11:17 am, Petr Pudlák wrote:
> > 2014-09-05 18:22 GMT+02:00 Bryan O’Sullivan <bos at serpentine.com>:
> >
> >
> > > On Thu, Sep 4, 2014 at 1:06 PM, Petr Pudlák <petr.mvd at gmail.com>
> wrote:
> > >
> > >> since I got no response from the QuickCheck mail address, so I'm
> > >> resending it here, if someone wants to comment on the idea.
> > >>
> > >
> > > I don't think it pays its way: it makes shrink a bit tidier, at the
> cost
> > > of breaking backwards compatibility in a widely used library.
> > >
> > That’s a problem. But I believe it the patch addresses it. QuickCheck
> > always uses ‘shrink’, not ‘shrinkA’, and as the default implementation of
> > ‘shrink’ is defined in terms of ‘shrinkA’, then it’s possible to define
> > instances both using ‘shrink’ and using ‘shrinkA’. So both old code and
> new
> > code that wants to take advantage of the Applicative interface work.
> >
> > I believe that in the long term this change would pay off: Compare the
> old
> > code
> >
> >  shrinkOne []     = []
> >  shrinkOne (x:xs) = [ x':xs | x'  <- shr x ]
> >                  ++ [ x:xs' | xs' <- shrinkOne xs ]
> >
> >  shrink (x, y) =
> >       [ (x', y) | x' <- shrink x ]
> >    ++ [ (x, y') | y' <- shrink y ]
> >
> >  shrink (x, y, z) =
> >    [ (x', y', z')
> >    | (x', (y', z')) <- shrink (x, (y, z)) ]
> >
> > against the improved piece
> >
> > traverse shr xs -- replaces the whole shrinkOne
> > shrinkA (x, y) = liftA2 (,) (shrinkA x) (shrinkA y)
> > shrinkA (x, y, z) = liftA3 (,,) (shrinkA x) (shrinkA y) (shrinkA z)
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140917/e4bd01d2/attachment.html>


More information about the Haskell-Cafe mailing list