Please use Generically instead of DefaultSignatures!

16 Likes

One issue is that it’s not really a replacement, due to how coercions work.

Consider the following program:

import GHC.Generics

class Foo a where
  foo :: proxy a -> Int
  default foo :: Eq a => proxy a -> Int
  foo _ = 42
  
instance Eq a => Foo (Generically a) where 
  foo _ = 42

data B 
  deriving stock Eq
  deriving anyclass Foo
  -- deriving Foo via (Generically B)

The -XDerivingVia version won’t work because the type role of proxy is not clear.

You can add the forall a b. Coercible a b => Coercible (proxy a) (proxy b) constraint to the class method + use standalone deriving when deriving via but I think it’s clear why that’s not an option “in reality”.

Also this does come up in practice quite often, e.g. you cannot Generically derive Generics.SOP via Generically.

1 Like

Worth noting that it does work fine if you use Proxy instead of proxy.

But I guess more generally it won’t work if the class type variable appears in a role where it has nominal role. So e.g. this doesn’t work either:

import GHC.Generics
import Data.Set

class Foo a where
  foo :: Set a -> Int
  
instance Eq a => Foo (Generically a) where 
  foo _ = 42

data B 
  deriving stock Eq
  deriving Foo via (Generically B)

whereas it does work with list. An interesting and non-obvious problem!

(It’s actually perfectly correct: nothing stops us from providing a different Ord instance for Generically a than for a, so Sets over the two should not be coercible!)

3 Likes

In this particular case, it’s enough to use the GGP module: https://hackage.haskell.org/package/generics-sop-0.5.1.4/docs/src/Generics.SOP.GGP.html#gdatatypeInfo

what does this change wrt via deriving?