There are too many error handling conventions used in library code!

This article on the 8 different error handling strategies various common Haskell libs use: http://www.randomhacks.net/articles/2007/03/10/haskell-8-ways-to-report-erro... got me thinking: we need to standardise/recommend a small set of methods for library error handling. The lack of consistent error reporting between libs results in verbose code, as we're not able to use a single error handling technique when gluing together code from different libs (i.e. we can't just use Maybe or Either/ErrorT). (It's always nice when you *can* use, say, a Maybe monad to glue code from a number of sources, but eventually you reach code with a different error system, and the Maybe monad breaks down). So, some questions I think we can tackle: * can we identify error handling strategies from the list that should not be used anymore? (throwDyn?) * can we move some of the outlying libraries to a more consistent error framework? * do we need more support for gluing together our different error systems? (it should be easier to glue code using , say, Maybe/Either). * what role does MonadError play here, as a generic error handler? * can we make precise recommendations about which error strategies to use? -- Don

G'day all.
Quoting Donald Bruce Stewart
This article on the 8 different error handling strategies various common Haskell libs use:
http://www.randomhacks.net/articles/2007/03/10/haskell-8-ways-to-report-erro...
got me thinking:
we need to standardise/recommend a small set of methods for library error handling.
For the record, here are the eight ways: 1. Call error 2. Return Maybe 3. Return Either 4. Return a generic Monad, a.k.a. NotJustMaybe. 5. Use MonadError and a custom error type. 6. throwDyn 7. ioError and catch 8. Monad transformers, implementing some combination of the above. Note: NotJustMaybe is claimed to be a generalisation of 1-3; in fact that's not quite true, since using this idiom to call Error does require a wrapper call. Perhaps this wrapper should be given a shorter and snappier name than runIdentity? One other one has been left out, and that's continuation-based error handling. Some general comments: 1. I've never seen some of these (8 in particular) used in any general- purpose library. 2. If it doesn't cross an API boundary, it's none of my business what error handling scheme you use. 3. Prolog, sadly, encourages failure-driven loops. Java, even more sadly, seems to encourage loops where normal termination is achieved by throwing an exception. Haskell, by contrast, never encourages a compromise like that. 4. There are clearly different kinds of error/exception, and we shouldn't expect one size to fit all. As some examples: - Failure to meet a precondition includes division by zero, head of an empty list, array bounds checking etc. Anything which the client could trivially ensure but hasn't must be due to a bug in the client code. Calling "error" is appropriate. - True absence of a return value, such as looking up a value in a Data.Map which isn't there, calls for Maybe or generic Monad. In the absence of a short-and-snappy version of runIdentity, there is an argument for also providing an "error" version. We need a good naming convention for this. - Exceptions are _undesired_ conditions which would otherwise break the logical flow of control. These come in two varieties: Some you want the client to intercept and deal with (e.g. Parsec parse errors) and some you want to leave it up to the client to decide (e.g. most I/O exceptions).
* what role does MonadError play here, as a generic error handler?
I think this is a perfect fit for any exception which the client MUST deal with. It's the Haskell equivalent of Java's checked exceptions, which are a right royal pain when they're mandatory, but occasionally a godsend when they're not.
* can we make precise recommendations about which error strategies to use?
No, but I think we can state some general principles. Cheers, Andrew Bromage

ajb@spamcop.net wrote:
6. throwDyn 7. ioError and catch
Since deprecating throwDyn was mentioned, I should say that the plan I've had in mind has been to merge (6) and (7) by using the Exception class: http://hackage.haskell.org/cgi-bin/haskell-prime/trac.cgi/wiki/ExtensibleExc... http://www.haskell.org/~simonmar/papers/ext-exceptions.pdf So there would be just one throw & catch, and you would be able to use them with arbitrary types. The scheme suggested in the paper is not completely satisfactory, and various people have suggested ways to simplify it, so it needs some reworking before I'd call it a proposal though. Just to clarify something I've seen mentioned: throwDyn is *not* tied to the IO monad, since it has type Typeable ex => ex -> a. However, you can only catch it in the IO monad. So you should think of it as a version of 'error' that you can use with something other than String. Cheers, Simon

On Mar 14, 2007, at 9:33 AM, Simon Marlow wrote:
ajb@spamcop.net wrote:
6. throwDyn 7. ioError and catch
Since deprecating throwDyn was mentioned, I should say that the plan I've had in mind has been to merge (6) and (7) by using the Exception class:
http://hackage.haskell.org/cgi-bin/haskell-prime/trac.cgi/wiki/ ExtensibleExceptions http://www.haskell.org/~simonmar/papers/ext-exceptions.pdf
So there would be just one throw & catch, and you would be able to use them with arbitrary types. The scheme suggested in the paper is not completely satisfactory, and various people have suggested ways to simplify it, so it needs some reworking before I'd call it a proposal though.
Just to clarify something I've seen mentioned: throwDyn is *not* tied to the IO monad, since it has type Typeable ex => ex -> a. However, you can only catch it in the IO monad. So you should think of it as a version of 'error' that you can use with something other than String.
Since I made the comment, I'll clarify. What I meant is just what you said: error _recovery_ is tied to the IO monad. The ErrorDynT proposal I made was a way to get some of the benefits of throwDyn and still be able to have error recovery in non-IO code.
Cheers, Simon
Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

Donald Bruce Stewart
The lack of consistent error reporting between libs results in verbose code, as we're not able to use a single error handling technique when gluing together code from different libs (i.e. we can't just use Maybe or Either/ErrorT).
Thank you for starting this discussion! As you pointed out on IRC, the forthcoming cabal-install means that Haskell programmers will tend to use more libraries in the future, making API inconsistencies more of a nuisance. The specific situation I'm trying to avoid is where libraries that are used together have arbitrary exception-reporting APIs. For example, consider a program to download a web page and parse it: 1. Network.URI.parseURI returns (Maybe URI). 2. Network.HTTP.simpleHTTP returns (IO (Result Request)), which is basically a broken version of (IO (Either ConnError Request)). 3. Parsec returns (Either ParseError a) So there's no hope that I can write anything like: do uri <- parseURI uriStr doc <- evenSimplerHTTP uri parsed <- parse grammar uriStr doc Every time I hit an API boundary, I need to write a function to lift errors into my monad. And since these errors have disparate types (strings, ConnError, ParseError), writing those lifting functions gets a little icky. An ideal error-reporting convention would have several properties: a) Provide a way to report "assertion failures" from any kind of code. These errors never should have happened, but cropped up anyway, so they aren't worth cluttering the API to think about. The existing 'error' function serves this purpose admirably. b) Provide a way to say, "You know that thing you just asked for? It doesn't exist" (e.g., Data.Map.lookup). The current convention of using Monad/fail is an admirable solution, because it integrates into whatever error-reporting style the caller is currently using. c) Provide a unified way to deal with the error ADTs defined by libraries, e.g., ConnError, ParseError, etc. At the moment, this is pretty non-trivial: You need to either smash everything down to a string, or use something hairy, such as '(Error e, Typeable e) => Either e a'. This is where novice Haskell programmers are most likely to wind up in trouble. d) Provide a way to deal with errors in mixed functional/IO-based code. It would be especially nice to have lifting functions that converted Either/ErrorT-based errors into the exceptions used in the IO monad. I think the current solutions for (a) and (b) are great, but (c) and (d) often frustrate me.
* can we identify error handling strategies from the list that should not be used anymore? (throwDyn?)
One point I made earlier about throwDyn: Out of the 8 error-handling strategies, throwDyn is the only one that can mix ConnError and ParseError in a reasonably seemless fashion. I'm not saying that programmers should use throwDyn; just that it's the only approach which really handles (c) above. And even then, it only works in the IO monad.
can we make precise recommendations about which error strategies to use?
As an aspiring Haskell library author, I crave guidance. :-) Thank you to everyone who's interested in this topic! Cheers, Eric

On Sunday 11 March 2007 09:13, Eric Kidd wrote:
Donald Bruce Stewart
writes: The lack of consistent error reporting between libs results in verbose code, as we're not able to use a single error handling technique when gluing together code from different libs (i.e. we can't just use Maybe or Either/ErrorT).
[snip]
An ideal error-reporting convention would have several properties:
a) Provide a way to report "assertion failures" from any kind of code. These errors never should have happened, but cropped up anyway, so they aren't worth cluttering the API to think about. The existing 'error' function serves this purpose admirably.
b) Provide a way to say, "You know that thing you just asked for? It doesn't exist" (e.g., Data.Map.lookup). The current convention of using Monad/fail is an admirable solution, because it integrates into whatever error-reporting style the caller is currently using.
c) Provide a unified way to deal with the error ADTs defined by libraries, e.g., ConnError, ParseError, etc. At the moment, this is pretty non-trivial: You need to either smash everything down to a string, or use something hairy, such as '(Error e, Typeable e) => Either e a'. This is where novice Haskell programmers are most likely to wind up in trouble.
d) Provide a way to deal with errors in mixed functional/IO-based code. It would be especially nice to have lifting functions that converted Either/ErrorT-based errors into the exceptions used in the IO monad.
I think the current solutions for (a) and (b) are great, but (c) and (d) often frustrate me.
* can we identify error handling strategies from the list that should not be used anymore? (throwDyn?)
One point I made earlier about throwDyn: Out of the 8 error-handling strategies, throwDyn is the only one that can mix ConnError and ParseError in a reasonably seemless fashion. I'm not saying that programmers should use throwDyn; just that it's the only approach which really handles (c) above. And even then, it only works in the IO monad.
I think you are largely right. (c) especially seems to be a weak point. One option that strikes me as a possibility is to add an (Error Dynamic) instance and use (MonadError Dynamic). This has the advantages of 'throwDyn' without tying it to the IO monad. Together with a suite of lifting functions, you could (as a library consumer) integrate almost any error handling convention into a single monad, leaving the ugliness of handling various error representations to the error handling code, where it belongs. Alternately, one could build an ErrorDyn monad directly and avoid the issue of MPTC+FDs that MonadError has.
can we make precise recommendations about which error strategies to use?
As an aspiring Haskell library author, I crave guidance. :-)
Thank you to everyone who's interested in this topic!
Cheers, Eric

