
Hi, I was surprised to see my code break with ghc-7, due to changed monad instances: With ghc-6.12.3 I have: Prelude> :m Control.Monad.Error Prelude Control.Monad.Error> fail "Bla" :: Either String () Loading package mtl-1.1.0.2 ... linking ... done. Left "Bla" but with ghc-7.0.4 and ghc-7.2.2 I get a fatal exception: *Main> fail "Bla" :: Either String () *** Exception: Bla I always viewed "Either String" as an alternative to Maybe with a failure message. The instance in ghc-7 comes from Control.Monad.Instances: instance Monad (Either e) where return = Right Left l >>= _ = Left l Right r >>= k = k r which indeed uses "error" as default implementation of fail. Is there (supposed to be) an overlapping "instance Monad (Either String)" somewhere else? Any comments (or notes) that I missed? Cheers Christian

On Mon, Nov 28, 2011 at 1:17 PM, Christian Maeder
Hi,
I was surprised to see my code break with ghc-7, due to changed monad instances:
With ghc-6.12.3 I have:
Prelude> :m Control.Monad.Error Prelude Control.Monad.Error> fail "Bla" :: Either String () Loading package mtl-1.1.0.2 ... linking ... done. Left "Bla"
but with ghc-7.0.4 and ghc-7.2.2 I get a fatal exception:
*Main> fail "Bla" :: Either String () *** Exception: Bla
I always viewed "Either String" as an alternative to Maybe with a failure message.
The instance in ghc-7 comes from Control.Monad.Instances: instance Monad (Either e) where return = Right Left l >>= _ = Left l Right r >>= k = k r
which indeed uses "error" as default implementation of fail. Is there (supposed to be) an overlapping "instance Monad (Either String)" somewhere else?
Any comments (or notes) that I missed?
Cheers Christian
It's not exactly a bug, it's a change in behaviour. Beforehand, there was no overlapping instance, the instance was just 'instance (Error e) => Monad (Either e) where' but the Error constraint proved to be more a hindrance than a help, since it prevented the instance being used with Left things that weren't Errors, even though that's often a useful thing to do. So it was agreed that the Error constraint should be removed, breaking 'fail' but making the instance much more generally applicable. Overlapping instances could be added for individual types, but overlapping instances are usually considered to cause more problems than they solve – ambiguity can easily arise in polymorphic functions over Either. Either still works as Maybe with added information, except now you lose the do-pattern-matching magic. Sometimes I use something like this:
maybe (Left "oh no!") Right $ do x:xs <- Just blah [...]
to use little bits of Maybe inside an Either do. Notice I get control of the error message here, too, so I can usually make it more useful.

I'd just like to add one further remark. If we had a separate MonadFail class then we could get back the original behavior by imposing an Error constraint on it, but without the problems we get by imposing it on the Monad instance instead. - Jake

On 28 November 2011 20:22, Jake McArthur
I'd just like to add one further remark. If we had a separate MonadFail class then we could get back the original behavior by imposing an Error constraint on it, but without the problems we get by imposing it on the Monad instance instead.
The problem with a separate MonadFail class is when to add that constraint to the type of a do-expression. Currently do-expression with a bind: do {p <- e; stmts} are translated to: let ok p = do {stmts} ok _ = fail "..." in e >>= ok With a separate MonadFail class we have 4 options: 1) Simply translate to: "e >>= \p -> do{stmts}" instead. This means pattern match errors are always turned into errors. 2) Give all do-expressions a MonadFail constraint. 3) Only give do-expressions with pattern bindings a MonadFail constraint. 4) Only give do-expressions with pattern bindings with uncomplete patterns a MonadFail constraint. To me 2, 3 and 4 seem fishy. I like 1 a lot but I'm unsure how many programs will break because of it. Regards, Bas

On Mon, Nov 28, 2011 at 2:47 PM, Bas van Dijk
4) Only give do-expressions with pattern bindings with uncomplete patterns a MonadFail constraint.
To me 2, 3 and 4 seem fishy. I like 1 a lot but I'm unsure how many programs will break because of it.
Number 4 is the one I had in mind. The basic rule would be that if the pattern is refutable (that is, not irrefutable as defined by section 3.17.2 in the Haskell 2010 report) then MonadFail is required. - Jake

On 11/28/2011 05:32 PM, Jake McArthur wrote:
On Mon, Nov 28, 2011 at 2:47 PM, Bas van Dijk
wrote: 4) Only give do-expressions with pattern bindings with uncomplete patterns a MonadFail constraint.
To me 2, 3 and 4 seem fishy. I like 1 a lot but I'm unsure how many programs will break because of it.
Number 4 is the one I had in mind. The basic rule would be that if the pattern is refutable (that is, not irrefutable as defined by section 3.17.2 in the Haskell 2010 report) then MonadFail is required.
That seems like a fishy rule for the purpose. Refutable: (a, b) Irrefutable: a Refutable patterns are those which immediately fail if the value bound is ⊥ (bottom). [1] If the value is ⊥ for a refutable monadic pattern, MonadFail can't do anything about this. An imprecise exception will be thrown. No exceptions.(pun horribly intended[2]). And I don't think we can tweak the suggested rule to allow single-constructor 'data' (which we know would never be able to call "fail" via pattern) if we want it also to behave exactly as nicely as we'd like for all GADTs. Argh. I suppose we could make a keyword 'fdo', generating type MonadFail, like 'mdo' generates MonadFix... (or actually we switched to "do { rec }" rather than "mdo" [3]... so.) -Isaac [1] H2010 says, as you cited, "It is sometimes helpful to distinguish two kinds of patterns. Matching an irrefutable pattern is non-strict: the pattern matches even if the value to be matched is ⊥. Matching a refutable pattern is strict: if the value to be matched is ⊥ the match diverges. The irrefutable patterns are as follows: a variable, a wildcard, N apat where N is a constructor defined by newtype and apat is irrefutable (see Section 4.2.3), var@apat where apat is irrefutable, or of the form ~apat (whether or not apat is irrefutable). All other patterns are refutable." [2] ...and not quite accurate because nontermination is also a ⊥. But I couldn't resist. [3] http://haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html#recurs...

On Mon, 2011-11-28 at 20:47 +0100, Bas van Dijk wrote:
On 28 November 2011 20:22, Jake McArthur
wrote: I'd just like to add one further remark. If we had a separate MonadFail class then we could get back the original behavior by imposing an Error constraint on it, but without the problems we get by imposing it on the Monad instance instead.
The problem with a separate MonadFail class is when to add that constraint to the type of a do-expression.
Currently do-expression with a bind:
do {p <- e; stmts}
are translated to:
let ok p = do {stmts} ok _ = fail "..." in e >>= ok
With a separate MonadFail class we have 4 options:
1) Simply translate to: "e >>= \p -> do{stmts}" instead. This means pattern match errors are always turned into errors.
It may be just me but I always desugared in head do {p <- e; stmts} => e >>= \p -> do {stmts} Hence I would prefer the option 1) with special syntax for MonadFail: do {p - e; stmts} => e >>= \p' -> case p' of p -> do {stmts}; _ -> fail "..."
2) Give all do-expressions a MonadFail constraint.
3) Only give do-expressions with pattern bindings a MonadFail constraint.
4) Only give do-expressions with pattern bindings with uncomplete patterns a MonadFail constraint.
To me 2, 3 and 4 seem fishy. I like 1 a lot but I'm unsure how many programs will break because of it.
From me +1 for 1) with the same note.
Regards,
Bas
Regards

Am 28.11.2011 15:30, schrieb Ben Millwood:
Any comments (or notes) that I missed?
Cheers Christian
It's not exactly a bug, it's a change in behaviour. Beforehand, there was no overlapping instance, the instance was just 'instance (Error e) => Monad (Either e) where' but the Error constraint proved to be more a hindrance than a help, since it prevented the instance being used with Left things that weren't Errors, even though that's often a useful thing to do. So it was agreed that the Error constraint should be removed, breaking 'fail' but making the instance much more generally applicable.
Was there a library proposal that I've missed? Does any release note mention this change? Previously correct programs can now crash quite unpredictably without warnings!
Overlapping instances could be added for individual types, but overlapping instances are usually considered to cause more problems than they solve – ambiguity can easily arise in polymorphic functions over Either.
Either still works as Maybe with added information, except now you lose the do-pattern-matching magic. Sometimes I use something like this:
maybe (Left "oh no!") Right $ do x:xs<- Just blah [...]
to use little bits of Maybe inside an Either do. Notice I get control of the error message here, too, so I can usually make it more useful.
My use case is (or better was) monadic code like: typeCheck :: Monad m => ... -> m (...) where I used the "Either String" Monad instance to extract the fail messages: case typeCheck ... of Right ... -> ... Left ... -> .... For this I now need another monad! Which one is recommended? Cheers Christian

Christian Maeder writes:
Am 28.11.2011 15:30, schrieb Ben Millwood:
It's not exactly a bug, it's a change in behaviour. Beforehand, there was no overlapping instance, the instance was just 'instance (Error e) => Monad (Either e) where' but the Error constraint proved to be more a hindrance than a help, since it prevented the instance being used with Left things that weren't Errors, even though that's often a useful thing to do. So it was agreed that the Error constraint should be removed, breaking 'fail' but making the instance much more generally applicable.
Was there a library proposal that I've missed? Does any release note mention this change?
The library proposal was http://thread.gmane.org/gmane.comp.lang.haskell.libraries/13196 The mtl package hasn't been released with GHC since 6.10, so the GHC 7.0.1 release notes don't mention changes to it, just that instances were added to base.

Ross Paterson writes:
Christian Maeder writes:
Was there a library proposal that I've missed? Does any release note mention this change?
The library proposal was http://thread.gmane.org/gmane.comp.lang.haskell.libraries/13196
The patches were on the ticket: http://hackage.haskell.org/trac/ghc/ticket/4159

Am 29.11.2011 13:00, schrieb Paterson, Ross:
Ross Paterson writes:
Christian Maeder writes:
Was there a library proposal that I've missed? Does any release note mention this change?
The library proposal was http://thread.gmane.org/gmane.comp.lang.haskell.libraries/13196
The patches were on the ticket: http://hackage.haskell.org/trac/ghc/ticket/4159
Thanks, I must have overlooked the consequences of "moving instances". My "no" would not have changed anything, though. Let's see who else will be bitten by this change (years later). Cheers Christian

On Tue, Nov 29, 2011 at 11:36 AM, Christian Maeder
Previously correct programs can now crash quite unpredictably without warnings!
Yeah, this bit the HTTP library too, but there was no way to address the infelicity without this happening.
My use case is (or better was) monadic code like:
typeCheck :: Monad m => ... -> m (...)
where I used the "Either String" Monad instance to extract the fail messages:
case typeCheck ... of Right ... -> ... Left ... -> ....
For this I now need another monad! Which one is recommended?
Cheers Christian
typeCheck :: ... -> Either String ... or even better, define a real error type, TypeError, and give typeCheck the return type Either TypeError ... which makes matching cases and reacting to problems much more straightforward, as well as up-front showing you the ways it can fail. You can then convert back to the generic version with 'either fail return' (or 'either (fail . show) return' in the TypeError case) but you probably won't need to most of the time, you'll just use the function as-is. Inside typeCheck, you just use Left instead of fail. If you use the do pattern-match failure, you isolate it in little Maybe blocks like the one I have above, with your own error message for each one. Something like: typeCheck :: AST -> Either TypeError Type typeCheck (Tuple xs) = do -- check the tuple has >= 2 elements check SyntaxError $ do [_,_] <- return (take 2 xs) return () -- type check them TupleType <$> mapM typeCheck xs check :: TypeError -> Maybe a -> Either TypeError a check err = maybe (Left err) Right Admittedly the 'return ()' is a little ugly, but the fact you're explicit about the error you're throwing makes up for it in my opinion. Notice that the line using mapM typeCheck xs wouldn't work in the past unless TypeError was an instance of Error; often there isn't a sensible way for it to be so.

I would rather not change my (nice) monadic typeCheck function. Do we have a "standard" monad instance to recover the "error-free" version from the monad version (that is more informative than Maybe)? Cheers Christian Am 29.11.2011 14:47, schrieb Ben Millwood:
On Tue, Nov 29, 2011 at 11:36 AM, Christian Maeder
wrote: Previously correct programs can now crash quite unpredictably without warnings!
Yeah, this bit the HTTP library too, but there was no way to address the infelicity without this happening.
My use case is (or better was) monadic code like:
typeCheck :: Monad m => ... -> m (...)
where I used the "Either String" Monad instance to extract the fail messages:
case typeCheck ... of Right ... -> ... Left ... -> ....
For this I now need another monad! Which one is recommended?
Cheers Christian
typeCheck :: ... -> Either String ...
or even better, define a real error type, TypeError, and give typeCheck the return type Either TypeError ... which makes matching cases and reacting to problems much more straightforward, as well as up-front showing you the ways it can fail.
You can then convert back to the generic version with 'either fail return' (or 'either (fail . show) return' in the TypeError case) but you probably won't need to most of the time, you'll just use the function as-is. Inside typeCheck, you just use Left instead of fail. If you use the do pattern-match failure, you isolate it in little Maybe blocks like the one I have above, with your own error message for each one. Something like:
typeCheck :: AST -> Either TypeError Type typeCheck (Tuple xs) = do -- check the tuple has>= 2 elements check SyntaxError $ do [_,_]<- return (take 2 xs) return () -- type check them TupleType<$> mapM typeCheck xs
check :: TypeError -> Maybe a -> Either TypeError a check err = maybe (Left err) Right
Admittedly the 'return ()' is a little ugly, but the fact you're explicit about the error you're throwing makes up for it in my opinion. Notice that the line using mapM typeCheck xs wouldn't work in the past unless TypeError was an instance of Error; often there isn't a sensible way for it to be so.

