Difference between revisions of "Failure"

From HaskellWiki
Jump to navigation Jump to search
(Page creation)
 
(rm →‎safe-failure: - deprecated)
 
(15 intermediate revisions by 6 users not shown)
Line 1: Line 1:
This page discusses the not-yet-released control-monad-failure package and its associated packages. As of this writing (November 7, 2009), the packages are expected to be released within the next week.
 
 
 
= Exceptions, errors, failures oh my! =
 
= Exceptions, errors, failures oh my! =
   
Line 6: Line 4:
   
 
* Error usually refers to a programming error. It can also refer to the "error" function, which in fact causes a runtime exception to be triggered.
 
* Error usually refers to a programming error. It can also refer to the "error" function, which in fact causes a runtime exception to be triggered.
* Exception usually refers to an exception which is thrown in the IO monad. It can also refer to the actually typeclass "Exception" which was introduced along with extensible exceptions.
+
* Exception usually refers to an exception which is thrown in the IO monad. It can also refer to the actual typeclass "Exception" which was introduced along with extensible exceptions.
 
* Fail is referring to the "fail" function, which is part of the Monad typeclass and is almost universally despised.
 
* Fail is referring to the "fail" function, which is part of the Monad typeclass and is almost universally despised.
   
Line 15: Line 13:
 
* readInt fails when it receives invalid input.
 
* readInt fails when it receives invalid input.
 
* head fails when it receives an empty list.
 
* head fails when it receives an empty list.
* lookup fails when the key is not find in the list.
+
* lookup fails when the key is not found in the list.
 
* at (also known as !!) fails when the index is past the end of the list.
 
* at (also known as !!) fails when the index is past the end of the list.
   
Line 25: Line 23:
   
 
* Maybe. However, there's no information on *what* failed.
 
* Maybe. However, there's no information on *what* failed.
* Either String. Two problems here: 1) Either is not a Monad by default. You can use the mtl or transformers instances, but that introduces orphan instances and all the associated issues. 2) A String is a bit limiting sometimes.
 
 
* The error function. But not all failures should be fatal.
 
* The error function. But not all failures should be fatal.
* Runtime exceptions. You need to be in IO to handle it, plus it's non-obvious that an exception might have been thrown based on return type.
+
* IO exceptions. But they force your code into your IO monad, plus it's non-obvious that a function might fail with an exception based solely on its return type.
 
* Custom error values. But how do you compose two libraries together?
 
* Custom error values. But how do you compose two libraries together?
  +
* The Either/ErrorT monads. The main problem with these lies in composability and extensibility.
   
  +
This abundance of error handling methods leads to lots of gluing code when combining libraries which use different notions of failure.
= Enter control-monad-failure, stage left =
 
  +
Examples:
   
  +
* The partial functions in the Prelude and other base modules, such as head, tail, fromJust, lookup, etc. use the error function.
What we want is a mechanism for failure which is flexible enough to provide all the information we might want. That happens to be provided very nicely by extensible exceptions. control-monad-failure is simply a mechanism for using extensible exceptions outside of the IO monad while explicitly stating the possibility of failure.
 
  +
* parsec models failure using Either ParseError
  +
* http models failure using Either ConnError
  +
* The HDBC package models failure using the SQLError exception
  +
* The cgi package uses exceptions
   
  +
Quoting from Eric Kidd:
MonadFailure is the typeclass used to glue everything else together. It lives in the Control.Monad.Failure module in the control-monad-failure package (fancy that), and consists entirely of the following two lines:
 
  +
{| class="wikitable"
  +
|-
  +
|
  +
<pre>
  +
Consider a program to download a web page and parse it:
   
  +
1. Network.URI.parseURI returns (Maybe URI).
class Monad m => MonadFailure e m where
 
  +
2. Network.HTTP.simpleHTTP returns (IO (Result Request)), which is basically a broken version of (IO (Either ConnError Request)).
failure :: e -> m a
 
  +
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
  +
</pre>
  +
|}
  +
 
= Enter failure package, stage left =
  +
  +