On Sunday 11 March 2007 11:22, Robert Dockins wrote: [snip]
One option that strikes me as a possibility is to add an (Error Dynamic) instance and use (MonadError Dynamic). This has the advantages of 'throwDyn' without tying it to the IO monad. Together with a suite of lifting functions, you could (as a library consumer) integrate almost any error handling convention into a single monad, leaving the ugliness of handling various error representations to the error handling code, where it belongs.
[snip] Here's a quick and dirty implementation for discussion. It compiles, but I haven't tested it. Rob Dockins ---------------------------------------------------------- {-# OPTIONS -fglasgow-exts #-} module ErrorDyn ( ErrorDyn , ErrorDynT , liftMaybe , liftEither , liftErrorT , liftWriter , liftWriterT , handleDynErr , catchDynErr , runErrorDynT , execErrorDynT , runErrorDyn , execErrorDyn ) where import Data.Monoid import Data.Typeable import Data.Dynamic import Control.Monad import Control.Monad.Identity import Control.Monad.Error import Control.Monad.Writer instance Error Dynamic where noMsg = toDyn () strMsg str = toDyn str type ErrorDyn = ErrorDynT Identity newtype ErrorDynT m a = EDT { unEDT :: ErrorT Dynamic m a } deriving (Monad, MonadTrans) runErrorDynT :: Monad m => ErrorDynT m a -> m (Either Dynamic a) runErrorDynT = runErrorT . unEDT execErrorDynT :: Monad m => ErrorDynT m a -> m a execErrorDynT m = runErrorDynT m >>= either unhdl return where unhdl dyn = fail $ "Unhandled dynamic error of type: "++(show dyn) runErrorDyn :: ErrorDyn a -> Either Dynamic a runErrorDyn = runIdentity . runErrorDynT execErrorDyn :: ErrorDyn a -> a execErrorDyn = runIdentity . execErrorDynT instance Monad m => MonadError Dynamic (ErrorDynT m) where throwError e = EDT (throwError e) catchError m f = EDT (catchError (unEDT m) (unEDT . f)) liftMaybe :: (Monad m) => Maybe a -> ErrorDynT m a liftMaybe = maybe (throwError noMsg) return liftEither :: (Monad m, Typeable e) => Either e a -> ErrorDynT m a liftEither = either (throwError . toDyn) return liftErrorT :: (Monad m, Typeable e) => ErrorT e m a -> ErrorDynT m a liftErrorT m = lift (runErrorT m) >>= liftEither liftWriter :: (Monad m, Eq e, Monoid e, Typeable e) => Writer e a -> ErrorDynT m a liftWriter m = do let (a, w) = runWriter m when (w /= mempty) (throwError (toDyn w)) return a liftWriterT :: (Monad m, Eq e, Monoid e, Typeable e) => WriterT e m a -> ErrorDynT m a liftWriterT m = do (a, w) <- lift (runWriterT m) when (w /= mempty) (throwError (toDyn w)) return a handleDynErr :: (Monad m, Typeable e) => (e -> ErrorDynT m a) -> ErrorDynT m a -> ErrorDynT m a handleDynErr f m = catchError m hdl where hdl e = maybe (throwError e) f (fromDynamic e) catchDynErr :: (Monad m, Typeable e) => ErrorDynT m a -> (e -> ErrorDynT m a) -> ErrorDynT m a catchDynErr = flip handleDynErr

Here's a quick and dirty implementation for discussion. It compiles, but I haven't tested it.
Rob Dockins
[snip] I was in the mood for coding yesterday, so I've got some code to show too. I have this little problem with overdesigning things; my code looks pretty at the user side, but relies too much on type classes hackery. So type errors will probably look awful. But at least it should be useful as an idea of what would be desirable to have. Here are four examples, each in a different monad, that use the different variants of myDiv in the original example by Eric Kidd:
inMaybe :: Maybe Float inMaybe = do a <- myDiv2 1 0 b <- absorb (myDiv3 1 2) -- absorb the Either monad c <- myDiv4 1 2 -- d <- absorb (myDiv5 1 2) -- This is going to be tricky: a MonadError m -- <- absorb (myDiv6 1 2) -- cant do: cant absorb the IO Monad of course e <- absorb (myDiv8' 1 2) return (b + c + e)
inEither :: Either String Float inEither = do a <- absorb$ myDiv2 1 0 -- absorb the Maybe monad b <- myDiv3 1 2 c <- myDiv4 1 2 -- d <- absorb (myDiv5 1 2) -- This is going to be tricky: a MonadError m -- <- absorb (myDiv6 1 2) -- cant do: cant absorb the IO Monad of course e <- absorb (myDiv8' 1 2) -- absorb the ErrorT [] monad. This is rather funny return (b + c + e)
instance MorphError CustomError String where morphError = show instance MorphError CE.Exception CustomError --TODO define a mapping
inIO :: IO Float inIO = do a <- absorb$ myDiv2 1 0 -- absorb the Maybe monad b <- absorb$ myDiv3 1 2 -- absorb the Either monad c <- myDiv4 1 2 -- d <- absorb (myDiv5 1 2) -- This is going to be tricky: a MonadError m ble <- absorb (myDiv6 1 2) e <- absorb (myDiv8 1 2) e' <- absorb (myDiv8' 1 2) return (b + c + e)
inErrIO :: ErrIO Float inErrIO = do a <- absorb$ myDiv2 1 1 -- absorb the Maybe monad b <- absorb$ myDiv3 1 2 -- absorb the Either monad c <- myDiv4 1 2 -- d <- absorb (myDiv5 1 2) -- This is going to be tricky: a MonadError m ble <- absorb (myDiv6 1 0) e <- absorb (myDiv8 1 2) return (b + c + e)
And here are the three combinators of Robert Dockins' code. I didn't work on the liftWriter combinator as it seemed too specific, but could be done too:
liftMaybe :: (Monad m) => Maybe a -> ErrorDynT m a liftMaybe = absorb
liftEither :: (Monad m, Typeable e) => Either e a -> ErrorDynT m a liftEither = absorb
liftErrorT :: (Monad m, Typeable e) => ErrorT e m a -> ErrorDynT m a liftErrorT = absorb
Now, the heart of the idea is a MonadAbsorb class that allows to mix monads, the semantics of which is left to the instances. But of course, it only makes sense to mix two monads when the target one 'contains' the other somehow.
class (Monad m1, Monad m2) => AbsorbMonad m1 m2 where absorb :: m1 a -> m2 a
You don't want to see my code for the instances, it is a nightmare of type class hackery. I managed to reduce the overlappings reasonably thanks to Oleg-tricks, but that means that error messages are unforgiving. /me cries for Chameleon-style type errors in GHC. (No animals were sacrificed to the evil gods of FDs during the make of this library) Since we need to merge different error ADTs, the relevant instances for AbsorbMonad make use of another class that provides this:
class MorphError e e' where morphError :: e -> e'
MorphError is evidently in need of a new name, but the concept is very useful to avoid having a hierarchy of Eithers when dealing with libraries. Just define what a ConnError and a ParseError mean to your personal error type: data CustomError = ... | ConnProblem ConnError | ... | ParseProblem String (Int,Int) | ... instance MorphError ParseError CustomError where morphError (ParseError pos msgs) = ParseProblem (unlines msgs) pos instance MorphError ConnError CustomError where morphError e = ConnProblem e I've cabalized and uploaded the code to a Darcs repo at the URL below. It compfiles fine with 6.6 and 6.7 here. I'll be delighted to accept patches improving the code (especially regarding the instances for AbsorbMonad). http://darcs.pepeiborra.com/AbsorbMonad/ If anything else, we could use it as starting point for a benchmark suite of type error debugging in Haskell, a la 'buggy nofib' but for types :) Cheers peep

Sorry for the badly laid out code. Same content as before but properly formatted to fit in 80? columns
Here's a quick and dirty implementation for discussion. It compiles, but I haven't tested it.
Rob Dockins
[snip] I was in the mood for coding yesterday, so I've got some code to show too. I have this little problem with overdesigning things; my code looks pretty at the user side, but relies too much on type classes hackery. So type errors will probably look awful. But at least it should be useful as an idea of what would be desirable to have. Here are four examples, each in a different monad, that use the different variants of myDiv in the original example by Eric Kidd:
inMaybe :: Maybe Float inMaybe = do a <- myDiv2 1 0 b <- absorb (myDiv3 1 2) -- absorb the Either monad c <- myDiv4 1 2 -- d <- absorb (myDiv5 1 2) -- This is going to be tricky: -- can't absorb a MonadError m -- <- absorb (myDiv6 1 2) -- cant do: cant absorb the -- IO Monad of course e <- absorb (myDiv8' 1 2) return (b + c + e)
inEither :: Either String Float inEither = do a <- absorb$ myDiv2 1 0 -- absorb the Maybe monad b <- myDiv3 1 2 c <- myDiv4 1 2 -- d <- absorb (myDiv5 1 2) -- This is going to be tricky: -- a MonadError m -- <- absorb (myDiv6 1 2) -- cant do: cant absorb the -- IO Monad of course e <- absorb (myDiv8' 1 2) -- absorb the ErrorT [] monad. return (b + c + e)
instance MorphError CustomError String where morphError = show instance MorphError CE.Exception CustomError -- TODO define a mapping
inIO :: IO Float inIO = do a <- absorb$ myDiv2 1 0 -- absorb the Maybe monad b <- absorb$ myDiv3 1 2 -- absorb the Either monad c <- myDiv4 1 2 -- d <- absorb (myDiv5 1 2) -- This is going to be tricky: -- a MonadError m ble <- absorb (myDiv6 1 2) e <- absorb (myDiv8 1 2) e' <- absorb (myDiv8' 1 2) return (b + c + e)
inErrIO :: ErrIO Float inErrIO = do a <- absorb$ myDiv2 1 1 -- absorb the Maybe monad b <- absorb$ myDiv3 1 2 -- absorb the Either monad c <- myDiv4 1 2 -- d <- absorb (myDiv5 1 2) -- This is going to be tricky: -- a MonadError m ble <- absorb (myDiv6 1 0) e <- absorb (myDiv8 1 2) return (b + c + e)
And here are the three combinators of Robert Dockins' code. I didn't work on the liftWriter combinator as it seemed too specific, but could be done too:
liftMaybe :: (Monad m) => Maybe a -> ErrorDynT m a liftMaybe = absorb
liftEither :: (Monad m, Typeable e) => Either e a -> ErrorDynT m a liftEither = absorb
liftErrorT :: (Monad m, Typeable e) => ErrorT e m a -> ErrorDynT m a liftErrorT = absorb
Now, the heart of the idea is a MonadAbsorb class that allows to mix monads, the semantics of which is left to the instances. But of course, it only makes sense to mix two monads when the target one 'contains' the other somehow.
class (Monad m1, Monad m2) => AbsorbMonad m1 m2 where absorb :: m1 a -> m2 a
You don't want to see my code for the instances, it is a nightmare of type class hackery. I managed to reduce the overlappings reasonably thanks to Oleg-tricks, but that means that error messages are unforgiving. /me cries for Chameleon-style type errors in GHC. (No animals were sacrificed to the evil gods of FDs during the make of this library) Since we need to merge different error ADTs, the relevant instances for AbsorbMonad make use of another class that provides this:
class MorphError e e' where morphError :: e -> e'
MorphError is evidently in need of a new name, but the concept is very useful to avoid having a hierarchy of Eithers when dealing with libraries. Just define what a ConnError and a ParseError mean to your personal error type: data CustomError = ... | ConnProblem ConnError | ... | ParseProblem String (Int,Int) instance MorphError ParseError CustomError where morphError (ParseError pos msgs) = ParseProblem (unlines msgs) pos instance MorphError ConnError CustomError where morphError e = ConnProblem e I've cabalized and uploaded the code to a Darcs repo at the URL below. It compfiles fine with 6.6 and 6.7 here. I'll be delighted to accept patches improving the code (especially regarding the instances for AbsorbMonad). http://darcs.pepeiborra.com/AbsorbMonad/ If anything else, we could use it as starting point for a benchmark suite of type error debugging in Haskell, a la 'buggy nofib' but for types :) Cheers pepe

On 3/11/07, Eric Kidd
Donald Bruce Stewart
writes: The lack of consistent error reporting between libs results in verbose code, as we're not able to use a single error handling technique when gluing together code from different libs (i.e. we can't just use Maybe or Either/ErrorT).
Thank you for starting this discussion!
As you pointed out on IRC, the forthcoming cabal-install means that Haskell programmers will tend to use more libraries in the future, making API inconsistencies more of a nuisance.
The specific situation I'm trying to avoid is where libraries that are used together have arbitrary exception-reporting APIs. For example, consider a program to download a web page and parse it:
1. Network.URI.parseURI returns (Maybe URI). 2. Network.HTTP.simpleHTTP returns (IO (Result Request)), which is basically a broken version of (IO (Either ConnError Request)). 3. Parsec returns (Either ParseError a)
So there's no hope that I can write anything like:
do uri <- parseURI uriStr doc <- evenSimplerHTTP uri parsed <- parse grammar uriStr doc
Couldn't we define (yet another) class to deal with these: class Failure f where try :: (Monad m) => f a -> m a 'try' would only depend on 'return' and 'fail'. The example would then become: do uri <- try $ parseURI uriStr doc <- try $ evenSimplerHTTP uri parsed <- try $ parse grammar uriStr doc We could define most of the instances in the same module and it would be a matter of importing 'Control.Failure' for most libraries, or I'm being particularly obtuse today?
Every time I hit an API boundary, I need to write a function to lift errors into my monad. And since these errors have disparate types (strings, ConnError, ParseError), writing those lifting functions gets a little icky.
An ideal error-reporting convention would have several properties:
a) Provide a way to report "assertion failures" from any kind of code. These errors never should have happened, but cropped up anyway, so they aren't worth cluttering the API to think about. The existing 'error' function serves this purpose admirably.
b) Provide a way to say, "You know that thing you just asked for? It doesn't exist" (e.g., Data.Map.lookup). The current convention of using Monad/fail is an admirable solution, because it integrates into whatever error-reporting style the caller is currently using.
c) Provide a unified way to deal with the error ADTs defined by libraries, e.g., ConnError, ParseError, etc. At the moment, this is pretty non-trivial: You need to either smash everything down to a string, or use something hairy, such as '(Error e, Typeable e) => Either e a'. This is where novice Haskell programmers are most likely to wind up in trouble.
d) Provide a way to deal with errors in mixed functional/IO-based code. It would be especially nice to have lifting functions that converted Either/ErrorT-based errors into the exceptions used in the IO monad.
I think the current solutions for (a) and (b) are great, but (c) and (d) often frustrate me.
* can we identify error handling strategies from the list that should not be used anymore? (throwDyn?)
One point I made earlier about throwDyn: Out of the 8 error-handling strategies, throwDyn is the only one that can mix ConnError and ParseError in a reasonably seemless fashion. I'm not saying that programmers should use throwDyn; just that it's the only approach which really handles (c) above. And even then, it only works in the IO monad.
can we make precise recommendations about which error strategies to use?
As an aspiring Haskell library author, I crave guidance. :-)
Thank you to everyone who's interested in this topic!
Cheers, Eric
Daniel Yokomizo.

