dep-t: Dependency injection for records-of-functions.

[ bsd3, control, library ] [ Propose Tags ]

Put all your functions in the environment record! Let all your functions read from the environment record! No favorites!


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.1.0.1, 0.1.0.2, 0.1.1.0, 0.1.2.0, 0.1.3.0, 0.4.0.0, 0.4.0.1, 0.4.0.2, 0.4.4.0, 0.4.5.0, 0.4.6.0, 0.5.0.0, 0.5.1.0, 0.6.0.0, 0.6.1.0, 0.6.2.0, 0.6.3.0, 0.6.4.0, 0.6.5.0, 0.6.6.0, 0.6.7.0, 0.6.8.0
Change log CHANGELOG.md
Dependencies base (>=4.10.0.0 && <5), mtl (>=2.2), transformers (>=0.5.0.0), unliftio-core (>=0.2.0.0) [details]
License BSD-3-Clause
Author Daniel Diaz
Maintainer diaz_carrete@yahoo.com
Category Control
Source repo head: git clone https://github.com/danidiaz/dep-t.git
Uploaded by DanielDiazCarrete at 2022-04-16T17:58:37Z
Distributions
Reverse Dependencies 4 direct, 0 indirect [details]
Downloads 3243 total (60 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2022-04-16 [all 1 reports]

Readme for dep-t-0.6.2.0

[back to package description]

dep-t

This package provides various helpers for the "record-of-functions" style of structuring Haskell applications. The guiding idea is that record-of-functions is a form of dependency injection, and the that the environment which contains the functions is akin to an ApplicationContext in object-oriented frameworks like Java Spring.

If every dependency knew about the concrete environment, that would increase coupling. The solution is to use Has-style classes so that each dependency knows only about those parts of the environment which it needs to function, and nothing more. Those Has-style classes can be tailor-made, but the package also provides a generic one.

Very loosely speaking, Has-style constraints correspond to injected member variables in object-oriented frameworks.

dep-t.png

  • Dep.Has contains a generic Has typeclass for locating dependencies in an environment. It can be useful independently of ReaderT, DepT or any monad transformer.
  • Dep.Env complements Dep.Has, adding helpers for building environments of records.
  • Dep.Tagged is a helper for disambiguating dependencies in Dep.Env environments.
  • Control.Monad.Dep contains the DepT monad transformer, a variant of ReaderT.
  • Control.Monad.Dep.Class is an extension of MonadReader, useful to program against both ReaderT and DepT.

The DepT transformer

DepT is a ReaderT-like monad transformer for dependency injection.

The difference with ReaderT is that DepT takes an enviroment whose type is parameterized by DepT itself.

Rationale

To perform dependency injection in Haskell, a common solution is to build a record of functions and pass it to the program logic using some variant of ReaderT.

To avoid becoming tied to a concrete reader environment, let's define some auxiliary typeclasses that extract functions from a generic environment:

type HasLogger :: (Type -> Type) -> Type -> Constraint
class HasLogger d e | e -> d where
  logger :: e -> String -> d ()

type HasRepository :: (Type -> Type) -> Type -> Constraint
class HasRepository d e | e -> d where
  repository :: e -> Int -> d ()

We see that the type e of the environment determines the monad d on which the effects take place.

Here's a monomorphic environment record with functions that have effects in IO:

type EnvIO :: Type
data EnvIO = EnvIO
  { _loggerIO :: String -> IO (),
    _repositoryIO :: Int -> IO ()
  }

instance HasLogger IO EnvIO where
  logger = _loggerIO

instance HasRepository IO EnvIO where
  repository = _repositoryIO

Record-of-functions-in-IO is a simple technique which works well in many situations. There are even specialized libraries that support it.

Here's a function which can get its dependencies from the monomorphic environment:

mkControllerIO :: (HasLogger IO e, HasRepository IO e) => Int -> ReaderT e IO String
mkControllerIO x = do
  e <- ask
  liftIO $ logger e "I'm going to insert in the db!"
  liftIO $ repository e x
  return "view"

That's all and well, but there are two issues that bug me:

  • We might want to write code that is innocent of IO and polymorphic over the monad, to ensure that the program logic can't do some unexpected missile launch, or to allow testing our app in a "pure" way.

  • What if the repository function needs access to the logger, too? The repository lives in the environment record, but isn't aware of it. That means it can't use the HasLogger typeclass for easy and convenient dependency injection. Why privilege the controller in such a way?

    In a sufficiently complex app, the diverse functions that comprise it will be organized in a big DAG of dependencies. And it would be nice if all the functions taking part in dependency injection were treated uniformly; if all of them had access to (some view of) the environment record.

To tackle these issues, we begin by giving the controller a more general signature:

mkControllerIO :: (HasLogger IO e, HasRepository IO e, MonadIO m, MonadReader e m) => Int -> m String

Now the function can work in other reader-like monads besides ReaderT.

Let's go one step further, and abstract away the IO, so that functions in the record can have effects in other monads:

mkController :: (HasLogger d e, HasRepository d e, LiftDep d m, MonadReader e m) => Int -> m String
mkController x = do
  e <- ask
  liftD $ logger e "I'm going to insert in the db!"
  liftD $ repository e x
  return "view"

Now both the signature and the implementation have changed:

  • There's a new type variable d, the monad in which functions taken from the environment e have their effects.

  • MonadIO has been replaced by LiftDep from Control.Monad.Dep.Class, a constraint that says we can lift d effects into m (though it could still make sense to require MonadIO m for effects not originating in the environment).

  • Uses of liftIO have been replaced by liftD.

If all those constraints prove annoying to write, there's a convenient shorthand using the MonadDep type family:

mkController :: MonadDep [HasLogger, HasRepository] d e m => Int -> m String

The new, more polymorphic mkController function can replace the original mkControllerIO:

mkControllerIO' :: (HasLogger IO e, HasRepository IO e) => Int -> ReaderT e IO String
mkControllerIO' = mkController

Now let's focus on the environment record. We'll parameterize its type by a monad:

type Env :: (Type -> Type) -> Type
data Env m = Env
  { _logger :: String -> m (),
    _repository :: Int -> m (),
    _controller :: Int -> m String
  }

instance HasLogger m (Env m) where
  logger = _logger

instance HasRepository m (Env m) where
  repository = _repository

Notice that the controller function is now part of the environment. No favorites here!

The following implementation of the logger function has no dependencies besides MonadIO:

mkStdoutLogger :: MonadIO m => String -> m ()
mkStdoutLogger msg = liftIO (putStrLn msg)

But look at this implementation of the repository function. It gets hold of the logger through HasLogger, just as the controller did:

mkStdoutRepository :: (MonadDep '[HasLogger] d e m, MonadIO m) => Int -> m ()
mkStdoutRepository entity = do
  e <- ask
  liftD $ logger e "I'm going to write the entity!"
  liftIO $ print entity

It's about time we choose a concrete monad and assemble an environment record:

envIO :: Env (DepT Env IO)
envIO =
  let _logger = mkStdoutLogger
      _repository = mkStdoutRepository
      _controller = mkController
   in Env {_logger,  _repository, _controller}

Not very complicated, except... what is that weird DepT Env IO doing there in the signature?

Well, that's the whole reason this library exists. For dependency injection to work for all functions, Env needs to be parameterized with a monad that provides that same Env environment. And trying to use a ReaderT (Env something) IO to parameterize Env won't fly; you'll get weird "infinite type" kind of errors. So I created the DepT newtype over ReaderT to mollify the compiler.

DepT has MonadReader and LiftDep instances, so the effects of mkController can take place on it.

So how do we invoke the controller now?

I suggest something like

runDepT (do e <- ask; _controller e 7) envIO 

or

(do e <- ask; _controller e 7) `runDepT` envIO 

The companion package dep-t-advice has some more functions for running DepT computations.

How to avoid using "ask" and "liftD" before invoking a dependency?

One possible workaround (at the cost of more boilerplate) is to define helper functions like:

loggerD :: MonadDep '[HasLogger] d e m => String -> m ()
loggerD msg = asks logger >>= \f -> liftD $ f msg

Which you can invoke like this:

usesLoggerD :: MonadDep [HasLogger, HasRepository] d e m => Int -> m String
usesLoggerD i = do
  loggerD "I'm calling the logger!"
  return "foo"

Though perhaps this isn't worth the hassle.

How to use "pure fakes" during testing?

The test suite has an example of using a Writer monad for collecting the outputs of functions working as "test doubles".

How to make a function "see" a different evironment from the one seen by its dependencies?

Sometimes we want a function in the environment to see a slightly different record from the record seen by the other functions, and in particular from the record seen by its own dependencies.

For example, the function might have a HasLogger constraint but we don't want it to use the default HasLogger instance of the environment.

The companion package dep-t-advice provides a deceive function that allows for this.

How to add AOP-ish "aspects" to functions in an environment?

The companion package dep-t-advice provides a general method of extending the behaviour of DepT-effectful functions, in a way reminiscent of aspect-oriented programming.

What if I don't want to use DepT, or any other monad transformer for that matter?

Check out the function fixEnv in module Dep.Env, which provides a transformer-less way to perform dependency injection, based on knot-tying.

That method requires an environment parameterized by two type constructors: one that wraps each field, and another that works as the effect monad for the components.

DepT caveats

The structure of the DepT type might be prone to trigger a known infelicity of the GHC simplifier.

  • This library was extracted from my answer to this Stack Overflow question.

  • The implementation of mapDepT was teased out in this other SO question.

  • An SO answer about records-of-functions and the "veil of polymorphism".

  • The answers to this SO question gave me the idea for how to "instrument" monadic functions (although the original motive of the question was different).

  • I'm unsure of the relationship between DepT and the technique described in Adventures assembling records of capabilities which relies on having "open" and "closed" versions of the environment record, and getting the latter from the former by means of knot-tying.

    It seems that, with DepT, functions in the environment obtain their dependencies anew every time they are invoked. If we change a function in the environment record, all other functions which depend on it will be affected in subsequent invocations. I don't think this happens with "Adventures..." at least when changing a "closed", already assembled record.

    With DepT a function might use local if it knows enough about the environment. That doesn't seem very useful for program logic; if fact it sounds like a recipe for confusion. But it enables complex scenarios for which the dependency graph needs to change in the middle of a request.

    All in all, perhaps DepT will be overkill in a lot of cases, offering unneeded flexibility. Perhaps using fixEnv from Dep.Env will end up being simpler.

    Unlike in "Adventures..." the fixEnv method doesn't use an extensible record for the environment but, to keep things simple, a suitably parameterized conventional one.

  • Another exploration of dependency injection with ReaderT: ReaderT-OpenProduct-Environment.

  • The ReaderT design pattern.

    Your application code will, in general, live in ReaderT Env IO. Define it as type App = ReaderT Env IO if you wish, or use a newtype wrapper instead of ReaderT directly.

    Optional: instead of directly using the App datatype, write your functions in terms of mtl-style typeclasses like MonadReader and MonadIO

  • RIO is a featureful ReaderT-like / prelude replacement library which favors monomorphic environments.

  • The van Laarhoven Free Monad.

    Swierstra notes that by summing together functors representing primitive I/O actions and taking the free monad of that sum, we can produce values use multiple I/O feature sets. Values defined on a subset of features can be lifted into the free monad generated by the sum. The equivalent process can be performed with the van Laarhoven free monad by taking the product of records of the primitive operations. Values defined on a subset of features can be lifted by composing the van Laarhoven free monad with suitable projection functions that pick out the requisite primitive operations.

    Another post about the van Laarhoven Free Monad. Is it related to the final encoding of Free monads described here?

  • Interesting SO response (from 2009) about the benefits of autowiring in Spring. The record-of-functions approach in Haskell can't be said to provide true autowiring. You still need to assemble the record manually, and field names in the record play the part of Spring bean names.

    Right now I think the most important reason for using autowiring is that there's one less abstraction in your system to keep track of. The "bean name" is effectively gone. It turns out the bean name only exists because of xml. So a full layer of abstract indirections (where you would wire bean-name "foo" into bean "bar") is gone

  • registry is a package that implements an alternative approach to dependency injection, one different from the ReaderT-based one.

  • Printf("%s %s", dependency, injection). Commented on HN, Lobsters.

  • Dependency Injection Principles, Practices, and Patterns This is a good book on the general princples of DI.

  • A series of posts—by one of the authors of the DI book—about building a DI container.

  • Lessons learned while writing a Haskell application. This post recommends a "polymorphic record of functions" style, which fits the philosophy of this library.

  • One big disadvantage of the records-of-functions approach:

    representing effects as records of functions rather than typeclasses/fused effect invocations destroys inlining, so you’ll generate significantly worse Core if you use this on a hot path.

  • ReaderT pattern is just extensible effects