[GHC] #9948: Recommend class constraint instead of instance constraint

#9948: Recommend class constraint instead of instance constraint -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.8.4 Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Consider the following example: {{{#!hs {-# LANGUAGE FlexibleInstances, UndecidableInstances #-} module Foo where class Foo a where foo :: Int -> a instance (Num a) => Foo a where foo x = error "" f :: Int -> a f = foo }}} GHC says {{{ No instance for (Num a) arising from a use of ‘foo’ Possible fix: add (Num a) to the context of the type signature for f :: Int -> a In the expression: foo In an equation for ‘f’: f = foo }}} A better error, in my opinion, would be: {{{ No instance for (Foo a) arising from a use of ‘foo’ Possible fix: add (Foo a) to the context of the type signature for f :: Int -> a In the expression: foo In an equation for ‘f’: f = foo }}} That is, I think GHC should recommend the superclass constraint arising from the use of `foo` rather than trying to match an instance and then recommending constraints from the instance. Here are several reasons a superclass constraint is preferable: 1. If the matching instance has several constraints, GHC will recommend putting *all* of those constraints on the function instead of a single superclass constraint. This (naively) results in unnecessarily long constraints on functions that call methods. 2. If the constraints on the instance change, GHC will recommend the corresponding change on the function constraints. This means the instance constraints are not isolated, but instead propagate through the code. 3. The instance constraints might not make sense on the function itself. For example, `f` might not use any methods from the `Num` class, but GHC recommends the `Num` constraint anyway. Recommending the direct superclass constraint should be **less** work for GHC than the current implementation: instead of trying to find a matching instance, it simply stops when it finds that `foo` is a method. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9948 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9948: Recommend class constraint instead of instance constraint -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): I'm -1 on this change. * `Num a` is the minimal constraint (in a logic sense) needed on `f`, as it implies all other constraints necessary. * Point (2) above talks about robustness in the presence of refactoring. While that case is true, other refactorings (say, splitting up the `Foo` class) prefer the `Num a` constraint. * Implementing this would be ''more'' work for GHC, I believe. When GHC is trying to satisfy the `Foo a` constraint that arises from the use of `foo`, it then naturally looks for `Foo` instances. It finds a matching one, and then proceeds to try to satisfy the instance's constraints. This process can continue arbitrarily deeply. To report the error requested would require, at the end, looking at the set of unsolved constraints and then trying to find some instance that covers them all. There might be more efficient/effective ways to do this (say, remember precisely the constraints that arise directly from constrained function usages), but it would be more work for GHC, regardless. As a smaller point (but which confused me at first), the original post uses the term "superclass" in a way different to the way I use it: I've always understood "superclass" to refer to constraints on a class definition, such as the `Bar a` in `class Bar a => Fuggle a`. Above, it seems the term "superclass" refers to an instance head. Please correct if I'm wrong. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9948#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9948: Recommend class constraint instead of instance constraint -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by crockeea: Old description:
Consider the following example:
{{{#!hs {-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
module Foo where
class Foo a where foo :: Int -> a
instance (Num a) => Foo a where foo x = error ""
f :: Int -> a f = foo }}}
GHC says
{{{ No instance for (Num a) arising from a use of ‘foo’ Possible fix: add (Num a) to the context of the type signature for f :: Int -> a In the expression: foo In an equation for ‘f’: f = foo }}}
A better error, in my opinion, would be:
{{{ No instance for (Foo a) arising from a use of ‘foo’ Possible fix: add (Foo a) to the context of the type signature for f :: Int -> a In the expression: foo In an equation for ‘f’: f = foo }}}
That is, I think GHC should recommend the superclass constraint arising from the use of `foo` rather than trying to match an instance and then recommending constraints from the instance.
Here are several reasons a superclass constraint is preferable:
1. If the matching instance has several constraints, GHC will recommend putting *all* of those constraints on the function instead of a single superclass constraint. This (naively) results in unnecessarily long constraints on functions that call methods.
2. If the constraints on the instance change, GHC will recommend the corresponding change on the function constraints. This means the instance constraints are not isolated, but instead propagate through the code.
3. The instance constraints might not make sense on the function itself. For example, `f` might not use any methods from the `Num` class, but GHC recommends the `Num` constraint anyway.
Recommending the direct superclass constraint should be **less** work for GHC than the current implementation: instead of trying to find a matching instance, it simply stops when it finds that `foo` is a method.
New description: Consider the following example: {{{#!hs {-# LANGUAGE FlexibleInstances, UndecidableInstances #-} module Foo where class Foo a where foo :: Int -> a instance (Num a) => Foo a where foo x = error "" f :: Int -> a f = foo }}} GHC says {{{ No instance for (Num a) arising from a use of ‘foo’ Possible fix: add (Num a) to the context of the type signature for f :: Int -> a In the expression: foo In an equation for ‘f’: f = foo }}} A better error, in my opinion, would be: {{{ No instance for (Foo a) arising from a use of ‘foo’ Possible fix: add (Foo a) to the context of the type signature for f :: Int -> a In the expression: foo In an equation for ‘f’: f = foo }}} That is, I think GHC should recommend the ~~super~~class constraint arising from the use of `foo` rather than trying to match an instance and then recommending constraints from the instance head. Here are several reasons a ~~super~~class constraint is preferable: 1. If the matching instance has several constraints, GHC will recommend putting *all* of those constraints on the function instead of a single ~~super~~class constraint. This (naively) results in unnecessarily long constraints on functions that call methods. 2. If the constraints on the instance change, GHC will recommend the corresponding change on the function constraints. This means the instance constraints are not isolated, but instead propagate through the code. 3. The instance constraints might not make sense on the function itself. For example, `f` might not use any methods from the `Num` class, but GHC recommends the `Num` constraint anyway. Recommending the direct ~~super~~class constraint should be **less** work for GHC than the current implementation: instead of trying to find a matching instance, it simply stops when it finds that `foo` is a method. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9948#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9948: Recommend class constraint instead of instance constraint -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by adamgundry): I think the message ought to keep saying `No instance for (Num a)` because that is exactly what is logically missing, as Richard says. There is an instance for `Foo a`, and it would be very confusing if GHC claimed there wasn't. I'd be open to the `Possible fix` line saying `(Num a) or (Foo a)`, but I suspect the work required to change it may outweigh the benefit. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9948#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

* Implementing this would be ''more'' work for GHC, I believe. When GHC is trying to satisfy the `Foo a` constraint that arises from the use of `foo`, it then naturally looks for `Foo` instances. It finds a matching one, and then proceeds to try to satisfy the instance's constraints. This
#9948: Recommend class constraint instead of instance constraint -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by crockeea): process can continue arbitrarily deeply. To report the error requested would require, at the end, looking at the set of unsolved constraints and then trying to find some instance that covers them all. There might be more efficient/effective ways to do this (say, remember precisely the constraints that arise directly from constrained function usages), but it would be more work for GHC, regardless. I'm suggesting that if `foo` is a method of class `Foo`, then GHC simply says `cannot deduce (Foo a)`. There's no need to match instances at all. This is already the behavior in the absence of instances, i.e. if I define `class Foo a` with method `foo` and no instances, and then write a function `f` that uses `foo`, GHC recommends a `Foo a` constraint. However, if i define instances as in my question, GHC starts recommending constraints from the matching *instance* instead.
As a smaller point (but which confused me at first), the original post
uses the term "superclass" in a way different to the way I use it: I've always understood "superclass" to refer to constraints on a class definition, such as the `Bar a` in `class Bar a => Fuggle a`. Above, it seems the term "superclass" refers to an instance head. Please correct if I'm wrong. By "superclass", I meant "class". Right now GHC proposes constraints from a matching instance head, which is more work and results in a mess. I would prefer if GHC, when I use `foo`, simply recommends the class (containing `foo`) constraint `Foo a`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9948#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9948: Recommend class constraint instead of instance constraint -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:4 crockeea]:
I'm suggesting that if `foo` is a method of class `Foo`, then GHC simply says `cannot deduce (Foo a)`. There's no need to match instances at all.
However, we would, of course, still like to find an instance where possible. Just determining if an instance exists requires looking up instances for `Foo`, and then perhaps recurring on any constraints to those instances. At the end of a chain of instance constraints, we might end up with some constraint, say `Bar Int a`, that is unsatisfiable. Only then do we know that no instance matches the original constraint. To report a missing `Foo a` constraint at this point, we would need to somehow the need for `Bar Int a` came from a desire for `Foo a`. Keeping track of this is the "more work" I was talking about. Nowhere near impossible, but strictly harder than what happens currently. In any case, I think the discussion about how hard this feature is to implement detracts from the debate we should be having: what is really the desired behavior, regardless of implementation challenge. (To be clear, the implementation is not particularly challenging here, I think -- just not completely trivial.) And, regardless of implementation issues, I prefer the current behavior over the new one proposed in this ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9948#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

However, we would, of course, still like to find an instance where
#9948: Recommend class constraint instead of instance constraint -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by crockeea): Replying to [comment:5 goldfire]: possible. I see your point. So it's good that GHC looks at instances and tries to find a RHS match. If he constraints are also satisfied, then no errors should be reported. The case I'm talking about is when there is a matching instance [on the RHS], but the instance constraints are not satisfied. {{{ data T a class Foo b where foo :: b -> Int instance (Integral a) => Foo (T a) f :: T a -> Int f = foo }}} I don't like that GHC behaves differently in the presence of a matching instance vs when there are no matching instances. One workaround for what I'm suggesting (that I find myself frequently using) is to comment out all instances of the class. Then GHC just says `no instance for `Foo a` arising from the use of `foo`` instead of recommending constraints from the matching instance. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9948#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9948: Recommend class constraint instead of instance constraint -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): I can see why you might want this behavior in some cases, but would you really want {{{ isPalindrome :: [a] -> Bool isPalindrome xs = xs == reverse xs }}} to suggest adding an `Eq [a]` constraint (that's not even valid Haskell 98!), or some function to dump a data structure to suggest adding a `Show [(Int, Maybe a)]` constraint? Whatever constraint GHC suggests, it won't be the appropriate one in every situation. The current behavior is the most obvious one to me (the suggested constraint is the same one that appears in the type that GHC would infer in the absence of a type signature). I'm also a bit confused by the workaround that you mentioned; if you know that `Foo` is the class containing `foo` (which you must to comment out its instances) then don't you already know what constraint to add? Is it very difficult in your use cases to work out what the parameter to the class should be? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9948#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9948: Recommend class constraint instead of instance constraint -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by crockeea): Replying to [comment:7 rwbarton]:
I can see why you might want this behavior in some cases, but would you really want
{{{ isPalindrome :: [a] -> Bool isPalindrome xs = xs == reverse xs }}}
to suggest adding an `Eq [a]` constraint (that's not even valid Haskell 98!), or some function to dump a data structure to suggest adding a `Show [(Int, Maybe a)]` constraint?
I see your point on these examples. How's the feature request for GHC mind-reading coming along?
I'm also a bit confused by the workaround that you mentioned; if you know that `Foo` is the class containing `foo` (which you must to comment out its instances) then don't you already know what constraint to add? Is it very difficult in your use cases to work out what the parameter to the class should be?
Yes, it should be pretty obvious which constraint I need. The only minor point I could make is that it isn't always immediately clear if the function you are using is top-level or a method. The only way to resolve that is to look at some documentation. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9948#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC