[GHC] #15987: GHC sometimes not computing open type family application in kind inference

GHC ghc-devs at haskell.org
Sun Dec 2 20:56:57 UTC 2018


#15987: GHC sometimes not computing open type family application in kind inference
-------------------------------------+-------------------------------------
        Reporter:  sheaf             |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.6.2
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  GHC rejects       |  Unknown/Multiple
  valid program                      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:  #12088, #12643,   |  Differential Rev(s):
  #14668, #15561                     |
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):

 * related:   => #12088, #12643, #14668, #15561


Comment:

 Thanks for the bug report. This is essentially a duplicate of #12088,
 which a long-standing issue in the way that groups of type-level
 declarations are kind-checked. #12088 itself has many other
 duplicates—last time I checked, these other tickets are also essentially
 duplicates of #12008:

 * #12643
 * #14668
 * #15561

 One thing I did not realize before this ticket is that GHC's SCC analysis
 treats open and closed type families differently—thanks for that bit of
 knowledge! Another trick (that you may find useful) is that Template
 Haskell splices can often force the SCC analysis to come to its senses.
 For example, this variation on your program also compiles:

 {{{#!hs
 {-# LANGUAGE DataKinds       #-}
 {-# LANGUAGE PolyKinds       #-}
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE TypeFamilies    #-}

 module Bug where

 import Data.Kind(Type)

 type family FooKind (a :: Type) :: k
 class Foo (a :: Type) where
   type FooType a :: FooKind a

 -- OK
 type instance FooKind Bool = Type
 instance Foo Bool where
   type FooType Bool = Int

 -- OK
 data A
 type instance FooKind A = Type
 $(pure [])
 instance Foo A where
   type FooType A = Int
 }}}

 It's a bit ugly, but it's a serviceable hack.

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


More information about the ghc-tickets mailing list