
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.

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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wed, Nov 26, 2008 at 1:54 PM, Miguel Mitrofanov
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)
The first is good, the second isn't. The first says the right thing: if you can prove Applicative f and Eq a, you have a way to prove AppEq f a. The second has the implication the wrong way around. Classes get the implication wrong too: class Eq a => Ord a doesn't say that if you can prove Eq a you can prove Ord a; it says that if you can prove Ord a you can prove Eq a /g -- I am in here

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.
Or perhaps a simpler way of explaining it is that (metasyntactically) for the class: > class CLASS a1 ... an where > f1 :: t1 > ... > fn :: tn the instance declaration: > instance CONTEXT a1 ... an => CLASS a1 ... an where > f1 :: t1 > ... > fn :: tn means *exactly*: > instance CLASS a1 ... an where > f1 :: CONTEXT a1 ... an => t1 > ... > fn :: CONTEXT a1 ... an => tn The ability to add contexts to a typeclass instance is not syntactic sugar per se ---because the latter declaration would be an invalid instance of the class (allowing the syntax might permit instances where contexts are inconsistent across f1...fn)--- but it's still just a sugary way of simplifying the declaration. While the latter declaration is unbearably syntactically salted, it's straightforward for explaining this common mistake. There've been a number of proposals for different syntax to make the current arrangement less confusing to newcomers, none of which has gained widespread currency. In the fine Haskell tradition of leaving things odd until a proper solution is found, I think the correct approach is to redesign the meaning of the original declaration such that it *does* propagate the constraints at instance-selection time, rather than trying to find a nicer coat of paint for the old bikeshed. The OverlappingInstances and IncoherentInstances flags are varnish to make the current arrangement tenable, but they cover up a whole area that is ripe for research. The new type families work covers a nearby domain, but I think active context propagation deals with a different set of concerns. -- Live well, ~wren
participants (5)
-
J. Garrett Morris
-
Miguel Mitrofanov
-
Paul Johnson
-
Ryan Ingram
-
wren ng thornton