The practice seems to be to not export it, but maybe it would be a better practice to export it. That way it can work without DefaultSignatures too, and if you use the generic-deriving package it could work with zero extensions or GHC-specific dependencies.

Are you adding support to hashable after all? I'd love that, but thought you decided against it because of the clash with the existing defaults.


On Wed, Dec 12, 2012 at 5:28 AM, Johan Tibell <johan.tibell@gmail.com> wrote:
Hi,

I noticed that you're not required to export the types mentioned in
the default method signature. For example, you could have:

    default hashWithSalt :: (Generic a, GHashable (Rep a)) => Int -> a -> Int
    hashWithSalt salt = ghashWithSalt salt . from

and not export the GHashable class. However, if users try to define an
instance of Hashable but forget to derive Generic:

    data Foo a = Foo a String
                 deriving (Eq)  -- Oops, forgot Generic here

    instance (Hashable a) => Hashable (Foo a)

they get a pretty bad error message:

Test.hs:10:10:
    Could not deduce (Generic (Foo a),
                      Data.Hashable.Class.GHashable (GHC.Generics.Rep (Foo a)))
      arising from a use of `Data.Hashable.Class.$gdmhashWithSalt'
    from the context (Hashable a)
      bound by the instance declaration at Test.hs:10:10-41
    Possible fix:
      add (Generic (Foo a),
           Data.Hashable.Class.GHashable
             (GHC.Generics.Rep (Foo a))) to the context of
        the instance declaration
      or add instance declarations for
         (Generic (Foo a),
          Data.Hashable.Class.GHashable (GHC.Generics.Rep (Foo a)))
    In the expression: (Data.Hashable.Class.$gdmhashWithSalt)
    In an equation for `hashWithSalt':
        hashWithSalt = (Data.Hashable.Class.$gdmhashWithSalt)
    In the instance declaration for `Hashable (Foo a)'

Exporting GHashable would help a little bit in that users would at
least know what this GHashable class that the error talks about is.

What's best practice?

-- Johan

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe