DerivingVia's error messages are bad

Continuing the discussion from GHC2024 – community input:

I thought I should elaborate on why I think the error messages of DerivingVia are bad, so here I go.

The error messages are bad because they mention coercion of class methods. This has a practical disadvantage: classes may have many methods, so this can cause a flood of error messages. For example consider this code:

newtype OrdList a = OrdList [a]
  deriving (Functor, Foldable) via Maybe

This produces 19 error messages. That’s insane! For anyone who did not notice, the issue here is quite simple and GHC will tell you (19 times):

    • Couldn't match representation of type: [a]
                               with that of: Maybe a

This shouldn’t be repeated 19 times.

I suspect this choice has been made because there is a case where individual methods do matter. Let’s say we correct the above mistake, but also derive Traversable:

newtype OrdList a = OrdList [a]
  deriving (Functor, Foldable, Traversable) via []

You may think nothing is wrong, but this still produces 4 error messages. That is because Traversable has some tricky methods like traverse. Let’s consider what the two instantiations of this method would look like:

traverse @[]      :: Applicative f => (a -> f b) -> [a] -> f [b]
traverse @OrdList :: Applicative f => (a -> f b) -> OrdList a -> f (OrdList b)

Coercing between these requires coercing between f [b] and f (OrdList b) but this is only possible if the first parameter of f has a phantom or representational role, but f is a variable, so we can’t know that for sure at compile time. If you can endure the deluge of error messages then you might notice that they do mention this:

        NB: We cannot know what roles the parameters to ‘f’ have;
          we must assume that the role is nominal

But note that now the error isn’t specific to the [] and OrdList instances at all. Any two different instances will fail on this method. So I would propose to report just a single error message saying that Traversable can never be derived via anything.

I think these two cases are the only possible errors, but even if that’s not the case I think it would be very useful to add special cases for these two errors.

6 Likes

As the person who implemented DerivingVia in GHC, I agree that the error message cascades here are unfortunate.

This does seem insane, although there is a reason for it. When I originally implemented DerivingVia, I encountered an example like the OrdList one above and wondered if GHC should do something like this:

  1. Add a check to see if the two types (in this example, Maybe and []) are representationally equal.
  2. If they are not representationally equal, throw a single error message stating as much and halt.
  3. If they are representationally equal, generate the instance and typecheck the individual methods.

Step (2) would ensure that we avoid the error cascade that could potentially result from step (3). Sadly, however, this approach wouldn’t work in general. Here is a counterexample:

import Data.Proxy

class HasTypeParams a where
  numTypeParams :: Proxy a -> Int

instance HasTypeParams (Maybe b) where
  numTypeParams _ = 1

instance HasTypeParams Bool where
  numTypeParams _ = 0

newtype Age = MkAge Int
  deriving HasTypeParams via Bool

Here, numTypeParams is a HasTypeParams class method where the type parameter a only appears as the argument to Proxy (this will be important later). After defining some basic HasTypeParams instances for Maybe b and Bool, we then define a HasTypeParams instance for Age (a newtype over Int) by deriving via Bool. At first glance, this seems suspect, since Int and Bool are not representationally equal. But despite this, GHC accepts this code:

> numTypeParams (Proxy @Age)
0

The reason this works is because under the hood, GHC is typechecking code that looks like this:

instance HasTypeParams Age where
  numTypeParams =
    coerce
      @(Proxy Bool -> Int)
      @(Proxy Age  -> Int)
      numTypeParams

Because Proxy has a phantom type argument, Proxy Bool is representationally equal to Proxy Age, so this code typechecks without issue. This is the main reason why GHC doesn’t implement a check like the one described in step (2) above; if it did, we wouldn’t be able to accept code like this.

Perhaps so. It’s worth noting that DerivingVia isn’t unique in this regard, however. Attempting to derive Traversable using GeneralizedNewtypeDeriving will also produce the same errors:

> newtype OrdList a = OrdList [a] deriving newtype (Functor, Foldable, Traversable)

<interactive>:8:70: error:
    • Couldn't match representation of type: m [a]
                               with that of: m (OrdList a)
        arising from the coercion of the method ‘sequence’
          from type ‘forall (m :: * -> *) a. Monad m => [m a] -> m [a]’
            to type ‘forall (m :: * -> *) a.
                     Monad m =>
                     OrdList (m a) -> m (OrdList a)’
      NB: We cannot know what roles the parameters to ‘m’ have;
        we must assume that the role is nominal
    • When deriving the instance for (Traversable OrdList)

[... error repeats three more times ...]

I suspect that these are not the only two ways that Coercible-related errors can manifest, but I agree that it would be helpful to have some way of only reporting the topmost error in a cascade of similar error messages. I haven’t thought deeply about what this would require in GHC’s implementation, but perhaps there is a way that we can:

  • Tag error messages as having a deriving-related provenance, and
  • If a group of user-reported errors all have the same message and all arise from the same derived instance, only report the first error.
2 Likes

I think this HasTypeParams example is very similar to the Traversable example, except the result is the opposite: all coercions should be allowed.

It seems to me like the parameters of type classes also have roles. E.g. Traversable has a nominal parameter while HasTypeParams has a phantom parameter. And these roles determine what you can derive.

1 Like

Class parameters already have roles: they are always nominal¹. This is so that you can’t coerce from Show Age to Show Int in case the two Show instances behave differently at runtime. Note that these roles say nothing about whether it is legal to use coerce in method definitions, so they wouldn’t be particularly useful for crafting the sorts of error messages you envision above (at least, not with GHC’s current role system).


¹ Unless you opt out of this via a combination of RoleAnnotations and IncoherentInstances. See this section of the GHC Users’ Guide.

2 Likes

Fair enough, but I feel my point still stands that there are only two exceptions to the rule that the representations have to match:

  1. Either all methods use the type in a phantom position in which case any deriving newtype/via works.
  2. Or at least one method uses the type in a nominal position in which case no deriving newtype/via is possible.

Thinking a bit more about it, I think I was very close with my idea to add roles to type class parameters. But instead of the type classes themselves, their dictionaries should have roles and those can be used to inform what kind of deriving is possible. With DerivingVia and GeneralizedNewtypeDeriving, you always want to coerce the whole dictionary anyway. If the type parameter of the dictionary is phantom then that is always possible, if it is representational then the representations need to match, and if it is nominal then no deriving should be allowed.

Hmm. Yes I think that’s right in principle. We could, I think, infer role annotations for the parameters of the dictionary type (as distinct from the always-nominal roles of the class arguments). We already have code to infer annotations.

But it’s tricky in practice, because in Core the code would look like

$fShowAge :: Show Age
$fShowAge = $fShowInt  |> co

where co :: Show Int ~ Show Age. In some ways that is exactly what we want (as you say we want to coerce the whole dictionary, and it is certainly sound to do so). But we don’t want to let the user coerce Show Age into Show Int as Ryan says. Maybe the constraint solver can be more picky for uesr-generated coercions tha for derived-generated coercions.

It’s an attractive thought.

1 Like