[GHC] #9948: Recommend class constraint instead of instance constraint

GHC ghc-devs at haskell.org
Thu Jan 1 21:00:34 UTC 2015


#9948: Recommend class constraint instead of instance constraint
-------------------------------------+-------------------------------------
              Reporter:  crockeea    |             Owner:
                  Type:  feature     |            Status:  new
  request                            |         Milestone:
              Priority:  normal      |           Version:  7.8.4
             Component:  Compiler    |  Operating System:  Unknown/Multiple
              Keywords:              |   Type of failure:  None/Unknown
          Architecture:              |        Blocked By:
  Unknown/Multiple                   |   Related Tickets:
             Test Case:              |
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
 Consider the following example:

 {{{#!hs
 {-# LANGUAGE FlexibleInstances, UndecidableInstances #-}

 module Foo where

 class Foo a where
   foo :: Int -> a

 instance (Num a) => Foo a where
   foo x = error ""

 f :: Int -> a
 f = foo
 }}}

 GHC says

 {{{
 No instance for (Num a) arising from a use of ‘foo’
     Possible fix:
       add (Num a) to the context of the type signature for f :: Int -> a
     In the expression: foo
     In an equation for ‘f’: f = foo
 }}}

 A better error, in my opinion, would be:

 {{{
 No instance for (Foo a) arising from a use of ‘foo’
     Possible fix:
       add (Foo a) to the context of the type signature for f :: Int -> a
     In the expression: foo
     In an equation for ‘f’: f = foo
 }}}

 That is, I think GHC should recommend the superclass constraint arising
 from the use of `foo` rather than trying to match an instance and then
 recommending constraints from the instance.

 Here are several reasons a superclass constraint is preferable:

 1. If the matching instance has several constraints, GHC will recommend
 putting *all* of those constraints on the function instead of a single
 superclass constraint. This (naively) results in unnecessarily long
 constraints on functions that call methods.

 2. If the constraints on the instance change, GHC will recommend the
 corresponding change on the function constraints. This means the instance
 constraints are not isolated, but instead propagate through the code.

 3. The instance constraints might not make sense on the function itself.
 For example, `f` might not use any methods from the `Num` class, but GHC
 recommends the `Num` constraint anyway.

 Recommending the direct superclass constraint should be **less** work for
 GHC than the current implementation: instead of trying to find a matching
 instance, it simply stops when it finds that `foo` is a method.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9948>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list