[GHC] #11719: Cannot use higher-rank kinds with type families

GHC ghc-devs at haskell.org
Wed Oct 10 19:19:10 UTC 2018


#11719: Cannot use higher-rank kinds with type families
-------------------------------------+-------------------------------------
        Reporter:  ocharles          |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:  8.8.1
       Component:  Compiler (Type    |              Version:  8.0.1-rc2
  checker)                           |
      Resolution:                    |             Keywords:  TypeInType
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  GHC rejects       |            Test Case:
  valid program                      |  dependent/should_compile/T11719
      Blocked By:                    |             Blocking:
 Related Tickets:  #13913            |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by RyanGlScott):

 Replying to [comment:14 goldfire]:
 > On the other hand, `F2` must return a polykinded constructor, and can
 have only one instance.

 That doesn't appear to be true, since this program (with multiple `F2`
 instances) typechecks:

 {{{#!hs
 {-# LANGUAGE DataKinds #-}
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeFamilies #-}
 module Bug where

 import Data.Kind

 type family F2 :: forall k. k -> Type
 type instance F2 = SBool
 type instance F2 = STuple0

 data SBool :: Bool -> Type where
   SFalse :: SBool False
   STrue  :: SBool True
 data STuple0 :: () -> Type where
   STuple0 :: STuple0 '()
 }}}

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


More information about the ghc-tickets mailing list