[GHC] #10524: PolyKinds doesn't interact well with DeriveFunctor

#10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: | Owner: RyanGlScott | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: GHC rejects Architecture: | valid program Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Using {{{PolyKinds}}} and {{{DeriveFunctor}}} in tandem on GHC 7.10.2-rc1 will cause a kind incompatibility in certain cases: {{{ GHCi, version 7.10.1.20150612: http://www.haskell.org/ghc/ :? for help λ> :set -XPolyKinds -XDeriveFunctor -ddump-deriv λ> newtype Compose f g a = Compose (f (g a)) deriving Functor ==================== Derived instances ==================== Derived instances: instance forall (k_axa :: BOX) (f_axb :: k_axa -> *) (g_axc :: * -> k_axa). (GHC.Base.Functor f_axb, GHC.Base.Functor g_axc) => GHC.Base.Functor (Ghci1.Compose f_axb g_axc) where GHC.Base.fmap f_axd (Ghci1.Compose a1_axe) = Ghci1.Compose (GHC.Base.fmap (GHC.Base.fmap f_axd) a1_axe) Generic representation: Generated datatypes for meta-information: Representation types: <interactive>:3:52: Kind incompatibility when matching types: f0 :: * -> * f :: k -> * Expected type: f (g b) Actual type: f0 (f1 b) Relevant bindings include a1 :: f (g a) (bound at <interactive>:3:52) fmap :: (a -> b) -> Compose f g a -> Compose f g b (bound at <interactive>:3:52) In the first argument of ‘Compose’, namely ‘fmap (fmap f) a1’ In the expression: Compose (fmap (fmap f) a1) When typechecking the code for ‘fmap’ in a derived instance for ‘Functor (Compose f g)’: To see the code I am typechecking, use -ddump-deriv }}} A workaround is to use {{{StandaloneDeriving}}}: {{{ λ> :set -XStandaloneDeriving λ> newtype Compose f g a = Compose (f (g a)) λ> deriving instance (Functor f, Functor g) => Functor (Compose f g) ==================== Derived instances ==================== Derived instances: instance (GHC.Base.Functor f_ayO, GHC.Base.Functor g_ayP) => GHC.Base.Functor (Ghci1.Compose f_ayO g_ayP) where GHC.Base.fmap f_ayQ (Ghci1.Compose a1_ayR) = Ghci1.Compose (GHC.Base.fmap (GHC.Base.fmap f_ayQ) a1_ayR) Generic representation: Generated datatypes for meta-information: Representation types: }}} This problem does not seem to occur in GHC HEAD, however: {{{ GHCi, version 7.11.20150608: http://www.haskell.org/ghc/ :? for help λ> :set -XPolyKinds -XDeriveFunctor -ddump-deriv λ> newtype Compose f g a = Compose (f (g a)) deriving Functor ==================== Derived instances ==================== Derived instances: instance forall (k_a148 :: BOX) (f_a149 :: k_a148 -> *) (g_a14a :: * -> k_a148). (GHC.Base.Functor f_a149, GHC.Base.Functor g_a14a) => GHC.Base.Functor (Ghci3.Compose f_a149 g_a14a) where GHC.Base.fmap f_a14b (Ghci3.Compose a1_a14c) = Ghci3.Compose (GHC.Base.fmap (GHC.Base.fmap f_a14b) a1_a14c) Generic representation: Generated datatypes for meta-information: Representation types: }}} Can this fix be backported in time for GHC 7.10.2? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10524 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): FWIW this isn't a regression, 7.8 fails with the same error and 7.6 bails out even earlier. And isn't 7.10's behavior in fact the correct one? The instance produced by 7.11 is ill-kinded: {{{ instance [safe] forall (k :: BOX) (f :: k -> *) (g :: * -> k). (Functor f, Functor g) => Functor (Compose f g) }}} `Functor`'s argument must really be of kind `* -> *`. (Though I don't know if this will cause any harm beyond confusing error messages down the line.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10524#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by RyanGlScott): It appears that since {{{f :: k -> *}}} and {{{g :: * -> k}}} in 7.10's {{{Functor}}} instance, and since the kind of {{{Compose}}} is {{{(k -> *) -> (k1 -> k) -> k1 -> *}}}, it would follow that {{{Compose f g}}} is of kind {{{* -> *}}} (unless I'm reading that wrong). I raised this issue since at the moment, 7.10 can handle certain poly- kinded derived {{{Functor}}} instances (e.g., {{{newtype Alt f a = Alt (f a) deriving Functor}}}), but throwing more than one poly-kinded type constructor into the mix causes things to go haywire. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10524#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): The instance head `Functor (Compose f g)` is well-kinded, but the context `(Functor f, Functor g)` is not unless `k = *`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10524#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by RyanGlScott): Oh, right. So in both GHC 7.10 and 7.11, the derived kinds for the type variables in {{{(Functor f, Functor g) => Functor (Compose f g)}}} are incorrect, but GHC 7.11 defers the errors until later. In that case, can this can of problem be fixed? Would {{{deriving}}} clauses always be able to infer the correct kinds, or would it be necessary in some cases to specify the kinds in a standalone {{{deriving}}} statement, e.g., {{{#!hs deriving instance (Functor (f :: * -> *), Functor (g :: * -> *)) => Functor (Compose f g) }}} (The kind signatures wouldn't be needed here due to the explicit {{{Functor}}} constraint, but you get the idea.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10524#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Good question. In principle there are classes at other kinds `Functor1`, `Functor2` (not part of a systematic naming scheme) for which you can write {{{ instance (Functor1 (f :: (* -> *) -> *), Functor2 (g :: * -> (* -> *))) => Functor (Compose f g) }}} but GHC will probably never be able to derive that instance. (Maybe if eventually get a polykinded `Functor`, but then the deriving clause could produce a kind-polymorphic instance and there is no problem.) So, I don't see any real issue with having ordinary `deriving` producing an instance for `Functor (Compose * f g)`, to write the kind variable explicitly. However, it's certainly more clear-cut with the standalone deriving declaration, since then the kind variable is determined by the context which you wrote explicitly. I think GHC may have some general principles regarding ordinary deriving declarations and how they are less general than standalone deriving, but I never understood the exact details (aside from the fact that a standalone deriving declaration lets you specify the context). Maybe they don't have anything to say about this case with a kind variable anyways. Not sure where that leaves this ticket; the behavior of HEAD is a bug that I'll file separately. Maybe a feature request dependent on the resolution of that bug. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10524#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10561 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * related: => #10561 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10524#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10561 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by RyanGlScott): It looks like {{{PolyKinds}}} also breaks deriving {{{Data}}} instances as well: {{{#!hs {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE PolyKinds #-} import Data.Data newtype WrappedFunctor f a = WrapFunctor (f a) deriving (Data, Typeable) }}} This will result in the error: {{{ No instance for (Typeable a) arising from the 'deriving' clause of a data type declaration Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself When deriving the instance for (Data (WrappedFunctor f a)) }}} (Presumably, it's trying to infer the instance context {{{Data (f a), Typeable f, Typeable a) => Data (WrappedFunctor f a)}}}, but can't.) I'm not sure if this is due to the same underlying issue, but it seems likely, since that code will compile without {{{PolyKinds}}}. I reproduced this on GHC 7.8, 7.10, and HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10524#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10524: PolyKinds doesn't interact well with DeriveFunctor
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #10561 | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10524: PolyKinds doesn't interact well with DeriveFunctor
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #10561 | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10524: PolyKinds doesn't interact well with DeriveFunctor
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #10561 | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10561 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): OK, so I fixed comment:7. But the original bug report remains {{{ newtype Compose f g a = Compose (f (g a)) deriving Functor }}} should be fine, but elicits {{{ T10524.hs:5:52: error: Couldn't match kind ‘k’ with ‘*’ arising from the first field of ‘Compose’ (type ‘f (g a)’) When deriving the instance for (Functor (Compose f g)) }}} After all, this explicit instance declaration typechecks fine {{{ instance (Functor f, Functor g) => Functor (Compose f g) where fmap fn (Compose x) = Compose (fmap (fmap fn) x) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10524#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10561 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): In my soon-to-be-merged branch, I can now accept the program in comment:7. I have not looked at the other issues at work here, though. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10524#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10524: PolyKinds doesn't interact well with DeriveFunctor
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #10561 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10561 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Confirming that the example from comment:7 is accepted. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10524#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10561 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes, but test `deriving/should_compile/T10561` still fails: {{{ newtype Compose f g a = Compose (f (g a)) deriving Functor }}} (with `-XPolyKinds`) produces {{{ T10561.hs:10:52: error: • Couldn't match kind ‘k’ with ‘*’ arising from the first field of ‘Compose’ (type ‘f (g a)’) • When deriving the instance for (Functor (Compose f g)) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10524#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10561 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I also experienced the same error as in comment:15 when I tried to derive a `Generic1` instance for `Compose` in Phab:D1543. A workaround is to use standalone deriving: {{{#!hs deriving instance Functor f => Generic1 (Compose f g) }}} If we fix this bug, we should remember to change that instance (located [http://git.haskell.org/ghc.git/blob/e0e03d5b9d5cd678f6402534451964d491f16540... here]). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10524#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10561 | Differential Rev(s): Phab:D2097 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2097 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10524#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10524: PolyKinds doesn't interact well with DeriveFunctor
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #10561 | Differential Rev(s): Phab:D2097
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T10561 Blocked By: | Blocking: Related Tickets: #10561 | Differential Rev(s): Phab:D2097 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * testcase: => deriving/should_compile/T10561 * resolution: => fixed * milestone: => 8.0.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10524#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T10561 Blocked By: | Blocking: Related Tickets: #10561 | Differential Rev(s): Phab:D2097 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => deriving -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10524#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC