Embracing Flexibility in Haskell Libraries: The Power of Records of Functions

Haskell, with its strong type system and emphasis on functional programming, presents unique opportunities and challenges when designing libraries. A common approach in Haskell is to define functionality using concrete top-level functions or type classes. However, there's an alternative approach that deserves more attention: using records of functions to expose core functionality. This design choice, especially relevant for Haskell which lacks features like monkey patching found in other languages, offers significant advantages in terms of mocking, fault injection, and instrumentation.

For context, I currently work at Mercury, a startup that builds a banking platform for startups. We use Haskell extensively in our backend services, and I've found this approach to be a powerful tool in our arsenal. In order to service the needs of our customers, we integrate with a variety of external services, and need to keep a constant eye on performance and reliability. Seeing a need for better debugging capabilities, I implemented and maintain the hs-opentelemetry library suite for distributed tracing in Haskell.

During the course of implementing support for instrumenting a number of third-party libraries, I've found that libraries that rely solely on concrete implementations are the most challenging to instrument, and anything short of forking them to add instrumentation provides only a partial solution at best. On the other hand, libraries that expose core functionality through records of functions are much easier to instrument, and often require only a few lines of code to add instrumentation.

Understanding Records of Functions

What do I mean when I say a record of functions? A record of functions is essentially a collection of related functions bundled together in a single record. This approach contrasts with defining each function at the top level or using type classes to abstract over different implementations.

One of the best examples, and perhaps the most widely used, is the SqlBackend definition from the persistent library. Instead of defining new datatypes for different SQL backends, persistent uses a record of functions to expose core functionality. This approach allows for easy extensibility and customization.

Real-World Example: The persistent Library's SqlBackend Type

Consider the SqlBackend type from the persistent library, a popular Haskell ORM:

