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

John Lato jwlato at gmail.com
Mon Jul 22 11:04:23 CEST 2013


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 <ericrasmussen at gmail.com>wrote:

> 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/Control-Monad-Catch.html
>
> 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 <jwlato at gmail.com> 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 <ericrasmussen at gmail.com>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 <ariep at xs4all.nl> 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 at haskell.org
>>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>>
>>>
>>>
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe at haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
>>>
>>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130722/f7f8639d/attachment.htm>


More information about the Haskell-Cafe mailing list