Decorate your records-of-functions with this weird trick

When structuring your Haskell applications using the “ReaderT pattern”, the environment will usually be a record of functions of various arities, like this:

{-# LANGUAGE BlockArguments, DeriveGeneric #-}
import Data.Function ((&))
import Data.List.NonEmpty (NonEmpty ((:|)))
import System.IO
import GHC.Generics

data Env m = Env {
        foo :: m ()
    ,   bar :: Int -> m Int
    ,   baz :: Int -> Bool -> m Char
    } deriving Generic

-- dummy environment value
env :: Env IO
env = Env {
        foo = pure ()
    ,   bar = \_ -> pure 5 
    ,   baz = \_ _ -> pure 'c'
    }

Sometimes, we need to “decorate” one or more functions in the record in order to add some new behavior. Behaviors like

  • Caching
  • Logging
  • Exception handling
  • Retries
  • and so on

Having to remember the exact number of arguments of each particular function in order to transform it is annoying. We want to be able to say things like: “if all the arguments to the function have a Show instance, make the function print its arguments when it’s called”.

This can be done with a little typeclass magic. Traverse the fields using generics, then traverse each function until the final monadic action, bingo.

Theres an unexpected roadblock, however.

When the environment record is polymorphic on the effect monad, it’s difficult for the helper typeclass to determine “am I already at the tip of the function, or is this just another (->) type constructor”?

“Functional Pearl: The Decorator Pattern in Haskell” acknowledges this difficulty, and proposes this solution:

However, these two instance overlap, because (m b) and (a → b) unify, with substitution m = ((->) a). So, instead, we factor the base case into IO and transformers. Since most non-IO monads in the standard libraries are defined as transformers applied to Id, this factoring covers most types in practice!

I guess some tasteful use of OverlappingInstances would also work. However, I’ve experimented with a different approach using coercions. This is available in th module Control.Monad.Dep.SimpleAdvice from package dep-t-advice.

The basic idea is to have a do-nothing transformer called AspectT which is pretty much the same as IdentityT. When we want to “decorate” an environment of type Env m, first we coerce it to Env (AspectT m). Now the typeclass doesn’t get confused, because there’s a concrete AspectT at the tip of the function. So we perform our decorative magic, and then we can coerce back to Env m.

In my library, the function that coerces to and from AspectT is called advising:

advising
    :: Coercible (r_ m) (r_ (AspectT m))	 
    => (r_ (AspectT m) -> r_ (AspectT m))	
    -> r_ m	
    -> r_ m

And the functions that actually apply the decorations are advise and adviseRecord. For example, to advise a single function in the environment:

import Control.Monad.Dep.SimpleAdvice (
                 AspectT(..),
                 advising, advise, adviseRecord,
                 Top)
import Control.Monad.Dep.SimpleAdvice.Basic (printArgs)

env' :: Env IO
env' = env & advising \envA -> envA { 
                           baz = advise (printArgs stdout "prefix ") (baz envA) 
                          }

where printArgs is of type Advice. How this works might be a bit clearer with a type hole

env_ :: Env IO
env_ = env & advising \envA -> envA { baz = _ (baz envA) }
--   * Found hole:
--        _ :: (Int -> Bool -> AspectT IO Char)
--             -> Int -> Bool -> AspectT IO Char

If we run the decorated baz, we get:

main :: IO ()
main = do
    _ <- baz env' 5 False
    pure ()
-- prefix: 5 False

We can also decorate all the functions in the record in one go:

env'' :: Env IO
env'' = env & advising (adviseRecord @_ @Top \_ -> 
                           printArgs stdout "prefix: ")

(The Top type application is because adviseRecord needs a little extra help with the expected constraints.)

It would be useful for logging purposes if printArgs knew the name of each of the fields it decorates. Turns out we can do that, because adviseRecord passes down that information in a NonEmpty (TypeRep,String):

env''' :: Env IO
env''' = env & advising (adviseRecord @_ @Top \((tr,fieldName) :| _) -> 
                            printArgs stdout (show tr ++ " " ++ fieldName))

This results in output like

main :: IO ()
main = do
    _ <- baz env''' 7 True
    pure ()
-- Env baz: 7 True

While writing this library I found a somewhat unexpected limitation of the coercion mechanism.

Here’s a gist with all the code.

Interesting. I was expecting an interface like

(forall a. n a -> m a) -> Env n -> Env m

Would that do the same job?

That interface is less versatile in that it doesn’t have access to function arguments for logging or debugging. It’s more versatile in that it can change the type of the monad, which Advices can’t.

It resembles the (non type-changing) makeExecutionAdvice function from the library.