Local Capabilities with MTL

MTL is a popular approach to writing applications in Haskell. Monad constraints provide capabilities such as error handling (MonadError), writable state (MonadState), and environmental context (MonadReader). An application typically has one monad stack, implemented as a monad transformer.

However, a common problem with MTL is that the capabilities are global and the requirements of individual components may conflict. For example, an HTTP component may require a MonadError ServantError whereas a DB component may require something else. A typical workaround is to introduce a monolithic error ADT, and an unfortunate level of coupling. The problem repeats for other capabilities. That’s not good, and we’d like something better.

In this post, we will demonstrate a way to encode capabilities that remain local to a single component. Our example builds on the Servant Tutorial and will also show how Servant client endpoints can be mocked out for unit testing. This post is a transcription of a test from FFunctor, which may be consulted for import, build-depends, and other practical matters.

Records of Functions

Many capabilities are provided by the mtl but a typical application will require many domain-specific commands that correspond to I/O actions, such as HTTP or DB access, random numbers, timings from a clock. An application is often comprised of multiple layers of these components.

One way to encode these domain-specific components is by having data types containing functions. For example, we may wish to have access to an HTTP server through a UserApi, defined as:

data User = User
  { name              :: String
  , age               :: Int
  , email             :: String
  , registration_date :: UTCTime
  }
data UserApi m = UserApi
  { apiGetUsers  :: m [User]
  , apiPostUsers :: User -> m User
  , apiPutUsers  :: Integer -> User -> m User
  }

An advantage of records of functions is that we can write custom implementations for use in unit tests, without ever talking to a real HTTP server, or performing any IO. Compare to the alternatives: applications that use I/O directly are not so testable, and a class encoding of UserApi would suffer from typeclass coherence problems that are only partially addressed by DerivingVia.

For testing we may wish to have a trivial mock with the Identity monad, or to have state and error handling via Either and State. Every unit test can have its own custom behaviour.

mockApi :: UserApi Identity
mockApi = UserApi (pure []) (\u -> pure u) (\_ u -> pure u)

Servant.Client

We may formalise the /users API as a type

type API = "users" :> Get '[JSON] [User]
      :<|> "users" :> ReqBody '[JSON] User :> Post '[JSON] User
      :<|> "users" :> Capture "userid" Integer :> ReqBody '[JSON] User
                   :> Put '[JSON] User

and generate functions that use the servant ClientM monad

getUsers  :: ClientM [User]
postUsers :: User -> ClientM User
putUsers  :: Integer -> User -> ClientM User
getUsers :<|> postUsers :<|> putUsers = client (Proxy @API)

We can provide a UserApi ClientM for these generated functions:

servantApi :: UserApi ClientM
servantApi = UserApi getUsers postUsers putUsers

But we almost certainly do not want to use ClientM as our application’s monad stack. Therefore we need a way to map a UserApi ClientM into a UserApi OurMonadStack. There are two parts to this:

  1. we need a transformation from ClientM to a constrained m
  2. and we need a way to apply that transformation to UserApi

The first part is easy: such a natural transformation is a one-liner:

liftClientM :: (MonadIO m, MonadError ServantError m)
            => ClientEnv -> ClientM a -> m a
liftClientM env ca = liftEither =<< (liftIO $ runClientM ca env)

where there are three requirements:

  1. a Servant.Client.ClientEnv, giving the host, port and other connection settings
  2. the ability to perform IO, implying MonadIO
  3. the ability to handle ServantError, implying MonadError

To apply liftClientM, we need a new typeclass, FFunctor.

FFunctor

FFunctor allows us to map over the type parameter of something that has kind (* -> *) -> *.

class FFunctor (f :: (* -> *) -> *) where
  ffmap :: (Functor m, Functor n)
        => (forall a . (m a -> n a)) -> f m -> f n

Note that HFunctor, MFunctor and MonadTrans do not have the correct shape, necessitating this new typeclass, first documented as such in Functor Functors.

However, not everything of the required kind may have an FFunctor defined. To be eligible, the f may only have m in covariant position (e.g. return parameters). A record of function that has a field of shape m a -> m b would not be able to have an FFunctor because m a appears in contravariant position.

Thankfully, UserAPI may have an instance of an FFunctor because all occurrences of m only appear in return values.

Writing instances of FFunctor is procedural. Each field has the natural transformation applied according to its number of parameters:

  1. If there are no parameters, the nt is applied as a regular function
  2. If there is one parameter, the nt is composed with (.)
  3. If there are more than one parameter, the Data.Composition package may be used, providing compositions of arbitrary arity. Compositions are conveniently named such that the number of dots after the initial one are the number of parameters, so (.:) handles two parameters, (.:.) handles three, (.::) handles four, and so on.

Here is our instance:

instance FFunctor UserApi where
  ffmap nt (UserApi f1 f2 f3) = UserApi (nt f1) (nt . f2) (nt .: f3)

or if you’re prepared to have some extra dependencies, Universum.VarArg abstracts over all arities with a single operator (...)

instance FFunctor UserApi where
  ffmap nt (UserApi f1 f2 f3) = UserApi (nt f1) (nt ... f2) (nt ... f3)

We can now generate a UserApi for our application’s monad stack, which we can create during initialisation from our ClientEnv configuration.

userApi :: (MonadIO m, MonadError ServantError m)
        => ClientEnv -> UserApi m
userApi env = ffmap (liftClientM env) servantApi

But this demands that we have a MonadError ServantError in our stack, that sucks!

ExceptT

The trick to overcome the problem of having MonadError ServantError in our global stack is to define a type alias

type UserApiT m = UserApi (ExceptT ServantError m)

This MTL trick can be used to add a variety of locally scoped capabilities to a component, e.g. MonadState via StateT, MonadReader via ReaderT, MonadWriter via WriterT.

Downstream user may prefer to depend on UserApiT and must handle ServantError at the point of use. They may chose to retry, recover, ignore errors, or translate errors into an application specific error ADT.

Note that we only need the minimal set of constraints, so we only require a Applicative to write:

doStuff :: Applicative m => UserApiT m -> String -> m Bool
doStuff http check = hasEmail <$> (runExceptT $ apiGetUsers http)
  where
    hasEmail (Left _)      = False
    hasEmail (Right users) = any ((== check) . email) users

Compare to the version where errors are ignored and must be handled at a higher layer.

doStuff' :: Applicative m => UserApi m -> String -> m Bool
doStuff' http check = hasEmail <$> apiGetUsers http
  where
    hasEmail users = any ((== check) . email) users

There is one remaining question, how do we create a UserApiT? Thankfully, Haskell is smarter than us and will happily conjure one up for us when we call userApi. The monad stack in this small application is IO with no additional capabilities:

myApp :: IO Bool
myApp = do
  mgr <- newManager defaultManagerSettings
  let base = BaseUrl Http "localhost" 8080 ""
      env = mkClientEnv mgr base
      api = userApi env
  doStuff api "wibble@wobble.com"
16 Likes

I have two rules of thumb that attack this problem in different ways.

  1. You usually don’t need a domain specific error type. String / Text is usually fine because most of the time you’re just logging the error. If you’re not doing branching / control flow on the details of the error, then having an ADT for it is overkill.

  2. I’ve started to conclude that it’s usually better to not put error handling in your global stack. If you leave it out of your stack, you can drop into an error handling context with ExceptT whenever necessary. This simplifies your global stack and gives you the local capability without going through the more complicated gymnastics.

4 Likes

Right, since http and db are typically IO, it’s better to use exceptions, and use monorphic Either or Maybe return types for functions that can/should be recovered from immediately by the caller.

3 Likes

If I have a global error type, I tend to agree… it’s nice to maybe add a little bit of contextual information though, turn it into a bit of a log message with a callstack and timestamps. If I have an error ADT I tend to split it up based on what can be reasonably expected … like is this “bounce the app” bad? Or is this “maybe log this” bad?

You still don’t really need an ADT for most of those things. Callstack and timestamps…sure they’re nice, but you can just put them in the string. You’re not going to dispatch on the state of those things. The questions of “bounce the app” bad or “maybe log this” bad can often be answered at the site of the error, avoiding the need for the complexity of defining that structure and figuring out how to combine various structures that you have in different parts of your app.

