Inferring instance constraints with DeriveAnyClass

Ryan Scott ryan.gl.scott at gmail.com
Mon Jun 13 19:32:26 UTC 2016


Andres,

I'm trying to think of a proper solution to Trac #12144 [1]. This bug
triggers when you try to use DeriveAnyClass in a somewhat exotic
fashion:

    {-# LANGUAGE DeriveAnyClass, KindSignatures #-}
    class C (a :: * -> *)
    data T a = MkT (a -> Int) deriving C

This currently gives a GHC panic:

    ghc: panic! (the 'impossible' happened)
      (GHC version 8.0.1 for x86_64-unknown-linux):
            contravariant

This baffled me until I realized why it's happening: for typeclasses
of kind * -> *, DeriveAnyClass simply re-uses the same algorithm that
DeriveFunctor uses for coming up with an instance context. For
instance, if you have:

    data T f a = MkT a (f a) deriving (Functor, C)

Then it would generate two instances of the form:

    instance Functor f => Functor (T f) where ...
    instance C f => C (T f) where ...

But #12144 reveals the fatal downside of doing this: DeriveFunctor has
special knowledge about type parameters in contravariant positions,
but this doesn't even make sense to think about with a class like C!
(The only reason GHC won't panic if a Functor instance is derived for
T is because there are Functor-specific checks that cause an error
message to pop up before the panic can be reached.)

My question is then: why does DeriveAnyClass take the bizarre approach
of co-opting the DeriveFunctor algorithm? Andres, you originally
proposed this in #7346 [2], but I don't quite understand why you
wanted to do it this way. Couldn't we infer the context simply from
the contexts of the default method type signatures? This is a question
that Reid Barton has also asked, to which José Pedro Magalhães
answered in the negatory [3]. But Pedro's reasoning has never quite
made sense to me, because we've been able to typecheck constraints
arising from default method type signatures for a long time, so why
would it be impractical to do so in this case?

I'd appreciate hearing a more detailed explanation on this issue,
because at the moment, I am completely stuck on figuring out how one
might fix #12144.

Regards,

Ryan S.
-----
[1] https://ghc.haskell.org/trac/ghc/ticket/12144
[2] https://ghc.haskell.org/trac/ghc/ticket/7346
[3] https://ghc.haskell.org/trac/ghc/ticket/5462#comment:30


More information about the ghc-devs mailing list