This line

    instance Monad m => Applicative m where

tells the compiler "Every type (of the appropriate kind) is an instance of Applicative.  And it needs to have a Monad instance as well."

That's what Edward means when he said that it means "every Applicative is a Monad".  Theoretically the statement makes no sense, but that's what this instance head means.  Everything is Applicative, and it also needs a Monad instance to use that Applicative.

Consider what happens for something that isn't a Monad, e.g. ZipList.  Since it's not a Monad, it would need its own instance

    instance Applicative ZipList where
    ...

But now you'd need to enable OverlappingInstances, because ZipList matches both this instance and the general one you've defined above (GHC doesn't consider constraints when matching instance heads).  OverlappingInstances is much more problematic than the other extensions because it could (and almost certainly would in this case) give rise to incoherence (see the warning under http://www.haskell.org/ghc/docs/latest/html/users_guide/type-class-extensions.html#instance-overlap).

You might want to read the wiki page on default superclass instances (http://ghc.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances) for further discussion of this problem.

John L.

On Tue, Sep 24, 2013 at 12:17 PM, Wvv <vitea3v@rambler.ru> wrote:
I suggest to add superclass' instances into  libraries.

http://ghc.haskell.org/trac/ghc/ticket/8348

In brief, we could write next:

>{-# LANGUAGE FlexibleInstances #-}
>{-# LANGUAGE UndecidableInstances #-}
>
>instance Monad m => Applicative m where
>    pure  = return
>    (<*>) = ap
>
>instance Monad m => Functor m where
>    fmap = liftM
>
>instance Monad m => Bind m where
>    (>>-) = flip (>>=)
>    B.join = M.join

this code is valid!

I've already defined 3 "superclassses" for Monad: Functor, Applicative and
Bind!

Similar idea said Edward Kmett in 2010 (founded by monoidal) (
http://stackoverflow.com/questions/3213490/how-do-i-write-if-typeclass-a-then-a-is-also-an-instance-of-b-by-this-definit/3216937#3216937
)

And he said "but effectively what this instance is saying is that every
Applicative should be derived by first finding an instance for Monad, and
then dispatching to it. So while it would have the intention of saying that
every Monad is Applicative (by the way the implication-like => reads) what
it actually says is that every Applicative is a Monad, because having an
instance head 't' matches any type. In many ways, the syntax for 'instance'
and 'class' definitions is backwards."

Why? I don't understand.
Not every Applicative is a Monad, but every Monad is Applicative



--
View this message in context: http://haskell.1045720.n5.nabble.com/Why-superclass-instances-are-bad-idea-tp5737056.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe