Consider this function from the http-conduit library:

-- | Download the specified URL (..)
--
-- This function will 'throwIO' an 'HttpException' for (..)
simpleHttp :: MonadIO m => String -> m ByteString

Notice that part of the semantics of this function—that it may throw an HttpException—is encoded in a comment, which the compiler cannot check. This is because Haskell’s notion of exceptions offers no mechanism for advertising to the user the fact that a function might throw an exception.

Michael Snoyman discusses some solutions to this problem, as well as some common anti-patterns, in his blog post Exceptions Best Practices. However, wouldn’t it be much nicer if we could simply express in the type that simpleHttp may throw a HttpException? In this blog post I will propose a very lightweight scheme to do precisely that.

If you want to experiment with this yourself, you can download CheckedRevisited.hs (tested with ghc 7.2, 7.4, 7.6, 7.8 and 7.10).

Note. This is an improved version of this blog post; Checked.hs demonstrates the previous approach; see also the discussion on reddit on the original post and on the improved version.

Throwing checked exceptions

Let’s introduce a type class for “checked exceptions” (à la Java):

class Throws e where

Here’s the key idea: this will be a type class without any instances. If we want to record in the type that some IO action throws a checked exception, we can now just add the appropriate type class constraint. For instance, we can define

throwChecked :: (Exception e, Throws e) => e -> IO a
throwChecked = Base.throwIO

and then use that as

simpleHttp :: (MonadIO m, Throws HttpException) => String -> m ByteString
simpleHttp _ = liftIO $ throwChecked HttpException

Unless we explicitly catch this exception, this annotation will now be propagated to every use site of simpleHttp:

useSimpleHttp :: Throws HttpException => IO ByteString
useSimpleHttp = simpleHttp "http://www.example.com"

Type annotations

There’s something a little peculiar about a type class constraint such as Throws HttpException: normally ghc will refuse to add a type class constraint for a known (constant) type. If you were to write

foo = throwChecked $ userError "Uhoh"

ghc will complain bitterly that

No instance for (Throws IOError)
    arising from a use of ‘throwChecked’
In the expression: throwChecked

until you give the type annotation explicitly (you will need to enable the FlexibleContexts language extension):

foo :: Throws IOError => IO a
foo = throwChecked $ userError "Uhoh"

I consider this a feature, not a bug of this approach: you are forced to explicitly declare the checked exceptions you throw.

Catching checked exceptions

In order to catch checked exceptions we need to somehow eliminate that Throws constraint. That is, we want a function of type

catchChecked :: Exception e => (Throws e => IO a) -> (e -> IO a) -> IO a

In the remainder of this section we explain how we can do this; it requires a bit of type level hacking, and the use of roles. Bear in mind though that you do not need to understand this section in order to be able to use checked exceptions; it suffices to know that a function catchChecked exists.

First, we define a newtype wrapper around an action that throws an exception:

newtype Wrap e a = Wrap { unWrap :: Throws e => a }

Then we define a newtype wrapper around the exception themselves:

newtype Catch e = Catch e

This Catch is used internally only and not exported; it is the only type that will get a Throws instance:

instance Throws (Catch e) where

Now we’re almost there. We are going to use coerce to pretend that instead of an exception of type e we have an exception of type Catch e:

coerceWrap :: Wrap e a -> Wrap (Catch e) a
coerceWrap = coerce

This requires the type argument e on the Throws class to be representational (this needs IncoherentInstances):

type role Throws representational

With all this in place, we can now eliminate Throws constraints:

unthrow :: proxy e -> (Throws e => a) -> a
unthrow _ = unWrap . coerceWrap . Wrap

and defining catchChecked is a simple matter:

catchChecked :: forall a e. Exception e
             => (Throws e => IO a) -> (e -> IO a) -> IO a
catchChecked act = Base.catch (unthrow (Proxy :: Proxy e) act)

Subclasses of exceptions

Suppose we had

readFile :: Throws IOException => FilePath -> IO String

then we can write a function to get a file either by reading a local file or by downloading it over HTTP:

get :: (Throws IOException, Throws HttpException)
    => String -> IO ByteString
get url = case removePrefix "file:" url of
            Just path -> readFile path
            Nothing   -> simpleHttp url

removePrefix :: [a] -> [a] -> Maybe [a]
removePrefix = ..

Alternatively we can define a bespoke exception hierarchy and combine the two exceptions:

data SomeGetException = forall e. Exception e => SomeGetException e

wrapIO :: (Throws IOException      => IO a)
       -> (Throws SomeGetException => IO a)
wrapIO = handleChecked $ throwChecked . SomeGetException

wrapHttp :: (Throws HttpException    => IO a)
         -> (Throws SomeGetException => IO a)
wrapHttp = handleChecked $ throwChecked . SomeGetException

get :: Throws SomeGetException => String -> IO ByteString
get url = case removePrefix "file:" url of
            Just path -> wrapIO   $ readFile path
            Nothing   -> wrapHttp $ simpleHttp url

This kind of custom exception hierarchy is entirely standard; I just wanted to show it fits nicely into this approach to checked exceptions.

Caveat

There is one caveat to be aware of. Suppose we write

returnAction = return (simpleHttp "http://www.example.com")

Ideally we’d give this a type such as

returnAction :: IO (Throws HttpException => IO ByteString)
returnAction = return (simpleHttp "http://www.example.com")

But this requires impredicative types, which is still a no-go zone. Instead the type of returnAction will be

returnAction :: Throws HttpException => IO (IO ByteString)
returnAction = return (simpleHttp "http://www.example.com")

which has the Throws annotation on returnAction itself; this means we can make the annotation disappear by adding an exception handler to returnAction even though it’s never called (because returnAction itself never throws any exception).

returnAction' :: IO (IO ByteString)
returnAction' = catchChecked returnAction neverActuallyCalled
  where
    neverActuallyCalled :: HttpException -> IO (IO ByteString)
    neverActuallyCalled = undefined

This is somewhat unfortunate, but it occurs only infrequently and it’s not a huge problem in practice. If you do need to return actions that may throw exceptions, you can use a newtype wrapper such as Wrap that we used internally in rethrowUnchecked (for much the same reason):

returnAction :: IO (Wrap HttpException IO)
returnAction = return (Wrap $ simpleHttp "http://www.example.com")

Of course you will probably want to define a datatype that is more meaningful for your specific application; for instance, see see the definition of HttpClient in the Repository.Remote module, which defines something like

data HttpClient = HttpClient {
    httpClientGet :: Throws SomeRecoverableException => URI -> ...
  }

Conclusions

Of course, a type such as

simpleHttp :: (MonadIO m, Throws HttpException) => String -> m ByteString

does not tell you that this function can only throw HttpExceptions; it can still throw all kinds of unchecked exceptions, not least of which asynchronous exceptions. But that’s okay: it can still be incredibly useful to track some exceptions through your code.

So there you have it: checked exceptions in Haskell using

  • one—singleton—type class Throws, with no instances
  • just two functions rethrowUnchecked and catchChecked
  • requiring only a handful of non-controversial language extensions
  • without the use of unsafeCoerce

and without introducing a special new kind of monad (such as in the control-monad-exception package) and without complicated type level hacking as in the Checked Exception for Free blogpost.