What we want is an abstract notion of failure which does not tie us to any particular error handling mechanism. This is what the [http://hackage.haskell.org/cgi-bin/hackage-scripts/package/failure failure] package intends to provide.
  +
 
Failure is the typeclass used to model this abstract notion of failure. It lives in the Control.Failure module and consists entirely of the following two lines:
  +
 
class Failure e f where
 
failure :: e -> f v
   
 
So now, you could define a safe head function as follows:
 
So now, you could define a safe head function as follows:
   
 
data EmptyListFailure = EmptyListFailure
 
data EmptyListFailure = EmptyListFailure
head :: MonadFailure EmptyListFailure m => [a] -> m a
+
head :: (Monad m, Failure EmptyListFailure m) => [a] -> m a
 
head [] = failure EmptyListFailure
 
head [] = failure EmptyListFailure
 
head (x:_) = return x
 
head (x:_) = return x
   
Notice how the opposite of failure is "return".
+
Notice how the opposite of failure is "return". Here, we introduced the Monad requirement explicitly; there are also two convenience classes that can help you out here:
   
  +
* ApplicativeFailure. In this case, just replace "return" with "pure"
== Catching failures ==
 
  +
* MonadFailure: code would remain exactly as-is.
   
 
== Handling failures ==
Catching isn't really the right term at all. When you catch an exception in the IO monad, it's sort of like fishing in the dark abyss which is the impurity of the real world. When dealing with a failure, it's obvious based on the type signature what might go wrong. In the example of head above, obviously head won't succeed if the list is empty.
 
   
  +
When dealing with a failure, the type signature states what might go wrong. In the example of head above, head will fail if the list is empty.
In any event, we need some instances of MonadFailure in order to actually call the head function. There are some built in with the control-monad-failure package. However, there are also two other packages available which provide more resilient options. The built in offerings are:
 
  +
  +
In any event, we need to instantiate Failure in order to actually call the head function. The failure package comes with instances for each of the above mentioned error handling mechanisms.
   
 
* Maybe. failure == Nothing
 
* Maybe. failure == Nothing
Line 58: Line 87:
 
* IO. failure == throw
 
* IO. failure == throw
 
* Either. failure == Left
 
* Either. failure == Left
* ErrorT (provided by mtl or transformers). failure == throwError.
 
   
  +
Note: we previously provided an instance for ErrorT, where failure == throwError. Now, however, this is provided by the control-monad-failure or control-monad-failure-mtl packages.
However, each of these runs into the issues described previously.
 
   
  +
However, there are also two other packages available which provide more resilient options.
=== control-monad-exception ===
 
   
  +
=== [http://hackage.haskell.org/cgi-bin/hackage-scripts/package/control-monad-exception control-monad-exception ]===
The c-m-e library allows you to cleanly define which failures might occur in a function, and to handle failures one at a time.
 
   
  +
c-m-e provides a EM monad for explicitly typed, checked exceptions a la Java.
FIXME: Jose, this could use a better description (clearly).
 
  +
The type of a EM computation carries the list of exceptions it can throw in its type. For example, let's say that we have a basic arithmetic expression evaluator which can throw divide by zero or sum overflow exceptions. Its type will be:
   
  +
eval :: (Throws DivByZero l, Throws SumOverflow l) => Expr -> EM l Double
=== attempt ===
 
  +
  +
Correspondingly, a computation which calls eval and handles only the DivByZero exception gets the type:
  +
  +
:t eval <expr> `catch` \DivByZero -> return 0
  +
eval <expr> :: Throws SumOverflow l => EM l Double
  +
  +
  +
=== [http://hackage.haskell.org/cgi-bin/hackage-scripts/package/attempt attempt] ===
   
 
Attempt is intended when you don't know what might go wrong, but you know it could happen. For example, let's say I want to define a type class:
 
Attempt is intended when you don't know what might go wrong, but you know it could happen. For example, let's say I want to define a type class:
Line 77: Line 114:
 
Other libraries may want to instantiate Convert for their own types. However, when writing the Convert typeclass, I don't know exactly what failures may occur. When writing the "Convert String Int" instances, it might be InvalidInteger. But when writing the "Convert English Spanish" typeclass (hey, it could happen) it might be InvalidGrammar.
 
Other libraries may want to instantiate Convert for their own types. However, when writing the Convert typeclass, I don't know exactly what failures may occur. When writing the "Convert String Int" instances, it might be InvalidInteger. But when writing the "Convert English Spanish" typeclass (hey, it could happen) it might be InvalidGrammar.
   
= safe-failure =
+
= Stack traces =
   
 
As an added bonus, control-monad-exception provides stack traces, or more exactly [http://pepeiborra.posterous.com/monadic-stack-traces-that-make-a-lot-of-sense monadic call traces], via [http://hackage.haskell.org/cgi-bin/hackage-scripts/package/monadloc MonadLoc].
safe-failure is a collection of functions which return values in the MonadFailure monad. It provides all the functions available in Neil Mitchell's safe package, plus a few extra.
 
   
= Stack traces =
+
= See also =
  +
  +
* [[Error]]
  +
* [[Exception]]
  +
* [[Error vs. Exception]]
  +
  +
= References =
   
  +
* http://www.randomhacks.net/articles/2007/03/10/haskell-8-ways-to-report-errors
As an added bonus, both control-monad-exception and attempt support MonadLoc, meaning you can get stack traces. More information available in Jose's blog post [http://pepeiborra.posterous.com/monadic-stack-traces-that-make-a-lot-of-sense].
 
  +
* http://www.haskell.org/pipermail/libraries/2007-March/007010.html

Latest revision as of 12:45, 12 August 2019

Exceptions, errors, failures oh my!

Terminology is a little confusing. There's a few different things floating around:

  • Error usually refers to a programming error. It can also refer to the "error" function, which in fact causes a runtime exception to be triggered.
  • Exception usually refers to an exception which is thrown in the IO monad. It can also refer to the actual typeclass "Exception" which was introduced along with extensible exceptions.
  • Fail is referring to the "fail" function, which is part of the Monad typeclass and is almost universally despised.

To avoid the baggage and name clashes introduced with all of the above, we use the term failure. This name is used consistently for module names, type classes, function names and the abstract concept.

But what is a failure? It's any time that something does not succeed. Of course, this depends on your definition of success. Here are some examples:

  • readInt fails when it receives invalid input.
  • head fails when it receives an empty list.
  • lookup fails when the key is not found in the list.
  • at (also known as !!) fails when the index is past the end of the list.

Now that we know what a failure is, let's discuss how to deal with it.

Prior Art

There are currently a number of methods available for dealing with failures. However, all of them are lacking in some way:

  • Maybe. However, there's no information on *what* failed.
  • The error function. But not all failures should be fatal.
  • IO exceptions. But they force your code into your IO monad, plus it's non-obvious that a function might fail with an exception based solely on its return type.
  • Custom error values. But how do you compose two libraries together?
  • The Either/ErrorT monads. The main problem with these lies in composability and extensibility.

This abundance of error handling methods leads to lots of gluing code when combining libraries which use different notions of failure. Examples:

  • The partial functions in the Prelude and other base modules, such as head, tail, fromJust, lookup, etc. use the error function.
  • parsec models failure using Either ParseError
  • http models failure using Either ConnError
  • The HDBC package models failure using the SQLError exception
  • The cgi package uses exceptions

Quoting from Eric Kidd:

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

Enter failure package, stage left

What we want is an abstract notion of failure which does not tie us to any particular error handling mechanism. This is what the failure package intends to provide.

Failure is the typeclass used to model this abstract notion of failure. It lives in the Control.Failure module and consists entirely of the following two lines:

   class Failure e f where
       failure :: e -> f v

So now, you could define a safe head function as follows:

   data EmptyListFailure = EmptyListFailure
   head :: (Monad m, Failure EmptyListFailure m) => [a] -> m a
   head [] = failure EmptyListFailure
   head (x:_) = return x

Notice how the opposite of failure is "return". Here, we introduced the Monad requirement explicitly; there are also two convenience classes that can help you out here:

  • ApplicativeFailure. In this case, just replace "return" with "pure"
  • MonadFailure: code would remain exactly as-is.

Handling failures

When dealing with a failure, the type signature states what might go wrong. In the example of head above, head will fail if the list is empty.

In any event, we need to instantiate Failure in order to actually call the head function. The failure package comes with instances for each of the above mentioned error handling mechanisms.

  • Maybe. failure == Nothing
  • List. failure == []
  • IO. failure == throw
  • Either. failure == Left

Note: we previously provided an instance for ErrorT, where failure == throwError. Now, however, this is provided by the control-monad-failure or control-monad-failure-mtl packages.

However, there are also two other packages available which provide more resilient options.

control-monad-exception

c-m-e provides a EM monad for explicitly typed, checked exceptions a la Java. The type of a EM computation carries the list of exceptions it can throw in its type. For example, let's say that we have a basic arithmetic expression evaluator which can throw divide by zero or sum overflow exceptions. Its type will be:

   eval :: (Throws DivByZero l, Throws SumOverflow l) => Expr -> EM l Double

Correspondingly, a computation which calls eval and handles only the DivByZero exception gets the type:

   :t eval <expr> `catch` \DivByZero -> return 0
     eval <expr> :: Throws SumOverflow l => EM l Double


attempt

Attempt is intended when you don't know what might go wrong, but you know it could happen. For example, let's say I want to define a type class:

   class Convert a b where
       convert :: a -> Attempt b

Other libraries may want to instantiate Convert for their own types. However, when writing the Convert typeclass, I don't know exactly what failures may occur. When writing the "Convert String Int" instances, it might be InvalidInteger. But when writing the "Convert English Spanish" typeclass (hey, it could happen) it might be InvalidGrammar.

Stack traces

As an added bonus, control-monad-exception provides stack traces, or more exactly monadic call traces, via MonadLoc.

See also

References