[Haskell-cafe] Applicative instances for Monads

Ben Millwood haskell at benmachine.co.uk
Sat Sep 25 11:29:17 EDT 2010


On Sat, Sep 25, 2010 at 3:01 AM, Gregory Crosswhite
<gcross at phys.washington.edu> wrote:
> ======================================================================
>
> import Control.Applicative
> import Control.Concurrent
> import Control.Concurrent.MVar
>
> newtype AIO a = AIO {unAIO :: IO a}
>
> instance Monad AIO where
>   return = AIO . return
>   (AIO x) >>= f = AIO (x >>= unAIO . f)
>
> instance Functor AIO where
>    fmap f (AIO x) = AIO (fmap f x)
>
> instance Applicative AIO where
>    pure = return
>    (AIO mf) <*> (AIO ma) = AIO $ do
>      f_box <- newEmptyMVar
>      forkIO (mf >>= putMVar f_box)
>      a_box <- newEmptyMVar
>      forkIO (ma >>= putMVar a_box)
>      f <- takeMVar f_box
>      a <- takeMVar a_box
>      return (f a)
>
> ======================================================================

This idea is pretty neat :) I think it should be found a place on the
wiki, or maybe even Hackage. The way in which it interacts with
exceptions, especially async exceptions, could be odd though, so it'd
be worth checking it pedantically adheres to the rules.

> To summarize:  on the one hand every Monad has a generic instance for
> Applicative, and yet on the other hand this instance is often arguably not
> the "correct" one because it ignores the fact that the second computation is
> independent of the first, which is a fact that can be exploited given
> additional knowledge about the structure of the Monad.
>
> I bring this up because there has been talk here of automatically having
> instances of Monad also be instances of Applicative, and what bugs me is
> that on the one hand this makes perfect since as every Monad can also be
> viewed as an Applicative, and yet on the other hand not only is there often
> more than one natural way to define an Applicative instance for selected
> Monads but furthermore the "generic" instance is often an inferior
> definition because it ignores the structure of the Monad.

I think what we learn from this is not that the Monad-based instance
of Applicative is necessarily the "wrong" one, but rather that there
is often more than one reasonable instance for a type, each suitable
for different uses. There are times when parallelisation is not a
priority, but determinism is, in which case we'd *want* the sequencing
of Monad even in the Applicative instance.

Often we use newtypes to distinguish between them (see: ZipList), and
if we accept that the Monad-based instance is always a useful one (and
if the Monad instance itself is useful I think it is) it makes sense
for it also to be the "default" one, so that we can have ap and <*>
always mean the same thing in the same context.


More information about the Haskell-Cafe mailing list