Warn for duplicate superclass constraints
With the following code, GHC warns that there are duplicate constraints:
{-# 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:
{-# 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
{-# 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.
Trac metadata
Trac field | Value |
---|---|
Version | 7.8.3 |
Type | FeatureRequest |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |