
If there is one thing that we really don't have enough of in Haskell, it is *ways to handle errors*! Thus, I am pleased to announce the release of the "error-message" package to help in filling this, erm, gap. This philosophy behind this package is that it is often better to find out all of the errors that have occured in a computation and report them simultaneously, rather than aborting as soon as the first error is encountered. Towards this end, this package supplies a type of /combinable error messages/ (ErrorMessage in the Data.ErrorMessage module) so that all of the errors from subcomputations can be gathered and presented together. The following provides an example of how these can be used: ================================================== sqrtWithError :: Float -> Either ErrorMessage Float sqrtWithError x | x < 0 = leftErrorMessageText ("Error computing the square root of " ++ (show x) ++ ":") "Square roots cannot be taken of negative numbers." | otherwise = Right (sqrt x) sumWithError :: Either ErrorMessage Float -> Either ErrorMessage Float -> Either ErrorMessage Float sumWithError (Left error1) (Left error2) = Left (error1 `mappend` error2) sumWithError (Left error) _ = Left error sumWithError _ (Left error) = Left error sumWithError (Right value1) (Right value2) = Right (value1 + value2) showSumOrErrorOf :: Float -> Float -> String showSumOrErrorOf x y = case sumWithError (sqrtWithError x) (sqrtWithError y) of Right value -> "The value is " ++ show value Left error -> show . formatErrorMessage $ error ================================================== The result of @showSumOrErrorOf (-1) (-2)@ is the string, Error computing the square root of -1: Square roots cannot be taken of negative numbers. Error computing the square root of -2: Square roots cannot be taken of negative numbers. whereas the result of @showSumOrErrorOf (-1) (-1)@ is the string, Error computing the square root of -1: Square roots cannot be taken of negative numbers. Note how the error message only appears once; this is because the process of combining the error messages automatically eliminates all identical headings under the assumption that they came from the same original computation, as was the case here. Currently, the definition of @sumWithError@ is largely boilerplate. Happily, the Haskell community has done a lot of work to identify patterns such as these and to write libraries that allow us to express them concisely. In particular, a standard trick when working with errors like this is to express the calculation as a 'Monad', such as by using the following definition: ================================================== sumWithError_2 argument1 argument2 = do value1 <- argument1 value2 <- argument2 return (value1 + value2) ================================================== Or, even more concisely: ================================================== sumWithError_3 = liftM2 (+) ================================================== Unfortunately though, neither of these definitions have the same semantics as the original @sumWithError@, as using both we get the following error message for @showSumOrErrorOf (-1) (-2)@: ================================================== Error computing the square root of -1: Square roots cannot be taken of negative numbers. ================================================== That is, we have lost the second of the two error messages. The reason for this is that 'Monad'-style error processing expresses the computation as a sequence, and gives up as soon as it sees any error. In this case of @sumWithError@, however, the evaluation of the second argument can proceed even if there was an error in the first argument. Thus, rather than using a 'Monad' pattern, we use an 'Applicative' pattern: ================================================== sumWithError_4 = liftA2 (+) ================================================== Now both error messages are displayed. Anyway, I hope that someone other than myself finds this pattern to be helpful. :-) Cheers, Greg

Gregory Crosswhite schrieb:
If there is one thing that we really don't have enough of in Haskell, it is *ways to handle errors*! Thus, I am pleased to announce the release of the "error-message" package to help in filling this, erm, gap.
This philosophy behind this package is that it is often better to find out all of the errors that have occured in a computation and report them simultaneously, rather than aborting as soon as the first error is encountered. Towards this end, this package supplies a type of /combinable error messages/ (ErrorMessage in the Data.ErrorMessage module) so that all of the errors from subcomputations can be gathered and presented together.
I would call such non-serious errors 'warnings'. Warnings can be collected using Writer monad.

