[GHC] #11357: Regression when deriving Generic1 on poly-kinded data family

#11357: Regression when deriving Generic1 on poly-kinded data family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.1 (CodeGen) | Keywords: Generics, | Operating System: Unknown/Multiple TypeInType | Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- On GHC 7.10.3, the following code compiles: {{{#!hs {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeFamilies #-} module ProxyFam where import GHC.Generics (Generic1) data family ProxyFam (a :: k) data instance ProxyFam (a :: k) = ProxyCon deriving Generic1 }}} But on GHC 8.1, it fails: {{{ $ /opt/ghc/head/bin/ghc ProxyFam.hs [1 of 1] Compiling ProxyFam ( ProxyFam.hs, ProxyFam.o ) ProxyFam.hs:10:53: error: • Can't make a derived instance of ‘Generic1 ProxyFam’: ProxyFam must not be instantiated; try deriving `ProxyFam k a' instead • In the data instance declaration for ‘ProxyFam’ }}} I'm not sure what exactly is going on here, but I have a hunch. The `Generic1` typeclass is of kind `* -> *`, which means that in a `Generic1 ProxyFam` instance, the kind of `a` is instantiated to `*`. Curiously, though, the same error does ''not'' appear when `deriving Generic` for a normal datatype (e.g., `data ProxyFam (a :: k) = ProxyCon deriving Generic1`). Richard, I'm stuck as to how to fix this. I suspect this was triggered by `-XTypeInType`-related changes, specifically, [http://git.haskell.org/ghc.git/blobdiff/6e56ac58a6905197412d58e32792a04a63b9... this change]: {{{#!diff diff --git a/compiler/typecheck/TcGenGenerics.hs b/compiler/typecheck/TcGenGenerics.hs index 2c5b80e..fb18517 100644 (file) --- a/compiler/typecheck/TcGenGenerics.hs +++ b/compiler/typecheck/TcGenGenerics.hs @@ -147,7 +146,7 @@ canDoGenerics tc tc_args -- -- Data family indices can be instantiated; the `tc_args` here are -- the representation tycon args - (if (all isTyVarTy (filterOut isKind tc_args)) + (if (all isTyVarTy (filterOutInvisibleTypes tc tc_args)) then IsValid else NotValid (tc_name <+> text "must not be instantiated;" <+> text "try deriving `" <> tc_name <+> tc_tys <> }}} What exactly does `filterOutInvisibleTypes` do? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11357 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11357: Regression when deriving Generic1 on poly-kinded data family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 8.1 (CodeGen) | Keywords: Generics, Resolution: | TypeInType 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): * milestone: => 8.0.1 Comment: I'm going to set the milestone to 8.0.1, since this affects the upcoming GHC 8.0 and it breaks a fair bit of `Generics`-related code in the wild. Please change the milestone if you disagree. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11357#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11357: Regression when deriving Generic1 on poly-kinded data family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Generics, Resolution: | TypeInType 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 thomie): * priority: high => highest * version: 8.1 => 7.11 Comment: I believe regressions are release blockers. Setting priority to highest. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11357#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11357: Regression when deriving Generic1 on poly-kinded data family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Generics, Resolution: | TypeInType 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): Something fishy is going on with the kind of the `ProxyFam` instance `TyCon`. I added `pprTrace`-ed the result of `tyConKind tc` right before the call to `filterOutInvisibleTypes` mentioned above, and noticed a discrepancy between datatypes and data families: {{{ $ inplace/bin/ghc-stage2 --interactive GHCi, version 8.1.20160109: http://www.haskell.org/ghc/ :? for help λ> :set -XDeriveGeneric -XTypeFamilies -XPolyKinds -fprint-explicit- foralls λ> import GHC.Generics λ> data Proxy (a :: k) = Proxy deriving Generic1 tc: Proxy tyConKind tc: forall k_a1Gj. k_a1Gj -> * tc_args: [*] filterOutInvisibleTypes tc tc_args: [] all isTyVarTy: True λ> data family ProxyFam (a :: k) λ> data instance ProxyFam (a :: k) = ProxyCon deriving Generic1 tc: R:ProxyFamka tyConKind tc: forall k_a1Ps -> k_a1Ps -> * tc_args: [*] filterOutInvisibleTypes tc tc_args: [*] all isTyVarTy: False <interactive>:5:53: error: • Can't make a derived instance of ‘Generic1 ProxyFam’: ProxyFam must not be instantiated; try deriving `ProxyFam k a' instead • In the data instance declaration for ‘ProxyFam’ }}} Notice that `tyConKind` for the datatype `Proxy` is `forall k. k -> *` (i.e., `k` is specified but not visible), but the `tyConKind` for the `ProxyFam` instance is `forall k -> k -> *` (`k` is visible)! This is definitely the reason why this bug is manifesting itself, although I'm not sure why `k` is a visible type argument in the `ProxyFam` instance. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11357#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11357: Regression when deriving Generic1 on poly-kinded data family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Generics, Resolution: | TypeInType 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 simonpj): * owner: => goldfire Comment: Richard this one too is "highest". Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11357#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11357: Regression when deriving Generic1 on poly-kinded data family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Generics, Resolution: | TypeInType, TypeFamilies 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): * cc: aaditmshah@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11357#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11357: Regression when deriving Generic1 on poly-kinded data family
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: goldfire
Type: bug | Status: new
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 7.11
(CodeGen) | Keywords: Generics,
Resolution: | TypeInType, TypeFamilies
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 Richard Eisenberg

