[Haskell-cafe] Error handling package

Michael Snoyman michael at snoyman.com
Tue Oct 20 19:02:08 EDT 2009


On Mon, Oct 19, 2009 at 3:46 PM, Jose Iborra <pepeiborra at gmail.com> wrote:

> You may want to take a look at another option in Hackage, the
> control-monad-exception package.


I've tried using the package; you can see the results at this github branch:
http://github.com/snoyberg/data-object/blob/control-monad-exception/Data/Object.hs.
I found the result to be too difficult to work with. For my purposes in this
library, non-explicit exceptions are much more appropriate. Thanks for the
great library though, I'll keep it in mind for future uses.

Michael


>
>
> http://pepeiborra.github.com/control-monad-exception/
>
> The control-monad-exception library provides the building blocks for
>
> * Explicitly Typed exceptions (checked or not)
> * which are composable
> * and even provide stack traces (experimental feature)
>
>
> On 19/10/2009, at 01:00, Michael Snoyman wrote:
>
>  (Sorry, accidently took off cafe.)
>>
>> On Mon, Oct 19, 2009 at 12:44 AM, Henning Thielemann <
>> lemming at henning-thielemann.de> wrote:
>>
>> On Mon, 19 Oct 2009, Michael Snoyman wrote:
>>
>> Does the explicit-exception package provide what you need?
>>
>> http://hackage.haskell.org/package/explicit-exception
>>
>>
>> I don't think so, but correct me if I'm wrong. I want to make it easy to
>> chain together
>> computations which could fail in different ways. For example, something
>> like this:
>>
>> attemptReadInt :: String -> Attempt Int
>> attemptLookup :: String -> [(String, String)] -> Attempt String
>> attemptLookupInt :: String -> [(String, String)] -> Attempt Int
>> attemptLookupInt k m = attemptLookup k m >>= attemptReadInt
>>
>> Now, in the explicit-exception package, I could- in this simple example-
>> define
>> something like:
>>
>> data MyErrors = KeyNotFound | InvalidInt
>>
>>
>> type Attempt = Exceptional MyErrors
>>
>> True; that's what I meant by I could do this in my simple example.
>>
>>
>> But this solution would not scale.
>>
>> You want to add other exceptions? The idea of my package is to make
>> exceptions explicit in the type. Otherwise you would use
>> extensible-exceptions. Or you could define MyErrors using an existential
>> type.
>>
>> Which is my point. I'm trying to provide a package for non-explicit
>> exceptions. To compare to other programming languages, I think your package
>> is providing the equivalent of Java checked exceptions, while mine is
>> providing (safe) unchecked exceptions. I say safe because you still need to
>> explicitly decide to turn an Attempt into a possible runtime exception which
>> will bring down your program.
>>
>> Defining MyErrors using an existential type would essentially recreate the
>> entire attempt package; I don't see that purpose in everyone wanted
>> unchecked exceptions needing to reinvent the wheel in non-compatible ways.
>> If multiple libraries use attempt, they can easily have their
>> possible-error-returning functions chain together safely.
>>
>>
> I believe that control-monad-exception solves this tension between
> composability and explicit exceptions.
> You can have explicit exceptions which are composable:
>
>  > data DivideByZero = DivideByZero deriving (Show, Typeable)
>  > data SumOverflow  = SumOverflow  deriving (Show, Typeable)
>
>  > instance Exception DivideByZero
>  > instance Exception SumOverflow
>
>  > data Expr = Add Expr Expr | Div Expr Expr | Val Double
>
>  > eval (Val x)     = return x
>  > eval (Add a1 a2) = do
>  >    v1 <- eval a1
>  >    v2 <- eval a2
>  >    let sum = v1 + v2
>  >    if sum < v1 || sum < v2 then throw SumOverflow else return sum
>  > eval (Div a1 a2) = do
>  >    v1 <- eval a1
>  >    v2 <- eval a2
>  >    if v2 == 0 then throw DivideByZero else return (v1 / v2)
>
>  GHCi infers the following types
>
>  > :t eval
>  >   eval :: (Throws DivideByZero l, Throws SumOverflow l) => Expr -> EM l
> Double
>
>  > :t eval `catch` \ (e::DivideByZero) -> return (-1)
>  >  .... :: Throws SumOverflow l => Expr -> EM l Double
>
>  > :t runEM(eval `catch` \ (e::SomeException) -> return (-1))
>  >  .... : Expr -> Double
>
>
>> Additionally, there's two immediate features I think I would miss from my
>> package:
>>
>> 1) fail works properly, so an Attempt would be a valid monad response from
>> people who
>> use that function.
>>
>> As far as I understand, 'fail' is used/abused for reporting failed pattern
>> matches in do notation. If a failed pattern match indicates a programming
>> error, it should be a really error, and not something that must be handled
>> at run-time.
>>
>> That's a lot of very debateable statements you just made. It might be that
>> it's strongly encouraged to only use fail for failed pattern matching, but
>> in practice you could use it for any monadic failure. Also, there's nothing
>> stopping a user from re-throwing pattern match exceptions received in an
>> Attempt.
>>
>
> I am with Henning on 'fail'.
> It must not be used as a replacement for throw, only for failed pattern
> matches which are programming errors and thus unchecked exceptions.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20091020/9270b64e/attachment.html


More information about the Haskell-Cafe mailing list