On Dec 4, 2009, at 7:55 AM, Henning Thielemann wrote:
Gregory Crosswhite schrieb:
If there is one thing that we really don't have enough of in Haskell, it is *ways to handle errors*! Thus, I am pleased to announce the release of the "error-message" package to help in filling this, erm, gap.
This philosophy behind this package is that it is often better to find out all of the errors that have occured in a computation and report them simultaneously, rather than aborting as soon as the first error is encountered. Towards this end, this package supplies a type of /combinable error messages/ (ErrorMessage in the Data.ErrorMessage module) so that all of the errors from subcomputations can be gathered and presented together.
I would call such non-serious errors 'warnings'. Warnings can be collected using Writer monad.
The errors are indeed serious because they prevent the computation from being finished; it's just that errors are often not "fatal" in the sense that you have to stop when you encounter the first one rather than seeing if anything else also went wrong. For example, consider compilation errors: any error causes the compilation to fail, but the compiler tries to uncover as many errors as it can at once so that it can show you the whole list rather than just the first one. On Dec 4, 2009, at 7:57 AM, Henning Thielemann wrote:
Gregory Crosswhite schrieb:
When I uploaded my new package, "error-message", I also went ahead and created a new category: "Error Handling".
"Error handling" is the same as "debugging" for you? I hope it is not intended for generating further confusion about "exception handling" and "debugging" (= help programmers to analyse errors).
No, but I can see how you would have gotten that impression since the examples I supply in my documentation are all programmer errors. The real purpose of this is to collect together errors that ultimately came from bad program inputs, i.e. "user errors". In particular, the motivation for this package was that I have written a build system, and I wanted to collect as many errors in the build as possible and show them all to the user at once. Cheers, Greg

In particular, the motivation for this package was that I have written a build system, and I wanted to collect as many errors in the build as possible and show them all to the user at once.
YMMV, but at least for me a deluge of errors is less helpful than a short list I can fix quickly, then try again. Often by fixing one error from the list a sizeable portion of the rest just vanish (I forget the English term for that kind of error). (In before "you can use sth like quickfix to go through the first few errors and compile again whenever you feel like it".) -- Ariel J. Birnbaum

On Thu, Dec 03, 2009 at 01:50:06PM -0800, Gregory Crosswhite wrote:
Or, even more concisely:
================================================== sumWithError_3 = liftM2 (+) ==================================================
Unfortunately though, neither of these definitions have the same semantics as the original @sumWithError@, as using both we get the following error message for @showSumOrErrorOf (-1) (-2)@:
================================================== Error computing the square root of -1: Square roots cannot be taken of negative numbers. ==================================================
That is, we have lost the second of the two error messages. The reason for this is that 'Monad'-style error processing expresses the computation as a sequence, and gives up as soon as it sees any error. In this case of @sumWithError@, however, the evaluation of the second argument can proceed even if there was an error in the first argument. Thus, rather than using a 'Monad' pattern, we use an 'Applicative' pattern:
================================================== sumWithError_4 = liftA2 (+) ==================================================
Now both error messages are displayed.
I see no inherent reason that liftM2 (+) cannot collect both error messages. No one says that "monad-style error processing" *must* stop as soon as it sees an error. And having different semantics for liftA2 and liftM2 (etc.) is strange at best. They ought to be equivalent for any type constructor with both Monad and Applicative instances. -Brent

