Hey everyone,
There is something that has been bugging me recently about the
Applicative class and the Monad class.
Any type constructor F that is a Monad has a natural Applicative instance,
(<$>) :: F (a -> b) -> F a -> F b
mf <$> ma = do
f <- mf
a <- ma
return (f a)
So it seems that defining something to be a Monad should automatically
make it an instance of Applicative with this definition for (<$>). So
far so good, but there are times when this implementation is too
"sequential". The nature of Applicative is that later actions are not
allowed to depend on earlier actions, which means that it is natural to
run them in parallel when possible. So for example, considering the
following alternative of Applicative for a newtype AIO that wraps an IO
computation:
======================================================================
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 seems to me to be an arguably better way to implement Applicative
because it uses the fact that we know that the second action is
independent from the first to gain parallelism by sparking them in
separate threads. So for example if one has six actions m1 ... m6 that
could run in parallel then one could write something like the following:
======================================================================
main = do
...
(x1,x2,x3,x4,x5,x6) <-
(,,,,,)
<$> a1
<*> a2
<*> a3
<*> a4
<*> a5
<*> a6
...
======================================================================
Here is another example: Consider the following instance of Applicative
for the Either type:
======================================================================
import Control.Applicative
import Data.Monoid
instance Monoid error => Applicative (Either error) where
pure = Right
Right f <*> Right x = Right (f x)
Left error <*> Right _ = Left error
Right _ <*> Left error = Left error
Left error1 <*> Left error2 = Left (error1 `mappend` error2)
display :: Either String Int -> IO ()
display = putStrLn . show
main = mapM_ (putStrLn . show)
[Right (+1) <*> Right 1
,Right (+1) <*> Left "[bad value]"
,Left "[bad function]" <*> Right 1
,Left "[bad function]" <*> Left "[bad value]"
]
======================================================================
This is much like the instance used by the Error monad, but it has the
advantage that rather than terminating at the first sign of error it
instead gathers together the errors produced by each subcomputation.
Again, we can do this because we know that we do not need the result of
the first computation in order to evaluate the second computation.
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.
Thoughts?
Cheers,
Greg
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe