[Haskell] Better Exception Handling

Scott Turner p.turner at computer.org
Tue Nov 30 15:58:33 EST 2004


Last week John Goerzen asked about exceptions in Haskell.  I responded with 
some code that supports a hierarchy of exception types. Jules Bean reacted 
that "the internal implementation with fromDynamic doesn't seem pretty 
though".

Although dynamic types reflect the common implementation of exceptions in Java 
and C++, I wondered to what extent this coding style could be supported with 
static type checking.  I've come up with a framework that does so.

The Haskell Main module using the FTP library remains comparable to John 
Goerzen's Python example.

main = runException $
 runException $ do
     ftp("ftp.kernel.org")
     (   cwd "/pub/linux/kernel/v2.4"
  `catchException` (\(ErrorPerm e) -> liftIO $ do
      putStrLn ("caught temp error in cwd: " ++ e)
      exitWith (ExitFailure 2))
      )
     retrbinary "RETR ChangeLog-2.4.13" 
      (\block -> write block)
     quit
 `catchException` (\(ErrorPerm e) -> liftIO $ do
     putStrLn ("Permissions error " ++ e)
     exitWith (ExitFailure 2))
 `catchException` (\(ErrorTemp e) -> liftIO $ do
     putStrLn ("Temporary error, please try again later " ++ e)
     exitWith (ExitFailure 1))
 `catchException` (\(FTPError e) -> liftIO $ do
     putStrLn ("Other FTP error " ++ e)
     exitWith (ExitFailure 2))
 `catchException` (\(AnyError e) -> liftIO $ do
     putStrLn ("Non-FTP error " ++ e)
     exitWith (ExitFailure 3))

The FTPError module demonstrates how to add new classes of errors
in the exception hierarchy.  In the statically typed framework this is
more verbose than previously.  The full sample code is at
http://www.pkturner.org/exception2.tar

1. The revised implementation builds on ErrorT rather than rolling its
   own.
2. The Exception class associates an error type with a monad that can
   throw and catch the type.
3. A monad like FTPException may propagate several error types.  These are
   held as alternatives in a master type FTPError.  A consequence is
   that exception handler functions return a Maybe result, so that
   a handler for a subtype can be promoted to a handler for its supertype.
   This is the first method for building an exception hierarchy, enhancing
   the basic use of ErrorT (from Control.Monad.Error).
4. FTPException is also a Subexception, meaning that it expands on the
   set of error types supported by an inner monad.  This is the second
   method for building an exception hierarchy.  It goes beyond
   lifting the actions of the inner monad in a couple of respects.
   a. The FTPException monad's actions are invoked from a more
      basic monad, which becomes its inner monad.
      If any error is thrown and not caught, the FTPException code
      will return to the invoking monad, propagating the error
      using a type which is natively understood by that monad.
   b. If one of the inner monad's errors is thrown, it can be caught
      and handled using the full abilities of the FTPException monad.
5. The root exception monad, AnyException, supports one error type,
   AnyError.


More information about the Haskell mailing list