catching IO errors in a monad transformer stack

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

Hi Eric:
The pattern may be the MonadCatchIO class:
http://hackage.haskell.org/package/MonadCatchIO-transformers
2013/7/18 Eric Rasmussen
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alberto.

Hi! The exception handling is a difficult thing. It is usually simple enough but sometimes it can be very difficult, especially when using continuations within the monadic computation. To feel it, I often remember how the exceptions are handled in the F# async workflow (the sources are open), but their approach should be slightly adopted for Haskell what I did in one my simulation library (as far as I understand, the IO exception cannot arise in a pure value; therefore IOException should be caught in another place, namely in the liftIO function). I'm not sure whether there is a common pattern for handling the exceptions (the mentioned MonadCatchIO instance contains a warning regarding ContT). Therefore it is reasonable to allow the programmer himself/herself to define these handlers through the type class. Thanks, David 19.07.2013, в 3:23, Alberto G. Corona написал(а):
Hi Eric:
The pattern may be the MonadCatchIO class:
http://hackage.haskell.org/package/MonadCatchIO-transformers
2013/7/18 Eric Rasmussen
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alberto. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
Hi Eric:
The pattern may be the MonadCatchIO class:
http://hackage.haskell.org/package/MonadCatchIO-transformers
2013/7/18 Eric Rasmussen
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alberto.

On Thursday 18 July 2013 23:05:33 Eric Rasmussen wrote:
[…] Would there be any interest in cleaning that up and adding it (or something similar) to Control.Monad.CatchIO? […]
MonadCatchIO-transformers is being deprecated, as recently GHC has removed the 'block' and 'unblock' functions, rendering the api provided by Control.Monad.CatchIO obsolete. Regards, Arie

Arie,
Thanks for calling that out. The most useful part for my case is the
MonadCatchIO implementation of catch:
catch :: Exception e => m a -> (e -> m a) -> m a
Hoogle shows a few similar functions for that type signature, but they
won't work for the case of catching an IOException in an arbitrary monad.
Do you happen to know of another approach for catching IOExceptions and
throwing them in ErrorT?
Thanks,
Eric
On Sun, Jul 21, 2013 at 7:00 AM, Arie Peterson
On Thursday 18 July 2013 23:05:33 Eric Rasmussen wrote:
[…] Would there be any interest in cleaning that up and adding it (or something similar) to Control.Monad.CatchIO? […]
MonadCatchIO-transformers is being deprecated, as recently GHC has removed the 'block' and 'unblock' functions, rendering the api provided by Control.Monad.CatchIO obsolete.
Regards,
Arie
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I think most people use monad-control these days for catching exceptions in
monad stacks (http://hackage.haskell.org/package/monad-control-0.3.2.1).
The very convenient lifted-base package (
http://hackage.haskell.org/package/lifted-base) depends on it and exports a
function Control.Exception.Lifted.catch:
Control.Exception.Lifted.catch :: (MonadBaseControl IO m, Exception e)
=> m a -> (e -> m a) -> m a
I'd recommend you use that instead of MonadCatchIO.
On Mon, Jul 22, 2013 at 4:13 AM, Eric Rasmussen
Arie,
Thanks for calling that out. The most useful part for my case is the MonadCatchIO implementation of catch:
catch :: Exception e => m a -> (e -> m a) -> m a
Hoogle shows a few similar functions for that type signature, but they won't work for the case of catching an IOException in an arbitrary monad. Do you happen to know of another approach for catching IOExceptions and throwing them in ErrorT?
Thanks, Eric
On Sun, Jul 21, 2013 at 7:00 AM, Arie Peterson
wrote: On Thursday 18 July 2013 23:05:33 Eric Rasmussen wrote:
[…] Would there be any interest in cleaning that up and adding it (or something similar) to Control.Monad.CatchIO? […]
MonadCatchIO-transformers is being deprecated, as recently GHC has removed the 'block' and 'unblock' functions, rendering the api provided by Control.Monad.CatchIO obsolete.
Regards,
Arie
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks John. I'll try it out, along with Kmett's exceptions package I just
found:
http://hackage.haskell.org/packages/archive/exceptions/0.1.1/doc/html/Contro...
I noticed on an issue for lens (https://github.com/ekmett/lens/issues/301)
they switched to this since MonadCatchIO is deprecated, and it has a more
general version of catch:
catch :: Exception e => m a -> (e -> m a) -> m a
On Sun, Jul 21, 2013 at 6:30 PM, John Lato
I think most people use monad-control these days for catching exceptions in monad stacks (http://hackage.haskell.org/package/monad-control-0.3.2.1). The very convenient lifted-base package ( http://hackage.haskell.org/package/lifted-base) depends on it and exports a function Control.Exception.Lifted.catch:
Control.Exception.Lifted.catch :: (MonadBaseControl IO m, Exception e) => m a -> (e -> m a) -> m a
I'd recommend you use that instead of MonadCatchIO.
On Mon, Jul 22, 2013 at 4:13 AM, Eric Rasmussen
wrote: Arie,
Thanks for calling that out. The most useful part for my case is the MonadCatchIO implementation of catch:
catch :: Exception e => m a -> (e -> m a) -> m a
Hoogle shows a few similar functions for that type signature, but they won't work for the case of catching an IOException in an arbitrary monad. Do you happen to know of another approach for catching IOExceptions and throwing them in ErrorT?
Thanks, Eric
On Sun, Jul 21, 2013 at 7:00 AM, Arie Peterson
wrote: On Thursday 18 July 2013 23:05:33 Eric Rasmussen wrote:
[…] Would there be any interest in cleaning that up and adding it (or something similar) to Control.Monad.CatchIO? […]
MonadCatchIO-transformers is being deprecated, as recently GHC has removed the 'block' and 'unblock' functions, rendering the api provided by Control.Monad.CatchIO obsolete.
Regards,
Arie
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I don't think there's anything necessarily wrong with ekmett's exceptions
package, but you should be aware that it may not do what you expect:
module Foo where
import Control.Monad.IO.Class
import Control.Monad.Catch
import Control.Exception (ArithException)
f :: CatchT IO String
f = catch (liftIO $ (div 1 0) `seq` return "unreachable") (\x -> let _ = x
:: ArithException in return "caught it")
g = do
x <- runCatchT f
print x
f' :: IO String
f' = catch ((div 1 0) `seq` return "unreachable") (\x -> let _ = x ::
ArithException in return "caught it")
g' = do
x <- f'
print x
*Foo Control.Exception> g
*** Exception: divide by zero
*Foo Control.Exception> g'
"caught it"
I expect this is actually working as designed, but you still may want to be
aware of it.
On Mon, Jul 22, 2013 at 3:45 PM, Eric Rasmussen
Thanks John. I'll try it out, along with Kmett's exceptions package I just found:
http://hackage.haskell.org/packages/archive/exceptions/0.1.1/doc/html/Contro...
I noticed on an issue for lens (https://github.com/ekmett/lens/issues/301) they switched to this since MonadCatchIO is deprecated, and it has a more general version of catch:
catch :: Exception e => m a -> (e -> m a) -> m a
On Sun, Jul 21, 2013 at 6:30 PM, John Lato
wrote: I think most people use monad-control these days for catching exceptions in monad stacks (http://hackage.haskell.org/package/monad-control-0.3.2.1). The very convenient lifted-base package ( http://hackage.haskell.org/package/lifted-base) depends on it and exports a function Control.Exception.Lifted.catch:
Control.Exception.Lifted.catch :: (MonadBaseControl IO m, Exception e) => m a -> (e -> m a) -> m a
I'd recommend you use that instead of MonadCatchIO.
On Mon, Jul 22, 2013 at 4:13 AM, Eric Rasmussen
wrote: Arie,
Thanks for calling that out. The most useful part for my case is the MonadCatchIO implementation of catch:
catch :: Exception e => m a -> (e -> m a) -> m a
Hoogle shows a few similar functions for that type signature, but they won't work for the case of catching an IOException in an arbitrary monad. Do you happen to know of another approach for catching IOExceptions and throwing them in ErrorT?
Thanks, Eric
On Sun, Jul 21, 2013 at 7:00 AM, Arie Peterson
wrote: On Thursday 18 July 2013 23:05:33 Eric Rasmussen wrote:
[…] Would there be any interest in cleaning that up and adding it (or something similar) to Control.Monad.CatchIO? […]
MonadCatchIO-transformers is being deprecated, as recently GHC has removed the 'block' and 'unblock' functions, rendering the api provided by Control.Monad.CatchIO obsolete.
Regards,
Arie
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (5)
-
Alberto G. Corona
-
Arie Peterson
-
David Sorokin
-
Eric Rasmussen
-
John Lato