[GHC] #16342: Kind inference crash

#16342: Kind inference crash -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Here's a gnarly test case {{{ {-# LANGUAGE MultiParamTypeClasses, TypeInType, ConstrainedClassMethods, ScopedTypeVariables #-} module Foo where import Data.Proxy class C (a::ka) x where cop :: D a x => x -> Proxy a -> Proxy a cop _ x = x :: Proxy (a::ka) class D (b::kb) y where dop :: C b y => y -> Proxy b -> Proxy b dop _ x = x :: Proxy (b::kb) }}} This crashes every recent GHC with {{{ • GHC internal error: ‘kb’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [avu :-> Type variable ‘b’ = b :: ka, avv :-> Type variable ‘y’ = y :: *, avw :-> Identifier[x::Proxy b, NotLetBound], avx :-> Type variable ‘ka’ = ka :: *] • In the kind ‘kb’ In the first argument of ‘Proxy’, namely ‘(b :: kb)’ In an expression type signature: Proxy (b :: kb) | 13 | dop _ x = x :: Proxy (b::kb) | ^^ }}} Yikes. Reason: * `C` and `D` are mutually recursive * `ka` and `kb` get bound to unification variables, and then get unified in the kind-inference phase * As a result the utterly-final class for `C` and `D` end up with the same `TyVar` for `ka`/`kb`. * And then, for one of them, the tyvar is not in scope when (much, much later) we check the default declaration. Gah! In `generaliseTcTyCon` I think we may need to do a reverse-map to ensure that each of the final `tyConTyVars` has the `Name` from this declaration, rather than accidentally getting a `Name` from another decl in the mutually recursive group. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16342 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16342: Kind inference crash -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by simonpj: Old description:
Here's a gnarly test case {{{ {-# LANGUAGE MultiParamTypeClasses, TypeInType, ConstrainedClassMethods, ScopedTypeVariables #-}
module Foo where
import Data.Proxy
class C (a::ka) x where cop :: D a x => x -> Proxy a -> Proxy a cop _ x = x :: Proxy (a::ka)
class D (b::kb) y where dop :: C b y => y -> Proxy b -> Proxy b dop _ x = x :: Proxy (b::kb) }}} This crashes every recent GHC with {{{ • GHC internal error: ‘kb’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [avu :-> Type variable ‘b’ = b :: ka, avv :-> Type variable ‘y’ = y :: *, avw :-> Identifier[x::Proxy b, NotLetBound], avx :-> Type variable ‘ka’ = ka :: *] • In the kind ‘kb’ In the first argument of ‘Proxy’, namely ‘(b :: kb)’ In an expression type signature: Proxy (b :: kb) | 13 | dop _ x = x :: Proxy (b::kb) | ^^ }}} Yikes.
Reason: * `C` and `D` are mutually recursive * `ka` and `kb` get bound to unification variables, and then get unified in the kind-inference phase * As a result the utterly-final class for `C` and `D` end up with the same `TyVar` for `ka`/`kb`. * And then, for one of them, the tyvar is not in scope when (much, much later) we check the default declaration.
Gah! In `generaliseTcTyCon` I think we may need to do a reverse-map to ensure that each of the final `tyConTyVars` has the `Name` from this declaration, rather than accidentally getting a `Name` from another decl in the mutually recursive group.
New description: Here's a gnarly test case {{{ {-# LANGUAGE MultiParamTypeClasses, TypeInType, ConstrainedClassMethods, ScopedTypeVariables #-} module Foo where import Data.Proxy class C (a::ka) x where cop :: D a x => x -> Proxy a -> Proxy a cop _ x = x :: Proxy (a::ka) class D (b::kb) y where dop :: C b y => y -> Proxy b -> Proxy b dop _ x = x :: Proxy (b::kb) }}} This crashes every recent GHC outright, with {{{ • GHC internal error: ‘kb’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [avu :-> Type variable ‘b’ = b :: ka, avv :-> Type variable ‘y’ = y :: *, avw :-> Identifier[x::Proxy b, NotLetBound], avx :-> Type variable ‘ka’ = ka :: *] • In the kind ‘kb’ In the first argument of ‘Proxy’, namely ‘(b :: kb)’ In an expression type signature: Proxy (b :: kb) | 13 | dop _ x = x :: Proxy (b::kb) | ^^ }}} Yikes. Reason: * `C` and `D` are mutually recursive * `ka` and `kb` get bound to unification variables, and then get unified in the kind-inference phase * As a result the utterly-final class for `C` and `D` end up with the same `TyVar` for `ka`/`kb`. * And then, for one of them, the tyvar is not in scope when (much, much later) we check the default declaration. Gah! In `generaliseTcTyCon` I think we may need to do a reverse-map to ensure that each of the final `tyConTyVars` has the `Name` from this declaration, rather than accidentally getting a `Name` from another decl in the mutually recursive group. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16342#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16342: Kind inference crash -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by aspiwack): * cc: aspiwack (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16342#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16342: Kind inference crash -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): If we type-checked `HsDecl GhcRn` into `HsDecl GhcTc`, this would be much easier. Of course, classes get type-checked in pieces, so we would need multiple phase parameters there... In any case, I agree that reverse-mapping may be the cheap and cheerful solution here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16342#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16342: Kind inference crash -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #16221 | Differential Rev(s): Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/444 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: => https://gitlab.haskell.org/ghc/ghc/merge_requests/444 * related: => #16221 Comment: This was allegedly fixed in [https://gitlab.haskell.org/ghc/ghc/commit/80dfcee61e3bfb67f131cd674f96467e16... 80dfcee6], although a test case has yet to materialize. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16342#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16342: Kind inference crash
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.6.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #16221 | Differential Rev(s):
Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/444
-------------------------------------+-------------------------------------
Comment (by Marge Bot

#16342: Kind inference crash -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.10.1 Component: Compiler | Version: 8.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #16221 | Differential Rev(s): | https://gitlab.haskell.org/ghc/ghc/merge_requests/444, Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/499 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: https://gitlab.haskell.org/ghc/ghc/merge_requests/444 => https://gitlab.haskell.org/ghc/ghc/merge_requests/444, https://gitlab.haskell.org/ghc/ghc/merge_requests/499 * milestone: => 8.10.1 Comment: https://gitlab.haskell.org/ghc/ghc/merge_requests/499 adds a regression test. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16342#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16342: Kind inference crash
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone: 8.10.1
Component: Compiler | Version: 8.6.3
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #16221 | Differential Rev(s):
| https://gitlab.haskell.org/ghc/ghc/merge_requests/444,
Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/499
-------------------------------------+-------------------------------------
Changes (by simonpj):
* status: patch => closed
* resolution: => fixed
Comment:
Test landed as
{{{
commit 07f378cee37338c5f2655b3a7e46dfef3f1c5cc1
Author: Simon Peyton Jones

#16342: Kind inference crash
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone: 8.10.1
Component: Compiler | Version: 8.6.3
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #16221 | Differential Rev(s):
| https://gitlab.haskell.org/ghc/ghc/merge_requests/444,
Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/499
-------------------------------------+-------------------------------------
Comment (by Marge Bot
participants (1)
-
GHC