[GHC] #8985: Strange kind error with type family, GADTs, data kinds, and kind polymorphism

#8985: Strange kind error with type family, GADTs, data kinds, and kind polymorphism -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.1 checker) | Operating System: Unknown/Multiple Keywords: | Type of failure: GHC rejects Architecture: Unknown/Multiple | valid program Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | -------------------------------------+------------------------------------- Consider the following test case (I've tried hard to make it minimal, which unfortunately means there's not a lot of intuition left): {{{ {-# LANGUAGE DataKinds, PolyKinds, TypeFamilies, GADTs, TypeOperators #-} data X (xs :: [k]) = MkX data Y :: (k -> *) -> [k] -> * where MkY :: f x -> Y f (x ': xs) type family F (a :: [[*]]) :: * type instance F xss = Y X xss works :: Y X '[ '[ ] ] -> () works (MkY MkX) = () fails :: F '[ '[ ] ] -> () fails (MkY MkX) = () }}} This code compiles in GHC 7.6.3, but it fails in GHC 7.8.1 (both rc2 and the actual release) with the following error: {{{ TestCase.hs:14:8: Couldn't match kind ‘k0’ with ‘*’ Expected type: F '['[]] Actual type: Y t0 t1 In the pattern: MkY MkX In an equation for ‘fails’: fails (MkY MkX) = () TestCase.hs:14:12: Couldn't match type ‘t0’ with ‘X’ ‘t0’ is untouchable inside the constraints (t1 ~ (x : xs)) bound by a pattern with constructor MkY :: forall (f :: k -> *) (x :: k) (xs :: [k]). f x -> Y f (x : xs), in an equation for ‘fails’ at TestCase.hs:14:8-14 Expected type: t0 x Actual type: X x In the pattern: MkX In the pattern: MkY MkX In an equation for ‘fails’: fails (MkY MkX) = () }}} I'm puzzled that simply adding the type family invokation makes the type checker fail with a kind error, even though the type family itself itsn't kind-polymorphic. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8985 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8985: Strange kind error with type family, GADTs, data kinds, and kind polymorphism ----------------------------------------------+---------------------------- Reporter: kosmikus | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects valid program | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------------+---------------------------- Comment (by simonpj): Thank you. It's a palpable bug in the kind unifier. Working on it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8985#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8985: Strange kind error with type family, GADTs, data kinds, and kind
polymorphism
----------------------------------------------+----------------------------
Reporter: kosmikus | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type checker) | Version: 7.8.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects valid program | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
----------------------------------------------+----------------------------
Comment (by Simon Peyton Jones

#8985: Strange kind error with type family, GADTs, data kinds, and kind
polymorphism
----------------------------------------------+----------------------------
Reporter: kosmikus | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type checker) | Version: 7.8.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects valid program | Unknown/Multiple
Test Case: | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
----------------------------------------------+----------------------------
Comment (by Simon Peyton Jones

#8985: Strange kind error with type family, GADTs, data kinds, and kind polymorphism ----------------------------------------------+---------------------------- Reporter: kosmikus | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler (Type checker) | Version: 7.8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects valid program | Unknown/Multiple Test Case: polykinds/T8985 | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------------+---------------------------- Changes (by simonpj): * status: new => merge * testcase: => polykinds/T8985 Comment: Great catch, thank you. Merge to 7.8.3. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8985#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8985: Strange kind error with type family, GADTs, data kinds, and kind polymorphism ----------------------------------------------+---------------------------- Reporter: kosmikus | Owner: Type: bug | Status: merge Priority: normal | Milestone: 7.8.3 Component: Compiler (Type checker) | Version: 7.8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects valid program | Unknown/Multiple Test Case: polykinds/T8985 | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------------+---------------------------- Changes (by thoughtpolice): * milestone: => 7.8.3 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8985#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8985: Strange kind error with type family, GADTs, data kinds, and kind polymorphism ----------------------------------------------+---------------------------- Reporter: kosmikus | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.8.3 Component: Compiler (Type checker) | Version: 7.8.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects valid program | Unknown/Multiple Test Case: polykinds/T8985 | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ----------------------------------------------+---------------------------- Changes (by thoughtpolice): * status: merge => closed * resolution: => fixed Comment: Merged to 7.8. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8985#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC