Why isn't this Overlapping?

Anthony Clayden anthony_clayden at clear.net.nz
Tue Apr 18 11:24:53 UTC 2017


> On Tue Apr 18 10:31:30 UTC 2017, Simon Peyton Jones wrote:
>
> Moreover, as discussed in the user manual section,
> GHC doesn’t complain about overlapping instances at the
instance decl,
> but rather where the instances are used.

Thank you Simon, yes I knew that, so I'd written a usage
(just didn't bother putting it in the message ):

foo :: (TypeEq a a' b) => a -> a' -> String
foo _ _ = "blah"

x = foo 'c' "String"

> That’s why there is no overlap complaint here

I didn't get a complaint about `x`, contrary to what I
expected.

On trying again just now:

y = foo 'c' 'd'

GHC _does_ complain of overlap.

I apologise for the distraction.


AntC

>> On 18 April 2017 01:50, Iavor Diatchki wrote
 
>> these two instances really should be rejected as they
violate the FD of the class:
>> we can derive `TypeEq a a True` using the first instance
and `TypeEq a a False`
>> using the second one.  Unfortunately, the check that we
are using
>> to validate FDs when `UndecidableInstances` is on,
>> is not quite correct (relevant tickets are #9210 and
#10675
>> where there are similar examples).


>>> On Sun, Apr 16, 2017 at 12:13 AM, Anthony Clayden wrote:

>>> --ghc 7.10 or 8.0.1
>>>
>>> {-# LANGUAGE DataKinds, KindSignatures, GADTs,
>>>          MultiParamTypeClasses,
>>>          FunctionalDependencies, FlexibleInstances,
>>>          UndecidableInstances, NoOverlappingInstances  
#-}

>>> class TypeEq a a' (b :: Bool) | a a' -> b
>>>
>>> instance (b ~ True) => TypeEq a a b
>>> instance (b ~ False) => TypeEq a a' b

>>> Those two instance heads are nearly identical,
>>> surely they overlap?
>> And for a type-level type equality test,
>>> they must be unifiable.
>>> But GHC doesn't complain.
>>>
>>> If I take off the FunDep, then GHC complains.
>>>
>>> AFAICT none of those extensions imply Overlaps,
>>> but to be sure I've put NoOverlapping.




More information about the Glasgow-haskell-users mailing list