data SqlBackend = SqlBackend
    { connPrepare :: Text -> IO Statement
    -- ^ This function should prepare a 'Statement' in the target database,
    -- which should allow for efficient query reuse.
    , connInsertSql :: EntityDef -> [PersistValue] -> InsertSqlResult
    -- ^ This function generates the SQL and values necessary for
    -- performing an insert against the database.
    , connInsertManySql :: Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
    -- ^ SQL for inserting many rows and returning their primary keys, for
    -- backends that support this functionality. If 'Nothing', rows will be
    -- inserted one-at-a-time using 'connInsertSql'.
    , connUpsertSql :: Maybe (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)
    -- ^ Some databases support performing UPSERT _and_ RETURN entity
    -- in a single call.
    --
    -- This field when set will be used to generate the UPSERT+RETURN sql given
    -- * an entity definition
    -- * updates to be run on unique key(s) collision
    --
    -- When left as 'Nothing', we find the unique key from entity def before
    -- * trying to fetch an entity by said key
    -- * perform an update when result found, else issue an insert
    -- * return new entity from db
    --
    -- @since 2.6
    , connPutManySql :: Maybe (EntityDef -> Int -> Text)
    -- ^ Some databases support performing bulk UPSERT, specifically
    -- "insert or replace many records" in a single call.
    --
    -- This field when set, given
    -- * an entity definition
    -- * number of records to be inserted
    -- should produce a PUT MANY sql with placeholders for records
    --
    -- When left as 'Nothing', we default to using 'defaultPutMany'.
    --
    -- @since 2.8.1
    , connStmtMap :: StatementCache
    -- ^ A reference to the cache of statements. 'Statement's are keyed by
    -- the 'Text' queries that generated them.
    , connClose :: IO ()
    -- ^ Close the underlying connection.
    , connMigrateSql
        :: [EntityDef]
        -> (Text -> IO Statement)
        -> EntityDef
        -> IO (Either [Text] [(Bool, Text)])
    -- ^ This function returns the migrations required to include the
    -- 'EntityDef' parameter in the @['EntityDef']@ database. This might
    -- include creating a new table if the entity is not present, or
    -- altering an existing table if it is.
    , connBegin :: (Text -> IO Statement) -> Maybe IsolationLevel -> IO ()
    -- ^ A function to begin a transaction for the underlying database.
    , connCommit :: (Text -> IO Statement) -> IO ()
    -- ^ A function to commit a transaction to the underlying database.
    , connRollback :: (Text -> IO Statement) -> IO ()
    -- ^ A function to roll back a transaction on the underlying database.
    , connEscapeFieldName :: FieldNameDB -> Text
    -- ^ A function to extract and escape the name of the column corresponding
    -- to the provided field.
    --
    -- @since 2.12.0.0
    , connEscapeTableName :: EntityDef -> Text
    -- ^ A function to extract and escape the name of the table corresponding
    -- to the provided entity. PostgreSQL uses this to support schemas.
    --
    -- @since 2.12.0.0
    , connEscapeRawName :: Text -> Text
    -- ^ A function to escape raw DB identifiers. MySQL uses backticks, while
    -- PostgreSQL uses quotes, and so on.
    --
    -- @since 2.12.0.0
    , connNoLimit :: Text
    , connRDBMS :: Text
    -- ^ A tag displaying what database the 'SqlBackend' is for. Can be
    -- used to differentiate features in downstream libraries for different
    -- database backends.
    , connLimitOffset :: (Int,Int) -> Text -> Text
    -- ^ Attach a 'LIMIT/OFFSET' clause to a SQL query. Note that
    -- LIMIT/OFFSET is problematic for performance, and indexed range
    -- queries are the superior way to offer pagination.
    , connLogFunc :: LogFunc
    -- ^ A log function for the 'SqlBackend' to use.
    , connMaxParams :: Maybe Int
    -- ^ Some databases (probably only Sqlite) have a limit on how
    -- many question-mark parameters may be used in a statement
    --
    -- @since 2.6.1
    , connRepsertManySql :: Maybe (EntityDef -> Int -> Text)
    -- ^ Some databases support performing bulk an atomic+bulk INSERT where
    -- constraint conflicting entities can replace existing entities.
    --
    -- This field when set, given
    -- * an entity definition
    -- * number of records to be inserted
    -- should produce a INSERT sql with placeholders for primary+record fields
    --
    -- When left as 'Nothing', we default to using 'defaultRepsertMany'.
    --
    -- @since 2.9.0
    , connVault :: Vault
    -- ^ Carry arbitrary payloads for the connection that
    -- may be used to propagate information into hooks.
    , connHooks :: SqlBackendHooks
    -- ^ Instrumentation hooks that may be used to track the
    -- behaviour of a backend.
    }

Most of the fields in SqlBackend are functions relevant to database operations. This design allows for highly customizable behavior at the level of individual operations.

If, for example, you wanted to understand how your application would respond in the face of a network outage during a transaction, you might override connCommit and connRollback to throw exceptions. This approach is much easier than turning off your WiFi or unplugging your ethernet cable whilst your test suite is running!

Examining other Approaches

Alternative Approach #1: Wrapping Concrete Implementation Functions

Another approach that some Haskell developers might consider is wrapping the original concrete implementation functions in a new module. In fact, I do this too for libraries like postgresql-simple since they don't provide any abstractions to work with. This method involves duplicating each function and exposing the same function signatures, essentially creating a facade over the original implementation.

Limitations of the Wrapping Approach

While this method is arguably the most obvious solution, it has several limitations:

  1. Limited Scope of Control: The primary issue is that this approach only affects code that explicitly uses the wrapped functions. If you're using third-party libraries or existing codebases that directly interact with the original module, they won't benefit from the modifications or extensions provided by the wrapping module. This limitation can lead to inconsistencies in behavior and missed opportunities for extended functionality. We see this issue in OpenTelemetry traces fairly often in the form of large gaps in traces. The code is doing... something? But, due to the inability to smuggle in instrumentation hooks, we can't tell what is taking so much time to execute.

  2. Duplication and Maintenance Overhead: This method requires duplicating the interface of the entire module you're wrapping. Any changes in the original module's interface, such as adding or modifying functions, necessitate corresponding updates in the wrapper. This duplication increases the maintenance burden and the risk of the wrapper becoming out of sync with the original module.

  3. Complexity in Integration: Integrating the wrapped module with existing code can become complex, especially in larger codebases. Developers need to be mindful of which module (original or wrapped) is being used in different parts of the application. This requirement can lead to confusion and bugs if not managed carefully. This can be mitigated somewhat by using tools like HLint to enforce consistent usage of the wrapped module, but you are in charge of constantly updating the HLint rules for modules that you wrap.

  4. Inflexibility in Runtime Behavior Modification: Unlike the records of functions approach, where individual functions can be dynamically swapped or extended at runtime, the wrapping approach is more static. Any behavior modification requires changing the wrapper implementation and redeploying the application, reducing the flexibility to adapt or extend functionality dynamically.

While wrapping concrete implementation functions in a new module offers a way to extend or modify behavior, it falls short in flexibility and control compared to using records of functions. The wrapping approach doesn't provide a universal solution, especially when dealing with third-party libraries or ensuring consistent behavior across an entire codebase.

Therefore, while it might be suitable for simple extensions or modifications, it's generally less effective for more complex or dynamic requirements. Th e records of functions approach, in contrast, offers a more robust and flexible solution, aligning better with the principles of maintainability and extensibility in functional programming.

Alternative Approach #2: Type Classes

Type classes offer abstraction, but they can lead to more complex type signatures and sometimes unnecessary boilerplate code. Moreover, they don't lend themselves as easily to runtime changes in behavior as records of functions do.

The real practical downside to them is that, if you are adding a type class to an existing library to provide overridable behaviour, you are typically going to be introducing breaking changes for existing consumers of your library.

Alternative Approach #3: Effect Systems

I'll assume here that you know what an effect system is. If you don't, I recommend watching this lovely StrangeLoop talk. The rest of this effect system section reproduces an abridged version of some documentation that I previously contributed to the fused-effects library, and we'll use it as a point of comparison to the records of functions approach.

Fair warning! The last time I used fused-effects was many moons ago, so this code probably doesn't compile anymore. I'm not going to update it, but I still think it provides a useful comparison to the records of functions approach.

One of the nice aspects of effects systems is that they can support multiple effect handlers. Effects only specify actions, they don't actually perform them. Therefore, it's possible to "reinterpret" effects. There are multiple senses in which an effect can be reinterpreted:

  • Implementing an effect in terms of other effects. "Reinterpreting" effects is a powerful tool for cleanly dividing implementations into the relevant abstraction layers with minimal leakage of implementation details.
  • Rewriting an effect and/or performing actions with the effect value and then performing the originally intended effect. This technique is conceptually similar to the middleware pattern commonly used in web applications. This known as interposition (see works by Oleg Kiselyov et al.)

Let's explore both of these effect interpretation strategies with a small motivating example:

✨ We would like to implement a client library for an HTTP-based API that provides interesting cat facts. ✨

Let's break down some of the properties of the API client that would be desirable for a production use case:

  1. We would like to have our cat facts API be able to support different cat fact data sources in the future.
  2. We would like to be able to mock failure conditions (such as network connectivity issues) for testing purposes.
  3. We would like to be able to track timing metrics for how quickly we can retrieve cat facts.

Initial setup

