+1

I would just suggest calling the exported function `genericRnf`.


Cheers,
Pedro

On Fri, Sep 21, 2012 at 10:21 AM, Herbert Valerio Riedel <hvr@gnu.org> wrote:
Hello Simon (et al.),

Some time ago, the `generic-deepseq` package was announced to the
haskell-cafe list, and some discussion took place[1], and the suggestion
came up that it might useful to be included to `deepseq` somehow.

IMHO, a least introduing way (which I've been using myself) would be to
add something along the code below to the `Control.DeepSeq` module (only
`genericsRnf` shall be exported, thus avoiding a PVP-major-bump):


    -- | Generics-based 'rnf' implementation
    genericsRnf :: (Generic a, GNFData (Rep a)) => a -> ()
    genericsRnf = grnf_ . from
    {-# INLINE genericRnf #-}

    -- | Hidden type-class, /not/ exported
    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 a => GNFData (M1 i c a) where
        grnf_ = grnf_ . unM1
        {-# INLINE grnf_ #-}

    instance (GNFData a, GNFData b) => GNFData (a :*: b) where
        grnf_ (x :*: y) = grnf_ x `seq` grnf_ y
        {-# INLINE grnf_ #-}

    instance (GNFData a, GNFData b) => GNFData (a :+: b) where
        grnf_ (L1 x) = grnf_ x
        grnf_ (R1 x) = grnf_ x
        {-# INLINE grnf_ #-}



this way, the client code can then chose to use a Generics-derived `rnf`
implementation expliclity by simply declaring:

    instance NFData FooBar where rnf = genericsRnf


...does this sound sensible?


cheers,
  hvr

 [1]: http://www.haskell.org/pipermail/haskell-cafe/2012-February/099551.html

--

_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://www.haskell.org/mailman/listinfo/libraries