[Haskell-beginners] how to catch the error thrown by openFile?

Daniel Fischer daniel.is.fischer at googlemail.com
Sun Sep 25 02:55:54 CEST 2011


On Sunday 25 September 2011, 00:27:54, Ovidiu Deac wrote:
> Thanks a lot! It took me a while to understand what you meant but
> eventually I got it.
> 
> This is the final version and it looks much better:
> 
> f :: MyMonad String
> f = do
>  liftIO $ putStrLn "Please enter a file name: "
>  name ←  liftIO getLine
>  hFile ←  ErrorT $ (openFile name ReadMode ↠ return.Right)
>                `catch` λ_ → return.Left $ KnownErr "open failed"

Note that

action >>= return . function

is 

liftM function action

(and ought to be the same as `fmap function action' if the Monad has a 
Functor instance).
It's mostly a matter of taste, but I prefer the fmap/liftM version (and 
fmap can be more efficient).

>  content ←  liftIO $ hGetContents hFile
>  return content

These two lines can be replaced by the shorter

   liftIO $ hGetContents hFile

By desugaring and the Monad laws,

do value <- action
   return value

~> (desugaring)

action >>= \value -> return value === action >>= return === action

(the first === is eta-reduction (\value -> return value) === return, the 
second is a Monad law - I don't remember the canonical numbering, but the 
Monad laws are

return x >>= f === f x
action >>= return === action
(action >>= g) >>= h === action >>= (\x -> h x >>= g)
)

> 
> Somehow I understand but I don't have the feeling yet why I apply
> ErrorT to the whole catched expression instead of liftIO. Do you have
> a nice explanation for it?

Hm, not sure whether I can come up with something nice.

Let's look at the types.

newtype ErrorT e m a = ErrorT { runErrorT :: m (Either e a) }

Thus, in your case, the value constructor ErrorT is a function with type

ErrorT :: IO (Either MyType a) -> MyMonad a

On the other hand, again specialised to your situation,

liftIO :: IO a -> MyMonad a

liftIO lifts any IO-action (which in general has no knowledge of MyType) to 
a MyMonad-action. That lifting consists of two steps, first the IO-action 
is transformed into an IO-action with return type (Either MyType a), then 
that is wrapped in ErrorT.
In particular,

liftIO action = ErrorT $ do { x <- action; return (Right x); }

or, by the definition of liftM,

liftIO action = ErrorT (liftM Right action)

pointfree:

liftIO = ErrorT . liftM Right  -- [1]

The first part of that, adding the (Either MyType), is done in the catch, 
so after the catch, only the second half of liftIO remains to be done, 
applying the value constructor ErrorT.

[1] In particular, liftIO cannot produce any actions that fail in the 
(ErrorT e IO) monad, and IO-failures cannot be caught or handled there.
To handle IO-failures in (ErrorT e IO), you need a construct as above, it 
could have the general form

catchIO :: IO a -> (IOError -> e) -> ErrorT e IO a
catchIO action trans =
    ErrorT $ liftM Right action `catch` (\err -> return (Left $ trans err))

or

    ErrorT $ liftM Right action `catch` (return . Left . trans)

if you use Prelude.catch, with Control.Exception.catch, the type would be

catchIO :: Exception ex => IO a -> (ex -> e) -> ErrorT a IO a

with the same implementation.

With that, the line above would become

  hFile <- openFile name ReadMode `catchIO` const (KnownErr "open failed")

But that is rather limited, it would often be desirable to do some IO 
immediately upon encountering the error, and maybe one can even completely 
recover from the error, so a more useful type would be

liftCatchIO :: Exception ex =>
         IO a -> (ex -> IO (Either e a)) -> ErrorT e IO a
liftCatchIO action handler = ErrorT $ liftM Right action `catch` handler

and the above

  hFile <- liftCatchIO (openFile name ReadMode)
                         (\_ -> return (Left $ KnownErr "open failed"))



More information about the Beginners mailing list