#11357: Regression when deriving Generic1 on poly-kinded data family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: merge Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Generics, Resolution: | TypeInType, TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T11357 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => merge * testcase: => deriving/should_compile/T11357 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11357#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11357: Regression when deriving Generic1 on poly-kinded data family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: merge Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Generics, Resolution: | TypeInType, TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T11357 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Well, that patch seemed to fix that problem, but it introduced another one. Vanilla datatypes and data family instances are still inconsistent w.r.t. which type variables are considered "instantiated" in a `Generic1` instance. For instance, this is rejected: {{{ λ> data Proxy k (a :: k) = ProxyCon deriving Generic1 <interactive>:32:43: error: • Can't make a derived instance of ‘Generic1 (Proxy *)’: Proxy must not be instantiated; try deriving `Proxy k a' instead • In the data declaration for ‘Proxy’ }}} And rightfully so, since the visible kind binder `k` is instantiated to `*`. But now it's possible to have an equivalent instance for a data family that squeaks past this check! {{{ λ> data family ProxyFam (a :: y) (b :: z) λ> data instance ProxyFam k (a :: k) = ProxyFamCon deriving Generic1 ==================== Derived instances ==================== Derived instances: instance GHC.Generics.Generic1 (Ghci13.ProxyFam *) where ... }}} I need to investigate further to see why this is the case. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11357#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11357: Regression when deriving Generic1 on poly-kinded data family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: merge Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Generics, Resolution: | TypeInType, TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T11357 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): So, is comment:9 a release blocker? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11357#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11357: Regression when deriving Generic1 on poly-kinded data family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Generics, Resolution: fixed | TypeInType, TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T11357 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as 1cbab8baccaf5be0d2938c869aa43a7e227f1395. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11357#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11357: Regression when deriving Generic1 on poly-kinded data family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Generics, Resolution: | TypeInType, TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T11357 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: closed => new * owner: goldfire => * resolution: fixed => Comment: Re-opening due to comment:9. Richard, do you think you could have a look at this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11357#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11357: Regression when deriving Generic1 on poly-kinded data family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Generics, Resolution: | TypeInType, TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T11357 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:10 simonpj]:
So, is comment:9 a release blocker?
I say "no". It seems to be triggered only when you're deriving `Generic1` for a datatype parameterized over mixed type and kind variables. This last bit is possible only with `-XTypeInType` and thus is not a regression. I'm frankly unsure (without more research) as to what the desired behavior should be here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11357#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11357: Regression when deriving Generic1 on poly-kinded data family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Generics, Resolution: fixed | TypeInType, TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T11357 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * resolution: => fixed Comment: I've spun off comment:9 into #11732. I don't think it's closely related to the original problem reported here, which was a real regression. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11357#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11357: Regression when deriving Generic1 on poly-kinded data family
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: closed
Priority: highest | Milestone: 8.0.1
Component: Compiler | Version: 7.11
(CodeGen) | Keywords: Generics,
Resolution: fixed | TypeInType, TypeFamilies
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: GHC rejects | Test Case:
valid program | deriving/should_compile/T11357
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11357: Regression when deriving Generic1 on poly-kinded data family -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Generics, Resolution: fixed | TypeInType, TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T11357 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Oh dear, the commit mentioned in comment:15 is actually for #12357. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11357#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC