[GHC] #15142: GHC HEAD regression: tcTyVarDetails

GHC ghc-devs at haskell.org
Sat May 12 10:57:39 UTC 2018


#15142: GHC HEAD regression: tcTyVarDetails
-------------------------------------+-------------------------------------
        Reporter:  RyanGlScott       |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  highest           |            Milestone:  8.6.1
       Component:  Compiler (Type    |              Version:  8.5
  checker)                           |             Keywords:  TypeInType,
      Resolution:                    |  TypeFamilies
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Compile-time      |  Unknown/Multiple
  crash or panic                     |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by RyanGlScott):

 Some more observations about this:

 * If you swap out `TypeInType` for just `DataKinds` and `PolyKinds`, then
 the program no longer panics, so `TypeInType` appears to be critical in
 triggering this panic.
 * If you try and give the parameter to `ListToTuple` an explicit kind
 signature:

   {{{#!hs
   {-# LANGUAGE MultiParamTypeClasses #-}
   {-# LANGUAGE TypeFamilies #-}
   {-# LANGUAGE TypeInType #-}
   module Bug where

   import Data.Kind

   class ListTuple (tuple :: Type) (as :: [(k, Type)]) where
     type ListToTuple (as :: [(k, Type)]) :: Type
   }}}

   Then this will typecheck on GHC 8.4.2, but on HEAD it will give an error
 message:

   {{{
   $ ~/Software/ghc/inplace/bin/ghc-stage2 Bug.hs
   [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )

   Bug.hs:9:29: error:
       • Expected a type, but ‘k’ has kind ‘k0’
       • In the kind ‘[(k, Type)]’
     |
   9 |   type ListToTuple (as :: [(k, Type)]) :: Type
     |                             ^
   }}}

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


More information about the ghc-tickets mailing list