ErrorT from mtl still has a 'fail' implementation that returns a Left.
Erik
On Wed, Nov 30, 2011 at 10:32, Christian Maeder
I would rather not change my (nice) monadic typeCheck function.
Do we have a "standard" monad instance to recover the "error-free" version from the monad version (that is more informative than Maybe)?
Cheers Christian
Am 29.11.2011 14:47, schrieb Ben Millwood:
On Tue, Nov 29, 2011 at 11:36 AM, Christian Maeder
wrote: Previously correct programs can now crash quite unpredictably without warnings!
Yeah, this bit the HTTP library too, but there was no way to address the infelicity without this happening.
My use case is (or better was) monadic code like:
typeCheck :: Monad m => ... -> m (...)
where I used the "Either String" Monad instance to extract the fail messages:
case typeCheck ... of Right ... -> ... Left ... -> ....
For this I now need another monad! Which one is recommended?
Cheers Christian
typeCheck :: ... -> Either String ...
or even better, define a real error type, TypeError, and give typeCheck the return type Either TypeError ... which makes matching cases and reacting to problems much more straightforward, as well as up-front showing you the ways it can fail.
You can then convert back to the generic version with 'either fail return' (or 'either (fail . show) return' in the TypeError case) but you probably won't need to most of the time, you'll just use the function as-is. Inside typeCheck, you just use Left instead of fail. If you use the do pattern-match failure, you isolate it in little Maybe blocks like the one I have above, with your own error message for each one. Something like:
typeCheck :: AST -> Either TypeError Type typeCheck (Tuple xs) = do -- check the tuple has>= 2 elements check SyntaxError $ do [_,_]<- return (take 2 xs) return () -- type check them TupleType<$> mapM typeCheck xs
check :: TypeError -> Maybe a -> Either TypeError a check err = maybe (Left err) Right
Admittedly the 'return ()' is a little ugly, but the fact you're explicit about the error you're throwing makes up for it in my opinion. Notice that the line using mapM typeCheck xs wouldn't work in the past unless TypeError was an instance of Error; often there isn't a sensible way for it to be so.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Yes, thanks, this works and is worth knowing. It looks a bit ugly but is shorter than making a new monad. Prelude Control.Monad.Identity Control.Monad.Error> runIdentity . runErrorT $ fail "bla" :: Either String () Left "bla" C. Am 30.11.2011 11:39, schrieb Erik Hesselink:
ErrorT from mtl still has a 'fail' implementation that returns a Left.
Erik

On 30/11/11 13:55, Christian Maeder wrote:
Yes, thanks, this works and is worth knowing. It looks a bit ugly but is shorter than making a new monad.
Prelude Control.Monad.Identity Control.Monad.Error> runIdentity . runErrorT $ fail "bla" :: Either String () Left "bla"
We should also add a type synonym for Error, like there is for Reader, State and RWS: type Error e a = ErrorT e a error :: Either e a -> Error e a error = ErrorT . Indentity runError :: Error e a -> Either e a runError = runIdentity . runErrorT mapError :: Error e a -> Error f a mapError f = mapErrorT (Identity . f . runIdentity) The only problem is that the name 'Error' is taken by a typeclass, and 'error' by everyone's least favorite prelude function. Twan

This would be wonderful, but as you noted, the obvious choice conflicts with the unfortunately named Error class used for ErrorT's argument. I usually use err, Err and runErr in my own code for what you describe.
Sent from my iPad
On Dec 2, 2011, at 11:13 AM, Twan van Laarhoven
On 30/11/11 13:55, Christian Maeder wrote:
Yes, thanks, this works and is worth knowing. It looks a bit ugly but is shorter than making a new monad.
Prelude Control.Monad.Identity Control.Monad.Error> runIdentity . runErrorT $ fail "bla" :: Either String () Left "bla"
We should also add a type synonym for Error, like there is for Reader, State and RWS:
type Error e a = ErrorT e a error :: Either e a -> Error e a error = ErrorT . Indentity runError :: Error e a -> Either e a runError = runIdentity . runErrorT mapError :: Error e a -> Error f a mapError f = mapErrorT (Identity . f . runIdentity)
The only problem is that the name 'Error' is taken by a typeclass, and 'error' by everyone's least favorite prelude function.
Twan
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (10)
-
Bas van Dijk
-
Ben Millwood
-
Christian Maeder
-
Edward Kmett
-
Erik Hesselink
-
Isaac Dupree
-
Jake McArthur
-
Maciej Marcin Piechotka
-
Paterson, Ross
-
Twan van Laarhoven