[GHC] #9939: Warn for duplicate superclass constraints

#9939: Warn for duplicate superclass constraints -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.8.3 Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- With the following code, GHC warns that there are duplicate constraints: {{{#!hs {-# LANGUAGE FlexibleInstances, UndecidableInstances #-} module Foo where class Foo a where foo :: Int -> a instance (Integral a, Integral a) => Foo a where foo x = (fromIntegral x) `div` 2 }}} However, when writing the code, I might start with: {{{#!hs {-# LANGUAGE FlexibleInstances, UndecidableInstances #-} module Foo where class Foo a where foo :: Int -> a instance Foo a where foo x = (fromIntegral x) `div` 2 }}} without any constraints on the instance. GHC complains that it needs `Num a` and `Integral a`, but of course `Num` is implied by `Integral`. I'm ''not'' asking that GHC figure this out on its own and only request the strongest constraint necessary. Rather, I'm suggesting that ''if'' I followed GHC's suggestion and wrote {{{#!hs {-# LANGUAGE FlexibleInstances, UndecidableInstances #-} module Foo where class Foo a where foo :: Int -> a instance (Num a, Integral a) => Foo a where foo x = (fromIntegral x) `div` 2 }}} then GHC should warn {{{ Duplicate constraint(s): Num a In the context: (Num a, Integral a) (Num a) is implied by (Integral a) }}} or something similar. The motivation for this feature request is that in large instances/programs, it is difficult for a human to keep track of superclasses. In large instances, GHC tends to request "weak" constraints first (say `Num`), then ask for progressively stronger constraints (say `Integral`). Again, I'm not suggesting that behavior should change. However, it tends to lead to instances that look like `(Num a, Real a, RealFrac a, RealFloat a) => ...` if by chance I happened to use methods from each class. It seems fairly simple for GHC to look at each constraint for an instance (or function), trace back up the class hierarchy to get a set of all implied constraints, and then warn if one set is a subset of another. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9939 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9939: Warn for duplicate superclass constraints -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 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): Another example I hit recently. `Language.Haskell.TH.Syntax` used to have {{{ class (Applicative m, Monad m) => Quasi m where ... }}} When I saw this recently, I realized the `Applicative m` constraint is now redundant and so I removed it. However, it would have been helpful if GHC had issued a warning. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9939#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9939: Warn for duplicate superclass constraints
-------------------------------------+-------------------------------------
Reporter: crockeea | Owner:
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.3
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 Simon Peyton Jones

#9939: Warn for duplicate superclass constraints
-------------------------------------+-------------------------------------
Reporter: crockeea | Owner:
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.3
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 Simon Peyton Jones

#9939: Warn for duplicate superclass constraints
-------------------------------------+-------------------------------------
Reporter: crockeea | Owner:
Type: feature request | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.3
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | typecheck/should_compile/T9939
| Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Changes (by simonpj):
* status: new => closed
* testcase: => typecheck/should_compile/T9939
* resolution: => fixed
Comment:
Well, I went ''way'' overboard on this, but it was fun! Thanks for the
suggestion. It showed up masses of unnecessary constraints in the
compiler itself, and in many libraries, as you can see from
{{{
commit c409b6f30373535b6eed92e55d4695688d32be9e
Author: Simon Peyton Jones
participants (1)
-
GHC