Records of Functions and Implicit Parameters

In this article we discuss how it is possible to use data and ImplicitParams to wire an application.

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

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

Records of Functions

In previous articles we have discussed records of functions as an alternative to typeclasses for creating boundaries between components in an application. The main benefit is when a component may have multiple implementations, avoiding the need for orphan instances and lawless typeclasses.

For example, we can define records of functions Http and Database to describe our interactions with external services:

data Http m = Http
  { getUsers :: m [String]
  , postUser :: String -> m ()
  }

data Database m = Database
  { dbHistory :: m [String]
  , dbAdd     :: String -> m ()
  }

We can write business logic using these records

doStuff :: Monad m => Http m -> Database m -> m ()
doStuff http db = do
  users <- (http & getUsers)
  void $ traverse (db & dbAdd) users

But the equivalent MTL is much cleaner:

doStuff_mtl :: (Monad m, Http m, Database m) => m ()
doStuff_mtl = do
  users <- getUsers
  void $ traverse dbAdd users

with no need to explicitly name or pass the http and db.

ImplicitParams

Growing lists of explicit parameters are even worse in larger codebases with many, deeply nested, record dependencies. One can lose sight of the business logic and be preoccupied passing records to all the functions that need them. What should be a one line change to add a new dependency (e.g. a Logger) inevitably results in large diffs that have a high likelihood of conflicting with other work-in-flight.

Encodings have been proposed along the lines of Classy Lenses and registry to reduce the boilerplate, but they require knowledge of TemplateHaskell, lenses and generic programming. The compiler errors can be very confusing.

Here we consider an alternative way to reduce the boilerplate using a language extension designed to introduce dynamic scope: ImplicitParams.

A function can have an implicit parameter by declaring a named constraint in the type signature. Names must begin with ?.

Implicit parameters can be used like any other explicit parameter, but remember that the ? is part of the name.

For example we can convert doStuff to use implicit parameters

doStuff_ip' :: Monad m => (?http :: Http m, ?db :: Database m) => m ()
doStuff_ip' = do
  users <- (?http & getUsers)
  void $ traverse (?db & dbAdd) users

The callers of doStuff do not need to pass Http or Database explicitly, the compiler will inject a value that is locally bound with the same name and type.

We can go further and push the implicit parameters to the functions on the record, e.g. redefine the records

data Http m = Http
  { _getUsers :: m [String]
  , _postUser :: String -> m ()
  }

data Database m = Database
  { _dbHistory :: m [String]
  , _dbAdd     :: String -> m ()
  }

with forwarders

getUsers = _getUsers ?http
postUser = _postUser ?http

dbHistory = _dbHistory ?db
dbAdd = _dbAdd ?db

Allowing us to write code with records of functions that looks almost identical to the MTL

doStuff_ip :: Monad m => (?http :: Http m, ?db :: Database m) => m ()
doStuff_ip = do
  users <- getUsers
  void $ traverse dbAdd users

And, of great importance is what the errors look like. What if we forgot to put an implicit db in the type signature? This is the error:

    ā€¢ Could not deduce: ?db::Database m arising from a use of ā€˜dbAdd'ā€™
      from the context: (Monad m, ?http::Http m)
        bound by the type signature for:
                   doStuff_ip :: forall (m :: * -> *).
                                 (Monad m, ?http::Http m) =>
                                 m ()

i.e. it says exactly what is missing, and where.

ImplicitParams are effectively a way to have opt-in local coherence without the drawbacks of orphan instances. Typeclasses can be reserved for lawful classes exhibiting global coherence, and lawless or non-unique polymorphism can be achieved with data and ImplicitParams.

For anybody coming from Scala: ImplicitParams are like the implicit keyword when in parameter position, but without the implicit search space (i.e. not in def or val position).

We can turn an explicit value into an implicit one by naming it in a let or where clause

callStuff = do
  http <- mkUsers HttpConfig
  db <- mkDatabase DatabaseConfig
  let ?http = http
      ?db = db
  doStuff_ip

Unfortunately, it is not possible to assign an implicit parameter in a do binding or a pattern match, it would be great to be able to write

callStuff = do
  ?http <- mkUsers HttpConfig
  ?db <- mkDatabase DatabaseConfig
  doStuff_ip

perhaps this could be a future ghc feature?

Finally, this article would not be complete without discussing the rough edges. In the reddit threads Whatā€™s wrong with ImplicitParams? and What about the ImplicitParams Haskell Language Extension? some authors point out that multiple implicit parameters can be introduced with the same name and the compiler accepts it, and other such oddities. Although this extension is almost 20 years old and has proven itself to be production ready (e.g. it is used to implement HasCallStack) its reach seems to be limited. I believe it is a little gem and deserves more attention!

Thanks for reading. Please share your experience with ImplicitParams (positive or negative) in the comments below, and happy hacking!

10 Likes

Iā€™m using something similar in my current graphics code, though Iā€™m limiting myself to situations where Iā€™m not using the equivalent of local on the implicit parameters and to when I donā€™t need a type parameter at present. When combined with the ā€œReaderT design patternā€ you can get ridiculous types that remain quite easy to use. e.g.

is horrifying looking, but

is all the user does to use it.

4 Likes

I havenā€™t seen the use of ImplicitParams before and was wondering what they wereā€¦

But after reading up they look pretty cool for that use-case. Thanks for showing!

1 Like

13.20.3. Implicit parameters and polymorphic recursion shows an oddity.

1 Like

I am working on a library called implicit-effects [1] that uses the same pattern as you described at the base. My library goes a bit further and make use of type families and constraint kinds to shield the implicit parameters from the users.

I am near in completing implicit-effects for first release, and it is currently a bit lacking on documentation. Hopefully I can share more about the techniques used in the near future.

[1] https://github.com/maybevoid/implicit-effects

1 Like