
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-the... ) 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-t... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.