[GHC] #15116: GHC internal error when GADT return type mentions its own constructor name

#15116: GHC internal error when GADT return type mentions its own constructor name -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 (Type checker) | Keywords: GADTs, | Operating System: Unknown/Multiple TypeInType | Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Take the following program: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeInType #-} module Bug where data A (a :: k) where MkA :: A MkA }}} On GHC 8.4.2, this is rejected with a sensible error message: {{{ $ /opt/ghc/8.4.2/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:6:12: error: • Data constructor ‘MkA’ cannot be used here (it is defined and used in the same recursive group) • In the first argument of ‘A’, namely ‘MkA’ In the type ‘A MkA’ In the definition of data constructor ‘MkA’ | 6 | MkA :: A MkA | ^^^ }}} On GHC HEAD, however, this causes a GHC internal error: {{{ $ ghc2/inplace/bin/ghc-stage2 Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:6:12: error: • GHC internal error: ‘MkA’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [asv :-> Type variable ‘k’ = k :: *, asw :-> Type variable ‘a’ = a :: k, rqs :-> ATcTyCon A :: forall k. k -> *] • In the first argument of ‘A’, namely ‘MkA’ In the type ‘A MkA’ In the definition of data constructor ‘MkA’ | 6 | MkA :: A MkA | ^^^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15116 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15116: GHC internal error when GADT return type mentions its own constructor name -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.5 checker) | Keywords: GADTs, Resolution: | TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: goldfire (added) Comment: Commit faec8d358985e5d0bf363bd96f23fe76c9e281f7 (`Track type variable scope more carefully.`) caused this, although it's not obvious to me from a quick glance why this would be the case... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15116#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15116: GHC internal error when GADT return type mentions its own constructor name -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.5 checker) | Keywords: GADTs, Resolution: | TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Ah, I see what is going on. This is due to the following change in `kcLTyClDecl`: {{{#!diff kcLTyClDecl :: LTyClDecl GhcRn -> TcM () -- See Note [Kind checking for type and class decls] kcLTyClDecl (L loc decl) + | hsDeclHasCusk decl + = traceTc "kcTyClDecl skipped due to cusk" (ppr tc_name) + | otherwise = setSrcSpan loc $ tcAddDeclCtxt decl $ - do { traceTc "kcTyClDecl {" (ppr (tyClDeclLName decl)) + do { traceTc "kcTyClDecl {" (ppr tc_name) ; kcTyClDecl decl - ; traceTc "kcTyClDecl done }" (ppr (tyClDeclLName decl)) } + ; traceTc "kcTyClDecl done }" (ppr tc_name) } + where + tc_name = tyClDeclLName decl }}} Now, if the declaration has a CUSK, then `kcTyClDecl` is skipped entirely. As a consequence, subsequent checks for each data constructor (`kcConDecl`) are also skipped. But `kcConDecl` was what was throwing the error message for the original program, so skipping it leads to pandemonium later down the line. How should we fix this? I can think of at least a couple of possibilities: 1. Never skip `kcTyClDecl` if the declaration has constructors. 2. Do the `kcConDecl` checks separately from `kcTyClDecl`. Thoughts? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15116#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15116: GHC internal error when GADT return type mentions its own constructor name -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.5 checker) | Keywords: GADTs, Resolution: | TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm on this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15116#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15116: GHC internal error when GADT return type mentions its own constructor name -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.5 checker) | Keywords: GADTs, Resolution: | TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Written before Simon's "I'm on this", but I thought it worthy of posting anyway: I like: 3. Add the right `APromotionErr` entries into the env't for `tcConDecl`. `kcTyClGroup` calls `getInitialKinds`, which returns a `NameEnv TcTyThing`, mapping names to `TcTyThing`s. Note how `TcTyThing` includes the `APromotionErr` constructor (see its definition in `TcRnTypes`). ``getInitialKinds` not only maps tycon names to `TcTyCon`s (stored in `ATcTyCon`) but it also maps datacons to `APromotionErr`s. This is done in `getInitialKinds`'s call to `mkPromotionErrorEnv`. So, when we look up a datacon in `kcTyClDecl`, we get a `APromotionErr`, just as we should. Compare to the env't in place for `tcTyClDecls`, which is built with `zipRecTyClss`. This env't does ''not'' have the `APromotionErr`s. (See comment above the call to `zipRecTyClss`.) The solution is to extend the env't used in type checking to have the `APromotionErr` entries -- but only for the datacons, not for the tycons (which are no longer errors!). So you'd This is gnarly code, but this aspect of it isn't as complicated as others. It would make for a good exercise for someone (cough cough) who is working toward becoming an Official Type Checker Grease Monkey. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15116#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15116: GHC internal error when GADT return type mentions its own constructor name
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler (Type | Version: 8.5
checker) | Keywords: GADTs,
Resolution: | TypeInType
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash or panic | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#15116: GHC internal error when GADT return type mentions its own constructor name -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.5 checker) | Keywords: GADTs, Resolution: fixed | TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | polykinds/T15116, T15116a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => polykinds/T15116, T15116a * resolution: => fixed Comment: Excellent bug report, and provocation to improve. Thanks. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15116#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15116: GHC internal error when GADT return type mentions its own constructor name -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.5 checker) | Keywords: GADTs, Resolution: fixed | TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | polykinds/T15116, T15116a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): For the record, I read this patch and think it's lovely. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15116#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15116: GHC internal error when GADT return type mentions its own constructor name -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.5 checker) | Keywords: GADTs, Resolution: fixed | TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | polykinds/T15116, T15116a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Thank you! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15116#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC