[GHC] #11399: Ill-kinded instance head involving -XTypeInType can invoke GHC panic

#11399: Ill-kinded instance head involving -XTypeInType can invoke GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Type checker) | Keywords: TypeInType | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This code: {{{#!hs {-# LANGUAGE FlexibleInstances, TypeInType #-} module FvProvFallsIntoAHole where import Data.Kind newtype UhOh (k :: * -> *) (a :: k *) = UhOh (k *) instance Functor k => Functor (UhOh k) where }}} produces this GHC panic: {{{ $ /opt/ghc/head/bin/ghc FvProvFallsIntoAHole.hs [1 of 1] Compiling FvProvFallsIntoAHole ( FvProvFallsIntoAHole.hs, FvProvFallsIntoAHole.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.1.20160108 for x86_64-unknown-linux): fvProv falls into a hole {aq6} Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11399 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11399: Ill-kinded instance head involving -XTypeInType can invoke GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): You don't even need `-XTypeInType`. I had this bite me earlier when I accidentally gave one too many type parameters to `K1`. {{{ class GEq1 t where gliftEq :: (a -> b -> Bool) -> t a -> t b -> Bool instance Eq c => GEq1 (K1 i c) where gliftEq _ (K1 c) (K1 d) = c == d }}} If you replace the instance with {{{ instance Eq c => GEq1 (K1 i c oops) where gliftEq _ (K1 c) (K1 d) = c == d }}} You get the same `fpProv falls into a hole` error. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11399#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11399: Ill-kinded instance head involving -XTypeInType can invoke GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ekmett): * priority: normal => highest * cc: ekmett (added) * milestone: => 8.0.1 Comment: Upgrading to `highest` as this can affect normal users, not just those on the bleeding edge. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11399#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11399: Ill-kinded instance head involving -XTypeInType can invoke GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => goldfire -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11399#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11399: Ill-kinded instance head involving -XTypeInType can invoke GHC panic
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: goldfire
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Compiler (Type | Version: 8.1
checker) |
Resolution: | Keywords: TypeInType
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#11399: Ill-kinded instance head involving -XTypeInType can invoke GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: merge Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash | polykinds/T11399 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => polykinds/T11399 * status: new => merge Comment: Ha! One fix closes four tickets. Merge to 8.0 branch. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11399#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11399: Ill-kinded instance head involving -XTypeInType can invoke GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash | polykinds/T11399 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11399#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC