[GHC] #13742: Code using ConstraintKinds needs explicit kind signature with GHC 8.2.1

GHC ghc-devs at haskell.org
Tue May 23 04:14:21 UTC 2017


#13742: Code using ConstraintKinds needs explicit kind signature with GHC 8.2.1
-------------------------------------+-------------------------------------
        Reporter:  albertov          |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  highest           |            Milestone:
       Component:  Compiler (Type    |              Version:  8.2.1-rc2
  checker)                           |             Keywords:
      Resolution:                    |  ConstraintKinds, KindSignatures
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:                    |
-------------------------------------+-------------------------------------

Comment (by ezyang):

 Here is a more minimized example:

 {{{
 {-# LANGUAGE KindSignatures #-}
 {-# LANGUAGE ConstraintKinds #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE UndecidableInstances #-}
 {-# LANGUAGE UndecidableSuperClasses #-}
 {-# LANGUAGE FlexibleContexts #-}

 module CKBug where

 import GHC.Exts (Constraint)

 type A l = (D l
   -- :: Constraint) -- Uncommenting this line allows GHC 8.2.1 to compile
 this
   )

 type B l = ( A l, A l )

 class B l => C l where
   type D l :: Constraint
 }}}

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


More information about the ghc-tickets mailing list