Eric Kidd wrote:
1. Network.URI.parseURI returns (Maybe URI). 2. Network.HTTP.simpleHTTP returns (IO (Result Request)), which is basically a broken version of (IO (Either ConnError Request)). 3. Parsec returns (Either ParseError a)
So there's no hope that I can write anything like:
do uri <- parseURI uriStr doc <- evenSimplerHTTP uri parsed <- parse grammar uriStr doc
do uri <- maybe (fail "broken uri") return $ parseURI uriStr doc <- either throwDyn return =<< evenSimplerHTTP uri parsed <- either throwDyn return $ parse grammar uriStr doc ...untested of course, and only intended to show the principle. You may not want to "throwDyn" everything, instead you might use a suitable MonadError or want to "show" those errors that aren't already strings, etc. You get a bit of noise, but also flexibility. Am I the only one who doesn't see a problem here?
c) Provide a unified way to deal with the error ADTs defined by libraries, e.g., ConnError, ParseError, etc. At the moment, this is pretty non-trivial: You need to either smash everything down to a string, or use something hairy, such as '(Error e, Typeable e) => Either e a'. This is where novice Haskell programmers are most likely to wind up in trouble.
Err, no, you either wrap everything up in a custom type data AllSortsOfErrors = WhoKnows | DescribedBy String | ConnError ConnError | ParseError ParseError | ... or you use Dynamic, which essentially is such a union containing everything. Of course, if all you're gonna do anyway is print a message and go on with your business, then smashing everything down to strings is exactly what the doctor ordered anyway.
d) Provide a way to deal with errors in mixed functional/IO-based code. It would be especially nice to have lifting functions that converted Either/ErrorT-based errors into the exceptions used in the IO monad.
See above. Of course, you could give "either throwDyn return" a name, I'm not sure it buys you that much, though.
One point I made earlier about throwDyn: Out of the 8 error-handling strategies, throwDyn is the only one that can mix ConnError and ParseError in a reasonably seemless fashion.
...but only if you're in IO code anyway and only if handling the exception will also be done in IO code. In all other cases, the most well known mix of ConnError and ParseError is called "Either ConnError ParseError".
can we make precise recommendations about which error strategies to use?
How about "don't forget about algebraic data types"? Other than that, make liberal use of MonadError. Given enough polymorphism, a lot of the heavy lifting simply vanishes. -Udo -- "Poor man... he was like an employee to me." -- The police commisioner on "Sledge Hammer" laments the death of his bodyguard

On 3/11/07, Udo Stenzel
do uri <- maybe (fail "broken uri") return $ parseURI uriStr doc <- either throwDyn return =<< evenSimplerHTTP uri parsed <- either throwDyn return $ parse grammar uriStr doc
...untested of course, and only intended to show the principle.
Ah, thank you for the interesting example! There are definitely some good ideas here. But I'm still concerned that this approach won't scale. In languages with better-developed library archives (Ruby, Perl, etc.), I frequently use over a dozen third-party libraries in one program. And that's the direction Hackage and cabal-install will be taking the Haskell community. I'm very sensitive to noise in code. I want my programs to be uncluttered, perhaps even beautiful (though I rarely achieve that goal). So the idea of using a bunch of little helper functions to adapt all the different error-reporting conventions bothers me. I mean, why is the error-reporting so interesting that it belongs right in the main program flow? In general, Haskell encourages programmers to hide irrelevant details in monads, and keep the main program clean. This would certainly be easier if we had more consistent error-reporting styles. But for now, at least, I'll definitely benefit from your suggestions. Many thanks! Cheers, Eric

On Sun, 11 Mar 2007, Donald Bruce Stewart wrote:
This article on the 8 different error handling strategies various common Haskell libs use: http://www.randomhacks.net/articles/2007/03/10/haskell-8-ways-to-report-erro...
got me thinking:
we need to standardise/recommend a small set of methods for library error handling.
What about localised exception messages? How shall I design a library that allow application programmers using that library to emit exception messages that are translated to the language of the application user?

