[GHC] #13526: -Wsimplifiable-class-constraints behaves differently with OVERLAPPING and OVERLAPPABLE

GHC ghc-devs at haskell.org
Tue Apr 4 20:21:17 UTC 2017


#13526: -Wsimplifiable-class-constraints behaves differently with OVERLAPPING and
OVERLAPPABLE
-------------------------------------+-------------------------------------
           Reporter:  cocreature     |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.1
           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:
-------------------------------------+-------------------------------------
 {{{
 {-# LANGUAGE FlexibleContexts, FlexibleInstances, FunctionalDependencies,
 MultiParamTypeClasses, UndecidableInstances #-}
 module Test where
 import Foreign.Ptr

 class DescendentOf a b where
     upCast :: Ptr b -> Ptr a
     upCast = castPtr

 class ChildOf b c | c -> b

 instance {-# OVERLAPPING #-} DescendentOf a a where
     upCast = id

 instance (DescendentOf a b, ChildOf b c) => DescendentOf a c

 data Value

 operateOnValue :: Ptr Value -> IO ()
 operateOnValue _ = pure ()

 typeOf :: DescendentOf Value v => Ptr v -> IO ()
 typeOf = operateOnValue . upCast
 }}}
 The above code results in the following warning with GHC 8.2rc1

 {{{
 Test.hs:21:11: warning: [-Wsimplifiable-class-constraints]
     The constraint ‘DescendentOf Value v’
       matches an instance declaration
     instance (DescendentOf a b, ChildOf b c) => DescendentOf a c
       -- Defined at Test.hs:14:10
     This makes type inference for inner bindings fragile;
       either use MonoLocalBinds, or simplify it using the instance
    |
 21 | typeOf :: DescendentOf Value v => Ptr v -> IO ()
 }}}

 However, if I add `OVERLAPPABLE` to the second instance, the warning
 disappears because such instances are explicitly excluded in the check for
 this warning. I think it would make sense to silence this warning also if
 there is any `OVERLAPPING` instance that matches. The current warning is
 confusing since in this case the constraint actually can’t be simplified
 without changing the meaning of the code (the first instance would no
 longer match).

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13526>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list