Recall that the definition of liftM2 is ================================================== liftM2 :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r liftM2 f m1 m2 = do { x1 <- m1; x2 <- m2; return (f x1 x2) } ================================================== which, if I understand correctly, desugars to ================================================== liftM2 f m1 m2 = m1 >>= ( \x1 -> m2 >>= ( \x2 -> return (f x1 x2) ) ) ================================================== The problem comes from the fact that >>= takes a *function* as its second argument, and so if the first argument is an error then we can't evaluate the second argument in order to see if it has an error as well. For example, consider the following script: =================================================== import Control.Applicative import Control.Monad import Data.ErrorMessage newtype E a = E (Either String a) instance Functor E where fmap _ (E (Left error)) = E (Left error) fmap f (E (Right argument)) = E (Right (f argument)) instance Applicative E where pure = E . Right (<*>) (E (Left error2)) (E (Left error1)) = E (Left (error1 ++ error2)) (<*>) (E (Left error)) _ = E (Left error) (<*>) _ (E (Left error)) = E (Left error) (<*>) (E (Right function)) (E (Right argument)) = E (Right (function argument)) instance Monad E where return = E . Right E (Left l) >>= _ = E (Left l) E (Right r) >>= f = f r fail msg = E (Left msg) sum_using_monad :: Either String Int (E sum_using_monad) = (liftM2 (+)) (E (Left "A")) (E (Left "B")) sum_using_applicative :: Either String Int (E sum_using_applicative) = (liftA2 (+)) (E (Left "A")) (E (Left "B")) main = do putStrLn . show $ sum_using_monad putStrLn . show $ sum_using_applicative =================================================== (Sorry about all of the annoying E's; I needed to do this in order to override the instance declaration for Either String.) Run this script and you will see: Left "A" Left "BA" Thus, the difference in the semantics is inherent from the way that >>= and liftM2 are defined. The only way that I can think to get around this is change the definition of >>= so that if the first argument is an error then it calls the second argument with "undefined"; if this returns a (Left error) then combine the two errors, and if it returns anything else or throws an exception (e.g. Prelude.undefined) then ignore it and just return the first argument. Cheers, Greg On Dec 5, 2009, at 1:28 PM, Brent Yorgey wrote:
On Thu, Dec 03, 2009 at 01:50:06PM -0800, Gregory Crosswhite wrote:
Or, even more concisely:
================================================== sumWithError_3 = liftM2 (+) ==================================================
Unfortunately though, neither of these definitions have the same semantics as the original @sumWithError@, as using both we get the following error message for @showSumOrErrorOf (-1) (-2)@:
================================================== Error computing the square root of -1: Square roots cannot be taken of negative numbers. ==================================================
That is, we have lost the second of the two error messages. The reason for this is that 'Monad'-style error processing expresses the computation as a sequence, and gives up as soon as it sees any error. In this case of @sumWithError@, however, the evaluation of the second argument can proceed even if there was an error in the first argument. Thus, rather than using a 'Monad' pattern, we use an 'Applicative' pattern:
================================================== sumWithError_4 = liftA2 (+) ==================================================
Now both error messages are displayed.
I see no inherent reason that liftM2 (+) cannot collect both error messages. No one says that "monad-style error processing" *must* stop as soon as it sees an error. And having different semantics for liftA2 and liftM2 (etc.) is strange at best. They ought to be equivalent for any type constructor with both Monad and Applicative instances.
-Brent _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, Dec 05, 2009 at 02:13:10PM -0800, Gregory Crosswhite wrote:
The problem comes from the fact that >>= takes a *function* as its second argument, and so if the first argument is an error then we can't evaluate the second argument in order to see if it has an error as well.
Hmm, that's true. I guess I misspoke about liftM2 (+) being able to collect both error messages.
instance Functor E where fmap _ (E (Left error)) = E (Left error) fmap f (E (Right argument)) = E (Right (f argument))
instance Applicative E where pure = E . Right (<*>) (E (Left error2)) (E (Left error1)) = E (Left (error1 ++ error2)) (<*>) (E (Left error)) _ = E (Left error) (<*>) _ (E (Left error)) = E (Left error) (<*>) (E (Right function)) (E (Right argument)) = E (Right (function argument))
OK, this looks like a perfectly valid Applicative instance for E (it satisfies the Applicative laws). So what we have here, it seems, is a type with at least two reasonable Applicative instances, one of which does *not* correspond to a Monad instance. My argument is that it is very strange (I might even go so far as to call it a bug) to have a type with an Applicative instance and a Monad instance which do not correspond, in the sense that pure = return (<*>) = ap although I certainly understand the motivation in this case. Hmm, I'll have to think about this a bit more. The Monad instance which tries passing undefined to the right-hand side of >>= if the left-hand side is an error is strangely compelling, if semantically unsound... -Brent

On Sun, Dec 06, 2009 at 03:50:55PM -0500, Brent Yorgey wrote:
So what we have here, it seems, is a type with at least two reasonable Applicative instances, one of which does *not* correspond to a Monad instance. My argument is that it is very strange (I might even go so far as to call it a bug) to have a type with an Applicative instance and a Monad instance which do not correspond, in the sense that
pure = return (<*>) = ap
There are several of these. Another is the possible Applicative instance for lists with pure = repeat (<*>) = zipWith id In these cases we usually make the Applicative instance match the Monad one and define an equivalent type for each other Applicative instance (e.g. ZipList in Control.Applicative).
participants (5)
-
Ariel J. Birnbaum
-
Brent Yorgey
-
Gregory Crosswhite
-
Henning Thielemann
-
Ross Paterson