[GHC] #14121: ghc master requires -XTypeInType where 8.2.1 does not

#14121: ghc master requires -XTypeInType where 8.2.1 does not -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This was found while building https://hackage.haskell.org/package/foundation with ghc head. The following code is reduced from Basement.Primitive.Error: {{{ {-# LANGUAGE MagicHash, PolyKinds, RankNTypes #-} module FoundationRegression where import GHC.Prim import GHC.Types (RuntimeRep) error :: forall (r :: RuntimeRep) . forall (a :: TYPE r) . String -> a error s = raise# undefined }}} This compiles works with 8.2.1, but fails on master: {{{ $ /opt/ghc/8.2.1/bin/ghc -c FoundationRegression.hs $ /opt/ghc/head/bin/ghc -c FoundationRegression.hs FoundationRegression.hs:7:17: error: Variable ‘r’ used as both a kind and a type Did you intend to use TypeInType? | 7 | error :: forall (r :: RuntimeRep) . forall (a :: TYPE r) . String -> a | ^^^^^^^^^^^^^^^^^ }}} After adding a TypeInType language pragma the program is accepted. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14121 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14121: ghc master requires -XTypeInType where 8.2.1 does not -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carter): I hit a similar issue recently in the land of 8.2.1, and I was surprised that datakinds didn't suffice. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14121#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14121: ghc master requires -XTypeInType where 8.2.1 does not -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.3 checker) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => invalid Comment: This program should indeed require `TypeInType`, and the fact that it is accepted without `TypeInType` in 8.2.1 is a fluke. The ability to bind a kind variable and use it as the kind of a different type variable in the same telescope is something that wasn't possible in a pre-`TypeInType` GHC, as this error message in GHC 7.10.3 reveals: {{{ GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help λ> :set -XKindSignatures -XRankNTypes -XPolyKinds λ> import Data.Proxy λ> let f :: forall (k :: *). forall (a :: k). Proxy a; f = Proxy <interactive>:4:10: Kind variable also used as type variable: ‘k’ In the type signature for ‘f’ }}} `RuntimeRep` wasn't introduced until 8.0, so I can't test your exact example in 7.10.3. But the principle is the same: if you use something as both type and kind, then you need `TypeInType`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14121#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14121: ghc master requires -XTypeInType where 8.2.1 does not -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.3 checker) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by duog): Thanks for the great explanation! Should this be in the release notes, or is it too niche? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14121#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14121: ghc master requires -XTypeInType where 8.2.1 does not -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.3 checker) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): If nothing else we should mention it in the migration guide. See [[Migration/8.4]]. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14121#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14121: ghc master requires -XTypeInType where 8.2.1 does not -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.3 checker) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Good thought bgamari, I've [https://ghc.haskell.org/trac/ghc/wiki/Migration/8.4?version=4 added a blurb] about this to the 8.4 migration guide. I don't think it would hurt adding mention of the fact that `TypeInType`'s validity checks tightened up in the release notes. FWIW, there is [https://phabricator.haskell.org/D3859 another patch] in the works that will make `TypeInType` pickier w.r.t. GADTs as well, so it might also behoove us to mention that as well. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14121#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14121: ghc master requires -XTypeInType where 8.2.1 does not -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.3 checker) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): As I've been working on these patches, I haven't added anything to the release notes because they are bug-fixes, plain and simple. That said, the changes do make GHC accept fewer programs, so a note may be helpful to users. Thanks for adding this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14121#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC