[GHC] #12201: Wrong instance selection with overlapping instances and local bindings

#12201: Wrong instance selection with overlapping instances and local bindings -------------------------------------+------------------------------------- Reporter: kanetw | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | 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: -------------------------------------+------------------------------------- test and test2 should have the same type, but it seems like the {-# OVERLAPPING #-} instance is chosen prematurely. {{{#!hs {-# LANGUAGE NoMonomorphismRestriction, FlexibleContexts, FlexibleInstances #-} module Bug where class A a where class A a => B a where data Foo s a instance {-# OVERLAPPING #-} A (Foo Int Bool) instance A (Foo s a) instance B (Foo s a) bar :: (A a, B a) => a bar = undefined helper :: Foo s Bool -> s -> Int helper = undefined {- *Bug> :t test test :: A (Foo s Bool) => s -> Int -} test = helper bar {- *Bug> :t test2 test2 :: s -> Int -} test2 = let foo = bar in helper foo }}} Compare with 7.10.3: {{{ *Bug> :t test test :: A (Foo s Bool) => s -> Int *Bug> :t test2 test2 :: A (Foo s Bool) => s -> Int }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12201 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12201: Wrong instance selection with overlapping instances and local bindings -------------------------------------+------------------------------------- Reporter: kanetw | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | 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: | -------------------------------------+------------------------------------- Description changed by kanetw: @@ -1,1 +1,1 @@ - test and test2 should have the same type, but it seems like the {-# + test and test2 should have the same type, but it seems like the non-{#- New description: test and test2 should have the same type, but it seems like the non-{#- OVERLAPPING #-} instance is chosen prematurely. {{{#!hs {-# LANGUAGE NoMonomorphismRestriction, FlexibleContexts, FlexibleInstances #-} module Bug where class A a where class A a => B a where data Foo s a instance {-# OVERLAPPING #-} A (Foo Int Bool) instance A (Foo s a) instance B (Foo s a) bar :: (A a, B a) => a bar = undefined helper :: Foo s Bool -> s -> Int helper = undefined {- *Bug> :t test test :: A (Foo s Bool) => s -> Int -} test = helper bar {- *Bug> :t test2 test2 :: s -> Int -} test2 = let foo = bar in helper foo }}} Compare with 7.10.3: {{{ *Bug> :t test test :: A (Foo s Bool) => s -> Int *Bug> :t test2 test2 :: A (Foo s Bool) => s -> Int }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12201#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12201: Wrong instance selection with overlapping instances and local bindings -------------------------------------+------------------------------------- Reporter: kanetw | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | 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 kanetw): Still present on latest HEAD: {{{ GHCi, version 8.1.20160616: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Bug ( /home/kane/ghc8-instance-bug/Bug.hs, interpreted ) /home/kane/ghc8-instance-bug/Bug.hs:22:1: warning: [-Wsimplifiable-class- constraints] The constraint ‘A (Foo s Bool)’ matches an instance declaration instance A (Foo s a) -- Defined at /home/kane/ghc8-instance-bug/Bug.hs:9:10 This makes type inference very fragile; try simplifying it using the instance Ok, modules loaded: Bug. *Bug> :t test test :: A (Foo s Bool) => s -> Int *Bug> :t test2 test2 :: s -> Int }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12201#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12201: Wrong instance selection with overlapping instances and local bindings -------------------------------------+------------------------------------- Reporter: kanetw | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | 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 kanetw): GHC doesn't seem to check superclass constraints for overlap before solving. {{{#!hs {-# LANGUAGE NoMonomorphismRestriction, FlexibleContexts, FlexibleInstances #-} module Bug where class A a where class A a => B a where data Foo s a instance {-# OVERLAPPING #-} A (Foo Int Bool) instance A (Foo s a) instance B (Foo s a) helper :: Foo s Bool -> s -> Int helper = undefined foo :: (A a, B a) => a foo = undefined bar :: B a => a bar = undefined {- *Bug> :t test_foo test_foo :: A (Foo s Bool) => s -> Int -} test_foo = helper foo {- *Bug> :t test_bar test_bar :: s -> Int -} test_bar = helper bar }}} GHC7 works as expected. I suspect the recent superclass solver changes caused this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12201#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12201: Wrong instance selection with overlapping instance in a superclass -------------------------------------+------------------------------------- Reporter: kanetw | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | 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: | -------------------------------------+------------------------------------- Description changed by kanetw: @@ -1,2 +1,2 @@ - test and test2 should have the same type, but it seems like the non-{#- - OVERLAPPING #-} instance is chosen prematurely. + test_foo and test_bar should have the same type, but it seems like the + non-{#- OVERLAPPING #-} instance is chosen prematurely. @@ -16,3 +16,0 @@ - bar :: (A a, B a) => a - bar = undefined - @@ -22,5 +19,5 @@ - {- - *Bug> :t test - test :: A (Foo s Bool) => s -> Int - -} - test = helper bar + foo :: (A a, B a) => a + foo = undefined + + bar :: B a => a + bar = undefined @@ -29,2 +26,2 @@ - *Bug> :t test2 - test2 :: s -> Int + *Bug> :t test_foo + test_foo :: A (Foo s Bool) => s -> Int @@ -32,1 +29,7 @@ - test2 = let foo = bar in helper foo + test_foo = helper foo + + {- + *Bug> :t test_bar + test_bar :: s -> Int + -} + test_bar = helper bar @@ -37,4 +40,4 @@ - *Bug> :t test - test :: A (Foo s Bool) => s -> Int - *Bug> :t test2 - test2 :: A (Foo s Bool) => s -> Int + *Bug> :t test_foo + test_foo :: A (Foo s Bool) => s -> Int + *Bug> :t test_bar + test_bar :: A (Foo s Bool) => s -> Int New description: test_foo and test_bar should have the same type, but it seems like the non-{#- OVERLAPPING #-} instance is chosen prematurely. {{{#!hs {-# LANGUAGE NoMonomorphismRestriction, FlexibleContexts, FlexibleInstances #-} module Bug where class A a where class A a => B a where data Foo s a instance {-# OVERLAPPING #-} A (Foo Int Bool) instance A (Foo s a) instance B (Foo s a) helper :: Foo s Bool -> s -> Int helper = undefined foo :: (A a, B a) => a foo = undefined bar :: B a => a bar = undefined {- *Bug> :t test_foo test_foo :: A (Foo s Bool) => s -> Int -} test_foo = helper foo {- *Bug> :t test_bar test_bar :: s -> Int -} test_bar = helper bar }}} Compare with 7.10.3: {{{ *Bug> :t test_foo test_foo :: A (Foo s Bool) => s -> Int *Bug> :t test_bar test_bar :: A (Foo s Bool) => s -> Int }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12201#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12201: Wrong instance selection with overlapping instance in a superclass -------------------------------------+------------------------------------- Reporter: kanetw | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | 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 simonpj): This is a delicate point about overlapping instances, which has never really been discussed. Here's what is happening. In `test_bar` we get one constraint so solve: `B (Foo s Bool)`. And there is an instance declaration that solves it {{{ instance B (Foo s a) }}} So GHC 8 just solves it, and I think it is right to do so. So we get {{{ test_bar :: s -> Int }}} Why does GHC 7 behave differently? GHC 7 used a tricky mechanism called "silent superclasses" to solve a tricky problem to do with recursive instances. As a result, GHC 7 effectively changed the instance for `B (Foo s a)` to {{{ instance A (Foo s a) => B (Foo s a) }}} Now when solving `B (Foo s Bool)` GHC 7 finds it needs `A (Foo s Bool)`, and can't solve that (because of the overlap in A), so it just abstract, giving {{{ test_bar :: A (Foo s Bool) => s -> Int }}} So the mysterious thing is really why GHC 8 accepts the instance declaration {{{ instance B (Foo s a) }}} After all, that instance must also solve `A (Foo s a)`, and that involves overlap. And that behaviour is the result of a second tricky issue. Suppose class `A` had a class method, and `Foo` had a data constructor, looking like this: {{{ data Foo s a = FNil | FCons a (Foo s a) class A a where op :: a -> Int instance A (Foo s a) where op FNil = 0 op (FCons _ f) = op f -- Needs A (Foo s a)! instance {-# OVERLAPPING #-} A (Foo Int Bool) where ... }}} When typechecking the commented line for `op`, we need to solve `A (Foo s a)`. And on this occasion it would be Bad to fail to solve it, saying "instance overlap". See `Note [Subtle interaction of recursion and overlap]` in `TcInstDcls`. So there is special magic to allow this to work. (For the afficionados, we use `SkolemTv True` rather than `SkolemTv False` in the `TcTyVarDetails`.) Alas, this magic also applies to the superclass solving, but I now think that it should not do so. Removing the magic would make the instance declaration be rejected; instead you would have to delay the superclass choice by writing {{{ instance A (Foo s a) => B (Foo s a) }}} I think this is probably the right thing to do. Do others agree? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12201#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12201: Wrong instance selection with overlapping instance in a superclass -------------------------------------+------------------------------------- Reporter: kanetw | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | 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 kanetw): That sounds like the right thing to do. It feels a bit unpleasant from an aesthetics perspective, but I can't really think of a better solution. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12201#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12201: Wrong instance selection with overlapping instance in a superclass -------------------------------------+------------------------------------- Reporter: kanetw | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: invalid | 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => invalid Comment: Closing since there appears to be no better ideas on the table. Feel free to re-open if you have a better alternative. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12201#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12201: Wrong instance selection with overlapping instance in a superclass -------------------------------------+------------------------------------- Reporter: kanetw | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: invalid | Keywords: Instances Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Instances -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12201#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC