Hi Eric:

The pattern may be the MonadCatchIO class:

http://hackage.haskell.org/package/MonadCatchIO-transformers


2013/7/18 Eric Rasmussen <ericrasmus...@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@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

Reply via email to