
Hi all, A why question: Why: Control.Monad.Error Prelude> runErrorT (fail "msg") :: IO (Either String Int) Left "msg" but Control.Monad.Error Prelude> (fail "msg") :: (Either String Int) *** Exception: msg ? -- Gracjan

Probably because in the instance of Monad Either, fail has not been
overloaded, and still has its default implementation:
fail = error
Whereas runErrorT explicitely catches the exception.
2011/5/16 Gracjan Polak
Hi all,
A why question: Why:
Control.Monad.Error Prelude> runErrorT (fail "msg") :: IO (Either String Int) Left "msg"
but
Control.Monad.Error Prelude> (fail "msg") :: (Either String Int) *** Exception: msg
?
-- Gracjan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Monday 16 May 2011 23:05:22, Yves Parès wrote:
Probably because in the instance of Monad Either, fail has not been overloaded, and still has its default implementation: fail = error
Right. It used to be different in mtl-1.*, when there was an instance Error e => Monad (Either e) where return = Right Left err >>= _ = Left err Right x >>= k = k x fail msg = strMsg msg defined in Control.Monad.Error. Now we have instance Monad (Either e) where ... defined in Control.Monad.Instances, and there's no method to get an arbitrary e from a String (except error).
Whereas runErrorT explicitely catches the exception.
`catches' is the wrong word, the Monad instance of ErrorT, instance (Monad m, Error e) => Monad (ErrorT e m) where ... has fail msg = ErrorT $ return (Left (strMsg msg)) That's probably what you meant, though.

Thanks Daniel, Yves and Edward for explanation. Two things come to my mind now. 1. It should be unified. Why? Because conceptually: runIdentity (runErrorT (fail "msg")) :: Either String Int Left "msg" and fail "msg" :: Either String Int *** Exception: msg Should be the same as Identity monad should not add structure. 2. I need a Failure monad that works well with pattern match failures (that call fail). I'd like to use it like this: runErrorT $ do Active <- getStatus -- ensure proper status Just elm <- lookup stuff there -- lookup element when (condition) $ fail "wrong!" -- check condition return 1234 -- return useful value sort of... Any ideas what could be used in place of Either monad? Basically I need working pattern match failures (I guess that means I need working fail method that is not equal to error). -- Gracjan

On Mon, May 16, 2011 at 4:41 PM, Gracjan Polak
Thanks Daniel, Yves and Edward for explanation. Two things come to my mind now.
1. It should be unified. Why? Because conceptually:
runIdentity (runErrorT (fail "msg")) :: Either String Int Left "msg"
and
fail "msg" :: Either String Int *** Exception: msg
Should be the same as Identity monad should not add structure.
ErrorT and Either are different types - I think it is okay that they are different. In some applications you might not want to silently discard pattern match failures.
2. I need a Failure monad that works well with pattern match failures (that call fail). I'd like to use it like this:
runErrorT $ do Active <- getStatus -- ensure proper status Just elm <- lookup stuff there -- lookup element when (condition) $ fail "wrong!" -- check condition return 1234 -- return useful value
sort of... Any ideas what could be used in place of Either monad? Basically I need working pattern match failures (I guess that means I need working fail method that is not equal to error).
ErrorT is a good choice for this. There is also the 'ExceptionT' monad transformer over here: http://hackage.haskell.org/packages/archive/exception-transformers/0.3/doc/h... Which you'll want to use with the exception-mtl package http://hackage.haskell.org/package/exception-mtl I don't have any experience with it, but from what I can tell those are the two choices already built. Antoine
-- Gracjan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Monday 16 May 2011 23:41:44, Gracjan Polak wrote:
Thanks Daniel, Yves and Edward for explanation. Two things come to my mind now.
1. It should be unified.
The (Either e) Monad instance was recently changed after people have long complained that there shouldn't be an (Error e) constraint. It's unlikely that that will be reverted soon.
Why? Because conceptually:
runIdentity (runErrorT (fail "msg")) :: Either String Int Left "msg"
and
fail "msg" :: Either String Int *** Exception: msg
Should be the same as Identity monad should not add structure.
It's the (Error e) Monad which adds the structure [nowadays, Error e = ErrorT e Identity].
2. I need a Failure monad that works well with pattern match failures (that call fail). I'd like to use it like this:
runErrorT $ do Active <- getStatus -- ensure proper status Just elm <- lookup stuff there -- lookup element when (condition) $ fail "wrong!" -- check condition return 1234 -- return useful value
sort of...
That does work, doesn't it?
Any ideas what could be used in place of Either monad? Basically I need working pattern match failures (I guess that means I need working fail method that is not equal to error).
Roll your own, data Result err a = Failure err | Success a deriving (stuff) instance (Error err) => Monad (Result err) where ... if ErrorT is too unwieldy. If you don't need the fail message, Maybe would work.

Daniel Fischer
On Monday 16 May 2011 23:41:44, Gracjan Polak wrote:
Thanks Daniel, Yves and Edward for explanation. Two things come to my mind now.
1. It should be unified.
The (Either e) Monad instance was recently changed after people have long complained that there shouldn't be an (Error e) constraint. It's unlikely that that will be reverted soon.
I did not request a revert, I asked about consistent behavior.
It's the (Error e) Monad which adds the structure [nowadays, Error e = ErrorT e Identity].
I do not understand this part. Can you elaborate?
2. I need a Failure monad that works well with pattern match failures (that call fail). I'd like to use it like this:
runErrorT $ do Active <- getStatus -- ensure proper status Just elm <- lookup stuff there -- lookup element when (condition) $ fail "wrong!" -- check condition return 1234 -- return useful value
sort of...
That does work, doesn't it?
Indeed this does work, but it is fragile wrt refactorings. Suppose we have the code: result <- runErrorT $ do lift $ print "was here" fail "msg" (result = Left "msg") after a while the print statement may be removed: result <- runErrorT $ do fail "msg" (result = Left "msg") and then somebody will see that inner 'do' does not depend on outer monad so next refactoring will be: let result = do fail "msg" (result = error "msg") And here code breaks...
Roll your own,
That is a good idea. I looked also at Attempt. Thanks for responses. -- Gracjan

On Mon, May 16, 2011 at 8:40 PM, Gracjan Polak
result <- runErrorT $ do lift $ print "was here" fail "msg"
(result = Left "msg")
after a while the print statement may be removed:
result <- runErrorT $ do fail "msg"
(result = Left "msg")
That seems pretty unlikely for me. If all you have is a "fail", then there is something wrong with this code. If there's anything besides "fail", then removing "runErrorT" would result in a type error. Cheers, =) -- Felipe.

On Tuesday 17 May 2011 01:40:41, Gracjan Polak wrote:
Daniel Fischer
writes: On Monday 16 May 2011 23:41:44, Gracjan Polak wrote:
Thanks Daniel, Yves and Edward for explanation. Two things come to my mind now.
1. It should be unified.
The (Either e) Monad instance was recently changed after people have long complained that there shouldn't be an (Error e) constraint. It's unlikely that that will be reverted soon.
I did not request a revert, I asked about consistent behavior.
Not directly, but for ghci> fail "msg" :: Either String Int and ghci> runIdentity (runErrorT (fail "msg")) :: Either String Int to have the same behaviour, there are three possibilities a) change ErrorT's behaviour, so that the latter matches the former. b) change (Either e)'s Monad instance so that the former matches the latter. c) change both. b) is the most reasonable, IMO, and that's reverting the change of the Monad instance of (Either e).
It's the (Error e) Monad which adds the structure [nowadays, Error e = ErrorT e Identity].
Misremembered, there never was a newtype doing for ErrorT what State does [did] for StateT etc.
I do not understand this part. Can you elaborate?
You wrote: "... Should be the same as Identity monad should not add structure." Now, the Identity Monad doesn't add the structure that makes the former result in (Left "msg"), Prelude Control.Monad.Identity> runIdentity (fail "msg") :: Either String Int *** Exception: msg The Monad instance that makes fail not be error is instance (Monad m, Error e) => Monad (ErrorT e m) where ...
2. I need a Failure monad that works well with pattern match failures
(that call fail). I'd like to use it like this: runErrorT $ do
Active <- getStatus -- ensure proper status Just elm <- lookup stuff there -- lookup element when (condition) $ fail "wrong!" -- check condition return 1234 -- return useful value
sort of...
That does work, doesn't it?
Indeed this does work, but it is fragile wrt refactorings.
Suppose we have the code:
result <- runErrorT $ do lift $ print "was here" fail "msg"
(result = Left "msg")
after a while the print statement may be removed:
result <- runErrorT $ do fail "msg"
(result = Left "msg")
and then somebody will see that inner 'do' does not depend on outer monad
But the transformation result <- runWhatEver stuff to let result = stuff generally doesn't typecheck, so it can't be generally correct, hence if it typechecks, one has to examine each case to decide where it's valid and where not. One big point of ErrorT is the working around the inner Monad's fail, so it should be a big warning sign if a `fail' appears.
so next refactoring will be:
let result = do fail "msg"
(result = error "msg")
And here code breaks...
Roll your own,
That is a good idea. I looked also at Attempt.
Thanks for responses.

I suspect it is because the "fail" method for the 'Either' monad
instance makes use of Haskell's error function, since the instance is
defined generally and there is no way to override it for (Either
String a).
On May 16, 2011, Gracjan Polak
Control.Monad.Error Prelude> runErrorT (fail "msg") :: IO (Either String Int) Left "msg"
ErrorT defines fail to yield a pure value, rather than an exception. Since ErrorT is a different type than Either (though the runErrorT method yields an Either), the instances are different.
but
Control.Monad.Error Prelude> (fail "msg") :: (Either String Int) *** Exception: msg
The Monad instance for Either is defined generally, e.g. "instance Monad (Either a) where" so there is know way of typechecking a fail method that injects a string into "Left" in that case. -- Edward Amsden Student Computer Science Rochester Institute of Technology www.edwardamsden.com
participants (6)
-
Antoine Latter
-
Daniel Fischer
-
Edward Amsden
-
Felipe Almeida Lessa
-
Gracjan Polak
-
Yves Parès