[GHC] #14132: Report an error for a missing class instance before an error for type family instances of an associated type.

GHC ghc-devs at haskell.org
Thu Aug 17 00:34:53 UTC 2017


#14132: Report an error for a missing class instance before an error for type
family instances of an associated type.
-------------------------------------+-------------------------------------
           Reporter:  duog           |             Owner:  (none)
               Type:  feature        |            Status:  new
  request                            |
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.1
  (Type checker)                     |
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following code
 {{{
 {-# LANGUAGE FlexibleContexts, TypeFamilies, DataKinds #-}

 import GHC.Generics
 import GHC.TypeLits

 type family RepHasNoInstance (f :: * -> *) ::  *

 -- edit 1
 -- type instance RepHasNoInstance f = Int

 -- edit 2
 -- class RepHasNoInstanceC (f :: * -> *)
 -- foo :: (Generic a, RepHasNoInstanceC (Rep a)) => a -> Int
 -- foo = const 1
 foo :: (Generic a, RepHasNoInstance (Rep a) ~ Int) => a -> Int
 foo = const 1

 data NotGeneric = NotGeneric

 bar :: NotGeneric -> Int
 bar = foo

 main :: IO ()
 main = return ()
 }}}

 gives an error like
 {{{
 associated-type-families-test.hs:21:7: error:
     • Couldn't match type ‘RepHasNoInstance (Rep NotGeneric)’
                      with ‘Int’
         arising from a use of ‘foo’
     • In the expression: foo
       In an equation for ‘bar’: bar = foo
    |
 21 | bar = foo
    |       ^^^
 }}}
 in ghcs: 8.0.2, 8.2.1, master(a few days old).

 The error message is for ambiguous types in 7.10.3

 Uncommenting edit 1, the error changes to:
 {{{
 associated-type-families-test.hs:16:7: error:
     • No instance for (Generic NotGeneric) arising from a use of ‘foo’
     • In the expression: foo
       In an equation for ‘bar’: bar = foo
    |
 16 | bar = foo
    |
 }}}

 I think this is a much better error message, since there is no hope for
 the associated type to have an instance for anything unless there is an
 instance (Generic NotGeneric).

 Uncommenting edit 2, (and commenting the existing foo) gives the "No
 instance for (Generic NotGeneric)" message.

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


More information about the ghc-tickets mailing list