Generic traversals with applicative difference lists

Posted on August 5, 2020

The Haskell library generic-data provides generic implementations of standard type classes. One of the goals of generic-data is to generate code which performs (at least) as well as something you would write manually. Even better, we can make sure that the compiled code is identical to what one would obtain from hand-written code, using inspection testing1.

During the exercise of building some inspection tests for generic-data, the most notable discrepancy to resolve was with the Traversable class.

To improve the traversals generated by generic-data, a useful data structure is applicative difference lists (it’s also been called Boggle before). It is a type-indexed variant of difference lists which simplifies applicative operations at compile time. This data structure is available as a library on Hackage: ap-normalize.

Generic traversals

The Traversable type class describes type constructors t which can be “mapped over” similarly to Functor, but using an effectful function a -> f b:

class (Functor t, Foldable t) => Traversable t where
  traverse :: forall f a b. Applicative f => (a -> f b) -> t a -> f (t b)

(We will not discuss the Functor and Foldable super classes.)

Throughout this post, fixing an applicative functor f, actions are what we call values of type f x, to evoke the idea that they are first-class computations.

Intuitively, a traversal walks over a data structure t a which contains “leaves” of type a, and performs some action (given by the a -> f b function) to transform them into “leaves” of type b, producing a new data structure t b.

There is a straightforward recipe to define traverse for many data types. This is best illustrated by a example. We will call this the “naive” definition because it’s just the obvious thing to write if one were to write a traversal. That is not meant to convey that it’s bad in any way.

Figure A
data Example a = Example Int a (Maybe a) (Example a)

-- Omitted: Functor and Foldable instances
instance Traversable Example where
  traverse :: Applicative f => (a -> f b) -> Example a -> f (Example b)
  traverse update (Example a b c d) =
    Example
      <$> pure a
      <*> update b
      <*> traverse update c
      <*> traverse update d
There are variations. (More on that later.)

For the sake of completeness, the recipe is roughly as follows, for a data type with a type parameter a:

  1. traverse each field individually, in one of the following ways depending on its type:

    1. if its type does not depend on a (e.g., Int), then the field is kept intact, and returned purely (using pure);

    2. if its type is equal to a, then we can apply the function a -> f b to it;

    3. if its type is of the form t a, where t is a traversable type we traverse it recursively;

  2. combine the field traversals using the Applicative combinator (<*>).

Noticing that the only case where we need another type to be traversable is to traverse fields whose type depend on a, we can define traverse for all types which don’t involve non-traversable primitive types such as IO or (->).

This is quite formulaic, and it can be automated in many ways. The most practical solution is to use the GHC extension DeriveTraversable (which implies DeriveFunctor and DeriveFoldable):

