(In reply to
http://www.haskell.org/pipermail/haskell/2005-December/017109.html
)

One of the key things about those nested monads is that
*often* you
don't have to write things like

    return $ throwError msg

but can simply write

    throwError msg

because the nest has all the features of its components.

The IO monad doesn't participate fully in this, but the
liftIO
function (from the MonadIO class) serves as an adapter.

> import Control.Monad.Error
> f () = do n <- liftIO readLn
>           when (n == 2) (throwError "2-char string")
>           sequence (replicate n (liftIO getChar))
>               `catchError` (throwError . ("g Error: "++))

(Pay no attention to the () parameter behind the curtain! 
I'm dodging
the monomorphism restriction, and don't want to give an
explicit type
signature.)

The inferred type is

    f :: (MonadError [Char] m, MonadIO m) => () -> m [Char]

i.e. it's usable for any nest of monads that provides the
MonadError String
and MonadIO features.

Now, how to run it?  Your type signatures of the form

    IO (Either String String)

are very reminiscent of the ErrorT monad transformer

    newtype ErrorT e m a
        = ErrorT {runErrorT :: (m (Either e a))}

with IO as m and String as e and a.  So, let's test f in
ErrorT String IO.

*Main> runErrorT (f ()) >>= print
0
Right ""
*Main> runErrorT (f ()) >>= print
2
Left "I don't like strings with 2 characters."
*Main> runErrorT (f ()) >>= print
4
Too
Right "Too\n"

Regards,
Tom
_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to