1 Like

Exactly, but not necessarilly the ability to take the remedial action. That’s why it makes sense to send it up the control flow to something that can… if an error ADT doesn’t represent action/resolutions that something can do higher up, I agree that strings (and the implicit action of “just log it”) is all we can do. I think most apps heavily overengineer their error types.

1 Like

With regard to locally different error requirements, I find that a version of MonadError without the functional dependency is quite useful. You just add a constraint for each type of error you want to throw. You might have to add some type annotations but TypeApplications makes this easy.

1 Like

Great post! :slight_smile: Two questions:

a) Using hoist would also work if m had a Monad instance. I guess you wanted a test for your ffunctor package? :slight_smile:

b) Would you be willing to make a servant cookbook out of this? https://github.com/haskell-servant/servant/issues/1042

1 Like

You usually don’t need a domain specific error type. String / Text is usually fine because most of the time you’re just logging the error.

I’ve been moving in the opposite direction of having custom types for my errors and my logs. It’s a specific instance of a more general pattern of keeping information structured in my code as long as possible.

For logs, the main advantage is that I can output a structured format (ie JSON) to feed into external tools. I can still keep a text log output for local development, and I don’t have to commit on a single format ahead of time. For errors, it’s useful for similar reasons even if I don’t expect to handle any of the errors in my domain logic. I can more easily plug the error data into a structured format and I can render error messages in different ways depending on context (ie command line vs UI).

On top of this, I’ve found that having a custom type for errors makes my code neater and improves my development experience. I don’t have to have a bunch of text interpolation in the middle of my domain logic, and if I throw the same kind of error from multiple places, I don’t end up having to copy and paste the text interpolation in multiple places (which normally results in a mess of slightly different messages for the same kind of error). It’s also nice for interactive development because if I get an error in GHCi I can immediately poke around the actual values I included in the error, rather than trying to parse the values from a string.

It also just doesn’t cost much to have a custom type for my errors. The main downside is that you end up coupling different components of your system because they all share an error type. In my current project I’ve gotten around this by having an existential type for domain-specific errors, but this is yet another place where row-typing and extensible sums would be incredibly useful. Besides, some level of centralization for errors and log messages is actually useful—it gives you an overview of the kind of log messages or errors your application might send out, it lets you change what you log without fiddling with your entire codebase and it let you check in one place that you aren’t logging or displaying anything you shouldn’t.

7 Likes

I’ve been moving in the opposite direction of having custom types for my errors and my logs.

I’m glad people are moving in this direction. It’s exactly this kind of stuff I was thinking about when I wrote https://hackage.haskell.org/package/logging-effect years ago.

2 Likes

Aha! I’m not sure it does. I investigated all these existing higher order functors before putting together FFunctor from the referenced blog post… they have a subtely different kind shape. Annoyingly the kind of m isn’t explicit in MFunctor but, if memory serves, it’s (* -> *) -> * -> * not (* -> *) -> *.

I’m a bit busy with parental duties so I’m not sure if I’d have time to write the cookbook, but I’d certainly like to see it if somebody transcribed it. I already got into trouble for spending time writing this post :grinning:

There is also genericClientHoist.

I think I’ll need this soonish, so I’ll play around then with the kind shapes. Thank you again for this post!

1 Like

I think it’s interesting to note the similarity against Effect in simple-effects. In simple-effects, we define effects as E m types, where m is a monad. In simple-effects, any of these effects must be an instance of the Effect type class, and one of the methods is liftThrough :: e m -> e (t m). Ignoring the constraints on it, this looks like an application of FFunctor, with m ~ m, n ~ t m. For reasons that currently escape me though we haven’t been able to replace liftThrough with a more general mapEffect function (like what FFunctor would stipulate).

1 Like

This is part of a series on alternatives to MTL for application design:

  1. Local Capabilities with MTL (this article)
  2. Some limits of MTL with records of functions
  3. Records of Functions and Implicit Parameters
3 Likes