
I've read Jeff Newbern's tutorial on monad transformers (http://www.nomaware.com/monads/html/index.html), but I don't grok it yet and I can't tell how to get started with this particular requirement, or even if I need monad transformers for this. I have a program that performs a series of IO operations, each which can result in an error or a value. If a step returns a value I usually want to pass that value on to the next step, if I get an error I want to do some error handling but usually want to skip the remaining steps. Thus I have a lot of functions with return types like IO (Either String x), where x might be (), Integer, or some other useful value type, and a lot of case statements like a :: Integer -> IO (Either String String) (a :: Either String Integer) <- some_io_action_returning_integer_or_error case a of -- got to get from (Either String Integer) to (Either String String) Left message -> return $ Left message -- continue on Right i -> do_more i If I was using just Either I know how to get rid of the case statements: import Control.Monad.Error p :: Integer -> Either String Integer q :: Integer -> Either String String r :: Either String String r = do a <- p 3 b <- q a return b which of course is much nicer. But how do I combine the Error and IO monads so that r could have the type IO (Either String String)?

Cat Dancer wrote:
I have a program that performs a series of IO operations, each which can result in an error or a value. If a step returns a value I usually want to pass that value on to the next step, if I get an error I want to do some error handling but usually want to skip the remaining steps.
Thus I have a lot of functions with return types like IO (Either String x), where x might be (), Integer, or some other useful value type, and a lot of case statements like
You are on the right track. The point is that (IO (Either String a)) is a Monad, too. This allows you to write the ever repeating case statements once and forall: newtype ErrorIO a = ErrorIO (IO (Either String a)) instance Monad ErrorIO where return x = return (Right x) f >>= g = do ex <- f case ex of e@(Left _) -> return e Right x -> g x It happens that you can parametrize this on IO: newtype ErrorT m a = ErrorT (m (Either String a)) type ErrorIO a = ErrorT IO a instance Monad m => Monad (ErrorT m) where ... -- same as above And you just rediscovered monad transformers. Regards, apfelmus PS: In the special case of IO, you can also use exceptions. But using ErrorT is better style.

On 12/7/06, apfelmus@quantentunnel.de
Cat Dancer wrote:
I have a program that performs a series of IO operations, each which can result in an error or a value. If a step returns a value I usually want to pass that value on to the next step, if I get an error I want to do some error handling but usually want to skip the remaining steps.
Thus I have a lot of functions with return types like IO (Either String x), where x might be (), Integer, or some other useful value type, and a lot of case statements like
You are on the right track. The point is that (IO (Either String a)) is a Monad, too. This allows you to write the ever repeating case statements once and forall:
newtype ErrorIO a = ErrorIO (IO (Either String a))
instance Monad ErrorIO where return x = return (Right x) f >>= g = do ex <- f case ex of e@(Left _) -> return e Right x -> g x
It happens that you can parametrize this on IO:
newtype ErrorT m a = ErrorT (m (Either String a)) type ErrorIO a = ErrorT IO a
instance Monad m => Monad (ErrorT m) where ... -- same as above
And you just rediscovered monad transformers.
I think I need to explain how thoroughly clueless I am :) I'm sure from a single example I could understand what was going on and elaborate from there. Let's say I want to get a line from the user, and either return an integer or an error string using ErrorT. import Control.Monad.Error import Control.Monad.Trans foo :: ?? foo = do -- something like this? a <- getLine if length a == 1 then return 123 else throwError "not a single character" main = do r <- ?? foo ?? print r -- prints Left "not a single character" or Right 123 ?

On 12/7/06, Cat Dancer
On 12/7/06, apfelmus@quantentunnel.de
wrote: I'm sure from a single example I could understand what was going on and elaborate from there. Let's say I want to get a line from the user, and either return an integer or an error string using ErrorT.
import Control.Monad.Error import Control.Monad.Trans
foo :: ??
foo :: ErrorT String IO Int if you're going to use this very often, you can use a line like type M = ErrorT String IO and then foo :: M Int
foo = do -- something like this? a <- getLine
Since ErrorT String IO Int is not the same as IO, you can't use IO operations directly. In this case, you want: < a <- lift getLine
if length a == 1 then return 123 else throwError "not a single character"
This is all fine
main = do r <- ?? foo ??
You want: < r <- runErrorT foo and then this will behave as expected:
print r -- prints Left "not a single character" or Right 123 ?
Your foo operation is in a monad which wraps IO. lift allows IO operations inside that wrapper, and runErrorT removes the wrapper. The same basic pattern works for other wrappers (like StateT or ListT) or combinations of wrappers (like StateT Int (ErrorT String IO)) /g -- It is myself I have never met, whose face is pasted on the underside of my mind.

On 12/7/06, J. Garrett Morris
foo :: ErrorT String IO Int
Since ErrorT String IO Int is not the same as IO, you can't use IO operations directly. In this case, you want:
< a <- lift getLine
You want:
< r <- runErrorT foo
Wow! I found your help terrific! Thank you! Can I give you some money?

On Fri, 08 Dec 2006 07:31:25 -0500, Cat Dancer wrote:
On 12/7/06, J. Garrett Morris
wrote: foo :: ErrorT String IO Int
Since ErrorT String IO Int is not the same as IO, you can't use IO operations directly. In this case, you want:
< a <- lift getLine
You want:
< r <- runErrorT foo
Wow! I found your help terrific! Thank you! Can I give you some money?
I didn't see the original question, but there are some examples of this in the ConfigFile (formerly part of MissingH) docs here: http://software.complete.org/configfile/static/doc/Data-ConfigFile.html#12 After you read that, you'll probably also want to scroll back and look at the other examples of usage: http://software.complete.org/configfile/static/doc/Data-ConfigFile.html#9 to really give you a complete sense of the styles available. The Error monad is one of the really awesome things about Haskell, IMHO. -- John
participants (4)
-
apfelmus@quantentunnel.de
-
Cat Dancer
-
J. Garrett Morris
-
John Goerzen