Free applicatives, the handle pattern, and remote systems

Jack Kelly profile image Jack Kelly 2025-10-13

We recently refactored some gnarly code that manipulated customer and order records in our enterprise resource planning (ERP) system. That system had a few idiosyncrasies which complicated this task:

  • Creating new records required referencing other entities by internal ID, so we had to do a number of lookups before issuing “create record” requests;
  • For some entity types, we found it easiest to issue “search” API calls and extract the required IDs from the returned search results. This necessitated an extra parsing step between “we have a successful response” and “we have the ID we’re looking for”; and
  • Requests are often slow, but the marginal cost of additional requests in a batch was quite low. This meant that we could expect some good results from batching related requests together.

The benefits of batching led us to seek a solution that permitted static analysis. Applicative functors have a completely static control flow, and cannot express computations where one step depends on the result of a previous step. A well-chosen applicative would let us analyse the requests we need to send without executing any of them, batch queries together without worrying about data dependencies, and then route relevant results to each individual query to parse (if necessary). Our library users could ignore batching details but still gain the efficiency benefits of a batch query API.

In this post, we’ll look how we’ve been using handles, what “free structures” are, how free applicatives elegantly solved some of our problems interfacing with a remote system, and how they interacted especially well with the “handle pattern”.

Handles, as Bellroy uses them

The “handle pattern” is a Haskell idiom that is similar to dependency injection in mainstream languages. Instead of directly writing in the side effects we want our code to perform, we accept a record of functions that we call a “handle”. (In an object-oriented language, we’d probably accept an object that implements an abstract interface instead of a record.) These handles can group related functions into a single record but often only contain one:

newtype Handle e m = Handle {
    performRequest :: ERP.Request -> m (Either e Aeson.Value)
  }

-- Plus some other handle-making functions e.g. for testing.
newHandle ::
  MonadIO m => ERP.Credentials -> m (Handle ERP.Error m)

Functions that consume handles generally look like this:

someFunction ::
  -- When all side effects come from handles,
  -- we rarely need anything stronger than `Monad`.
  Monad m =>
  -- First: Any handles we need
  FooHandle m -> BarHandle m ->
  -- Second: Other "normal" arguments
  Argument1 -> .. -> ArgumentN ->
  m Result

This idiom is a simpler, library-free alternative to effect system libraries like effectful, bluefin, heftia, and polysemy. We previously wrote about an experiment with effectful, but we have still not committed to an effect system. Instead, we are refactoring towards handles as a way to encapsulate our side effects, and because it should be easy to convert handle-using code to an effect system if and when we choose one.

Because we have code written against other idioms (e.g. MTL-style classes), and because we often find it convenient to introduce an ExceptT e or MaybeT monad transformer in the body of our functions, we sometimes need to change the monad of a handle that we’ve been given. We do this by providing a hoistHandle function:

hoistHandle :: (forall x . f x -> g x) -> Handle f -> Handle g
hoistHandle f Handle {performRequest} =
  Handle {performRequest = f . performRequest}

That first argument, forall x . f x -> g x, is worth commenting on. A forall in a type signature explicitly introduces a type variable that is provided by the function’s caller. For a simpler example of how forall works here, let’s look at the map function on lists, but with explicit foralls:

map :: forall a b . (a -> b) -> [a] -> [b]

The caller of map gets to choose the types of a and b, and GHC is often smart enough to figure this out automatically:

-- GHC concludes that it needs to call
-- `map` with `Int` for `a` and `String` for `b`.
ghci> map show [1, 2, 3]
["1","2","3"]

In our hoistHandle function, we let the caller choose f and g, but they must provide us a function where we are allowed to choose x. The types force this function to convert f x into g x in a way that’s blind to what x actually is — guaranteeing that the conversion only changes structure, not wrapped values. It also ensures that we can write hoistHandle for a handle containing multiple functions, because we can choose a different x for each one.

Building our applicative

We want to build a structure that is essentially a syntax tree of the operations we want to perform. This means it needs to hold the requests we want to send, and because we want it to be an applicative, we’ll add constructors to represent pure and (<*>):

data Query a where
  QueryAndParse ::
    FromJSON x =>
    ERP.Request -> (x -> Either Text a) -> Query a

  -- Extra constructors to hold applicative structure
  Pure :: a -> Query a
  Ap :: Query (a -> b) -> Query a -> Query b

deriving stock instance Functor Query

instance Applicative Query where
  pure = Pure

  Pure f <*> Pure x = Pure $ f x
  QueryAndParse req f <*> Pure a =
    QueryAndParse req $ fmap ($ a) . f
  -- Plus another seven cases, being careful that
  -- each case obeys the applicative laws.

The QueryAndParse constructor captures the request we want to make against the ERP. It also holds a FromJSON x constraint so we can parse the raw response into some intermediate type representing an API response, and a function x -> Either Text a to extract just the data we want from that API response.

This could work, but it’s a fair amount of boilerplate, and the next time we want an applicative like this we’d need to repeat most of it. In the next section, we’ll use a free applicative to separate the general “applicative” code from the specific “query and parse” code.

What is a “free structure”?

To understand how free applicatives help us with this problem, we need to have some idea what “freeness” means in this context. The Haskell community usually talks about taking “the free $class over $type” as a way to make $type an instance of $class, by adding just enough structure to construct a lawful instance of $class. Packages like free provide wrapping types that hold values of $type and provide instances of $class.

Let’s pare our Query type back to something much smaller: a type representing a single request against our ERP:

data OneQuery a where
  QueryAndParse ::
    FromJSON x =>
    ERP.Request -> (x -> Either Text a) -> OneQuery a

We will now re-write Query as the free Applicative over OneQuery. To make OneQuery into an Applicative, we’ll use the free Applicative from Control.Applicative.Free. Here is its interface:

-- `Ap f` is the free applicative over `f`. We never use its
-- constructors directly; instead, we use `liftAp` and the
-- `Applicative` interface (`pure`, `(<*>)`, `liftA2`, etc.)
data Ap f a

-- For *any* `f`, `Ap f` is an applicative.
instance Applicative (Ap f)

-- We can turn any `f a` into an `Ap f a`.
liftAp :: f a -> Ap f a

-- If we can turn our `f` into some applicative `g`, then we can turn
-- `Ap f a` into `g a` in a way that respects the Applicative laws:
--
-- runAp _ (pure x) = pure x
-- runAp f (x <*> y) = (runAp f x) <*> (runAp f y)
--
-- Similar to the `forall x. f x -> g x` in `hoistHandle` above,
-- this lets us turn each `f x` stored in the `Ap f a` into a
-- corresponding `g x`, while remaining ignorant of the specific
-- type `x`.
runAp :: Applicative g => (forall x. f x -> g x) -> Ap f a -> g a

We’ll skip the implementations because we won’t ever manually recurse through an Ap f a value; from a modularity perspective, we are only interested in the abstract interface. We declare Query as the free applicative over OneQuery, make it a newtype to establish an abstraction boundary between the query library and its callers, and use deriving newtype to avoid writing any applicative structure ourselves:

newtype Query a = Query (Free.Ap OneQuery a)
  deriving stock Functor
  deriving newtype Applicative

-- Helper functions to avoid building `Query` values by hand.

query ::
  FromJSON a => ERP.Request -> Query a
query _ req =
  Query . Free.liftAp $ QueryAndParse req Right

queryAndParse ::
  FromJSON a => ERP.Request -> (a -> Either Text b) -> Query b
queryAndParse req f =
  Query . Free.liftAp $ QueryAndParse req f

Building a Query

From this infrastructure, we can write functions representing individual queries. These are direct applications of the query and queryAndParse helpers:

queryLocationId ::
  ERP.Location.Name -> Query ERP.Location.Id
queryLocationId locationName =
  query $ ERP.lookupLocation locationName

queryOrderId ::
  ERP.Order.Name -> Query ERP.Order.Id
queryOrderId orderName =
  queryAndParse
    (ERP.searchOrders orderName) $ \case ->
      [order] -> Right order
      (_:_) -> Left "Multiple Orders in response"
      [] -> Left "No Orders in response"

From these functions we can build up complex queries using applicative operations:

queryOrderAndLocation ::
  ERP.Order.Name -> ERP.Location.Name ->
  Query (ERP.Order.Id, ERP.Location.Id)
queryOrderAndLocation orderName locationName =
  liftA2 (,) (queryOrderId orderName) (queryLocationId locationName)

Running a Query

We can run a Query by using runAp. Because we’re in an applicative context and we’re making requests that don’t alter the remote system, we can run every request and use a Validation to collect all failures:

data RunQueryError e = RequestError e | JsonError Text | ParseResultError Text
type RunQueryErrors e = NonEmpty (RunQueryError e)

runQuery :: forall e m a.
  Monad m =>
  ERP.Handle e m ->
  Query a ->
  m (Validation (RunQueryErrors e) a)
runQuery ERP.Handle{performRequest} (Query q) =
  getCompose $ Free.runAp (Compose . go) q
  where
    go :: OneQuery x -> m (Validation (RunQueryErrors e) x)
    go (QueryAndParse req parse) = performRequest req <&> \case
      Left reqErr -> Failure . NonEmpty.singleton $ RequestError reqErr
      Right value -> case Aeson.parseEither Aeson.parseJSON value of
        Left jsonErr -> Failure . NonEmpty.singleton . JsonError $ Text.pack jsonErr
        Right x -> case parse x of
          Left parseErr -> Failure . NonEmpty.singleton $ ParseResultError parseErr
          Right a -> Success a

The implementation can be mostly derived by following the types, but we’ll highlight some specifics:

  • Validation e a is a type that’s structurally isomorphic to Either e a, but provides an Applicative instance that accumulates errors:

    -- From the validation-selective package.
    instance Semigroup e => Applicative (Validation e) where
      pure = Success
    
      -- This asymmetric way of writing <*> maximises laziness.
      Failure e1 <*> b = Failure $ case b of
        Failure e2 -> e1 <> e2
        Success _  -> e1
      Success _ <*> Failure e = Failure e
      Success f <*> Success a = Success (f a)
  • Since the composition of any two applicatives is itself an applicative, Data.Functor.Compose lets us combine the m and Validation e applicatives into Compose m (Validation e), which executes actions in m and accumulates errors — exactly what we want.

  • Since we use the Compose constructor to wrap the result of go, Free.runAp will return a Compose m (Validation e) a which we must unwrap with getCompose.

  • The go function processes a single request held in a OneQuery x, and Free.runAp uses it to build up the applicative combination of each result.

  • We accept a handle telling us how to contact the ERP. This is the key location where the handle pattern and the free applicative interact, giving the library user a lot of power: the handle parameter frees us from being coupled to any particular monad and makes it easier to write tests for this code. We’ll see another way to construct a ERP.Handle very soon.

  • The caller of the Query interface has no idea that we’re building and consuming free structures under the hood. It’s an implementation detail that doesn’t distort the abstraction boundary at all.

Extracting requests

Now that we can execute queries, let’s explore the main benefit of free applicatives: the ability to analyse the applicative program without running it. We can extract a monoidal summary of any free applicative’s structure via runAp_:

runAp_ :: Monoid m => (forall x . f x -> m) -> Ap f a -> m

For an intuition why this is true, consider that the constant functor Const r has an Applicative instance whenever r is a monoid, because pure stores a mempty value and (<*>) combines the held values with (<>). For a fun exercise, implement runAp_ in terms of runAp and Const.

We can use runAp_ to extract a list of every request a Query a will send:

allRequests :: Query a -> [Request]
allRequests (Query q) = ordNub $ Free.runAp_ go q
  where
    go :: OneQuery x -> [Request]
    go (QueryAndParse req _) = [req]

Once we have the list of requests, we can look for ways to optimise them. De-duplicating the requests with ordNub is an easy optimisation, but if the remote API supports it, we could do more advanced optimisations like using a batch request API.

As a simple demonstration, we can perform all the lookup requests in advance and construct a Map Request Aeson.Value:

type SavedRequests = Map Request Aeson.Value

saveRequests ::
  forall e m.
  Monad m =>
  Handle e m -> [Request] -> m (Either e SavedRequests)
saveRequests Handle{performRequest} requests =
  runExceptT $ Map.fromList <$> traverse go requests
  where
    go :: Request -> ExceptT e m (Request, Aeson.Value)
    go req = (req,) <$> ExceptT $ performRequest req

Using a collection of saved results, we can construct a handle that returns the saved responses instead of performing real requests:

newtype UnsavedRequestError = UnsavedRequestError Request

newHandleFromSavedRequests ::
  (Applicative m) => SavedRequests -> Handle UnsavedRequestError m
newHandleFromSavedRequests requests =
  Handle
    { performRequest = \req ->
        pure . maybe (Left (UnsavedRequestError req)) Right $
          Map.lookup req requests
    }

This gives us a great story for testing. Since our runQuery works with any handle, we can capture some real requests to a file, redact any sensitive information, and create a pure handle built from saved requests. We can then use this handle to write test cases that run real code without performing side-effects.

If this example moved too quickly, or you want to see another application of free structures, Justin Le has a spectacular post on matching regular expressions using the free Alternative.

Payoffs and limitations

What have we achieved? We decided that we wanted an applicative to describe queries against our remote system. Instead of inventing a complicated data structure to represent the syntax tree of pure and (<*>) calls, we defined a type just to hold one request and took the free applicative over it. We also used the handle pattern to ask for only the side-effects that we needed. Both patterns are reasonably easy to implement, and in exchange we got some pretty neat benefits that would’ve been harder to realise with either technique alone:

  1. We can analyse a Query without running it, and use the Query to inform the handle we do eventually use;

  2. As a special case of (1), library users can code against a convenient interface and request individual records, but we can inspect the set of queries before we begin execution and issue optimised, parallelised, de-duplicated and batched requests in their place;

  3. We don’t have to abort at the first failed request — we can collect and report every problem with a Query; and

  4. We can record and replay requests, giving us a great testing story in the style of Ruby’s vcr library.

It’s not all roses, though. We lose a significant amount of expressive power by giving up the monadic interface. For APIs where we need to interleave pure queries and side-effecting requests, losing the Monad instance might be a bridge too far. Chris Penner suggests that Selective functors could be closer to the sweet spot, but then you lose the nice ergonomics of -XApplicativeDo. Chris Done identifies an “Applicative-wired Monad” pattern which uses a monad only to plumb together applicative values.

So where does this leave us? The handle pattern has been working well for us and we plan to continue refactoring code to use handles for the foreseeable future. In narrow contexts where we want to take advantage of static analysis, a well-chosen free applicative has given us a surprising amount of modularity, testability and opportunities for automatic optimisation. In the function that “runs” the free applicative, these two idioms interacted in a very satisfying way: the handle parameter gave us a lot of flexibility without asking library users to write a lot of boilerplate.