"read: no parse" with functionShow

Nick Smallbone nick.smallbone at gmail.com
Sun Jul 22 14:01:49 BST 2012


Hi Brent,

You're right that functionShow internally generates a partial function
on Strings - I hadn't thought much about that before. In itself, this
isn't a problem: the function won't be applied to arbitrary strings,
only to strings in the image of show, and QuickCheck should shrink
away the partially-defined parts to leave a total function which can
be printed. Indeed, you can generate a random function this way and
try applying it to an Elt and see that it works.

The problem is that Test.QuickCheck.Function's shrinking doesn't work
on partial functions. The shrink function will return _|_ instead of a
list of shrink candidates. Also, if you apply a showable function at
an input where there's no matching case, we pick a default result;
this default result is taken from the image of the function so can be
_|_ if the function is partial. I've just pushed a patch that fixes
all this: the shrinking works for partial functions, and we generate
default results using arbitrary instead.

(Koen may also want to chime in.)

Nick

On 22 July 2012 12:36, Brent Yorgey <byorgey at seas.upenn.edu> wrote:
> Hello,
>
> I was using the new Test.QuickCheck.Function module (which is
> otherwise lovely) and ran into a problem.  The documentation states
> (re: instances of the Function class) "If your type has a Show
> instance, you can use functionShow to write the instance".  (Actually,
> this should mention 'Read' as well, but no matter.)  So I did as
> follows:
>
>   newtype Elt = Elt { unElt :: Char }
>     deriving (Eq, Read, Show)
>
>   instance Arbitrary Elt where
>     arbitrary = elements (map Elt "abcde")
>
>   instance CoArbitrary Elt where
>     coarbitrary = coarbitrary . ord . unElt
>
>   instance Function Elt where
>     function = functionShow
>
> However, when running tests involving (Fun Elt ...), I keep getting
> "Prelude.read: no parse" errors.  This puzzled me for quite a while
> until I dove into the QuickCheck source.  I realized that functionShow
> just calls (functionMap show read)... but functionMap only works if
> the two types are *isomorphic*!  My type (and MOST types with
> Show+Read instances) is definitely not isomorphic to String; it is
> only isomorphic to a subset of String.  What seems to be happening is
> that QuickCheck is generating random Strings and then trying to
> convert them to Elts via 'read', which of course is not going to work.
>
> I next tried
>
>   instance Function Elt where
>     function = functionMap unElt Elt
>
> but although this no longer crashes, it has a similar problem:
> arbitrary Chars are being generated and then converted to Elt, which
> is wasteful since I only want to consider specifically the Chars 'a'
> through 'e', as you can see in my Arbitrary instance for Elt.  Elt is
> not really isomorphic to Char, at least not semantically.
>
> It seems the only viable way to write a Function instance for Elt would be
>
>   instance Function Elt where
>     function f = Table [(Elt c, f (Elt c)) | c <- "abcde"]
>
> but the Table constructor is not exported.  Also, even if Table were
> exported, it seems ugly having to specify essentially the same
> information as I already did for the Arbitrary instance.
>
> I suppose I could also use functionMap with Either () (Either ()
> (Either () (Either () ()))) but that seems like a hack.
>
> Any thoughts are appreciated.  Thanks!
>
> -Brent
>
> _______________________________________________
> QuickCheck mailing list
> QuickCheck at projects.haskell.org
> http://projects.haskell.org/cgi-bin/mailman/listinfo/quickcheck



More information about the QuickCheck mailing list