[Haskell-cafe] Explicitly Typed Exceptions in Haskell 98 (Was: Idiomatic error handling in Haskell)

Henning Thielemann lemming at henning-thielemann.de
Mon Mar 7 12:14:17 CET 2011


On Wed, 2 Mar 2011, Henning Thielemann wrote:

> On Wed, 2 Mar 2011, Rouan van Dalen wrote:
>
>> I would like to know what is the preferred Haskell mechanism for handling 
>> exceptions in the IO monad?  I am not concerned with mechanisms such as 
>> Maybe / Either, but would like to know about exception mechanisms inside 
>> the IO monad.
>> 
>> The 2 I know of are:
>>  o) throwDyn
>>  o) ioError and catch
>> 
>> I do need the exceptions to be extendable.  So which is the preferred way
>> to handle exceptions in Haskell for new libs?


I recently had an idea of how to design extensible explicit type safe 
exceptions in Haskell 98, i.e. with single parameter type classes and 
non-overlapping instances. It seems to work quite well, the only drawback 
is that you have to define n^2 instances for n exceptions. This is much 
inspired by:
   http://users.dsic.upv.es/~jiborra/papers/explicitexceptions.pdf


Consider two exceptions: ReadException and WriteException. In order to be 
able to freely combine these exceptions, we use type classes, since type 
constraints of two function calls are automatically merged.

import Control.Monad.Exception.Synchronous (ExceptionalT, )

class ThrowsRead  e where throwRead  :: e
class ThrowsWrite e where throwWrite :: e

readFile  :: ThrowsRead  e => FilePath -> ExceptionalT e IO String
writeFile :: ThrowsWrite e => FilePath -> String -> ExceptionalT e IO ()


For example for

copyFile src dst =
    writeFile dst =<< readFile src

the compiler automatically infers

copyFile ::
   (ThrowsWrite e, ThrowsRead e) =>
   FilePath -> FilePath -> ExceptionalT e IO ()


Instead of ExceptionalT you can also use EitherT or ErrorT. It's also 
simple to add parameters to throwRead and throwWrite, such that you can 
pass more precise information along with the exception. I just want to 
keep it simple for now.

With those definitions you can already write a nice library and defer the 
decision of the particular exception types to the library user. The user 
might define something like

data ApplicationException =
      ReadException
    | WriteException

instance ThrowsRead ApplicationException where
    throwRead = ReadException

instance ThrowsWrite ApplicationException where
    throwWrite = WriteException


Using ApplicationException however it is cumbersome to handle only 
ReadException and propagate WriteException. The user might write 
something like

   case e of
      ReadException -> handleReadException
      WriteException -> throwT throwWrite

in order to handle a ReadException and regenerate a 'ThrowWrite e => e' 
type variable, instead of the concrete ApplicationException type.

He may choose to switch on multi-parameter type classes and overlapping 
instances, define an exception type like 'data EE l' and then use the 
technique from control-monad-exception for exception handling with the 
ExceptionalT monads.

Now I like to propose a technique for handling a particular set of 
exceptions in Haskell 98:

data ReadException e =
      ReadException
    | NoReadException e

instance ThrowsRead (ReadException e) where
     throwRead = ReadException

instance ThrowsWrite e => ThrowsWrite (ReadException e) where
     throwWrite = NoReadException throwWrite


data WriteException e =
      WriteException
    | NoWriteException e

instance ThrowsRead e => ThrowsRead (WriteException e) where
     throwRead = NoWriteException throwRead

instance ThrowsWrite (WriteException e) where
     throwWrite = WriteException



Defining exception types as a sum of "this particular exception" and 
"another exception" lets us compose concrete types that can carry a 
certain set of exceptions on the fly. This is very similar to switching 
from particular monads to monad transformers. Thanks to the type class 
approach the order of composition needs not to be fixed by the throwing 
function but is determined by the order of catching. We even do not have 
to fix the nested exception type fully when catching an exception. It is 
enough to fix the part that is interesting for 'catch':


import Control.Monad.Exception.Synchronous (Exceptional(Success,Exception))

catchRead :: ReadException e -> Exceptional e String
catchRead ReadException = Success "catched a read exception"
catchRead (NoReadException e) = Exception e

throwReadWrite :: (ThrowsRead e, ThrowsWrite e) => e
throwReadWrite =
    asTypeOf throwRead throwWrite

exampleCatchRead :: (ThrowsWrite e) => Exceptional e String
exampleCatchRead =
    catchRead throwReadWrite


Note how in exampleCatchRead the constraint ThrowsRead is removed from the 
constraint list of throwReadWrite.

As I said, the nasty thing is, that the library has to define n^2 
instances for n exceptions. Even worse, if an application imports package 
A and package B with their sets of exceptions, you have to make the 
exception types of A instances of the exception class of B and vice versa, 
and these are orphan instances.

However I am still uncertain, how sophisticated an exception system really 
must be. In principle it must be possible to throw exceptions here and 
there and catch only some of them at several places. But how realistic is 
that? Isn't it more common that there are only few places, maybe even one 
place, where exceptions in an application are catched and reported to the 
user. Isn't it more common that in these few places all possible 
exceptions are handled? I am afraid that much effort is put into designing 
a sophisticated exception handling system like control-monad-exception, 
that needs type extensions, only to see, that in the end it is not good 
style to use all the features of that system.



More information about the Haskell-Cafe mailing list