[GHC] #12423: Panic with DeriveAnyClass and DefaultSignatures

#12423: Panic with DeriveAnyClass and DefaultSignatures -------------------------------------+------------------------------------- Reporter: knrafto | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: -------------------------------------+------------------------------------- With the code {{{#!hs {-# LANGUAGE DefaultSignatures, DeriveAnyClass #-} class Eq1 f where (==#) :: Eq a => f a -> f a -> Bool default (==#) :: Eq (f a) => f a -> f a -> Bool (==#) = (==) data Foo a = Foo (Either a a) deriving (Eq, Eq1) }}} GHC 8.0.1 and 7.10.3 both panic: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-apple-darwin): in other argument Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12423 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12423: Panic with DeriveAnyClass and DefaultSignatures -------------------------------------+------------------------------------- Reporter: knrafto | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 dfeuer): `DefaultSignatures` isn't actually relevant here; `DeriveAnyClass` seems to be solely responsible. I get the same error using {{{#!hs {-# LANGUAGE DeriveAnyClass #-} class Eq1 f where (==#) :: Eq a => f a -> f a -> Bool data Foo a = Foo (Either a a) deriving (Eq, Eq1) }}} Most surprisingly, to me, these examples compile successfully if `Foo` is modified just a drop. Both of the following work: {{{#!hs data Foo2 a = Foo2 a deriving (Eq, Eq1) data Foo3 a b = Foo3 (Either a b) deriving (Eq, Eq1) }}} (the latter needing the obvious `Eq a => Eq1 (Either a)` instance.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12423#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12423: Panic with DeriveAnyClass -------------------------------------+------------------------------------- Reporter: knrafto | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12423#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12423: Panic with DeriveAnyClass -------------------------------------+------------------------------------- Reporter: knrafto | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | GenericDeriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12144 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => GenericDeriving * related: => #12144 Comment: *sigh* I know what's happening here. The algorithm that GHC uses to infer constraints for `* -> *`-kinded things is co-opted from the `DeriveFunctor` algorithm, which doesn't know how to deal with argument types like `Either a a` (since it expects that last type parameter `a` to only ever be used as the very last type in a type application). If you tried to derive a `Functor` instance for `data Foo a = Foo (Either a a)`, it'd give a proper error, since GHC has [http://git.haskell.org/ghc.git/blob/613d745523f181991f6f916bbe58082b7970f7e6... checks] specifically for derived `Functor` instances. On the other hand, there aren't any checks like that for things that are derived in general with `DeriveAnyClass`, so it falls through to [http://git.haskell.org/ghc.git/blob/0676e68cf5fe8696f1f760fef0f35dba14db1104... some code] which throws a GHC panic. Urk. There are two ways we can proceed here. One thing we can do is to put these same checks for `Functor` in place for all `DeriveAnyClass`-derived typeclasses. That would eliminate the GHC panic, but it would simply replace one error message with another. Another approach, which Simon suggests in [https://mail.haskell.org/pipermail/ghc-devs/2016-June/012276.html this ghc-devs thread], is to instead adopt a different strategy for inferring constraints for `DeriveAnyClass`-derived things. Instead of using the `DeriveFunctor` algorithm, we'd collect all of the constraints given by the default signatures of the typeclass, and then simplify as needed. It should be noted that even with the second approach, you still wouldn't be able to derive an `Eq1` instance for `data Foo a = Foo (Either a a)`, since you can't eta-reduce the last type variable. But you would be allowed to derive more things with `DeriveAnyClass` than you could before. A similar problem popped up in #12144, except that uses the last type variable in a contravariant position (another thing which the `DeriveFunctor` algorithm chokes on). Even though this ticket is technically a duplicate of #12144, I'll keep this one open, since it's of a somewhat different nature and provides another nice test case. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12423#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12423: Panic with DeriveAnyClass -------------------------------------+------------------------------------- Reporter: knrafto | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12144 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: GenericDeriving => Generics -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12423#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12423: Panic with DeriveAnyClass -------------------------------------+------------------------------------- Reporter: knrafto | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12144 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I apologize, comment:3 is wrong in stating that you can't derive an `Eq1` instance for `Foo`. It is most certainly possible to–after all, you can create the following instance! {{{#!hs instance Eq1 Foo }}} That eta-reduction stuff was me confusing the details of `DeriveAnyClass` with other deriving mechanisms, like `GeneralizedNewtypeDeriving` and `DeriveFunctor`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12423#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12423: Panic with DeriveAnyClass -------------------------------------+------------------------------------- Reporter: knrafto | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #12144 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * failure: None/Unknown => Compile-time crash -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12423#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12423: Panic with DeriveAnyClass -------------------------------------+------------------------------------- Reporter: knrafto | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #12144 | Differential Rev(s): Phab:D2961 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2961 * milestone: => 8.2.1 Comment: A WIP attempt at fixing this is at Phab:D2961. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12423#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12423: Panic with DeriveAnyClass
-------------------------------------+-------------------------------------
Reporter: knrafto | Owner:
Type: bug | Status: patch
Priority: normal | Milestone: 8.2.1
Component: Compiler | Version: 8.0.1
Resolution: | Keywords: Generics
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case:
Blocked By: | Blocking:
Related Tickets: #12144 | Differential Rev(s): Phab:D2961
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#12423: Panic with DeriveAnyClass -------------------------------------+------------------------------------- Reporter: knrafto | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash | tests/deriving/should_compile/T12423 Blocked By: | Blocking: Related Tickets: #12144 | Differential Rev(s): Phab:D2961 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * testcase: => tests/deriving/should_compile/T12423 * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12423#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC