[GHC] #12768: 8.0.2 derives invalid code when class method is constrained by itself

#12768: 8.0.2 derives invalid code when class method is constrained by itself -------------------------------------+------------------------------------- Reporter: jophish | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 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: -------------------------------------+------------------------------------- GHC 8.0.1 is able to compile this without a problem and doesn't require FlexibleContexts. {{{#!hs {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ConstrainedClassMethods #-} module A where class C m where foo :: C m => m () newtype N m a = N (m a) deriving C }}} Compare the output of 8.0.1, 8.0.2 and 8.1. I turned on -fdefer-type- errors in order for -ddump-deriv to work. {{{ $ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.0.1 $ ghc -ddump-deriv A.hs [1 of 1] Compiling A ( A.hs, A.o ) ==================== Derived instances ==================== Derived instances: instance A.C m_aNK => A.C (A.N m_aNK) where A.foo = GHC.Prim.coerce (A.foo :: m_ap1 ()) :: A.N m_ap1 () GHC.Generics representation types: }}} {{{ $ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.0.2 $ ghc A.hs [1 of 1] Compiling A ( A.hs, A.o ) A.hs:10:12: error: • Couldn't match type ‘m’ with ‘N m’ arising from the coercion of the method ‘foo’ from type ‘C m => m ()’ to type ‘C (N m) => N m ()’ ‘m’ is a rigid type variable bound by the deriving clause for ‘C (N m)’ at A.hs:10:12 • When deriving the instance for (C (N m)) $ ghc -ddump-deriv -fdefer-type-errors A.hs [1 of 1] Compiling A ( A.hs, A.o ) ==================== Derived instances ==================== Derived instances: instance A.C m_awm => A.C (A.N m_awm) where A.foo = GHC.Prim.coerce @(A.C m_ap0 => m_ap0 ()) @(A.C (A.N m_ap0) => A.N m_ap0 ()) A.foo GHC.Generics representation types: A.hs:11:12: warning: [-Wdeferred-type-errors] • Couldn't match type ‘m’ with ‘N m’ arising from a use of ‘GHC.Prim.coerce’ ‘m’ is a rigid type variable bound by the instance declaration at A.hs:11:12 • In the expression: GHC.Prim.coerce @(C m => m ()) @(C (N m) => N m ()) foo In an equation for ‘foo’: foo = GHC.Prim.coerce @(C m => m ()) @(C (N m) => N m ()) foo When typechecking the code for ‘foo’ in a derived instance for ‘C (N m)’: To see the code I am typechecking, use -ddump-deriv In the instance declaration for ‘C (N m)’ • Relevant bindings include foo :: N m () (bound at A.hs:11:12) }}} There's no '8.0.2' version to report this against so I've chosen 8.1. GHC 8.1 gives very similar results: {{{ $ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.1.20160930 $ ghc A.hs [1 of 1] Compiling A ( A.hs, A.o ) A.hs:11:12: error: • Couldn't match type ‘m’ with ‘N m’ arising from the coercion of the method ‘foo’ from type ‘C m => m ()’ to type ‘C (N m) => N m ()’ ‘m’ is a rigid type variable bound by the deriving clause for ‘C (N m)’ at A.hs:11:12 • When deriving the instance for (C (N m)) $ ghc -ddump-deriv -fdefer-type-errors A.hs [1 of 1] Compiling A ( A.hs, A.o ) ==================== Derived instances ==================== Derived instances: instance A.C m_awK => A.C (A.N m_awK) where A.foo = GHC.Prim.coerce @(A.C m_app => m_app ()) @(A.C (A.N m_app) => A.N m_app ()) A.foo GHC.Generics representation types: A.hs:11:12: warning: [-Wsimplifiable-class-constraints] The constraint ‘C (N m)’ matches an instance declaration instance C m => C (N m) -- Defined at A.hs:11:12 This makes type inference for inner bindings fragile; either use MonoLocalBinds, or simplify it using the instance A.hs:11:12: warning: [-Wdeferred-type-errors] • Couldn't match type ‘m’ with ‘N m’ arising from a use of ‘GHC.Prim.coerce’ ‘m’ is a rigid type variable bound by the instance declaration at A.hs:11:12 • In the expression: GHC.Prim.coerce @(C m => m ()) @(C (N m) => N m ()) foo In an equation for ‘foo’: foo = GHC.Prim.coerce @(C m => m ()) @(C (N m) => N m ()) foo When typechecking the code for ‘foo’ in a derived instance for ‘C (N m)’: To see the code I am typechecking, use -ddump-deriv In the instance declaration for ‘C (N m)’ • Relevant bindings include foo :: N m () (bound at A.hs:11:12) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12768 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12768: 8.0.2 derives invalid code when class method is constrained by itself -------------------------------------+------------------------------------- Reporter: jophish | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by jophish): * Attachment "A.hs" added. Minimal testcase -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12768 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12768: 8.0.2 derives invalid code when class method is constrained by itself -------------------------------------+------------------------------------- Reporter: jophish | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Can't you just delete the `C m =>` constraint on `foo`? Is this reduced from a real program? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12768#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12768: 8.0.2 derives invalid code when class method is constrained by itself -------------------------------------+------------------------------------- Reporter: jophish | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by jophish): Yes, as 8.1 suggests, this constraint is redundant. I encountered this in the trifecta library. It can be seen in the `rend` and `restOfLine` member functions of the `DeltaParsing` class here https://hackage.haskell.org/package/trifecta-1.6/docs/src/Text.Trifecta.Comb... (this is fixed in trifecta's HEAD now). I imagine that this can happen when a top level constrained function is moved to be a member of a class. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12768#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12768: 8.0.2 derives invalid code when class method is constrained by itself -------------------------------------+------------------------------------- Reporter: jophish | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: simonpj (added) * milestone: => 8.0.2 Comment: Simon, the code above stopped typechecking after one of your commits: 96d451450923a80b043b5314c5eaaa9d0eab7c56. Is this expected behavior? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12768#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12768: 8.0.2 derives invalid code when class method is constrained by itself -------------------------------------+------------------------------------- Reporter: jophish | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): There is a real difficulty here, if I'm not mistaken. Consider {{{ class C a where op :: D a => a -> a instance C [a] where op = opList opList :: D [a] => [a] -> [a] opList = ... }}} Now suppose we try GND: {{{ newtype N a = MkN [a] deriving( C ) }}} The GND is expecting to get an implementation of `op` for `N` from that for `opList`, something like {{{ instance C [a] => C (N a) where op = opN opN :: D (N a) => N a -> N a opN = ...opList... -- Uses coerce }}} But the call to `opList` in the definition of `opN` needs `(D [a])` whereas what we are given is `D (N a)`. **And these are not inter-coercible**. For example we might have manually written instances {{{ instance D [a] where ... instance D (N a) where ... }}} and there is no relation between them. So in this case, the code for `opN` is **not** representationally the same as the code for `opList`, so GND (which is all about representational equivalence) doesn't really apply. In the actual example, `D` is just `C` again, but I don't think we should treat it any differently. The actual error is generated by an attempt to coerce {{{ coerce @(C m => m ()) @(C (N m) => N m ()) }}} which rightly fails. So I think GND just doesn't work here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12768#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12768: 8.0.2 derives invalid code when class method is constrained by itself -------------------------------------+------------------------------------- Reporter: jophish | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: bgamari (added) Comment: That's a very good point about `D [a]` and `D (N a)` not being inter- coercible in general w.r.t the class `C`. It sound like in order to make this work for the special case of `D = C`, we'd have to equip GHC with some special knowledge that the `C (N a)` instance was generated through GND, which sounds quite gross. So now the question becomes: should we avoid backporting 96d451450923a80b043b5314c5eaaa9d0eab7c56 to 8.0.2 since it causes some programs which compile in 8.0.1 to fail in 8.0.2? Or should we simply add a section to the release notes explaining the scenario, and recommend the (admittedly simple) workaround? Ben, do you have any thoughts on this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12768#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12768: 8.0.2 derives invalid code when class method is constrained by itself -------------------------------------+------------------------------------- Reporter: jophish | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Well I guess that * if we are doing GND for `(C (N a))`, where `N` is a newtype * then `(C a)` is representationally equal to `(C (N a))` and that's just what we need here. But I don't see an easy way to incorporate that knowledge in the solver. And this is very much a weird case: the `(C m)` constraint is entirely redundant. I worked out how GHC 8.0 is working. We generate this: {{{ instance C m => C (N m) where foo = coerce (foo :: m ()) :: N (m ()) }}} From this instance decl we generate {{{ dfCN :: C m => C (N m) dfCN d = MkC ($cfooN d) $cfooN :: C m => C (N m) => N m () $cfooN d _ = foo d d |> (a coercion) }}} Notice that in `$cfooN` we don't need the second dictionary argument (corresponding to the `C m` constrain in `foo`'s signature in the class decl). It just so happens that the instance context can satisfy it. But exploiting this fluke involves instantiating the call to `foo`, which is what I am now not doing. In comment:4, the fluke would require that from `C a` (the context of the instance decl) we could prove `D a` (the requirement of the call in the method body), again ignoring the supplied `(D (N a))`. I think the 8.0 behaviour is actually INCORRECT (it misbehaves in examples like comment:4), so I think we should indeed adopt the change for the 8.0 branch. Do we have any actual user complaints? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12768#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12768: 8.0.2 derives invalid code when class method is constrained by itself -------------------------------------+------------------------------------- Reporter: jophish | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I'm disinclined to fix this, too, for the reasons you articulated. The only place I'm aware of at the moment that exploited this trick was in the [https://github.com/ekmett/trifecta trifecta] library, and, as jophish noted in comment:2, the HEAD version of trifecta has already been patched to avoid this bug. But there could be other occurrences lurking in the wild, too... we'd probably need a build of Stackage with 8.0.2 to be sure. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12768#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12768: 8.0.2 derives invalid code when class method is constrained by itself
-------------------------------------+-------------------------------------
Reporter: jophish | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 8.0.2
Component: Compiler | Version: 8.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 Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#12768: 8.0.2 derives invalid code when class method is constrained by itself
-------------------------------------+-------------------------------------
Reporter: jophish | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 8.0.2
Component: Compiler | Version: 8.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 Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#12768: 8.0.2 derives invalid code when class method is constrained by itself -------------------------------------+------------------------------------- Reporter: jophish | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.1 Resolution: fixed | 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: => fixed Comment: After talking with bgamari about this, I've opted to simply note the difference in behavior for this program in the 8.0.2 release notes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12768#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12768: 8.0.2 derives invalid code when class method is constrained by itself -------------------------------------+------------------------------------- Reporter: jophish | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.1 Resolution: fixed | 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: closed => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12768#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12768: 8.0.2 derives invalid code when class method is constrained by itself -------------------------------------+------------------------------------- Reporter: jophish | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.1 Resolution: fixed | 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 bgamari): * status: merge => closed Comment: Merged to `ghc-8.0` as 411bd2dfed3d6cfe73cd0e4521acee67f18a8fe7. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12768#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12768: 8.0.2 derives invalid code when class method is constrained by itself -------------------------------------+------------------------------------- Reporter: jophish | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.1 Resolution: fixed | 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 simonpj): See #13293 for another example of the same issue. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12768#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12768: 8.0.2 derives invalid code when class method is constrained by itself -------------------------------------+------------------------------------- Reporter: jophish | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: deriving 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): * keywords: => deriving -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12768#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC