Luminescent Dreams

Haskell Exceptions and Abstractions, or Part 2 of Abstracting the Monad Stack

January 01, 0001

Error handling is a big deal for me. I have probably studied this more than anything else in Haskell because I find it so important to carefully handle unexpected errors. I have presented on this before, but those older presentations lacked a nuance of understanding that I have developed in the last few years.

This article carries on from my previous one, Abstracting the Monad Stack. In that article, I was unable to get all the way to exception abstraction. That this article took me so long to write demonstrates that I was correct in my assessment that this was too much for me to roll into my previous article.

Abstracting out the Exception

Code for this section

I still want to throw exceptions from my library, and my library has the HealthException type:

data HealthException = TimeSeriesExc SeriesExc
                     | UnknownException String
                     deriving (Eq, Show)


type Health r m = (MonadIO m, MonadReader r m, HasHealthContext r)

However, the higher-level context of my application frequently has a different exception type, which may well encompass exceptions from other modules:

data WebExc = WebExcHealth HealthException
            | WebExcHttp HttpException
            | AppForbidden
            | AppUnauthorized

Typically, I would have to unwrap the monad stack for my library in order to rewrap the exception class into the WebExc exception. Again, this works, but it creates tedious boilerplate that we would like to remove:

handleGetHistory :: Interval UTCTime -> WebM ([Sample Weight], [Sample TimeDistance], [Sample Steps])
handleGetHistory interval = do
    WebContext{..} <- ask
    weightRes <- getWeights interval
    timeDistanceRes <- getTimeDistance interval
    stepRes <- getSteps interval

    case (weightRes, timeDistanceRes, stepRes) of
        (Left err, _, _) -> throwError $ WebExcHealth err
        (_, Left err, _) -> throwError $ WebExcHealth err
        (_, _, Left err) -> throwError $ WebExcHealth err
        (Right weights, Right timeDistances, Right steps) -> pure (weights, timeDistances, steps)

In order to make this goal, we can do something similar to HasHealthContext, but this time for writing. Start out by building a class that describes the process of “wrapping” this exception. We must also declare such an exception in our type constraints.

class AsHealthException exc where
    _HealthException :: HealthException -> exc
    _TimeSeriesExc :: SeriesExc -> exc
    _TimeSeriesExc = _HealthException . TimeSeriesExc
    _UnknownException :: String -> exc
    _UnknownException = _HealthException . UnknownException

type Health r exc m = (MonadIO m, MonadReader r m, HasHealthContext r, MonadError exc m, AsHealthException exc)

This class declares a generic function that wraps all health exceptions, and then two dedicated functions for simply creating and wrapping a TimeSeriesExc and an UnknownException. The new components to the type constraint both declare that the calling monad must implement MonadReader, and that the exceptions being raised in the monad must support AsHealthException.

In the library code, you use these exceptions like so:

getWeights :: Health r exc m => Interval UTCTime -> m a
getWeights = throwError $ _HealthException $ UnknownException "demonstrating with _HealthException"

getTimeDistance :: Health r exc m => Interval UTCTime -> m a
getTimeDistance = throwError $ _UnknownException "demonstrating with _UnknownException"

Note how the exception is no longer explicitely called out in the type signatures for getWeights or getTimeDistance. However, that an exception is thrown is still strictly type checked and even documented in the constrant on the exc parameter in Health r exc m.

The caller must implement this class to make the wrapping transparent.

instance AsHealthException WebExc where
    _HealthException = WebExc . WebExcHealth

With this one change, we almost magically see our calling code collapse into something quite reasonable.

handleGetHistory :: Interval UTCTime -> WebM ([Sample Weight], [Sample TimeDistance], [Sample Steps])
handleGetHistory interval = do
    WebContext{..} <- ask
    weights <- getWeights interval
    timeDistances <- getTimeDistance interval
    steps <- getSteps interval
    pure (weights, timeDistances, steps)

Handle an exception inside the monad

Code for this section

Let’s say that there are certain exceptions that you need to handle in place. For instance, assume that when I save a TimeDistance workout, I want to update some summary data. This is slightly contrived since in this case I would usually generate the summaries based on queries, but it serves to illustrate a point.

handleSaveTimeDistance got quite a few updates alongside handleGetHistory, so it has changed from our original example and looks like this:

handleSaveTimeDistance :: Maybe SampleID -> SetTimeDistanceParameters -> WebM (Sample TimeDistance)
handleSaveTimeDistance sampleId params =
    let workoutFromParams = undefined
        workout = workoutFromParams params
    in saveTimeDistance sampleId workout

Now I add the update function, keeping it within the Health monad for simplicity. I also add a fictitious rollback and commit functions. If written, they would assume that, like in any database setup, they are safely written to disk but in a way that does not take effect until a single monotonic commit function happens. Just for the fun of it, I’ll also add a checkAuthorization function, which would be run before actually saving any data to disk.

checkAuthorization :: WebM ()
checkAuthorization = undefined

updateTimeDistanceSummary :: Health r exc m => TimeDistance -> m a
updateTimeDistanceSummary _ = undefined

commit :: Health r exc m => m ()
commit = undefined

rollback :: Health r exc m => m ()
rollback = undefined

However, this turns out to be super simple. Remember that I am working in MonadError, and so I have access to the already-familiar catchError. I have no need for anything complicated.

handleSaveTimeDistance :: Maybe SampleID -> SetTimeDistanceParameters -> WebM (Sample TimeDistance)
handleSaveTimeDistance sampleId params =
    let workoutFromParams = undefined
        workout = workoutFromParams params
    in
    catchError (do checkAuthorization
                   res <- saveTimeDistance sampleId workout
                   updateTimeDistanceSummary workout
                   commit
                   pure res)
               handler
    where
    handler err@(WebExcHealth _) = do
        rollback
        throwError err
    handler exc = throwError exc

Sprinkling in a bit of Template Haskell

Code for this section

The class declaration for AsHealthException above still looks like boilerplate, but I present it as explanation. The Lens library actually provides a function that does exactly this. Note that introducing TemplateHaskell also requires introducing additional files. Code generation from the lenses (or any other TemplateHaskell code generation) does not become available in the file in which it is declared.

{-# LANGUAGE TemplateHaskell #-}

import Control.Lens (makeClassyPrisms, prism)

data HealthException = ...

makeClassyPrisms ''HealthException

The library code must be changed just a bit. The functions on AsHealthException actually create Prisms now, a fairly complex data structure that I only barely grasp. In order to throw the exception, it must first be injected appropriately into a prism, and so the code becomes this:

getWeights :: Health r m => Interval UTCTime -> m (Either HealthException a)
getWeights = throwError $ review _HealthException $ UnknownException "demonstrating with _HealthException"

getTimeDistance :: Health r m => Interval UTCTime -> m (Either HealthException a)
getTimeDistance = throwError $ review _UnknownException "demonstrating with _UnknownException"

Client code is a little different, also, but only in the AsHealthException instance:

instance AsHealthException WebExc where
    _HealthException = prism WebExcHealth unwrap
        where unwrap (WebExcHealth exc) = Right exc
              unwrap exc = Left exc

Again, _HeathException is now a prism, as are _TimeSeriesExc and _UnknownException. This adds some extra options for unwrapping the exception, but I do not currently use, or have a good example of, such a handler.

End of a journey

This has already been a long journey in the making. At the end of it, however, you have learned how to use type constraints to effectively abstract an entire monad stack, making a significantly more reusable and simultaneously much easier to read and use.

This is probably not the only way to set up reusable monad stacks, but it is the one that I find the easiest to understand, the easiest to build, and the easiest to use. I ask you to try this kind of setup for your own code to see where it works and where it breaks. I also would like feedback on how well this worked for you and whether you have a different means of building the same kind of flexibility.

While we have covered a lot of ground, there is much more to do. In my next article I will provide a summary template of everything we have built here.

After that, it is time to start designing architectures that can handle dependency injection for mocking out resources in test, or even allowing run-time configuration of resource backends.

Creative Commons License
Haskell Exceptions and Abstractions, or Part 2 of Abstracting the Monad Stack by Savanni D’Gerinel is licensed under a Creative Commons Attribution-NonCommercial-ShareAlike 4.0 International License.