[GHC] #15308: Error message prints explicit kinds when it shouldn't

GHC ghc-devs at haskell.org
Sun Jun 24 13:49:22 UTC 2018


#15308: Error message prints explicit kinds when it shouldn't
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.6.1
          Component:  Compiler       |           Version:  8.4.3
  (Type checker)                     |
           Keywords:  TypeInType     |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Poor/confusing
  Unknown/Multiple                   |  error message
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 When compiled, this program:

 {{{#!hs
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeInType #-}
 {-# OPTIONS_GHC -fno-print-explicit-kinds #-}
 module Bug where

 import Data.Kind

 data Foo (a :: Type) :: forall b. (a -> b -> Type) -> Type where
   MkFoo :: Foo a f

 f :: Foo a f -> String
 f = show
 }}}

 Gives the following error:

 {{{
 $ /opt/ghc/8.4.3/bin/ghc Bug.hs
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )

 Bug.hs:13:5: error:
     • No instance for (Show (Foo a b f)) arising from a use of ‘show’
     • In the expression: show
       In an equation for ‘f’: f = show
    |
 13 | f = show
    |     ^^^^
 }}}

 This error message is slightly incorrect, however. In "`No instance for
 (Show (Foo a b f))`", it claims that `Foo` has three visible type
 parameters, but it only has two. (I've even made sure to enable `-fno-
 print-explicit-kinds` at the type to ensure that the invisible `b` kind
 shouldn't get printed, but it was anyway.)

 This is a regression that was apparently introduced between GHC 8.0 and
 8.2, since in GHC 8.0.2, it prints the correct thing:

 {{{
 $ /opt/ghc/8.0.2/bin/ghc Bug.hs
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )

 Bug.hs:13:5: error:
     • No instance for (Show (Foo a f)) arising from a use of ‘show’
     • In the expression: show
       In an equation for ‘f’: f = show
 }}}

 But it does not in GHC 8.2.1:

 {{{
 $ /opt/ghc/8.2.1/bin/ghc Bug.hs
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )

 Bug.hs:13:5: error:
     • No instance for (Show (Foo a b f)) arising from a use of ‘show’
     • In the expression: show
       In an equation for ‘f’: f = show
    |
 13 | f = show
    |     ^^^^
 }}}

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


More information about the ghc-tickets mailing list