[Haskell-cafe] Applicative and Monad transformers

Jeremy Shaw jeremy at n-heptane.com
Wed Aug 26 11:20:03 EDT 2009


Hello,

I have seen it said that all Monads are Applicative Functors because
you can just do:

instance (Monad f, Applicative f) => Applicative (ReaderT r f) where
    pure = return
    (<*>) = ap

However, that instance for ReaderT does not exhibit the properties I
was hoping for. By substitution the definition of ap:

ap                :: (Monad m) => m (a -> b) -> m a -> m b
ap                =  liftM2 id

liftM2  :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 f m1 m2          = do { x1 <- m1; x2 <- m2; return (f x1 x2) }

we see that it becomes:

instance (Monad f, Applicative f) => Applicative (ReaderT r f) where
    pure = return
    f <*> x = do { f' <- f; x' <- x; return (f' x') }

What I would prefer is:

instance (Monad f, Applicative f) => Applicative (ReaderT r f) where
    pure a = ReaderT $ const (pure a)
    f <*> a = ReaderT $ \r -> 
              ((runReaderT f r) <*> (runReaderT a r))

I assume that only one version is correct, but I am having a hard time
figuring out which one. 

I have attached a file which shows my motivation for prefering the
second variation. There is a 'looker' function which does three
lookups and combines the results using the Applicative Functor.

With the first Applicative instance for ReaderT you will only get a
failure message for the first lookup that fails -- which is what you
expect with monadic behaviour. With the second instance, you get back
a list of all the lookups that failed, which seems like what I would
expect with Applicative Functor behaviour.

Thanks!
- jeremy

-------------- next part --------------
{-# LANGUAGE FlexibleContexts, FlexibleInstances #-}
module Main where

import Control.Applicative (Applicative((<*>), pure), (<$>))
import Control.Monad (Monad((>>=), return), ap)
import Control.Monad.Reader (MonadReader(ask, local), ReaderT(ReaderT, runReaderT))
import Data.Monoid(Monoid(mappend))


instance (Monad f, Applicative f) => Applicative (ReaderT r f) where
    pure = return
    (<*>) = ap

{-
instance (Monad f, Applicative f) => Applicative (ReaderT r f) where
    pure a = ReaderT $ const (pure a)
    f <*> a = ReaderT $ \r -> 
              ((runReaderT f r) <*> (runReaderT a r))
-}
instance (Monoid e) => Applicative (Either e) where
    pure = Right
    (Left errF) <*> (Left errA) = Left (errF `mappend` errA)
    (Left err)  <*> _           = Left err
    _           <*> (Left err)  = Left err
    (Right f)   <*> (Right a)   = Right (f a)

instance Monad (Either [String]) where
    return = Right 
    (Right a) >>= f = f a
    (Left e) >>= f = (Left e)
    fail str = Left [str]

lookupE :: (Eq a) => a -> [(a,b)] -> (Either a b)
lookupE a env =
    case lookup a env of
      Just b -> Right b
      Nothing -> Left a

look :: String -> ReaderT [(String,b)] (Either [String]) b
look a =
    do env <- ask
       case lookup a env of
         Just b -> return b
         Nothing -> fail a

looker :: ReaderT [(String, Int)] (Either [String]) (Int, Int, Int)
looker = ((,,) <$> look "foo" <*> look "bar" <*> look "baz")

test :: Either [String] (Int, Int, Int)
test =
    runReaderT looker [("bar", 1)]
-------------- next part --------------





More information about the Haskell-Cafe mailing list