Proposal: Applicative => Monad: Call for consensus

Bas van Dijk v.dijk.bas at gmail.com
Wed Jan 5 12:24:11 CET 2011


On Wed, Jan 5, 2011 at 11:33 AM, Simon Marlow <marlowsd at gmail.com> wrote:
> Furthermore, we have some significant compatibility issues with Haskell
> 98/2010 code.  I wouldn't be in favour of doing this unless we can retain
> Haskell 98/2010 compatibility somehow (e.g. with superclass defaults or
> class aliases).

It would indeed be really nice to have something like this:

{-# LANGUAGE DefaultInstances #-}

class Functor f where
    fmap :: (a → b) → f a → f b

class Functor f ⇒ Applicative f where
    pure  :: a → f a
    (<*>) :: f (a → b) → f a → f b

    instance Functor f where
        fmap f m = pure f <*> m

class Applicative m ⇒ Monad m where
    return :: a → m a
    (>>=)  :: m a → (a → m b) → m b

    instance Applicative m where
        pure = return
        mf <*> mx = do f ← mf
                       x ← mx
                       return (f x)
        -- The following is nicer
        -- but may cause a circular definition:
        mf <*> mx = do f ← mf
                       fmap f mx

Now to make a type (for example Maybe) an instance of Monad the only
thing to do is to declare:

instance Monad Maybe where
    return        = Just
    Nothing >>= _ = Nothing
    Just x  >>= f = f x

And you will get the Applicative and Functor instances for free.

The Eq and Ord classes also benefit from this language extension:

class Eq a where
    (==) :: a → a → Bool

class Eq a ⇒ Ord a where
    compare :: a → a → Ordering

    instance Eq a where
        x == y = compare x y == Eq

Just like default methods, default instances can be overwritten by a
user defined instance.

There's the question whether a default instance should be required to
be a super class of the class that defines the default instance. For
example, should the following be allowed:

class Foo a where
  instance Bar a

class Bar a

I can't see a use of this yet, but I also can't see a reason why it
shouldn't be allowed.

Now only someone has to implement it :-)

Regards,

Bas



More information about the Libraries mailing list