{-# LANGUAGE ExistentialQuantification, FlexibleInstances, GADTs,
GeneralizedNewtypeDeriving, KindSignatures, OverloadedStrings, MultiParamTypeClasses,
RankNTypes, TypeApplications, TypeOperators, UndecidableInstances #-}
module CatFacts
    ( main
    ) where
-- from base
import Control.Applicative
import Data.Foldable (traverse_)
import Control.Exception (throwIO)
import Data.Kind (Type)
-- from fused-effects
import Control.Algebra
import Control.Carrier.Reader
import Control.Carrier.Error.Either
import Control.Carrier.Interpret
-- from transformers
import Control.Monad.IO.Class
-- From aeson
import Data.Aeson
-- From bytestring
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy as L
-- From time
import Data.Time.Clock
-- From http-client
import qualified Network.HTTP.Client as HTTP
import Network.HTTP.Client.Internal (Response(..), ResponseClose(..))
-- From http-client-tls
import qualified Network.HTTP.Client.TLS as HTTP
-- From http-status
import Network.HTTP.Types.Header
import Network.HTTP.Types.Status
import Network.HTTP.Types.Version

Since one of the best parts about effects is being able to think at a domain language level, let's start with defining the desired data which we wish to retrieve and an interface that feels natural to work with:

-- | The basic fact that we will retrieve.
newtype CatFact = CatFact
  { catFact :: String
  } deriving (Show)

instance FromJSON CatFact where
  parseJSON = withObject "CatFact" (\o -> CatFact <$> o .: "text")

-- | Our high level effect type that will be able to target different data sources.
data CatFactClient (m :: Type -> Type) k where
  ListFacts :: Int {- ^ Number of facts to fetch -} -> CatFactClient m [CatFact]

listFacts :: Has CatFactClient sig m => Int -> m [CatFact]
listFacts n = send (ListFacts n)

Now that we have our very simple DSL in place, let's think about the underlying API: we know that it's an HTTP-based system, so let's introduce the notion of a handler that is provided a request and hands back an HTTP response.

data Http (m :: Type -> Type) k where
  SendRequest :: HTTP.Request -> Http m (HTTP.Response L.ByteString)

sendRequest :: Has Http sig m => HTTP.Request -> m (HTTP.Response L.ByteString)
sendRequest r = send (SendRequest r)

The listFacts function provides the ‘what’ of this API, and the sendRequest function provides the ‘how’. In decomposing this problem into a set of effects, each responsible for a single layer of the original problem description, we provide ourselves with a flexible, composable vocabulary rather than a single monolithic action.

"Stacking" effects

The production use-case

Now that we have these two mini-DSL effect types established, we need to stitch them together.

Let's take a moment to think about what could go wrong with an HTTP API from which we plan to fetch some JSON and convert it into a list of CatFacts.

We can conceive that the server might occasionally return a malformed JSON response:

newtype JsonParseError = JsonParseError String
  deriving (Show, Eq)

decodeOrThrow :: (Has (Throw JsonParseError) sig m, FromJSON a) => L.ByteString -> m a
decodeOrThrow = either (throwError . JsonParseError) pure . eitherDecode

A more HTTP-centric issue is that we might receive a content type we can't use. In this case, anything that's not application/json:

newtype InvalidContentType = InvalidContentType String
  deriving (Show, Eq)

Now we need to support fetching JSON given an HTTP request. We have no guarantee that an arbitrary HTTP request will actually return JSON, so for this implementation we have to account for failure conditions. This provides a great opportunity to see how effect handlers can actually rely on multiple underlying effects!

newtype CatFactsApi m a = CatFactsApi { runCatFactsApi :: m a }
 deriving
   ( Monad
   , Functor
   , Applicative
   , MonadIO
   , Alternative
   )

catFactsEndpoint :: HTTP.Request
catFactsEndpoint = HTTP.parseRequest_ "https://cat-fact.herokuapp.com/facts/random"

instance ( Has Http sig m
         , Has (Throw JsonParseError) sig m
         , Has (Throw InvalidContentType) sig m
         , Algebra sig m
         ) =>
         Algebra (CatFactClient :+: sig) (CatFactsApi m) where
  alg hdl sig ctx = case sig of
    L (ListFacts numberOfFacts) -> do
      resp <- sendRequest (catFactsEndpoint { HTTP.queryString = "?amount=" <> B.pack (show numberOfFacts) })
      case lookup hContentType (HTTP.responseHeaders resp) of
        Just "application/json; charset=utf-8" -> (<$ ctx) <$> decodeOrThrow (HTTP.responseBody resp)
        other -> throwError (InvalidContentType (show other))
    R other -> CatFactsApi (alg (runCatFactsApi . hdl) other ctx)

We implement a CatFacts effect handler that depends on three underlying effects:

  1. Http - we need to be able to make requests
  2. Throw JsonParseError - we need to be able to signal that some aspect of the JSON wasn't what we expected.
  3. Throw InvalidContentType - we need to be able to signal what we got wasn't JSON at all!

The nice aspect of this is that we have neatly contained the failure scenarios to their relevant strata rather than leaking them into the higher-level abstraction (listFacts)!

Now we need to support performing HTTP requests:

newtype HttpClient m a = HttpClient { runHttp :: m a }
  deriving
    ( Monad
    , Functor
    , Applicative
    , MonadIO
    , Alternative
    )

instance (MonadIO m, Algebra sig m) => Algebra (Http :+: sig) (HttpClient m) where
  alg hdl sig ctx = case sig of
    L (SendRequest req) -> (<$ ctx) <$> liftIO (HTTP.getGlobalManager >>= HTTP.httpLbs req)
    R other -> HttpClient (alg (runHttp . hdl) other ctx)

Note for the above code snippets how the CatFactsApi carrier delegates fetching JSON to any other effect that supports retrieving JSON given an HTTP request specification.

Note as well that CatFactsApi itself doesn't know how to perform an HTTP request. It delegates the request itself to a handler that implements the Algebra class for (Http :+: sig).

Putting it all together for the actual production use case:

handlePrint :: Either InvalidContentType (Either JsonParseError [CatFact]) -> IO ()
handlePrint r =
  case r of
    Left invalidContentTypeError -> print invalidContentTypeError
    Right ok -> case ok of
      Left jsonParseError -> print jsonParseError
      Right facts -> traverse_ (putStrLn . catFact) facts

catFactsRunner :: Has Http sig m => m (Either InvalidContentType (Either JsonParseError [CatFact]))
catFactsRunner =
  runError @InvalidContentType $
  runError @JsonParseError $
  runCatFactsApi $
  listFacts 10

main :: IO ()
main = runHttp catFactsRunner >>= handlePrint

Produces:

The Bengal is the result of crossbreeding between domestic cats and Asian leopard cats, and its name is derived from the scientific name for the Asian leopard cat (Felis bengalensis).
A happy cat holds her tail high and steady.
Kittens remain with their mother till the age of 9 weeks.
Recent studies have shown that cats can see blue and green. There is disagreement as to whether they can see red.
A steady diet of dog food may cause blindness in your cat - it lacks taurine.
Cat owners are 25% likely to pick George Harrison as their favorite Beatle.
The catnip plant contains an oil called hepetalactone which does for cats what marijuana does to some people. Not all cats react to it those that do appear to enter a trancelike state. A positive reaction takes the form of the cat sniffing the catnip, then licking, biting, chewing it, rub & rolling on it repeatedly, purring, meowing & even leaping in the air.
The color of the points in Siamese cats is heat related. Cool areas are darker.
Cats have free-floating clavicle bones that attach their shoulders to their forelimbs, which allows them to squeeze through very small spaces.
Wikipedia has a recording of a cat meowing, because why not?

Testing with alternative effect handlers

Per point 2. of our initial implementation criteria, we want to be able to simulate failure cases for testing purposes. This is a great case for swapping in an alternative effect handler for our HTTP layer.

This time let's go from the bottom up. In situations where IO is involved, failure scenarios tend to surface from least-pure parts of code. In this case, we should therefore implement some facilities to experiment with the most failure-prone area: the network itself.

newtype MockHttpClient m a = MockHttpClient { runMockHttpClient :: ReaderC (HTTP.Request -> IO (HTTP.Response L.ByteString)) m a }
  deriving
   ( Monad
   , Functor
   , Applicative
   , MonadIO
   , Alternative
   )

runMockHttp :: (HTTP.Request -> IO (HTTP.Response L.ByteString)) -> MockHttpC m a -> m a
runMockHttp responder m = runReader responder (runMockHttpClient m)

instance (MonadIO m, Algebra sig m) => Algebra (Http :+: sig) (MockHttpClient m) where
  alg hdl sig ctx = case sig of
    L (SendRequest req) -> do
      responder <- MockHttpClient ask
      (<$ ctx) <$> liftIO (responder req)
    R other -> MockHttpClient (alg (runMockHttpClient . hdl) (R other) ctx)

faultyNetwork :: HTTP.Request -> IO (HTTP.Response L.ByteString)
faultyNetwork req = throwIO (HTTP.HttpExceptionRequest req HTTP.ConnectionTimeout)

wrongContentType :: HTTP.Request -> IO (HTTP.Response L.ByteString)
wrongContentType req = pure resp
  where
    resp = Response
      { responseStatus = ok200
      , responseVersion = http11
      , responseHeaders = [("Content-Type", "text/xml")]
      , responseBody = "[{\"text\": \"Cats are not dogs\"}]"
      , responseCookieJar = mempty
      , responseClose' = ResponseClose (pure ())
      }

badJson :: HTTP.Request -> IO (HTTP.Response L.ByteString)
badJson req = pure Response
  { responseStatus = ok200
  , responseVersion = http11
  , responseHeaders = [("Content-Type", "application/json; charset=utf-8")]
  , responseBody = "{}"
  , responseCookieJar = mempty
  , responseClose' = ResponseClose (pure ())
  }

Let's update our main function and watch it in action:

main :: IO ()
main = do
  -- Should return JsonParseError
  runMockHttp badJson catFactsRunner >>= handlePrint
  -- Should return InvalidContentType
  runMockHttp wrongContentType catFactsRunner >>= handlePrint

Which returns:

JsonParseError "Error in $: parsing [] failed, expected Array, but encountered Object"
InvalidContentType "Just \"text/xml\""

With effects, we have fine-grained ways of testing slices of our API. All that's needed to turn an integration test into a unit test or vice versa is a different set of Algebra-implementing effect handlers!

Observing & altering effects

Building new effect handling algebras can be a little bit verbose. In simpler situations, we may want to simply operate on an effect without having to implement a whole new Algebra instance. We still have yet to build a solution to tracking operational metrics (like request timings), so let's look at how to build a sort of "effect middleware" using InterpretC.

InterpretC is an effect carrier that is intended for prototyping new effects that passes a callback function each occurence of the specified effect type that is called via send. One trick that can be useful is to intercept an effect, operate on the effect, and then re-send the effect (a.k.a. interposition). In other words, it's perfectly valid to have multiple handlers for the same effect type and dispatch to the ones higher in the effect stack! Let's use this approach to time and log our HTTP requests:

traceHttp
  :: (Has Http sig m, MonadIO m)
  => (forall s. Reifies s (Interpreter Http m) => InterpretC s Http m a)
  -> m a
traceHttp = runInterpret $ \ _ r@(SendRequest req) ctx -> do
  startTime <- liftIO getCurrentTime
  liftIO (putStr (B.unpack (HTTP.path req) ++ " ... "))
  -- Pass the request on to something that actually knows how to respond.
  resp <- sendRequest req
  -- Once the actual response is obtained,
  -- we can capture the end time and status of the response.
  endTime <- liftIO getCurrentTime
  let timeSpent = endTime `diffUTCTime` startTime
  liftIO $ putStrLn ("[" ++ show (statusCode $ HTTP.responseStatus resp) ++ "] took " ++ show timeSpent ++ "\n\n")
  pure (resp <$ ctx)

Updating our main function once more:

main :: IO ()
main = runHttp (traceHttp catFactsRunner) >>= handlePrint

Returns:

/facts/random ... [200] took 0.979107082s


Cats have a special scent organ located in the roof of their mouth, called the Jacobson's organ. It analyzes smells - and is the reason why you will sometimes see your cat "sneer" (called the flehmen response or flehming) when they encounter a strong odor.
It's important for cats to have regular ear exams—this is something you can do at home! Gently fold back the ears and look into the ear canal. The inner ear should be pale pink with little to no earwax. If you notice redness, swelling, discharge, or a lot of earwax, it's time to see a veterinarian.
Siamese kittens are born white because of the heat inside the mother's uterus before birth. This heat keeps the kittens' hair from darkening on the points.
Declawing a cat is the same as cutting a human's fingers off at the knuckle. There are several alternatives to a complete declawing, including trimming or a less radical (though more involved) surgery to remove the claws. Instead, train your cat to use a scratching post.
There is a species of cat smaller than the average housecat. It is native to Africa and it is the Black-footed cat (Felis nigripes). Its top weight is 5.5 pounds.
Gatos.
Cats are the most interesting mammals on earth.
Cats have free-floating clavicle bones that attach their shoulders to their forelimbs, which allows them to squeeze through very small spaces.
Fossil records from two million years ago show evidence of jaguars.
Since cats are so good at hiding illness, even a single instance of a symptom should be taken very seriously.

Wrapping up our effect system exploration

Reviewing our initial criteria, we have an eminently extensible system that lets us maintain a healthy separation of concerns– All while still allowing non-invasive behavior changes through the ability to intercept, rewrite, and resend effects!

  • We would like to have our cat facts API be able to support different cat fact data sources in the future.
  • We would like to be able to mock failure conditions (such as network connectivity issues) for testing purposes.
  • We would like to be able to track timing metrics for how quickly we can retrieve cat facts.

Comparison to records of functions

Effect systems in Haskell provide an elegant way to manage and abstract effects in your codebase. However, their effectiveness diminishes when dealing with external libraries that rely on concrete implementations rather than abstract effects.

  1. Limited Influence on External Code: If an external library uses concrete implementation functions directly, the effect system in your code cannot alter or extend the behavior of these functions. The effect system works well within the boundaries of the codebase where it is implemented but has no reach into third-party libraries not designed to interact with it.
  2. Integration Complexity: Integrating external libraries that do not use effect systems can lead to a mismatch in design patterns. This often requires additional wrappers or adapters, complicating the overall system design.
  3. Overhead in Adapting External Libraries: To leverage the benefits of your effect system, you might need to wrap external library functionalities within your own effectful abstractions. This adds an extra layer of complexity and maintenance overhead. When you'd like to use 3rd-party code.

Records of Functions: A More Universal Approach

In contrast, the records of functions approach offers a more universally applicable solution for dealing with both internal and external code.

Flexibility with External Libraries: Since the record of functions approach involves passing around a record containing function implementations, it's easier to extend or modify behaviors of external libraries. You can create a record that matches the external library's API and then pass around modified versions of this record as needed.

Ease of Mocking and Instrumentation: For testing or instrumentation purposes, it's straightforward to substitute parts of the external library's functionality by providing alternative implementations in the record. This is beneficial for cases where you don't control the source code.

Uniformity Across Codebases: Using records of functions promotes a consistent design pattern that can be applied uniformly, irrespective of whether the code is internal or part of an external library. This uniformity simplifies understanding and maintaining the codebase.

Less Intrusive: Unlike effect systems, which require a fundamental adoption of a specific paradigm throughout your codebase, records of functions can be introduced more incrementally and less intrusively.

Conclusion

Adopting a record of functions approach in Haskell library design offers a versatile and powerful way to expose core functionality. It simplifies mocking, allows for dynamic behavior modifications, and makes fault injection and instrumentation more straightforward. As Haskell continues to evolve, embracing such patterns can lead to more robust, flexible, and maintainable codebases.

I guess, at the end of the day, I'm asking you to consider using records of functions in your Haskell libraries– especially if you want there to be enough companies succeeding at using Haskell in production that you can get a job doing it. 😄