Trying to refactor DeriveAnyClass, stuck on typechecker-related code

Ryan Scott ryan.gl.scott at gmail.com
Sun Aug 28 01:02:37 UTC 2016


Indeed, I managed to fix the type family reduction problem by
partially CPSing the genInst function, which allowed me to collect the
Rep instance and add it to the environment before invoking
simplifyInstanceContexts.

But I've ran into another, probably more fundamental issue. Consider
the following example (adapted from
https://ghc.haskell.org/trac/ghc/ticket/12423):

    class Eq1 f where
      (==#) :: forall a. Eq a => f a -> f a -> Bool
      default (==#) :: forall x y. (Eq (f x), Eq (f y))
                    => f x -> f y -> Bool
      (==#) x y = x == x && y == y

    data Foo a = Foo (Maybe a)
        deriving (Eq, Eq1)

With my changes, the above derived Eq1 Foo instance will fail with the
following error:

    No instance for (Eq x)
      arising from the first field of ‘Foo’ (type ‘Maybe a’)

(But a manually defined Eq1 Foo works.) This error message is bizarre,
but it makes sense when you think about how the new DeriveAnyClass
context inference algorithm works:

* First, GHC collects the constraints from the default signatures (Eq
(f x), Eq (f y))
* Then, it substitutes the class variable (f) with the instantiated
type (Foo) to obtain (Eq (Foo x), Eq (Foo y))
* Then, it reduces (Eq (Foo x), Eq (Foo y)) by using the existing
instance Eq a => Eq (Maybe a) to obtain (Eq x, Eq y)
* Then, it tries to solve (Eq x) as a wanted constraint

At that point, GHC stops, since the only given constraint is (Eq a)
from the (non-default) type signature for (==#), but the type variable
a is completely different from x (and y)! For better or worse, the
forall'd type variables in the non-default type signature for (==#)
have no relation to the ones in the default type signature (cf. Trac
#12533).

Somehow, I have to figure out how to make GHC use (Eq a) to discharge
the (Eq x) and (Eq y) obligations, but I have no idea how to do that.
Does anyone have ideas?

Ryan S.

On Sat, Aug 27, 2016 at 6:37 PM, Matthew Pickering
<matthewtpickering at gmail.com> wrote:
> Ryan and I chatted about this on IRC and he has a plan to fix this problem.
>
> On Sat, Aug 27, 2016 at 5:07 PM, Ryan Scott <ryan.gl.scott at gmail.com> wrote:
>> Simon,
>>
>> I'm currently working on a solution to #12144, which changes the way
>> inferred contexts for DeriveAnyClass works, as per your suggestion
>> here [1]. I've made some good progress in that instances derived using
>> DeriveAnyClass now emit contexts that are gathered from the default
>> signatures of the derived class itself.
>>
>> However, I've come to an impasse. This approach currently fails to
>> work with most GHC Generics-style classes, for reasons that I'll
>> explain below. Consider this example (abridged from here [2]):
>>
>>     data StrictMaybe a = StrictNothing | StrictJust !a
>>       deriving (FullyStrict, Generic)
>>
>>     class FullyStrict a where
>>       fullyStrict :: proxy a -> Bool
>>       default fullyStrict :: (GFullyStrict (Rep a)) => proxy a -> Bool
>>       fullyStrict _ = gfullyStrict (Proxy :: Proxy (Rep a p))
>>
>> With the new approach, the derived FullyStrict instance for
>> StrictMaybe a will emit the context (GFullyStrict (Rep (StrictMaybe
>> a)), but then fail with the error:
>>
>>     No instance for (GFullyStrict (Rep (StrictMaybe a))
>>
>> I think I understand why this is happening: if you look at the
>> definition of tcDeriving in TcDeriv [3], it calls
>> simplifyInstanceContexts, which would normally reduce type families
>> like Rep. But the problem is that the Rep (StrictMaybe a) instance is
>> also being derived at the same time (via the derived Generic
>> instance)! What's worse, the call to simplifyInstanceContexts happens
>> before the code that adds Rep (StrictMaybe a) to the type family
>> instance environment (tcExtendLocalFamInstEnv (bagToList famInsts)).
>> So simplifyInstanceContexts is unable to reduce Rep (StrictMaybe a),
>> and as a result the context fails to simplify, resulting in the above
>> error.
>>
>> This leads me to think we need to be adding Rep (StrictMaybe a) to the
>> instance environment before calling simplifyInstanceContexts. But with
>> the way the code is structured currently, I don't see an easy way to
>> do this. The problem is that the genInst function [4] generates all of
>> the following at the same time in one large bundle:
>>
>> * The instance code itself (InstInfo RdrName)
>> * The associated type family instances (BagDerivStuff)
>> * Auxiliary top-level bindings (BagDerivStuff)
>>
>> And within tcDeriving, the call to genInst takes as input the output
>> of simplifyInstanceContexts, making it impossible to get the type
>> family instances before calling simplifyInstanceContexts.
>>
>> Here are my questions: is it possible to take type family instances
>> out of BagDerivStuff and instead add them to the instance environment
>> before simplifyInstanceContexts? Would there be any typechecking
>> issues involved with having the associated family instances in the
>> local environment before the actual class instances themselves?
>>
>> Ryan S.
>> -----
>> [1] https://mail.haskell.org/pipermail/ghc-devs/2016-June/012276.html
>> [2] http://git.haskell.org/ghc.git/blob/0050aff22ba04baca732bf5124002417ab667f8a:/testsuite/tests/generics/GFullyStrict.hs
>> [3] http://git.haskell.org/ghc.git/blob/0050aff22ba04baca732bf5124002417ab667f8a:/compiler/typecheck/TcDeriv.hs#l364
>> [4] http://git.haskell.org/ghc.git/blob/0050aff22ba04baca732bf5124002417ab667f8a:/compiler/typecheck/TcDeriv.hs#l2269
>> _______________________________________________
>> ghc-devs mailing list
>> ghc-devs at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


More information about the ghc-devs mailing list