[Haskell-cafe] ANN: generic-deepseq 1.0.0.0

Maxime Henrion mhenrion at gmail.com
Sun Feb 19 18:11:51 CET 2012


On Sun, 2012-02-19 at 16:17 +0100, Bas van Dijk wrote:
> On 19 February 2012 13:12, Maxime Henrion <mhenrion at gmail.com> wrote:
> > Any suggestions are welcome.
> 
> Nice work but it would be nice to have this functionality directly in
> the deepseq package as in:
> 
> #ifdef GENERICS
> {-# LANGUAGE DefaultSignatures, TypeOperators, FlexibleContexts #-}
> #endif
> 
> class NFData a where
>     rnf :: a -> ()
>     rnf a = a `seq` ()
> 
> #ifdef GENERICS
>     default rnf :: (Generic a, GNFData (Rep a)) => a -> ()
>     rnf = grnf . from
> 
> class GNFData f where
>     grnf :: f a -> ()
> 
> instance GNFData U1 where
>     grnf U1 = ()
>     {-# INLINE grnf #-}
> 
> instance NFData a => GNFData (K1 i a) where
>     grnf = rnf . unK1
>     {-# INLINE grnf #-}
> 
> instance GNFData f => GNFData (M1 i c f) where
>     grnf = grnf . unM1
>     {-# INLINE grnf #-}
> 
> instance (GNFData f, GNFData g) => GNFData (f :+: g) where
>     grnf (L1 x) = grnf x
>     grnf (R1 x) = grnf x
>     {-# INLINE grnf #-}
> 
> instance (GNFData f, GNFData g) => GNFData (f :*: g) where
>     grnf (x :*: y) = grnf x `seq` grnf y
>     {-# INLINE grnf #-}
> #endif
> 
> Unfortunately this is not possible since the two default
> implementations conflict. I see two solutions:
> 
> 1) Change the DefaultSignatures extension to always give preference to
> the default signature. I think giving preference to the default
> signature makes sense since it's usually more specific (more
> constraint) and thus "more correct" than the default implementation.
> 
> 2) Remove the default implementation of rnf. I understand the default
> implementation gives some convenience when writing instances for types
> that have an all strict representation, as in:
> 
> instance NFData Int
> instance NFData Word
> instance NFData Integer
> ...
> 
> However, I think having the default implementation can mask some bugs as in:
> data T = C Int; instance NFData T
> which will neither give a compile time error nor warning.
> 
> I don't think it's that much more inconvenient to write:
> 
> instance NFData Int where rnf = rnf'
> instance NFData Word where rnf = rnf'
> instance NFData Integer where rnf = rnf'
> ...
> where
> rnf' :: a -> ()
> rnf' a = a `seq` ()
> 
> So I would vote for option 2, removing the default rnf implementation.
> If I find some time I will turn this into an official proposal.

I agree it would have been nice to have that functionality directly in
the deepseq package, or at least in a way that extends the existing
functionality rather than completely replace it. However, as you noted,
it isn't possible to do that in a backwards compatible way, unless we
hack the implementation of the DefaultSignatures extension. That being
said, even if it was possible to do this in a backwards compatible way,
I'm not entirely sure it would be desirable to do so  because there is
one subtle difference between this code and the deepseq package.

With the generic-deepseq package, you should only need to provide an
explicit DeepSeq instance for some type if it is abstract, because you
can't get a Generic instance in that case (unless the library author
derived Generic himself, but that would be a weird and dangerous thing
to do for an abstract datatype). If you're not dealing with an abstract
datatype, you _shouldn't_ have an explicit instance, because it would be
possible to write an incorrect one, while that is impossible if you just
derive a generic implementation (as long as the generic code is correct,
of course).

So, knowing that it would necessarily be backwards incompatible (I
wasn't intending to hack on GHC :-), and also that, in the end, this is
not quite the same class as the NFData class from the deepseq package, I
thought it made more sense to create another package that would be
mostly compatible with deepseq, but with a different class name so as to
force people to reevaluate the need for their instances if they have
some. I'd be interested in knowing what you and others think about that.
Maybe I'm being overly cautious?

I kept the rest of the API identical so that it's still easy to switch
to this package, thus you can still use the ($!!), force, and rnf
functions. I'm guilty of not having preserved the "rnf :: a -> ()"
function as the class function though, it's a wrapper around "deepseq"
in my code. I just didn't see the point of having a class function with
such a signature versus having a function just like "seq :: a -> b ->
b". In retrospect, that might have been a bad idea, and maybe I should
switch to have an "rnf :: a -> ()" class function to make switching even
easier?

Thanks a lot for your input!

Maxime Henrion
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 834 bytes
Desc: This is a digitally signed message part
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120219/a499c6c2/attachment.pgp>


More information about the Haskell-Cafe mailing list