[GHC] #14209: GHC 8.2.1 regression involving telescoping kind signature

GHC ghc-devs at haskell.org
Sat Sep 9 19:45:48 UTC 2017


#14209: GHC 8.2.1 regression involving telescoping kind signature
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  high           |         Milestone:  8.2.2
          Component:  Compiler       |           Version:  8.2.1
  (Type checker)                     |
           Keywords:  TypeInType     |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  GHC rejects
  Unknown/Multiple                   |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following program typechecks in GHC 8.0.1 and 8.0.2:

 {{{#!hs
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE TypeInType #-}
 module Bug where

 data MyProxy k (a :: k) = MyProxy
 data Foo (z :: MyProxy k (a :: k))
 }}}

 But in GHC 8.2.1, it's rejected:

 {{{
 GHCi, version 8.2.1: http://www.haskell.org/ghc/  :? for help
 Loaded GHCi configuration from /home/rgscott/.ghci
 [1 of 1] Compiling Bug              ( Bug.hs, interpreted )

 Bug.hs:6:1: error:
     Kind variable ‘k’ is implicitly bound in datatype
     ‘Foo’, but does not appear as the kind of any
     of its type variables. Perhaps you meant
     to bind it explicitly somewhere?
     Type variables with inferred kinds:
       (k :: *) (a :: k) (z :: MyProxy k a)
   |
 6 | data Foo (z :: MyProxy k (a :: k))
   | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
 }}}

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


More information about the ghc-tickets mailing list