In re http://thread.gmane.org/gmane.comp.lang.haskell.libraries/6382 I read this thread (as I found it populated on 2011-08-12) with interest even though I have not written three lines of Haskell. I am trying to invent a programming language with referential transparency and I am thinking about what construct(s) it should provide to catch errors. Catching errors is necessary because I want the language to be suitable for building systems that run code by various contributors without trusting the integrity of the system as a whole to the contributions. Errors should be caught and reported to the responsible programmers. Let "RT" stand for referential transparency or referentially transparent as grammatically appropriate in each instance. I wanted to learn from the experience with Haskell because Haskell is one of the few pure functional programming languages in use (I'm not sure about the ML family, and I'm pretty sure that Erlang and the E language are not pure). At least with Haskell I know for sure it is pure, so I think that the community around Haskell has advanced understanding of how to go far within a purely RT world. So I start poking around to figure out how errors are caught, and the upshot, from this thread, seems to be, that errors cannot be caught in Haskell. I see you all talking about how libraries' APIs should incorporate error reporting, but these seem like really exceptions rather than errors, in that you, the library prorammers, have to plan to detect them and you are just looking for a non-noisy way to pass them back through the API, since these "errors" represent cases that for good reason shouldn't dominate the body of your code (all of us would prefer, and with excellent reason, that the bulk of our code reflects programming for the normal and happy cases). Maybe these error cases you're discussing, some of them, reflect an error on the part of the programmer of the _client_ code _calling_ the library, and that's why you want to use the term "error". But a true programming error (for example, in the library code) might not be possible to anticipate and program around; after all, it's an error. A programming mistake. For example, what happens if we try to take the head of an empty list? Everything dies, right? Haskell won't catch that, right? So, here's what I'm thinking for my language. Every data type (I don't think I'll need Unit) will have implicitly some error indications as possible values. So for example, if an Integer is expected, we might get an integer, such as 3 for example, but we could instead receive an error indication. It should be possible to test explicitly for an error indication, and on finding one, it should be possible to test it for membership in various interesting classes of errors (including programmer-defined ones) and it should be possible to dig into the error indication and extract a brief explanation in natural language of what went wrong. I'm thinking location information such as source file name (or something like that) and line number could fit in there as well. Functions that are not designed for the explicit purpose of looking for error cases, for example `+`, would propagate errors along to their results if such were found in one or more essential inputs (False && error could return False rather than the error). Now if it looks as though I'm just reinventing something that a monad can do elegantly, I'm not sure. The monadic examples I have been seeing all seem to require the use of the bind function to glue together the function applications that could encounter an error. A reader of the code can't tell that the order of the binds doesn't matter. It looks like I/O code, where the order definitely does matter. But if I want to return for example a/b + c/d, and either division could accidentally attempt to divide by zero, I don't want to specify which division comes "first" in some chain of binds; that's overspecification, isn't it? Because the result does not depend on any ordering of the addends. Addition is commutative, and it remains commutative if we extend the domains to include error indications. Error some_specs + 3 = Error some_specs; 3 + Error some_specs = Error some_specs; still commutative. If I adopt this scheme, have I learned everything I can about error catching from Haskell and incorporated that learning into my design? I apologize for posting off topic in your thread, but this is a branching topic closely related to your topic and if I can get the advice of people who are experienced in pure functional programming and who have thought about the problems of error reporting, I might be able to avoid making some really stupid design mistake. I suggest the subject "Learning from Haskell -- Catching Errors" as the subject for any followups to this message. Thanks loads for any response. And if you think my idea is crackpot, please don't hold back on your opinion. I am trying to make a useful contribution, and if I am barking up the wrong tree, that purpose will not be served. Please feel free to tell me I should read one thing or another that my question indicates I have missed, before trying to design a new RT programming language. Again, my question is "If I adopt this scheme, have I learned everything I can about error catching from Haskell and incorporated that learning into my design?" Jack Waugh http://jackwaugh.com/