{-# LANGUAGE DeriveTraversable #-}

data Example a = Example Int a (Maybe a) (Example a)
  deriving (Functor, Foldable, Traversable)

You may be wondering: if it’s built into GHC, why would I bother with generic deriving? There isn’t a substantial difference from a user’s perspective (so you should just use the extension). But from the point of view of implementing a language, deriving instances for a particular type class is a pretty ad hoc feature to include in a language specification. Generic deriving subsumes it, turning that feature into a library that regular people, other than compiler writers, can understand and improve independently from the language itself.

Well, that’s the theory. Generic metaprogramming in Haskell has a ways to go before it can fully replace an integrated solution like DeriveTraversable. The biggest issue currently is that GHC does not perform as much inlining as one might want. A coarse but effective answer to overcome this obstacle might be an annotation to explicitly indicate that some pieces of source code must be gone after compilation.

So the other way to derive traverse that I want to talk about is to use GHC.Generics. generic-data provides a function gtraverse which can be used as the definition of traverse for many types with a Generic1 instance. Although it does not use the deriving keyword2, it is still a form of “deriving” since the syntax of the instance does not depend on the particular shape of Example.

{-# LANGUAGE DeriveGeneric #-}

data Example a = Example Int a (Maybe a) (Example a)
  deriving Generic1

instance Traversable Example where
  traverse = gtraverse

All three instances above behave the same (the naive one, the DeriveTraversable one, and the generic one). However, if we look not only at the behavior but the generated code itself, the optimized GHC Core code produced by the compiler is not the same in all cases. The definition of gtraverse until generic-data version 0.8.3.0 results in code which looks like the following (various details were simplified for clarity’s sake3):

Figure B
traverseExample :: Applicative f => (a -> f b) -> Example a -> f (Example b)
traverssExample update (Example a b c d) =
  (\((K1 a' :*: K1 b') :*: (K1 c' :*: K1 d')) -> Example a' b' c' d')
    <$> ((:*:)
           <$> ((:*:) <$> (K1 <$> pure a)
                      <*> (K1 <$> update b))
           <*> ((:*:) <$> (K1 <$> traverse update c)
                      <*> (K1 <$> traverse update d)))

That function traverses each field (using pure, update, traverse update), wraps them in a newtype K1, and collects them in a pair of pairs (_ :*: _) :*: (_ :*: _), and then replaces those pairs with the Example constructor.

Clearly, this does not look the same as the naive version shown earlier. Let’s enumerate the differences:

This definition cannot actually be simplified because the applicative functor f and its operations (<$>) and (<*>) are abstract, their definitions are not available for inlining. This definition (Figure B) is only equivalent to the naive one (Figure A) if we assume the laws of the Applicative class (notably associativity), but the compiler has no knowledge of those. And so the simplifier is stuck there.

To be fair, it’s actually not so clear that these differences lead to performance problems in practice. Here are some mitigating factors to consider:

  1. For many concrete applicative functors, inlining (<$>) and (<*>) does end up simplifying away all of the noise.

  2. Even if we didn’t build up pairs explicitly using (:*:), (<*>) may allocate closures which are about as costly as pairs anyway.

  3. Tree-like (Free) monads are more performant when associating actions to the right (a <*> (b <*> (c <*> d))).

Nevertheless, it seems valuable to explore alternative implementations. To echo the three points just above:

  1. The new definition of gtraverse will simplify to the naive version even while the applicative functor is still abstract.

  2. Properly measuring the subtle difference between pairs and closures sounds like a pain. Knowing that the code that eventually runs allows one to switch from one system (DeriveTraversable) to another (generic-data) without risk of regressions—modulo all the transient caveats that make this ideal story not true today.

  3. If actions must be associated another way, this is just another library function to be written.

Streamlining traversals with difference lists

The main idea in this solution is that the definition of gtraverse should explicitly reassociate and simplify the traversal.

An obvious approach is thus to represent the syntax of the traversal explicitly, as an algebraic data type where a constructor encodes the applicative combinator (<*>), possibly in a normalized form. This is a free applicative functor:

data Free f a where
  Pure :: a -> Free f a
  Ap :: Free f (b -> a) -> f b -> Free f a

-- This is actually a regular data type, just using GADTSyntax for clarity.

However, this is a recursive structure: that blocks compiler optimizations because GHC does not inline recursive functions (if it did, this could be a viable approach).

Notice that this free applicative functor is basically a list, a heterogeneous list of f b values where b varies from element to element. If recursion is the problem, maybe we should find another representation of lists which is not recursive. As it turns out, difference lists will be the answer.

Difference lists, briefly

Let us digress with a quick recap of difference lists, so we’re on the same page, and as a reference to explain by analogy the fancier version that’s to come.

Here’s a list.

1 : 2 : 3 : []

A difference list is a list with a hole _ in place of its end []. The word “difference” means that it is the result of “subtracting” the end from the list:

1 : 2 : 3 : _

In Haskell, a difference list is represented as a function, whose input is a list to fill the hole with, and whose output is the whole list after adding the difference around the hole. A function “from holes to wholes”.

type DList a = [a] -> [a]

example :: DList Int
example hole = 1 : 2 : 3 : hole

Difference lists are interesting because they are super easy to concatenate: just fill the hole in one difference list with the other list. In Haskell, this is function composition, (.). For instance, the list above is the composition of the two lists below:

ex1, ex2 :: DList Int
ex1 hole = 1 : hole
ex2 hole = 2 : 3 : hole

example = ex1 . ex2

Difference lists are an alternative representation of lists with a performant concatenation operation, which doesn’t allocate any transient intermediate structure. The trade-off is that other list operations are more difficult to have, notably because it’s expensive to inspect the list to know whether it is empty or not.

The following functions complete the picture with a constructor of difference lists and an eliminator into regular list. Internally they involve the list constructors in very simple ways, which is actually key to the purpose of difference lists. singleton is literally the list constructor (:) (thus representing the singleton list [x] as a list with a hole x : []), and toList applies a difference list to the empty list (filling the hole with []).

singleton :: a -> DList a
singleton = (:)

toList :: DList a -> [a]
toList u = u []

Applicative difference lists

Why were we talking about lists? Applicative programming essentially consists in describing lists of actions (values of type f x for some x) separated by (<*>) and terminated (on the left end) by pure _ (we’ll come back later to putting (<$>) back).

pure Example
  <*> pure a
  <*> update b
  <*> traverse update c
  <*> traverse update d

Once we have a notion of lists, a difference list is a list with a hole _ in place of its end:

_
  <*> pure a
  <*> update b
  <*> traverse update c
  <*> traverse update d

So constructing a traversal as a difference list of actions would allow us to maintain this structure of left-associated (<*>). In particular, this will guarantee that there are no extra (<$>) in the middle. Once we’ve completed the list, we top it off with a term pure _, where the remaining hole expects a pure function without any of the applicative functor nonsense which was blocking compile-time evaluation.

Let’s see how it looks in Haskell. This is where things ramp up steeply. While the types may look daunting, I want to show that we can ignore 90% of it to see that, under the hood, this is the same as plain difference lists [a] -> [a].

You’re not missing much from ignoring 90% of the code: it is entirely constrained by the types. That’s the magic of parametricity.

What programming with parametricity feels like
How to draw an owl. Step 1: Draw some circles. Step 2: Draw the rest of the fucking owl.

The analogy with difference lists

The first thing to note is that since we’ve replaced the list constructor (:) with (<*>), actions f x represent both individual list elements a and whole lists [a].

We will draw the analogy between simple difference lists and applicative difference lists by erasure. Erase the type parameter of f, and anything that has something to do with that parameter. What is left is basically the code of DList, carefully replacing f with a or [a] as is appropriate.4

A first example is that (<*>) thus corresponds to both flip (:) and (++) (flip (:) because as we will soon see, we are really building snoc lists here).

-- (<*>) vs (:) and (++)
(<*>)    :: f (x -> y) -> f x -> f y
         :: f          -> f   -> f     -- erased
flip (:) :: [a]        -> a   -> [a]
(++)     :: [a]        -> [a] -> [a]

For another warm-up example, fmap, which acts on the type parameter of f, erases to the identity function.

-- fmap vs id
fmap :: (x -> y) -> f x -> f y
                 :: f   -> f     -- erased
id               :: [a] -> [a]

The applicative difference lists described above are given by the following type ApDList. Similar to simple difference lists, they are also functions “from holes to wholes”, where both “holes” and “wholes” (complete things without holes) are actions in this case, f (x -> r) and f r, if we ignore Yoneda. We will not show the definition of Yoneda, but for the purpose of extending the metaphor with DList, Yoneda f is the same as f:

newtype ApDList f x = ApDList (forall r. Yoneda f (x -> r) -> f r)
   type ApDList f   =         (                 f          -> f  )  -- erased
   type   DList a   =         (                 [a]        -> [a])

Applicative: empty list and concatenation

While simple difference lists define a monoid, applicative difference lists similarly define an applicative functor, with a product (<*>) and an identity pure which indeed erase to the concatenation of difference lists (function composition) and the empty difference list (the identity function).

An important fact about this instance is that it has no constraints whatsoever; the type constructor f can be anything. The lack of constraints restricts the possible constructs used in this instance. It’s all lambdas and applications: that’s how we can tell without even looking at the definitions that pure and (<*>) can only be some flavor of the identity function and function composition.

instance Applicative (ApDList f) where
  pure x = ApDList (\t -> lowerYoneda (fmap ($ x) t))
  ApDList uf <*> ApDList ux = ApDList (\t -> ux (Yoneda (\c -> uf (fmap (\d e -> c (d . e)) t))))

Empty difference lists: erasure of pure, which corresponds to id.

-- pure vs id, signature
pure :: x -> ApDList f x  -- Empty ApDList
id   ::        DList a    -- Empty DList

-- pure vs id, definition
pure x = ApDList (\t -> lowerYoneda (fmap ($ x) t))
id     =         (\t ->                         t )

Where lowerYoneda is also analogous to the identity function.

lowerYoneda :: Yoneda f x -> f x

Concatenation of difference lists: erasure of (<*>), which corresponds to (.).

-- (<*>) vs (.), signature
(<*>) :: ApDList f (x -> y) -> ApDList f x -> ApDList f y  -- Concatenate ApDList
(.)   ::   DList a          ->   DList a   ->   DList a    -- Concatenate   DList

-- (<*>) vs (.), definition
ApDList uf <*> ApDList ux = ApDList (\t -> ux (Yoneda (\c -> uf (fmap (\d e -> c (d . e)) t))))
        uf  .          ux =         (\t -> ux (              uf                           t  ))

Remark: this composition operator is actually flipped. The standard definition goes uf . ux = (\t -> uf (ux t)). This is fine here because applicative lists are actually snoc lists—the reverse of “cons”—where elements are added to the right of lists, so the “holes” of the corresponding difference lists are on the left:

uf = ((_ <*> a) <*> b) <*> c)  -- A snoc list, separated by (<*>)
ux = (_ <*> x) <*> y

uf <*> ux = ((((_ <*> a) <*> b) <*> c) <*> x) <*> y

To concatenate uf and ux, we put uf in the hole on the left end of ux, rather than the other way around; this is why, in the definition above, uf is inside and ux is outside.

Lift and lower: creation and destruction

We have defined concatenation to combine applicative difference lists. We also need ways to construct and eliminate them. We lift elements as singleton lists and lower lists into simple actions.

Lifting creates a new ApDList, with the invariant that it represents a left-associated list of actions separated by (<*>) (the left-associativity is why it needs to be a snoc list). That invariant is preserved by the concatenation operation we defined just earlier. One can easily check that liftApDList is the only function in this little ApDList library (4 functions) where (<*>) from the Applicative f instance is used.

-- Singleton ApDList
liftApDList :: Applicative f => f x -> ApDList f x
listApDList u = ApDList (\t -> lowerYoneda t <*> u)

-- Singleton DList (snoc version)
snocSingleton :: a -> DList a
snocSingleton u = (\t -> t ++ [u])

Lowering consumes an ApDList by filling the hole with an action, producing a whole action. This is the only function about ApDList where pure from Applicative f is used. We use pure to terminate lists of actions in the same way [] terminates regular lists. (This is oversimplified from the real version.)

lowerApDList :: Applicative f => ApDList f x -> f x
lowerApDList (ApDList u) = u (Yoneda (\f -> pure f))

-- By analogy
toList :: DList a -> [a]
toList u = u []

-- lowerApDList vs toList
lowerApDList (ApDList u) = u (Yoneda (\f -> pure f))
                      u  = u         (      pure _)    -- erased
toList                u  = u                []

Simplifying traversals

Having defined difference lists and their basic operations, we can pretend that they are really just lists. Similarly, we can pretend that applicative difference lists ApDList f x are just actions f x, thanks to there being an instance of the same Applicative interface. With that setup, fixing the generic gtraverse function is actually a very small change, that will be explained through an example. We started with this result:

Figure B, again
traverseExample :: Applicative f => (a -> f b) -> Example a -> f (Example b)
traverssExample update (Example a b c d) =
  (\((K1 a' :*: K1 b') :*: (K1 c' :*: K1 d')) -> Example a' b' c' d')
    <$> ((:*:)
           <$> ((:*:) <$> (K1 <$> pure a)
                      <*> (K1 <$> update b))
           <*> ((:*:) <$> (K1 <$> traverse update c)
                      <*> (K1 <$> traverse update d)))

After the patch, we get the following (Figure C), where the only textual difference is that we inserted lowerApDList at the root and liftApDList at the leaves of the traversal. That changes the types of things in the middle from f to ApDList f. In the source code behind gtraverse, this type change appears as a single substitution in one type signature.5

Figure C
traverseExample :: Applicative f => (a -> f b) -> Example a -> f (Example b)
traverssExample update (Example a b c d) =
  lowerApDList $
  (\((K1 a' :*: K1 b') :*: (K1 c' :*: K1 d')) -> Example a' b' c' d')
    <$> ((:*:)
           <$> ((:*:) <$> (K1 <$> pure a)
                      <*> (K1 <$> liftApDList (update b)))
           <*> ((:*:) <$> (K1 <$> liftApDList (traverse update c))
                      <*> (K1 <$> liftApDList (traverse update d))))

Again leveraging parametricity, we don’t need to work out the simplification in detail. Just from looking at the traverseExample definition here and the ApDList library outlined above, we can tell the following:

  1. the resulting term will have three occurrences of (<*>) from Applicative f, since there are three uses of liftApDList;

  2. all Applicative combinators for ApDList (pure, (<*>) and <$>) maintain a list structure as an invariant, so that in the end these three (<*>) will be chained together in the shape of a list;

  3. finally, lowerApDList puts a pure at the end of that list.

Provided everything does get inlined, the resulting term is going to be of this form.

traverseExample :: Applicative f => (a -> f b) -> Example a -> f (Example b)
traverssExample update (Example a b c d) =
  pure _
    <*> update b
    <*> traverse update c
    <*> traverse update d

There is just one remaining unknown, which is the argument of pure.

  1. Whatever it is, it contains only stuff that was between lowerApDList and liftApDList and that was not an ApDList combinator (pure, (<*>), (<$>)), which we expect to have been reduced. That leaves us with a, the constructors (:*:) and K1, and the lambda at the top.

  2. The only constructs allowed to combine those are function applications and lambdas, because the combinators where they could have come from, pure, (<*>), and (<$>), are pure lambda terms.

With the constraint that it must all be well-typed, that doesn’t leave a lot of room. I’d be hard-pressed to find another way to put these together:

\b0 c0 d0 ->
  (\((K1 a' :*: K1 b') :*: (K1 c' :*: K1 d')) -> Example a' b' c' d')
    ((K1 a :*: K1 b0) :*: (K1 c0 :*: K1 d0))

Which beta-reduces to:

\b0 c0 d0 -> Example a b0 c0 d0

-- equal to --

Example a

With all of that, we’ve managed to make gtraverse simplify to roughly the naive definition, using only simplification rules from the pure Core calculus, and no external laws as rewrite rules.

Figure D
traverseExample :: Applicative f => (a -> f b) -> Example a -> f (Example b)
traverssExample update (Example a b c d) =
  pure (Example a)
    <*> update b
    <*> traverse update c
    <*> traverse update d

Loose ends

There are a few more details to discuss, which explain the remaining differences between the naive definition, this latest definition, and what’s actually implemented in the latest version of generic-data (0.9.0.0).

Simplifying pure on the right

The naive version of traverse starts with Example <$> pure a. By an Applicative law, it is equivalent to pure (Example a). The naive version (Figure A) is indeed too naive: for fields of constant types, which don’t depend on the type parameter of the applicative functor f, we can pass them directly as argument to the constructor instead of wrapping them in pure and unwrapping them at run time.

The new version of gtraverse achieves that by not wrapping pure a under liftApDList (Figure C). So this pure does not come from Applicative f, but from Applicative (ApDList f), where it is defined as the identity function (more or less). Notably, this “fusion” happens even if pure is used in the middle of the list, not only at the end.

Simplifying pure on the left

While pure on the right of (<*>) got simplified, there is a remaining pure on the left, which could be turned into (<$>) (Figure D).

Applicative difference lists alone won’t allow us to do that, because all actions are immediately put into arguments of (<*>) by liftApDList. We cannot inspect applicative difference lists and change how the first element is handled, because it is an argument to an abstract (<*>). We can make another construction on top of applicative difference lists to postpone wrapping the first element in a difference list, so we can then use (<$>) instead of (<*>) (and an extra pure) to its left. There is an extra constructor to represent an empty list of actions.

data ApCons f c where
  PureAC :: c -> ApCons f c
  LiftAC :: (a -> b -> c) -> f a -> ApDList f b -> ApCons f c

instance Applicative f => Applicative (ApCons f) where {- ... -}

In fact, we can extend that idea to use another applicative combinator, liftA2 which can do the job of one (<$>) and one (<*>) at the same time. We take off the first two elements of the list, using two extra constructors to represent empty and singleton lists.

data ApCons2 f c where
  PureAC2 :: c -> ApCons2 f c
  FmapAC2 :: (b -> c) -> f b -> ApCons2 f c
  LiftApAC2 :: (a -> b -> c -> d) -> f a -> f b -> ApDList f c -> ApCons2 f d
  -- Encodes   liftA2 _ _ _ <*> _

instance Applicative f => Applicative (ApCons2 f) where {- ... -}

The complete implementation can be found in the library ap-normalize.

Conclusion

We’ve described a generic implementation of traverse which can be simplified to the same Core term as a semi-naively handwritten version, using only pure lambda-calculus transformations—a bit more than beta-reduction, but nothing as dangerous as custom rewrite rules.

The Traversable instances generated using the generic-data library are now identical to instances derived by GHC using the well-oiled DeriveTraversable extension—provided sufficient inlining. This is a small step towards turning anything that has to do with deriving into a generic affair.

Applicative difference lists

The heavy lifting is performed by applicative difference lists, an adaptation of difference lists, from list (really monoids) to applicative functors. This idea is far from new, depending on how you look at it:

Difference lists are well-known as a technique for improving asymptotic (“big-O”) run time; it is less widespread that they can often be optimized away entirely using only inlining and simplification. (I’ve written about this before too.) Inlining and simplification are arguably a lightweight compiler optimization (“peephole optimization” of lambda terms) as opposed to, for instance, custom rewrite rules, which are unsafe, and other transformations that rely on non-trivial program analyses.

While a sufficiently smart compiler could be hypothesized to optimize anything, surely it is more practical to invest in data structures that can be handled by even today’s really dumb compilers.

Types and parametricity

I like expressive static type system. Here, the rich types allow us to give applicative difference lists the interface of an applicative functor, so that the original implementation of gtraverse barely has to change, mostly swapping one implementation of (<*>) for another. As I’ve tried to show here, while the types can appear a little crazy, we can rely on the fact that they must be erased during compilation, so the behavior of the program (what we care about) can still be understood in terms of more elementary structures: if we ignore coercions that have no run-time presence and a few minor details, an applicative difference list is just a difference list

Parametric polymorphism constrains the rest of the implementation; typed holes are a pretty fun way to take advantage of that, but if a program is uniquely constrained, maybe it shouldn’t appear in source code in the first place.

Staged metaprogramming

This technique is a form of staged metaprogramming: we use difference lists as a compile-time structure that should be eliminated by the compiler. This is actually quite similar to Typed Template Haskell,6 where the main difference is that the separation between compile-time and run-time computation is explicit. The advantage of that separation is that it allows arbitrary recursion and IO at compile-time, and there is a strong guarantee that none of it is left at run-time.

However, there are limitations on the expressiveness of Typed Template Haskell: only expressions can be quoted (whereas (Untyped) Template Haskell also has representations for patterns, types, and declarations), and we can’t inspect quoted expressions without giving up types (using unType).

Aside from compile-time IO which is extremely niche anyway, I believe the other advantages have more to do with GHC.Generics being held back by temporary implementation issues than some fundamental limitation of that kind of framework. In contrast, what makes GHC.Generics interesting is that it is minimalist: all it gives us is a Generic instance for each data type, the rest of the language stays the same. No need to quote things if it’s only to unquote them afterwards. Rather, a functional programming language can be its own metalanguage.


P.S.: Abstract nonsense

This is a purely theoretical note for curious readers. You do not need to understand this to understand the rest of the library. You do not need to know category theory to be an expert in Haskell.

ApDList is exactly Curry (Yoneda f) f a, where Curry and Yoneda are defined in the kan-extensions library as:

newtype Curry f g a = Curry (forall r. f (a -> r) -> g r)
newtype Yoneda f a = Yoneda (forall r. (a -> r) -> f r)

Curry is particularly relevant to understand the theoretical connection between applicative difference lists and plain difference lists [a] -> [a] via Cayley’s theorem:

A monoid m is a submonoid of Endo m = (m -> m): there is an injective monoid morphism liftEndo :: m -> Endo m.

(More precisely, lift = (<>).)

Endo m corresponds to difference lists if we take the list monoid m = [a].

This theorem can be generalized to other categories, by generalizing the notion of monoid to monoid objects, and by generalizing the definition of Endo to an exponential object Endo m = Exp(m, m).

As it turns out, applicative functors are monoid objects, and the notion of exponential is given by Curry above.

An applicative functor f is a substructure of Endo f = Curry f f: there is an injective transformation liftEndo :: f a -> Endo f a.

(“Sub-applicative-functor” is a mouthful.)

However if we take that naive definition Endo f = Curry f f, that is different from ApDList (missing a Yoneda), and it is not what we want here. The instance Applicative (Endo f) inserts an undesirable application of (<$>) in its definition of pure.

The mismatch is due to the fact that the syntactic concerns discussed here (all the worrying about where (<$>) and (<*>) get inserted) are not visible at the level of that categorical formalization. Everything is semantic, with no difference between pure f <*> u and f <$> u for instance.

Anyway, if one really wanted to reuse Curry, Curry (Yoneda f) (Yoneda f) should work fine as an alternative definition of ApDList f.

Cayley’s theorem also applies to monads, so these three things are, in a sense, the same:

For more details about that connection, read the paper Notions of computation as monoids, by Exequiel Rivas and Mauro Jaskelioff (JFP 2017).


More about it

On Hackage