
On 19 February 2012 13:12, Maxime Henrion
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. Regards, Bas