You may find these papers relevant, especially the first. (Yes, you can catch and recover from head []!) http://research.microsoft.com/en-us/um/people/simonpj/papers/imprecise-exn.h... http://research.microsoft.com/en-us/um/people/simonpj/papers/asynch-exns.htm Simon | -----Original Message----- | From: libraries-bounces@haskell.org [mailto:libraries-bounces@haskell.org] On | Behalf Of Jack Waugh | Sent: 12 August 2011 20:35 | To: libraries@haskell.org | Subject: Re: There are too many error handling conventions used in library code! | | In re | http://thread.gmane.org/gmane.comp.lang.haskell.libraries/6382 | | I read this thread (as I found it populated on 2011-08-12) | with interest even though I have not written three lines | of Haskell. | | I am trying to invent a programming language with | referential transparency and I am thinking about what | construct(s) it should provide to catch errors. Catching | errors is necessary because I want the language to be | suitable for building systems that run code by various | contributors without trusting the integrity of the system | as a whole to the contributions. Errors should be caught | and reported to the responsible programmers. | | Let "RT" stand for referential transparency or | referentially transparent as grammatically appropriate in | each instance. | | I wanted to learn from the experience with Haskell because | Haskell is one of the few pure functional programming | languages in use (I'm not sure about the ML family, and I'm | pretty sure that Erlang and the E language are not pure). | At least with Haskell I know for sure it is pure, so | I think that the community around Haskell has advanced | understanding of how to go far within a purely RT world. | | So I start poking around to figure out how errors are | caught, and the upshot, from this thread, seems to be, | that errors cannot be caught in Haskell. I see you all | talking about how libraries' APIs should incorporate | error reporting, but these seem like really exceptions | rather than errors, in that you, the library prorammers, | have to plan to detect them and you are just looking | for a non-noisy way to pass them back through the API, | since these "errors" represent cases that for good reason | shouldn't dominate the body of your code (all of us would | prefer, and with excellent reason, that the bulk of our | code reflects programming for the normal and happy cases). | Maybe these error cases you're discussing, some of them, | reflect an error on the part of the programmer of the | _client_ code _calling_ the library, and that's why you | want to use the term "error". But a true programming error | (for example, in the library code) might not be possible | to anticipate and program around; after all, it's an error. | A programming mistake. | | For example, what happens if we try to take the head of | an empty list? Everything dies, right? Haskell won't | catch that, right? | | So, here's what I'm thinking for my language. Every data | type (I don't think I'll need Unit) will have implicitly | some error indications as possible values. | So for example, if an Integer is expected, we might get | an integer, such as 3 | for example, but we could instead receive an error | indication. It should be possible to test explicitly | for an error indication, and on finding one, it should be | possible to test it for membership in various interesting | classes of errors (including programmer-defined ones) and | it should be possible to dig into the error indication and | extract a brief explanation in natural language of what | went wrong. I'm thinking location information such as | source file name (or something like that) and line number | could fit in there as well. | | Functions that are not designed for the explicit purpose of | looking for error cases, for example `+`, would propagate | errors along to their results if such were found in one or | more essential inputs (False && error could return False | rather than the error). | | Now if it looks as though I'm just reinventing | something that a monad can do elegantly, I'm not sure. | The monadic examples I have been seeing all seem to | require the use of the bind function to glue together | the function applications that could encounter an error. | A reader of the code can't tell that the order of the | binds doesn't matter. It looks like I/O code, where the | order definitely does matter. But if I want to return for | example a/b + c/d, and either division could accidentally | attempt to divide by zero, I don't want to specify which | division comes "first" in some chain of binds; that's | overspecification, isn't it? Because the result does | not depend on any ordering of the addends. Addition is | commutative, and it remains commutative if we extend the | domains to include error indications. Error some_specs | + 3 = Error some_specs; 3 + Error some_specs = Error | some_specs; still commutative. | | If I adopt this scheme, have I learned everything I can | about error catching from Haskell and incorporated that | learning into my design? | | I apologize for posting off topic in your thread, but | this is a branching topic closely related to your topic | and if I can get the advice of people who are experienced | in pure functional programming and who have thought about | the problems of error reporting, I might be able to avoid | making some really stupid design mistake. | | I suggest the subject "Learning from Haskell -- Catching | Errors" as the subject for any followups to this message. | | Thanks loads for any response. And if you think my idea | is crackpot, please don't hold back on your opinion. | I am trying to make a useful contribution, and if I am | barking up the wrong tree, that purpose will not be served. | Please feel free to tell me I should read one thing or | another that my question indicates I have missed, before | trying to design a new RT programming language. | | Again, my question is "If I adopt this scheme, have I | learned everything I can about error catching from Haskell | and incorporated that learning into my design?" | | Jack Waugh http://jackwaugh.com/ | | | | _______________________________________________ | Libraries mailing list | Libraries@haskell.org | http://www.haskell.org/mailman/listinfo/libraries

Simon Peyton-Jones writes in http://article.gmane.org/gmane.comp.lang.haskell.libraries/16016 :
You may find these papers relevant, especially the first. (Yes, you can catch and recover from head []!)
http://research.microsoft.com/en-us/um/people/simonpj/papers/imprecise-exn.h...
Thank you very much; this is exactly the paper I needed to read, pointed out to me exactly when I needed to read it. Jack Waugh
participants (11)
-
ajb@spamcop.net
-
Daniel Yokomizo
-
dons@cse.unsw.edu.au
-
Eric Kidd
-
Henning Thielemann
-
Jack Waugh
-
Pepe Iborra
-
Robert Dockins
-
Simon Marlow
-
Simon Peyton-Jones
-
Udo Stenzel