[Haskell] IO, exceptions and error handling

David Menendez zednenem at psualum.com
Tue Jun 15 01:00:49 EDT 2004


Graham Klyne writes:

> Another approach that occurs to me is to introduce an error Monad
> along the lines of that described by Philip Wadler as "E" in his
> "Essence of functional programming" paper [1].  (Or just use Either
> as an error monad?, which is part of what I've been doing with my XML
> work.)

Control.Monad.Error defines a class MonadError and some instances that
provide the functionality of Wadler's E monad.

> The disadvantages I see here are: (a) it requires existing code to be
> modified to return the error monad value. (b) it imposes a strict
> sequencing on the order of computation, which as far as I can see is
> not necessary to achieve the required error handling.  For example, a
> computation that returns a result that is not actually used in a
> subsequent computation would still cause an exception;  e.g.
>      do { b <- f1   -- False
>         ; c <- f2   -- raises exception
>         ; d <- f3   -- value required
>         ; return (if b then c else d)
>         }
> (I know this could be coded differently to avoid the claimed problem,
> but to my mind it still illustrates unnecessary complexity compared
> with:
>      if f1 then f2 else f3
> In effect, it requires the programmer to figure out the lazy
> evaluation sequences instead of letting the Haskell system do it.)

I usually do that as:

> do b <- f1
>    if b then f2 else f3

It's only slightly more complex, it's lazy, and it works with any monad.

But your general point is still valid.

--

As for bridging errors from one library to another, if you use
MonadError e m rather than a specific error monad, you can do something
along these lines:

> import Control.Monad.Error
> 
> data XmlError = X1 | X2 | X3 | XOther String
>     deriving (Eq, Show)
> 
> instance Error XmlError where
>   strMsg = XOther
> 
> 
> data AppError = AppXmlError XmlError | AppOther String
>     deriving (Eq, Show)
> 
> instance Error AppError where
>   strMsg = AppOther
> 
> --
> 
> xmlFunc :: (MonadError XmlError m)
>         => String -> m String
> xmlFunc str = throwError X1
> 
> 
> appFunc :: (MonadError AppError m)
>         => String -> m String
> appFunc s
>   = do s' <- mapError AppXmlError (xmlFunc s)
>        return ("result: " ++ s')
> 
> 
> mapError :: (MonadError e m)
>          => (e' -> e) -> ErrorT e' m a -> m a
> mapError f m = runErrorT m >>= either (throwError . f) return
>
>   -- n.b. runErrorT :: ErrorT e m a -> m (Either e a)
>
> test :: String -> Either AppError String
> test = appFunc
-- 
David Menendez <zednenem at psualum.com> <http://www.eyrie.org/~zednenem/>


More information about the Haskell mailing list