[Haskell-cafe] Applicative/Monad for Either

Ryan Ingram ryani.spam at gmail.com
Wed Jan 21 17:39:32 EST 2009


I think it's possible, but not in a very clean way.

First lets look at ap:

> ap mf mx = do
>   f <- mf
>   x <- mx
>   return (f x)

equivalently, desugared:

> ap mf mx = mf >>= \f -> mx >>= \x -> return (f x)

So, it's possible to make a definition of >>= where "ap" works as you like:

>    Z (Left e1) >>= f = case f (error "urk") of
>        Z (Left e2) -> Z (Left (mappend e1 e2))
>        Z (Right _) -> Z (Left e1)
>    Z (Right a) >>= f = f a

(Does this definition of >>= break any of the monad laws?  I can't see
where it does, but I haven't proved that it doesn't.)

Now "ap" will reduce how you want, but monadic (non-applicative)
computations like this have a problem:

> throw :: e -> Z e a
> throw e = Z (Left e)
> urk = throw "uhoh" >>= \b -> if b then return "ok" else throw "urk"

In order to determine whether the constructor on the right of >>= is
"Left" or "Right", we need to examine the value from the left of >>=.
But there is no value there; it's _|_.

So I don't think there's a way to make this into a particularily safe
to use monad, if you require the law "(<*>) = ap"

  -- ryan

On Wed, Jan 21, 2009 at 2:03 PM, Tony Morris <tmorris at tmorris.net> wrote:
> -----BEGIN PGP SIGNED MESSAGE-----
> Hash: SHA1
>
> In the code below, the Applicative instance accumulates on the Left
> constructor using Monoid/mappend.
> Is it possible to write an equivalent Monad such that ap = (<*>) ? I'm
> finding difficulty in proving to myself either way.
>
>
>
>
> import Control.Monad.Instances
> import Control.Applicative
> import Data.Monoid
>
> newtype Z e a = Z {
>  either :: Either e a
> }
>
> instance Functor (Z e) where
>  fmap f (Z e) = Z (f `fmap` e)
>
> instance (Monoid e) => Applicative (Z e) where
>  pure = Z . Right
>  (Z (Left e1)) <*> (Z (Left e2)) = Z (Left (e1 `mappend` e2))
>  (Z (Left e1)) <*> (Z (Right _)) = Z (Left e1)
>  (Z (Right _)) <*> (Z (Left e2)) = Z (Left e2)
>  (Z (Right f)) <*> (Z (Right a)) = Z (Right (f a))
>
> instance (Monoid e) => Monad (Z e) where
>  return = pure
>  (Z e) >>= f = error "todo" -- ?
>
> - --
> Tony Morris
> http://tmorris.net/
>
> S, K and I ought to be enough for anybody.
>
> -----BEGIN PGP SIGNATURE-----
> Version: GnuPG v1.4.6 (GNU/Linux)
> Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org
>
> iD8DBQFJd5vImnpgrYe6r60RAoUNAJ4jn0GfC6zsP9giPGop1ILExiHrLQCfSoc2
> 0QXf533sWb3HyrL0pQNjMww=
> =R36O
> -----END PGP SIGNATURE-----
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list