[GHC] #9939: Warn for duplicate superclass constraints

GHC ghc-devs at haskell.org
Tue Dec 30 01:49:30 UTC 2014


#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


More information about the ghc-tickets mailing list