[Haskell-cafe] catching IO errors in a monad transformer stack

Eric Rasmussen ericrasmussen at gmail.com
Fri Jul 19 08:05:33 CEST 2013


Thanks Alberto!

I was able to derive MonadCatchIO for my stack and generalize my IO error
handling to:

{-# LANGUAGE FlexibleContexts #-}

import Prelude hiding (catch)

import Control.Monad.Error
import Control.Monad.State
import Control.Monad.CatchIO

import System.IO.Error (tryIOError)
import Control.Exception (IOException)

guardIO :: (MonadCatchIO m, MonadError String m) => IO a -> m a
guardIO action =
  liftIO action `catch` \e -> throwError $ show (e :: IOException)

As David mentioned it can be better to leave this to the individual, but it
seems like it would be fairly common to want a drop-in replacement for
liftIO that would automatically handle IO exceptions using ErrorT instead
of breaking the flow of the program or requiring the developer to catch
everything separately.

My example above might be too specific because not everyone will represent
errors with String when using ErrorT, but we could accommodate that with:

guardIO' :: (MonadCatchIO m, MonadError e m) => IO a -> (IOException -> e)
-> m a
guardIO' action convertExc =
  liftIO action `catch` \e -> throwError $ convertExc e

Would there be any interest in cleaning that up and adding it (or something
similar) to Control.Monad.CatchIO?

Either way I will write up a blog post on it since I couldn't find any
tutorials breaking this process down.

Thanks everyone!








On Thu, Jul 18, 2013 at 4:23 PM, Alberto G. Corona <agocorona at gmail.com>wrote:

> Hi Eric:
>
> The pattern may be the MonadCatchIO class:
>
> http://hackage.haskell.org/package/MonadCatchIO-transformers
>
>
> 2013/7/18 Eric Rasmussen <ericrasmussen at gmail.com>
>
>> Hello,
>>
>> I am writing a small application that uses a monad transformer stack, and
>> I'm looking for advice on the best way to handle IO errors. Ideally I'd
>> like to be able to perform an action (such as readFile
>> "file_that_does_not_exist"), catch the IOError, and then convert it to a
>> string error in MonadError. Here's an example of what I'm doing now:
>>
>> {-# LANGUAGE FlexibleContexts #-}
>>
>> import Control.Monad.Error
>> import Control.Monad.State
>>
>> import System.IO.Error (tryIOError)
>>
>> catcher :: (MonadIO m, MonadError String m) => IO a -> m a
>> catcher action = do
>>   result <- liftIO $ tryIOError action
>>   case result of
>>     Left  e -> throwError (show e)
>>     Right r -> return r
>>
>> This does work as expected, but I get the nagging feeling that I'm
>> missing an underlying pattern here. I have tried catch, catchError, and
>> several others, but (unless I misused them) they don't actually help here.
>> The tryIOError function from System.IO.Error is the most helpful, but I
>> still have to manually inspect the result to throwError or return to my
>> underlying monad.
>>
>> Since this has come up for me a few times now, I welcome any advice or
>> suggestions on alternative approaches or whether this functionality already
>> exists somewhere.
>>
>> Thanks!
>> Eric
>>
>>
>>
>>
>>
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>
>
> --
> Alberto.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130718/d4b68887/attachment.htm>


More information about the Haskell-Cafe mailing list