[GHC] #14147: Confusing error messages with PolyKinds and superclasses

GHC ghc-devs at haskell.org
Wed Aug 23 00:06:34 UTC 2017


#14147: Confusing error messages with PolyKinds and superclasses
-------------------------------------+-------------------------------------
           Reporter:  enolan         |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.1
           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:
-------------------------------------+-------------------------------------
 This program compiles fine:
 {{{#!hs
 {-# LANGUAGE FlexibleInstances #-}
 import Data.Typeable

 newtype Tagged t v = Tagged v
   deriving Typeable

 class (Typeable t) => MyClass t where
   classF :: t -> Int

 instance Typeable t => MyClass (Tagged t Int) where
   classF (Tagged n) = n
 }}}

 But if I add `PolyKinds` to the `LANGUAGE` pragma I get:
 {{{
 code/junk/typeable-problems.hs:17:10: error:
     • Could not deduce (Typeable k)
         arising from the superclasses of an instance declaration
       from the context: Typeable t
         bound by the instance declaration
         at code/junk/typeable-problems.hs:17:10-45
     • In the instance declaration for ‘MyClass (Tagged t Int)’
    |
 17 | instance Typeable t => MyClass (Tagged t Int) where
    |          ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
 }}}

 Which is very confusing since I don't have a `k` variable anywhere. Adding
 `-fprint-explicit-kinds` is somewhat better:
 {{{
 code/junk/typeable-problems.hs:17:10: error:
     • Could not deduce (Typeable * k)
         arising from the superclasses of an instance declaration
       from the context: Typeable k t
         bound by the instance declaration
         at code/junk/typeable-problems.hs:17:10-45
     • In the instance declaration for ‘MyClass (Tagged k t Int)’
    |
 17 | instance Typeable t => MyClass (Tagged t Int) where
    |          ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
 }}}

 But still confusing. It doesn't really point me towards the solution -
 specifying that the kind of t is `*` explicitly - if I don't already know
 how the extension works.

 It's also annoying that turning on an extension causes a type error, but I
 don't know if that's fixable.

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


More information about the ghc-tickets mailing list