[Haskell-cafe] Instances that shouldn't overlap

Miguel Mitrofanov miguelimo38 at yandex.ru
Wed Nov 26 16:54:58 EST 2008


Maybe it'd be more intuitive if written backwards:

AppEq f a <= (Applicative f, Eq a)

or even

AppEq f a => (Applicative f, Eq a)

On 27 Nov 2008, at 00:39, Ryan Ingram wrote:

> A common mistake (and a confusing bit about typeclasses) is that
> whether or not the constraints on an instance apply are irrelevant.
>
> Specifically, the code "instance (Applicative f, Eq a) => AppEq f a"
> means that, given any types f and a, I can tell you how to make them
> an instance of AppEq.  But I also ask you to please add the
> constraints "Applicative f" and "Eq a".  That is to say, only the
> stuff on the right of the => apply when determining whether an
> instance applies.
>
> If you take out the overlapping specific instance for Interval, the
> compiler will give you a different error:
>
> "No instance for Applicative Interval".  You can see what happened
> here: the compiler wants an instance for AppEq Interval Integer.  It
> sees the instance "AppEq f a" and adds the constraints "Ord Integer"
> and "Applicative Interval".  Ord Integer is already fulfilled, but it
> can't discharge the constraint on Applicative, so the compile fails.
>
> Similarily, in your case, the compiler can't decide whether to apply
> the "Ord a => AppEq Interval a" instance, or the "Applicative f, Eq a
> => AppEq f a" instance; the right hand sides of the instance
> declarations both match (and add different constraints to the left
> hand side).
>
> You can use -XOverlappingInstances, but beware, dragons lie in that  
> direction.
>
> I think this is a fundamental weakness of the typeclass system, but I
> haven't seen a design that avoids it for code as complicated as this.
>
> On Wed, Nov 26, 2008 at 12:05 PM, Paul Johnson <paul at cogito.org.uk>  
> wrote:
>> Hi,
>>
>> I'm trying to set up some operators for applicative versions of  
>> prelude
>> types.  For instance:
>>
>> -- | Applicative Equality.
>> class (Eq a) => AppEq f a where
>> (.==.), (./=.) :: f a -> f a -> f Bool
>>
>> instance (Applicative f, Eq a) => AppEq f a where
>> (.==.)  = liftA2 (==)
>> (./=.)  = liftA2 (/=)
>>
>>
>> Hopefully the intention is fairly straightforward: if "f" is an  
>> instance of
>> Applicative then the lifted implementation of the underlying type.
>> Otherwise I can just give my own instance, which is useful for  
>> things that
>> "wrap" prelude types but where "fmap" doesn't work.  For instance:
>>
>> data (Ord a) => Interval a = Interval a a
>>
>> instance (Ord a) => AppEq Interval a where
>> i1@(Interval _ u1) .==. i2@(Interval _ u2)
>>    | isSingleton i1 && isSingleton i2 && u1 == u2  = Interval True  
>> True
>>    | has i1 u2 || has i2 u1                        = Interval False  
>> True
>>    | otherwise                                     = Interval False  
>> False
>> i1 ./=. i2 = let Interval b1 b2 = (i1 .==. i2) in Interval (not b2)  
>> (not
>> b1)
>>
>> isSingleton :: (Ord a) => Interval a -> Bool
>> isSingleton (Interval lower upper) = lower == upper
>>
>> has :: (Ord a) => Interval a -> a -> Bool
>> has (Interval lower upper) v = v >= lower && v <= upper
>>
>>
>> You can't (easily) define fmap for Interval because the function  
>> given as an
>> argument might not be monotonic.  So instead you have to write custom
>> implementations for each lifted function, as shown here for (.==.)  
>> and
>> (./=.) .  The same principle works for AppOrd, AppNum etc, but I'm  
>> trying to
>> solve the problem for just AppEq for now.
>>
>> This compiles, but when I try to use it I get this in ghci:
>>
>> *Interval> let i1 = Interval 4 5
>> *Interval> let i2 = Interval 4 6
>> *Interval> i1 .==. i2
>>
>> <interactive>:1:0:
>> Overlapping instances for AppEq Interval Integer
>>   arising from a use of `.==.' at <interactive>:1:0-9
>> Matching instances:
>>   instance (Ord a) => AppEq Interval a
>>     -- Defined at Interval.hs:(22,0)-(27,78)
>>   instance (Control.Applicative.Applicative f, Eq a) => AppEq f a
>>     -- Defined at AppPrelude.hs:(32,0)-(34,23)
>> In the expression: i1 .==. i2
>> In the definition of `it': it = i1 .==. i2
>>
>> I'm puzzled, because Interval is not an instance of Applicative, so  
>> the
>> second instance doesn't apply.  Can anyone help me out?
>>
>> I'm using ghc 6.8.3, so its possible that this was a bug fixed in  
>> 6.10.
>>
>> Paul.
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list