| CARVIEW |
Distributive Functor is actually Representable”, as the documentation for Representable tells us straight away, and yet it is far from obvious why that should be the case. At first glance, Distributive, the dual to Traversable, appears to have little if anything to do with Representable, the class for functors isomorphic to functions. The goal of this post is making this connection explicit. In the process, we will tease out a fair amount of information about the two classes, and also contemplate what makes it tricky to fully bridge the gap to Representable.
The basic facts
Over the course of this post, the focus will alternate between Distributive and Representable. In this first section, we will review the basic definitions and laws upon which we will build. Following that, we will work on both ends, aiming at making the classes meet in the middle.
Distributive
Let’s begin by jotting down a few basic facts about Distributive. Here is a minimalistic definition of the class:
(In what follows, when used as a placeholder name for a functor, g will always stand for a distributive or representable functor, while f will typically stand for the other functor involved in distribute.)
distribute is dual to sequenceA; accordingly, we will adopt the duals of the Traversable laws: 1
Identity:
Composition:
Naturality (ensured by parametricity):
-- For any natural transformation t -- t :: (Functor f1, Functor f2) => forall x. f1 x -> f2 x fmap t . distribute = distribute . tThis naturality law is stronger than its
Traversablecounterpart. TheApplicativeconstraint insequenceAmeans only natural transformations between applicative functors that preservepureand(<*>)are preserved bydistribute. In contrast,distributeis oblivious to any specifics off1andf2functor, and so any natural transformation will do.
Homogeneous pairs are one example of a distributive functor:
data Duo a = Duo a a
deriving (Eq, Ord, Show, Functor, Foldable, Traversable)
fstDuo, sndDuo :: Duo a -> a
fstDuo (Duo x _) = x
sndDuo (Duo _ y) = y
instance Distributive Duo where
distribute m = Duo (fstDuo <$> m) (sndDuo <$> m)Duo will be used in this post as a running example whenever a concrete illustration of Distributive and adjacent classes is called for. For the moment, here is a simple demonstration of distribute @Duo in action. It illustrates the zip-like flavour of distribute, which is shared by the closely related collect and cotraverse from Data.Distributive:
The function functor is a very important example of Distributive. Consider the following combinator:
It changes a f (r -> a) functorial value into a r -> f a function, which feeds its argument to all of the available r -> a functions. flap is a lawful implementation of distribute:
flap will be used in this post as a synonym for distribute @((->) _) whenever convenient, or necessary to avoid circularity. 2
Representable
As for Representable, for our immediate purposes it suffices to characterise it as a class for functors isomorphic to functions:
class Functor g => Representable g where
type Rep g
tabulate :: (Rep g -> a) -> g a
index :: g a -> Rep g -> aHere, Rep g is some concrete type such that tabulate and index witness an isomorphism between Rep g -> a and g a. Accordingly, the laws are:
Home direction (from
g aand back):Away direction (to
g aand back):
Duo can be given a Representable instance: pick Bool (or any other type with two inhabitants) as Rep g, and associate each possible value with a component of the pair:
instance Representable Duo where
type Rep Duo = Bool
tabulate f = Duo (f False) (f True)
index (Duo x y) = \case
False -> x
True -> yIn order to treat the two classes in an even-handed way, I have opted to leave out the Distributive g => Representable g relationship that exists in the Data.Functor.Rep version of Representable . In any case, every representable is indeed distributive, with a default definition of distribute which uses the isomorphism to delegate to flap (that is, distribute for functions):
distributeRep :: (Representable g, Functor f) => f (g a) -> g (f a)
distributeRep = tabulate . flap . fmap indexThe lawfulness of distributeRep follows from the lawfulness of flap. 3
Our ultimate aim here is to go the other way around, from Distributive to Representable.
No need to choose
If we are to start from Distributive, though, there is a pretty fundamental difficulty: setting up a Representable g instance requires picking a suitable Rep g, and there is nothing in Distributive that could possibly correspond to such a choice. That being so, we will spend some more time contemplating Representable, looking for a way to somehow obviate the need for specifying Rep g.
askRep
Let’s have another look at the type of tabulate:
tabulate is a natural transformation from the function functor ((->) (Rep g) to g. Now, all natural transformations from a function functor have the form: 4
-- For some type R, functor G, and any
t :: forall x. (R -> x) -> G x
-- There is a
w :: G R
-- Such that
t f = f <$> w
w = t idIn words, the natural transformation must amount to mapping the function over some functorial value. In our case, t is tabulate; as for w, we will call it askRep, which is the name it goes by in Data.Functor.Rep. 5. That being so, we have:
The Representable laws can be recast in terms of askRep and index. Here is the home direction of the isomorphism:
That is, we can reconstruct any u :: g a by taking askRep and replacing every Rep g provided by it with the a value that applying index u on it gives us.
It is worth noting that index u <$> askRep = u also tells us that for any u :: g a there is a function (namely, index u) which will change askRep into u through fmap. That largely corresponds to the intuition that a representable functor must have a single shape.
The away direction of the isomorphism becomes:
index . tabulate = id
index (f <$> askRep) = f
-- index is a natural transformation
f <$> index askRep = f
-- fmap @((->) _) = (.)
f . index askRep = f
-- In particular, suppose f = id
-- (note that this step is reversible)
index askRep = idIntuitively, if we think of Rep g values as corresponding to positions in the g shape that can be queried through index, index askRep = id tells us that each and every Rep g will be found in askRep occupying the position it corresponds to. For example, with the Representable instance from the previous section, askRep @Duo looks like this:
Lastly, we can also express distributeRep in terms of askRep:
distributeRep m
tabulate (flap (index <$> m))
flap (index <$> m) <$> askRep
(\r -> (\f -> f r) <$> (index <$> m)) <$> askRep
(\r -> (\u -> index u r) <$> m) <$> askRep
distributeRep m = (\r -> (\u -> index u r) <$> m) <$> askRepThat is, replace every Rep g in askRep with the result of using it to index every g a in m.
Extracting and revealing
Now let’s direct our attention to index:
Flipping index gives us:
fromRep converts a Rep g into what I will call a polymorphic extractor, of type forall a. g a -> a, which gives us a out of g a. The existence of fromRep is quite suggestive. Since forall a. g a -> a doesn’t use Rep g, finding an inverse to fromRep, and thus showing those two types are isomorphic, might give us a way to work with Representable without relying on Rep g.
How might we go about converting a polymorphic extractor into a Rep g value? To do it in a non-trivial way , we will need a g (Rep g) source of Rep g on which we can use the extractor. Considering the discussion in the previous subsection, askRep looks like a reasonable option:
Now let’s check if fromRep and toRep are indeed inverses, beginning with the toRep . fromRep direction:
toRep . fromRep
(\p -> p askRep) . (\r -> \u -> index u r)
\r -> (\u -> index u r) askRep
\r -> index askRep r
-- index askRep = id
idWe can proceed similarly with fromRep . toRep:
To simplify this further, we can note that a polymorphic extractor forall x. g x -> x amounts to natural transformation from g to Identity. That being so, we have, for any extractor p and any f:
The above is the usual naturality property, fmap f . p = p . fmap f, except that, to account for the omission of the Identity newtype boilerplate, fmap @Identity has been replaced on the left-hand side by plain function application. We can now carry on:
\p -> \u -> index u (p askRep)
\p -> \u -> p (index u <$> askRep)
-- index u <$> askRep = u
\p -> \u -> p u
idAnd there it is: for any Representable, Rep g must be isomorphic to forall x. g x -> x. That being so, we can use forall x. g x -> x as a default Rep g that can be specified in terms of g alone. The change of perspective can be made clearer by setting up an alternative class:
type Pos g = forall x. g x -> x
elide :: g a -> Pos g -> a
elide u = \p -> p u
class Functor g => Revealable g where
reveal :: (Pos g -> a) -> g a
chart :: g (Pos g)
reveal e = e <$> chart
chart = reveal id
{-# MINIMAL reveal | chart #-}Both the arrangement of those definitions and my idiosyncratic choice of names call for some explanation:
Pos gis a synonym for the type of polymorphic extractors. The namePosis short for “position”, and is meant to allude to the intuition that an extractor picks a value from some specific position in ag-shaped structure.elidecorresponds toindex, defined in such a way thatfromRep = id. Since all it does is applying aPos gextractor, on its own it doesn’t require any constraints ong. The choice of name is motivated by howelidehides thegshape, in that that the only information aboutu :: g athat can be recovered fromelide uare theavalues that aPos gextractor can reach.reveal, in turn, corresponds totabulate, and is the inverse ofelide. IfgisRepresentable, thegshape can be reconstituted with no additional information, and so it is possible to undo the hiding performed byelide.chartcorresponds toaskRep, with it andrevealbeing interdefinable. In particular,chartcan be used to reveal theg athat corresponds to aPos g -> afunction by providing the means to reach every position in thegshape. 6
Here is the Duo instance of Revealable. Note how each position in chart holds its own extractor:
distribute can be implemented for Revealable in a way completely analogous to how it was done for Representable:
distributeRev :: (Revealable g, Functor f) => f (g a) -> g (f a)
distributeRev = reveal . flap . fmap elideOr, in terms of chart:
That is, distributeRev m amounts to mapping every extractor in chart over m.
As for the laws, just like we were able to choose between expressing the Representable isomorphism directly, via tabulate, or indirectly via askRep, here we can use either reveal or chart:
reveal . elide = id
-- Or, equivalently
elide u <$> chart = u
elide . reveal = id
-- Or, equivalently
p chart = pWith Revealable, though, we can streamline things by showing p chart = p follows from elide u <$> chart = u. The proof relies on the naturality of the polymorphic extractors:
elide u <$> chart = u
-- Apply some p :: Pos g to both sides
p (elide u <$> chart) = p u
-- p is natural
elide u (p chart) = p u
-- elide u p = p u
(p chart) u = p u
-- u is arbitrary
p chart = pThat being so, elide u <$> chart = u is the only law we need to characterise Revealable. Since elide does not depend on the Revealable instance, we might as well inline its definition, which leaves us with:
I suggest calling it the law of extractors: it tells us that the extractors provided by chart suffice to reconstitute an arbitrary g a value.
Revisiting Distributive
In Revealable, we have a class equivalent to Representable which doesn’t rely on the Rep type family. That makes it feasible to continue our investigation by attempting to show that every Distributive functor is Revealable.
Natural wonders
Naturality laws and parametricity properties not infrequently have interesting consequences that seem to us as hidden in plain sight. Considering the increased strength of Distributive’s naturality law relative to its Traversable counterpart and the important role naturality properties had in setting up Revealable, resuming our work on Distributive from the naturality law sounds like a reasonable bet:
-- For any natural transformation t
-- t :: (Functor f1, Functor f2) => forall x. f1 x -> f2 x
fmap t . distribute = distribute . tIn particular, suppose f1 is a function functor:
Now, by the same argument used back when we defined askRep, t must have the form:
Therefore:
In particular, suppose f = id. We then end up with an specification of distribute in terms of distribute id:
distribute id has the following type:
This looks a lot like something that holds extractors, and the specification itself mirrors the definition of distributeRev in terms of chart. As a preliminary check, distribute @Duo id holds fstDuo and sndDuo on their respective positions, exactly like chart @Duo:
Given the clear resemblance, I will optimistically refer to distribute id as chartDist:
We therefore have:
Now suppose m = Identity u for some u :: g a, and invoke the identity law:
distribute (Identity u) = (\p -> p <$> Identity u) <$> chartDist
distribute (Identity u) = (\p -> Identity (p u)) <$> chartDist
runIdentity <$> distribute (Identity u)
= runIdentity <$> ((\p ->Identity (p u)) <$> chartDist)
runIdentity <$> distribute (Identity u)
= (\p -> runIdentity (Identity (p u))) <$> chartDist
runIdentity <$> distribute (Identity u)
= (\p -> p u) <$> chartDist
-- By the identity law
runIdentity (Identity u) = (\p -> p u) <$> chartDist
u = (\p -> p u) <$> chartDistWe therefore have a Distributive version of the law of extractors, with chartDist playing the role of chart. It is also possible to turn things around and obtain the identity law from this law of extractors:
(\p -> p u) <$> chartDist = u
runIdentity . Identity . (\p -> p u) <$> chartDist = u
runIdentity . (\p -> Identity (p u)) <$> chartDist = u
runIdentity . (\p -> p <$> Identity u) <$> chartDist = u
-- distribute m = (\p -> p <$> m) <$> chartDist
runIdentity <$> distribute (Identity u) = u
runIdentity <$> distribute (Identity u) = runIdentity (Identity u)
fmap runIdentity . distribute = runIdentityThese are auspicious results. Given that the law of extractors is enough to establish an implementation of chart as lawful, and that there can’t be multiple distinct lawful implementations of distribute 7, all we need to do is to identify chartDist with chart.
The roadblock, and a detour
Identifying chartDist with chart, however, is not trivial. As similar as chart and chartDist might feel like, their types differ in an insurmountable way:
In particular:
The
ainforall a. G (G a -> a)can be directly specialised to a concrete choice ofa, and, as far as the specialised typeG (G A -> A)is concerned, it is conceivable that the involvedG A -> Afunctions might not be natural inA.Accordingly, a rank-2 function that takes a
Pos G, such as the argument toreveal, can be mapped overchart, but notchartDist.There is no way to obtain the impredicative type of
chart, or the rank-3 type ofreveal, throughdistribute.
To put it in another way, chartDist doesn’t have a type strong enough to, on its own, ensure that it provides natural, polymorphic extractors, and Distributive is not enough to implement a chart which provides such guarantees.
Still, not all is lost. If there is a way to use the laws of Distributive to show that the extractors of chartDist are natural, we should be able to claim chart and chartDist are morally the same, providing the same extractors with subtly different types.
(Meta note: while I believe the following argument suffices for the task at hand, it is not as crystalline as the derivations elsewhere in this post. Upgrading it to a proper proof will probably require some tricky parametricity maneuver which I haven’t managed to fully figure out yet.)
Let’s turn to the composition law, the one we haven’t touched so far:
That is, given some m :: Compose fo fi (g a) (“o” is for outer, and “i” for inner):
Let’s use distribute m = (\p -> p <$> m) <$> chartDist on the left-hand side, and on the outer distribute on the right-hand side:
getCompose <$> ((\p -> p <$> m) <$> chartDist)
= (\q -> q <$> (distribute <$> getCompose m)) <$> chartDistNote that the left-hand side chartDist has type g (g a -> a), while the right-hand side one has type g (g (fi a) -> fi a). Since we can’t take for granted that the extractors provided by them (which are bound to p and q, respectively) are natural, it is important to keep track of this difference.
Tidying the equation a little further, we get:
getCompose <$> ((\p -> p <$> m) <$> chartDist)
= (\q -> q <$> (distribute <$> getCompose m)) <$> chartDist
(\p -> getCompose (p <$> m)) <$> chartDist
= (\q -> q . distribute <$> getCompose m) <$> chartDist
(\p -> fmap p <$> getCompose m) <$> chartDist
= (\q -> q . distribute <$> getCompose m) <$> chartDistOn either side of the equation, we have fmap being used to obtain a g (fo (fi a)) result. That being so, any fo (fi a) value that, thanks to fmap, shows up in the left-hand side must also show up in the right-hand side. More precisely, given any p :: g a -> a drawn from chartDist on the left-hand side, there must be some q :: g (fi a) -> fi a drawn from the chartDist on the right hand side such that…
… and vice versa. That allows us to reason about p and q, which amount to the extractors drawn from chartDist we are interested in.
As neither p nor q involve fo, and the equation must hold for all choices of fo, we can freely consider the case in which it is Identity, or anything else that has an injective fmap. If fmap is injective, the equation further simplifies to:
Now, fmap p :: fi (g a) -> fi a cannot affect the fi shape; therefore, the same holds for q . distribute :: fi (g a) -> fi a. distribute :: fi (g a) -> g (fi a) is natural in fi, and so it, too, can’t affect the fi shape. It follows that q :: g (fi a) -> fi a is also unable to affect the fi shape.
Zooming back out, we have just established that, if the composition law holds, chartDist :: g (g (fi a) -> fi a) only provides extractors that preserve the fi shape. chartDist, however, is defined as distribute id :: forall b. g (g b -> b), which is fully polymorphic on the element type b. That being so, if there is a way for distribute id to somehow produce non-natural extractors, it cannot possibly rely in any way about the specifics of b. That, in particular, rules out any means of, given b ~ fi a for some functor fi, producing just non-natural extractors that preserve the fi shape: such a distinction cannot be expressed. We must conclude, therefore, that if the composition law holds chartDist can only provide natural extractors, as we hoped to show.
The converse of this conclusion, by the way, also holds: assuming the identity law holds, if all q drawn from chartDist are natural, the composition law must hold. To show that, we can use the fact that, for a natural q :: forall x. g x -> x, q chartDist = q holds, just like it does for chart:
(\p -> p u) <$> chartDist = u
q ((\p -> p u) <$> chartDist)) = q u
-- Since q is natural, q . fmap f = f . q
(\p -> p u) (q chartDist) = q u
(q chartDist) u = q u
q chartDist = qAs a consequence, q . distribute = fmap q:
q (distribute m)
q ((\p -> p <$> m) <$> chartDist)
-- q is natural
(\p -> p <$> m) (q chartDist)
(\p -> p <$> m) q
q <$> mWe can now return to the rearranged version of the composition law we were dealing with in the preceding argument, this time without taking it for granted:
(\p -> fmap p <$> getCompose m) <$> chartDist
= (\q -> q . distribute <$> getCompose m) <$> chartDistBy the above, however, if q is natural the right-hand side amounts to…
… which is the same as the left-hand side.
In summary
After quite a long ride, we have managed to shed some light on the connection between Distributive and Representable:
Every
Distributiveis indeedRepresentable, even though, as expected,Representablecannot be implemented in terms ofdistribute.The connection is mediated by choosing
forall x. g x -> x, the type of polymorphic extractors, as a default representation, encoded here as theRevealableclass. It can then be shown that this representation is mirrored inDistributivebychartDist = distribute id :: Distributive g => g (g a -> a), which gives a corresponding characterisation ofDistributivein terms of extractors.The single-shapedness characteristic of both distributive and representable functors follows from the identity law of
Distributive.The composition law plays an important, if unobvious, role in the connection, as it ensures the naturality of the extractors provided by
chartDist, a property that can’t be established on the basis of the involved types.
The Select loophole
There is one aspect of our investigation that is worth a closer look. All the concern with establishing that chartDist can only provide natural extractors, which kept us busy for a good chunk of the previous section, might have felt surprising. chartDist, after all…
… is fully polymorphic in a, and therefore its definition cannot rely on anything specific about a. That being so, it may seem outlandish to suppose that specialising chartDist to, say, g (g Integer -> Integer) might somehow bring forth non-natural g Integer -> Integer extractors that perform Integer-specific operations.
To illustrate why the naturality of extractors is, in fact, a relevant issue, let’s consider the curious case of Select:
-- A paraphrased, non-transformer version of Select.
newtype Select r a = Select { runSelect :: (a -> r) -> a }
instance Functor (Select r) where
fmap f u = Select $ \k -> f (u `runSelect` \a -> k (f a))(A Select r a value can be thought of as a way to choose an a value based on some user-specified criterion, expressed as an a -> r function.)
Corner cases such as r ~ () aside, Select r cannot be Representable, as that would require it to be isomorphic to a function functor; that being so, it should be similarly ill-suited for Distributive. In spite of that, there is a nontrivial implementation of a Select r combinator with the type chartDist would have: 8
chartSelect :: Select r (Select r a -> a)
chartSelect = Select $ \k -> \u -> u `runSelect` \a -> k (const a)What’s more, chartSelect follows the law of extractors:
-- Goal:
(\p -> p u) <$> chartSelect = u
-- LHS
(\p -> p u) <$> chartSelect
(\p -> p u) <$> Select $ \k -> \u -> u `runSelect` \a -> k (const a)
Select $ \k' ->
(\p -> p u) (\u -> u `runSelect` \a -> k' ((\p -> p u) (const a)))
Select $ \k' -> u `runSelect` \a -> k' ((\p -> p u) (const a))
Select $ \k' -> u `runSelect` \a -> k' (const a u)
Select $ \k' -> u `runSelect` \a -> k' a
u -- LHS = RHSThat means the distribute candidate we get out of chartSelect…
nonDistribute :: Functor f => f (Select r a) -> Select r (f a)
nonDistribute m = Select $
\k -> (\u -> u `runSelect` \a -> k (a <$ m)) <$> m… follows the identity law. As Select r is not supposed to be Distributive, we expect nonDistribute to break the composition law, and that is indeed what happens. 9
Now, by the earlier arguments about the naturality of extractors, if a candidate implementation of chartDist follows the extractors law and only provides natural extractors, the corresponding distribute must follow the composition law. Since chartSelect follows the extractors law but doesn’t give rise to a lawful distribute, we must conclude that it provides non-natural extractors. How does that come to pass?
Every criterion function k :: a -> r gives rise to a non-natural extractor for Select r a, namely \u -> u `runSelect` k :: Select a r -> a. chartSelect indirectly makes all these non-natural extractors available through its own criterion argument, the k that shows up in its definition. (How the encoding works can be seen in the verification above of the law of extractors: note how performing the fmap between the third and fourth lines of the proof requires replacing k :: (Select r a -> a) -> r with k' :: a -> r.)
Non-naturality sneaking into chartSelect has to do with Select r not being a strictly positive functor; that is, it has an occurrence of the element type variable, a, to the left of a function arrow. 10 The lack of strict positivity creates a loophole, through which things can be incorporated to a Select r a value without being specified. It is a plausible conjecture that the composition law of Distributive is a way of ruling out functors that aren’t strictly positive, with lack of strict positivity being the only possible source of non-naturality in chartDist, and any non-trivial lack of strict positivity leading to non-naturality and the composition law being broken. 11
Further reading
There are other interesting ways of approaching Distributive and Representable that I haven’t covered here to avoid making this post longer than it already is. Here are a few suggestions for further reading:
Chris Penner’s Adjunctions and Battleship post is a fine introduction to
Adjunction, the class for Hask-Hask adjunctions, which provides an alternative encoding ofRepresentable.The following Stack Overflow answers by Conor McBride on Naperian functors, “Naperian” here being an alternative name for
Representable:Which Haskell Functors are equivalent to the Reader functor, which introduces Naperian functors in a style reminiscent of the
askRep-centric formuation ofRepresentablediscussed here.Writing cojoin or cobind for n-dimensional grid type, which includes an outline of how Naperian functors are handled by container theory.
On a final note, there is a reworking of Representable being developed as part of a potential future release of the distributive package. It aims at unifying the presentations of distributive into a single class that fits equally well the various use cases. An overview of how this new formulation could be a nice topic for a future, follow-up post.
The
Data.Distributivedocumentation, as of the version 0.6.2.1 of the distributive package, mentions a different set of properties in lieu of these laws, the crucial one beingdistribute . distribute = id. Though that is a viable approach, I feel that in the context of what this post aims at such a formulation raises more questions than they answer. (For instance, regardingdistribute . distribute = id: Are there twoDistributiveinstances involved? If so, how are we supposed to check that an individual instance is lawful? Does that law correspond to anything fromTraversable?) That being so, I have chosen to take a step back and regard the “dual toTraversable” formulation as the starting point.↩︎The name
flap, which I have borrowed from relude, is a play on howdistribute @((->) _) @((->) _)turns out to beflip.↩︎Here is a proof of its lawfulness:
↩︎-- Goal (identity law): fmap runIdentity . distributeRep = runIdentity fmap runIdentity . distributeRep -- LHS fmap runIdentity . tabulate . flap . fmap index -- tabulate is natural tabulate . fmap runIdentity . flap . fmap index -- flap follows the identity law tabulate . runIdentity . fmap index tabulate . index . runIdentity -- tabulate . index = id runIdentity -- LHS = RHS -- Goal (composition law): fmap getCompose . distributeRep = distributeRep . fmap distributeRep . getCompose distributeRep . fmap distributeRep . getCompose -- RHS tabulate . flap . fmap index . fmap tabulate . fmap flap . fmap (fmap index) . getCompose -- index . tabulate = id tabulate . flap . fmap flap . fmap (fmap index) . getCompose tabulate . flap . fmap flap . getCompose . fmap index -- flap follows the composition law tabulate . fmap getCompose . flap . fmap index -- tabulate is natural fmap getCompose . tabulate . flap . fmap index fmap getCompose . distributeRep -- RHS = LHSThat is a manifestation of the Yoneda lemma. For a Haskell-oriented introduction to it, see Dan Piponi’s Reverse Engineering Machines with the Yoneda Lemma.↩︎
askRepis indeedaskforMonadReader (Rep g) g; accordingly,tabulateisasks/reader.↩︎On a technical note, given that the type of
chartamounts tog (forall x. g x -> x)using these definitions as written requires theImpredicativeTypesextension and, ideally, GHC 9.2 or above. Doing it withoutImpredicativeTypeswould require makingPos ganewtypeinstead of a mere synonym.↩︎In brief: two implementations of
distribute :: f (g a) -> g (f a)might differ by what they do to theavalues,fshapes, orgshapes. Naturality meansaandfcan’t be affected bydistribute, and so any difference would have to arise from what is done tog. However, the identity law means thegshape can’t be affected either. Therefore, implementations which follow the identity law can’t differ.↩︎I originally realised it is possible through a Stack Overflow answer by Sergei Winitzki. I thank him for helping to drive this post to completion, as thinking about
Selectwas instrumental in putting the pieces together.↩︎Sparing the very messy full proof, the gist of it has to do with the
(<$)tricknonDistributeuses to borrow the shape ofmin order to have something to feed thek :: f a -> rcriterion. In the left-hand side of the composition law,fmap getCompose . distribute, the trick is applied once, at the outermost level, while in the right-hand side,distribute . fmap distribute. getCompose, thanks to thefmap distributeit is also done inside of the outer layer. That being so, there is no way the two sides might be equal.↩︎Though it doesn’t explicitly mention strict positivity, Michael Snoyman’s Covariance and Contravariance is an useful primer on polarity, production and consumption in functors. In particular, the
CallbackRunnerexample in the “Positive and negative position” section towards the end is aFunctorthat isn’t strictly positive.↩︎On a tangential note, the lack of strict positivity also breaks down the intuitive notion of the shape, as something that can be distinguished from the
avalues contained or produced by some functorial valuef a. WhilechartSelectabiding by the law of extractors suggests that we should think ofSelect ras single-shaped, it is hard to even tell what a shape is supposed to be in this case. IfSelect r awere a garden-variety function type, we might say that there is onearesult for every possiblea -> rcriterion. However, the number of possiblea -> rfunctions also depends on the choice ofa. As a result, the number of inhabitants (that is, distinct possible values) ofSelect r agrows much faster than linearly with the number of inhabitants ofa. Were we to saySelect ris a single-shaped functor, we would have to concede the shape is is bigger on the inside.↩︎
Post licensed under a
Creative Commons Attribution-ShareAlike 4.0 International License.
Divisible type class. The conversation pointed to an interesting rabbit hole, and jumping into it resulted in these notes, in which I attempt to get a clearer view of picture of the constellation of monoidal functor classes that Divisible belongs to. The gist of it is that “Divisible is a contravariant Applicative, and Decidable is a contravariant Alternative” is not a full picture of the relationships between the classes, as there are a few extra connections that aren’t obvious to the naked eye.
Besides Gabriella’s post, which is an excellent introduction to Divisible, I recommend as background reading Tom Ellis’ Alternatives convert products to sums, which conveys the core intuition about monoidal functor classes in an accessible manner. There is a second post by Tom, The Mysterious Incomposability of Decidable, that this article will be in constant dialogue with, in particular as a source of examples. From now on I will refer to it as “the Decidable post”. Thanks to Gabriella and Tom for inspiring the writing of this article.
For those of you reading with GHCi on the side, the key general definitions in this post are available from this .hs file.
Applicative
As I hinted at the introduction, this post is not solely about Divisible, but more broadly about monoidal functor classes. To start from familiar ground and set up a reference point, I will first look at the best known of those classes, Applicative. We won’t, however, stick with the usual presentation of Applicative in terms of (<*>), as it doesn’t generalise to the other classes we’re interested in. Instead, we will switch to the monoidal presentation: 1
zipped :: Applicative f => f a -> f b -> f (a, b)
zipped = liftA2 (,)
-- An operator spelling, for convenience.
(&*&) :: Applicative f => f a -> f b -> f (a, b)
(&*&) = zipped
infixr 5 &*&
unit :: Applicative f => f ()
unit = pure ()
-- Laws:
-- unit &*& v ~ v
-- u &*& unit ~ u
-- (u &*& v) &*& w ~ u &*& (v &*& w)(Purely for the sake of consistency, I will try to stick to the Data.Functor.Contravariant.Divisible naming conventions for functions like zipped.)
The matter with (<*>) (and also liftA2) that stops it from being generalised for our purposes is that it leans heavily on the fact that Hask is a Cartesian closed category, with pairs as the relevant product. Without that, the currying and the partial application we rely on when writing in applicative style become unfeasible.
While keeping ourselves away from (<*>) and liftA2, we can recover, if not the full flexibility, the power of applicative style with a variant of liftA2 that takes an uncurried function:
(That is admittedly a weird name; all the clashing naming conventions around this topic has left me with few good options.)
On a closing note for this section, my choice of operator for zipped is motivated by the similarity with (&&&) from Control.Arrow:
In particular, (&*&) for the function Applicative coincides with (&&&) for the function Arrow.
Leaning on connections like this one, I will use Control.Arrow combinators liberally, beginning with the definition of the following two convenience functions that will show up shortly:
Divisible
As summarised at the beginning of the Decidable post, while Applicative converts products to products covariantly, Divisible converts products to products contravariantly. From that point of view, I will take divided, the counterpart to zipped, as the fundamental combinator of the class:
-- This is the divided operator featured on Gabriella's post, soon to
-- become available from Data.Functor.Contravariant.Divisible
(>*<) :: Divisible k => k a -> k b -> k (a, b)
(>*<) = divided
infixr 5 >*<
-- Laws:
-- conquered >*< v ~ v
-- u >*< conquered ~ u
-- (u >*< v) >*< w ~ u >*< (v >*< w)Recovering divide from divided is straightforward, and entirely analogous to how lizip can be obtained from zipped:
Lessened currying aside, we might say that divide plays the role of liftA2 in Divisible.
It’s about time for an example. For that, I will borrow the one from Gabriella’s post:
data Point = Point { x :: Double, y :: Double, z :: Double }
deriving Show
nonNegative :: Predicate Double
nonNegative = Predicate (0 <=)
-- (>$<) = contramap
nonNegativeOctant :: Predicate Point
nonNegativeOctant =
adapt >$< nonNegative >*< nonNegative >*< nonNegative
where
adapt = x &&& y &&& zThe slight distortion to Gabriella’s style in using (&&&) to write adapt pointfree is meant to emphasise how that deconstructor can be cleanly assembled out of the component projection functions x, y and z. Importantly, that holds in general: pair-producing functions a -> (b, c) are isomorphic (a -> b, a -> c) pairs of projections. That gives us a variant of divide that takes the projections separately:
tdivide :: Divisible k => (a -> b) -> (a -> c) -> k b -> k c -> k a
tdivide f g u v = divide (f &&& g) u vBesides offering an extra option with respect to ergonomics, tdivide hints at extra structure available from the Divisible class. Let’s play with the definitions a little:
tdivide f g u v
divide (f &&& g) u v
contramap (f &&& g) (divided u v)
contramap ((f *** g) . dup) (divided u v)
(contramap dup . contramap (f *** g)) (divided u v)
contramap dup (divided (contramap f u) (contramap g v))
divide dup (contramap f u) (contramap g v)divide dup, which duplicates input in order to feed each of its arguments, is a combinator worthy of a name, or even two:
dplus :: Divisible k => k a -> k a -> k a
dplus = divide dup
(>+<) :: Divisible k => k a -> k a -> k a
(>+<) = dplus
infixr 5 >+<So we have:
Or, using the operators:
An alternative to using the projections to set up a deconstructor to be used with divide is to contramap each projection to its corresponding divisible value and combine the pieces with (>+<). That is the style favoured by Tom Ellis, 2 which is why I have added a “t” prefix to tdivide comes from. For instance, Gabriella Gonzalez’s example would be spelled as follows in this style:
nonNegativeOctantT :: Predicate Point
nonNegativeOctantT =
x >$< nonNegative >+< y >$< nonNegative >+< z >$< nonNegativeAlternative
The (>+<) combinator defined above is strikingly similar to (<|>) from Alternative, down to its implied monoidal nature: 3
It is surprising that (>+<) springs forth in Divisible rather than Decidable, which might look like the more obvious candidate to be Alternative’s contravariant counterpart. To understand what is going on, it helps to look at Alternative from the same perspective we have used here for Applicative and Divisible. For that, first of all we need an analogue to divided. Let’s borrow the definition from Applicatives convert products to sums:
combined :: Alternative f => f a -> f b -> f (Either a b)
combined u v = Left <$> u <|> Right <$> v
(-|-) :: Alternative f => f a -> f b -> f (Either a b)
(-|-) = combined
infixr 5 -|-
-- We also need a suitable identity:
zero :: Alternative f => f Void
zero = empty
-- Laws:
-- zero -|- v ~ v
-- u -|- zero ~ u
-- (u -|- v) -|- w ~ u -|- (v -|- w)(I won’t entertain the various controversies about the Alternative laws here, nor any interaction laws involving Applicative. Those might be interesting matters to think about from this vantage point, though.)
A divide analogue follows:
combine :: Alternative f => (Either a b -> c) -> f a -> f b -> f c
combine f u v = fmap f (combined u v)Crucially, Either a b -> c can be split in a way dual to what we have seen earlier with a -> (b, c): an Either-consuming function amounts to a pair of functions, one to deal with each component. That being so, we can use the alternative style trick done for Divisible by dualising things:
tcombine :: Alternative f => (a -> c) -> (b -> c) -> f a -> f b -> f c
tcombine f g = combine (f ||| g)tcombine f g u v
combine (f ||| g) u v
fmap (f ||| g) (combined u v)
fmap (forget . (f +++ g)) (combined u v)
fmap forget (combined (fmap f u) (fmap g v))
combine forget (fmap f u) (fmap g v)To keep things symmetrical, let’s define:
So that we end up with:
For instance, here is the Alternative composition example from the Decidable post…
alternativeCompose :: [String]
alternativeCompose = show <$> [1,2] <|> reverse <$> ["hello", "world"]… and how it might be rendered using combine/(-|-):
alternativeComposeG :: [String]
alternativeComposeG = merge <$> [1,2] -|- ["hello", "world"]
where
merge = show ||| reverseThere is, therefore, something of a subterranean connection between Alternative and Divisible. The function arguments to both combine and divide, whose types are dual to each other, can be split in a way that not only reveals an underlying monoidal operation, (<|>) and (>+<) respectively, but also allows for a certain flexibility in using the class combinators.
Decidable
Last, but not least, there is Decidable to deal with. Data.Functor.Contravariant.Divisible already provides chosen as the divided analogue, so let’s just supply the and operator variant: 4
(|-|) :: Decidable k => k a -> k b -> k (Either a b)
(|-|) = chosen
infixr 5 |-|
-- Laws:
-- lost |-| v ~ v
-- u |-| lost ~ u
-- (u |-| v) |-| w ~ u |-| (v |-| w)choose can be recovered from chosen in the usual way:
choose :: Decidable k => (a -> Either b c) -> k b -> k c -> k a
choose f u v = contamap f (chosen u v)The a -> Either b c argument of choose, however, is not amenable to the function splitting trick we have used for divide and combine. Either-producing functions cannot be decomposed in that manner, as the case analysis to decide whether to return Left or Right cannot be disentangled. This is ultimately what Tom’s complaint about the “mysterious incomposability” of Decidable is about. Below is a paraphrased version of the Decidable example from the Decidable post:
data Foo = Bar String | Baz Bool | Quux Int
deriving Show
pString :: Predicate String
pString = Predicate (const False)
pBool :: Predicate Bool
pBool = Predicate id
pInt :: Predicate Int
pInt = Predicate (>= 0)
decidableCompose :: Predicate Foo
decidableCompose = analyse >$< pString |-| pBool |-| pInt
where
analyse = \case
Bar s -> Left s
Baz b -> Right (Left b)
Quux n -> Right (Right n)The problem identified in the post is that there is no straightfoward way around having to write “the explicit unpacking into an Either” performed by analyse. In the Divisible and Alternative examples, it was possible to avoid tuple or Either shuffling by decomposing the counterparts to analyse, but that is not possible here. 5
In the last few paragraphs, we have mentioned Divisible, Alternative and Decidable. What about Applicative, though? The Applicative example from the Decidable post is written in the usual applicative style:
applicativeCompose :: [[String]]
applicativeCompose =
f <$> [1, 2] <*> [True, False] <*> ["hello", "world"]
where
f = (\a b c -> replicate a (if b then c else "False"))As noted earlier, though, applicative style is a fortunate consequence of Hask being Cartesian closed, which makes it possible to turn (a, b) -> c into a -> b -> c. If we leave out (<*>) and restrict ourselves to (&*&), we end up having to deal explicitly with tuples, which is a dual version of the Decidable issue:
monoidalCompose :: [[String]]
monoidalCompose =
consume <$> [1, 2] &*& [True, False] &*& ["hello", "world"]
where
consume (a, (b, c)) = replicate a (if b then c else "False")Just like a -> Either b c functions, (a, b) -> c functions cannot be decomposed: the c value can be produced by using the a and b components in arbitrary ways, and there is no easy way to disentangle that.
Decidable, then, relates to Applicative in an analogous way to how Divisible does to Alternative. There are a few other similarities between them that are worth pointing out:
Neither
ApplicativenorDecidableoffer a monoidalf a -> f a -> f aoperation like the ones ofAlternativeandDecidable. A related observation is that, for example,Op’sDecidableinstance inherits aMonoidconstraint fromDivisiblebut doesn’t actually use it in the method implementations.choose Leftandchoose Rightcan be used to combine consumers so that one of them doesn’t actually receive input. That is analogous to how(<*) = lizip fstand(*>) = lizip sndcombine applicative values while discarding the output from one of them.Dually to how
zipped/&*&for the function functor is(&&&),chosenfor decidables such asOpandPredicateamounts to(|||). My choice of|-|as the corresponding operator hints at that.
In summary
To wrap things up, here is a visual summary of the parallels between the four classes:

Applicative and Decidable in one diagonal, and Alternative and Divisible in the other.To my eyes, the main takeaway of our figure of eight trip around this diagram has to do with its diagonals. Thanks to a peculiar kind of duality, classes in opposite corners of it are similar to each other in quite a few ways. In particular, the orange diagonal classes, Alternative and Divisible, have monoidal operations of f a -> f a -> f a signature that emerge from their monoidal functor structure.
That Divisible, from this perspective, appears to have more to do with Alternative than with Applicative leaves us a question to ponder: what does that mean for the relationship between Divisible and Decidable? The current class hierarchy, with Decidable being a subclass of Divisible, mirrors the Alternative-Applicative relationship on the other side of the covariant-contravariant divide. That, however, is not the only reasonable arrangement, and possibly not even the most natural one. 6
Appendixes
dplus is a monoidal operation
If we are to show that (>+<) is a monoidal operation, first of all we need an identity for it. conquer :: f a sounds like a reasonable candidate. It can be expressed in terms of conquered, the unit for divided, as follows:
The identity laws do come out all right:
conquer >+< v = v -- Goal
conquer >+< v -- LHS
dup >$< (conquer >*< v)
dup >$< ((const () >$< conquered) >*< v)
dup >$< (first (const ()) >$< (conquered >*< v))
first (const ()) . dup >$< (conquered >*< v)
-- conquered >*< v ~ v
first (const ()) . dup >$< (snd >$< v)
snd . first (const ()) . dup >$< v
v -- LHS = RHS
u >+< conquer = u -- Goal
u >+< conquer -- LHS
dup >$< (u >*< discard)
dup >$< (u >*< (const () >$< conquered))
dup >$< (second (const ()) >$< (u >*< conquered))
second (const ()) . dup >$< (u >*< conquered)
-- u >*< conquered ~ u
second (const ()) . dup >$< (fst >$< u)
fst . second (const ()) . dup >$< u
u -- LHS = RHSAnd so does the associativity one:
(u >+< v) >+< w = u >+< (v >+< w) -- Goal
(u >+< v) >+< w -- LHS
dup >$< ((dup >$< (u >*< v)) >*< w)
dup >$< (first dup >$< ((u >*< v) >*< w))
first dup . dup >$< ((u >*< v) >*< w)
u >+< (v >+< w) -- RHS
dup >$< (u >*< (dup >$< (v >*< w)))
dup >$< (second dup >$< (u >*< (v >*< w)))
second dup . dup >$< (u >*< (v >*< w))
-- (u >*< v) >*< w ~ u >*< (v >*< w)
-- assoc ((x, y), z) = (x, (y, z))
second dup . dup >$< (assoc >$< ((u >*< v) >*< w))
assoc . second dup . dup >$< ((u >*< v) >*< w)
first dup . dup >$< ((u >*< v) >*< w) -- LHS = RHSHandling nested Either
The examples in this appendix are available as a separate .hs file.
There is a certain awkwardness in dealing with nested Either as anonymous sums that is hard to get rid of completely. Prisms are a tool worth looking into in this context, as they are largely about expressing pattern matching in a composable way. Let’s bring lens into Tom’s Decidable example, then:
A cute trick with prisms is using outside to fill in the missing cases of a partial function (in this case, (^?! _Quux):
anonSum :: APrism' s a -> (s -> b) -> s -> Either a b
anonSum p cases = set (outside p) Left (Right . cases)
decidableOutside :: Predicate Foo
decidableOutside = analyse >$< pString |-| pBool |-| pInt
where
analyse = _Bar `anonSum` (_Baz `anonSum` (^?! _Quux))An alternative is using matching to write it in a more self-explanatory way:
matchingL :: APrism' s a -> s -> Either a s
matchingL p = view swapped . matching p
decidableMatching :: Predicate Foo
decidableMatching =
choose (matchingL _Bar) pString $
choose (matchingL _Baz) pBool $
choose (matchingL _Quux) pInt $
error "Missing case in decidableMatching"These implementations have a few inconveniences of their own, the main one perhaps being that there is noting to stop us from forgetting one of the prisms. The combinators from the total package improve on that by incorporating exhaustiveness checking for prisms, at the cost of requiring the sum type to be defined in a particular way.
There presumably also is the option of brining in heavy machinery, and setting up an anonymous sum wrangler with Template Haskell or generics. In fact, it appears the shapely-data package used to offer precisely that. It might be worth it to take a moment to make it build with recent GHCs.
All in all, these approaches feel like attempts to approximate extra language support for juggling sum types. As it happens, though, there is a corner of the language which does provide extra support: arrow notation. Converting the example to arrows provides a glimpse of what might be:
-- I'm going to play nice, rather than making b phantom and writing a
-- blatantly unlawful Arrow instance just for the sake of the notation.
newtype Pipecate a b = Pipecate { getPipecate :: a -> (Bool, b) }
instance Category Pipecate where
id = Pipecate (True,)
Pipecate q . Pipecate p = Pipecate $ \x ->
let (bx, y) = p x
(by, z) = q y
in (bx && by, z)
instance Arrow Pipecate where
arr f = Pipecate (const True &&& f)
first (Pipecate p) = Pipecate $ \(x, o) ->
let (bx, y) = p x
in (bx, (y, o))
instance ArrowChoice Pipecate where
left (Pipecate p) = Pipecate $ \case
Left x ->
let (bx, y) = p x
in (bx, Left y)
Right o -> (True, Right o)
fromPred :: Predicate a -> Pipecate a ()
fromPred (Predicate p) = Pipecate (p &&& const ())
toPred :: Pipecate a x -> Predicate a
toPred (Pipecate p) = Predicate (fst . p)
decidableArrowised :: Predicate Foo
decidableArrowised = toPred $ proc foo -> case foo of
Bar s -> fromPred pString -< s
Baz b -> fromPred pBool -< b
Quux n -> fromPred pInt -< ndecidableArrowised corresponds quite closely to the various Decidable-powered implementations. Behind the scenes, case commands in arrow notation give rise to nested eithers. Said eithers are dealt with by the arrows, which are combined in an appropriate way with (|||). (|||), in turn, can be seen as an arrow counterpart to chosen/(|-|). Even the -< “feed” syntax, which the example above doesn’t really take advantage of, amounts to slots for contramapping. If someone ever feels like arranging a do-esque noation for Decidable to go with Gabriella’s DivisibleFrom, it seems case commands would be a nice starting point.
See the relevant section of the Typeclassopedia for a brief explanation of it.↩︎
See, for instance, this Twitter conversation, or the
Divisibleexample in the Decidable post. Note that, though I’m using(>$<)here for ease of comparison, the examples in this style arguably look tidier when spelled withcontramap.Speaking of operator usage, it is not straightforward to decide on the right fixities for all those operators, and it is entirely possible that I have overlooked something. I have picked them aiming to have both styles work without parentheses, and to have the pairs associated to the right, that is:
↩︎adapt >$< u >*< v >*< w = adapt >$< (u >*< (v >*< w)) f >$< u >+< g >$< v >+< h >$< v = (f >$< u) >+< (g >$< v) >+< (h >$< w)A proof that
(>+<)is indeed monoidal is in an end note to this post.On a related note, my choice of
>+<as thedplusoperator is, in part, a pun on(<+>)fromArrowPlus.(>+<)for many instances works very much like(<+>), monoidally combining outputs, even if there probably isn’t a sensible way to actually make the types underlying the variousDivisiblefunctors instances ofArrowPlus.↩︎Both dhall and co-log-core define
(>|<)aschosen-like operators. To my eyes, though,>|<fitsdplusbetter. As a compromise, I opted to not use>|<for neither of them here.↩︎I will play with a couple of approaches to nested
Eitherergonomics at the end of the post, in an appendix.↩︎See also contravariant issue #64, which suggests no longer making
Decidablea subclass ofDivisible. Though the argument made by Zemyla is a different one, there are resonances with the observations made here. On a related development, semigroupoids has recently introduced aConcludeclass, which amounts to “Decidablewithout a superclass constraint onDivisible”.↩︎
Post licensed under a
Creative Commons Attribution-ShareAlike 4.0 International License.
Maybe and IO, respectively (contrast Just 3 *> Just 3 with print 3 *> print 3). More precisely, idempotency means that f <$> u <*> u = (\x -> f x x) <$> u. Given the informal description I began with, though, one might wonder whether the simpler property u *> u = u, which seems to capture the intuition about repeated effects, is equivalent to the usual idempotency property. In this post, I will tell how I went about exploring this conjecture, as well as a few things I learnt about parametricity along the way.
Before I begin, a few remarks about this notion of idempotency. The earliest mention of it that I know of is in Combining Monads, a paper by King and Wadler 1. There, idempotent monads are presented alongside the most widely known concept of commutative monads (f <$> u <*> v = flip f <$> v <*> u). Both properties generalise straightforwardly to applicative functors, which has the neat side-effect of allowing myself to skirt the ambiguity of the phrase “idempotent monad” (in category theory, that usually means a monad that, in Haskell parlance, has a join that is an isomorphism – a meaning that mostly doesn’t show up in Haskell). Lastly, I knew of the conjecture about idempotency amounting to u *> u = u through a Stack Overflow comment by David Feuer, and so I thank him for inspiring this post.
Prolegomena
Given we are looking into a general claim about applicatives, our first port of call are the applicative laws. Since the laws written in terms of (<*>) can be rather clunky to wield, I will switch to the monoidal presentation of Applicative:
-- fzip and unit correspond to (<*>) and pure, respectively.
fzip :: Applicative f => (f a, f b) -> f (a, b)
fzip (u, v) = (,) <$> u <*> v
unit :: Applicative f => f ()
unit = pure ()Note I am using an uncurried version of fzip, as I feel it makes what follows slightly easier to explain. I will also introduce a couple teensy little combinators so that the required tuple shuffling becomes easier on the eye:
app :: (a -> b, a) -> b
app (f, x) = f x
dup :: a -> (a, a)
dup x = (x, x)
{-
I will also use the Bifunctor methods for pairs, which amount to:
bimap f g (x, y) = (f x, g y)
first f = bimap f id
second g = bimap id g
-}
--The converse definitions of pure and (<*>) in terms of unit and fzip would be:
Using that vocabulary, the applicative laws become:
-- "~" here means "the same up to a relevant isomorphism"
fzip (u, unit) ~ u -- up to pairing with ()
fzip (unit, u) ~ u -- up to pairing with ()
fzip (fzip (u, v), w) ~ fzip (u, fzip (v, w)) -- up to reassociating pairsAs for the idempotency property, it can be expressed as:
(*>) and its sibling (<*) become:
(Proofs of the claims just above can be found at the appendix at the end of this post.)
Finally, the conjecture amounts to:
That fzip (u, u) = dup <$> u implies snd <$> fzip (u, u) is immediate, as snd . dup = id. Our goal, then, is getting fzip (u, u) = dup <$> u out of snd <$> fzip (u, u) = u.
Drawing relations
How might we get from snd <$> fzip (u, u) = u to fzip (u, u) = dup <$> u? It appears we have to take a fact about the second components of the pairs in fzip (u, u) (note that mapping snd discards the first components) and squeeze something about the first components out of it (namely, that they are equal to the second components everywhere). At first glance, it doesn’t appear the applicative laws connect the components in any obviously exploitable way. The one glimmer of hope lies in how, in the associativity law…
… whatever values originally belonging to v must show up as second components of pairs on the left hand side, and as first components on the right hand side. While that, on its own, is too vague to be actionable, there is a seemingly innocuous observation we can make use of: snd <$> fzip (u, u) = u tells us we can turn fzip (u, u) into u using fmap (informally, we can say that they have the same shape), and that they can be related using snd while making use of a free theorem 2. For our current purposes, that means we can borrow the types involved in the left side of the associativity law and use them to draw the following diagram…
fzip
(F (a, b), F c) --------> F ((a, b), c)
| | | |
| | | |
snd| |id snd| |id
| | | |
v v v v
(F b, F c ) --------> F ( b, c)
fzip
… such that we get the same result by following either path from the top left corner to the bottom right one. Omitting the occurrences of id, we can state that through this equation:
In words, it doesn’t matter whether we use snd after or before using fzip. fmap and first, left implicit in the diagram, are used to lift snd across the applicative layer and the pairs, respectively. This is just one specific instance of the free theorem; instead of snd and id, we could have any functions – or, more generally, any relations 3– between the involved types. Free theorems tell us about relations being preserved; in this case, snd sets up a relation on the left side of the diagram, and fzip preserves it.
We can get back to our problem by slipping in suitable concrete values in the equation. For an arbitrary u :: F A, we have…
… and, thanks to our snd <$> fzip (u, u) = u premise:
Now, why should we restrict ourselves to the left side of the associativity law? We can get a very similar diagram to work with from the right side:
fzip
(F a, F (b, c)) --------> F (a, (b, c))
| | | |
| | | |
id| |snd id| |snd
| | | |
v v v v
(F a, F c ) --------> F (a, c )
fzip
Or, as an equation:
Proceeding just like before, we get:
second snd <$> fzip (u, fzip (u, u)) = fzip (u, snd <$> fzip (u, u))
second snd <$> fzip (u, fzip (u, u)) = fzip (u, u)Since fzip (u, fzip (u, u)) ~ fzip (fzip (u, u), u) (associativity), we can shuffle that into:
-- Both first fst and second snd get rid of the value in the middle.
first fst <$> fzip (fzip (u, u), u) = fzip (u, u)The equations we squeezed out of the diagrams…
… can be combined into:
This kind of looks like idempotency, except for the extra occurrence of u tagging along for the ride. We might have a go at getting rid of it by sketching a diagram of a slightly different nature, which shows how the relations play out across the specific values that appear in the equation above:
fzip
(u, u) :: (F a , F a) -----------> F ( a , a)
| | | |
| | | |
R| S| {dup}| {id}|
| | | |
| | fzip | |
(fzip (u, u), u) :: (F (a, a), F a) -----------> F ((a, a), a)
dup can be used to relate fzip (u, u) and fzip (fzip (u, u), u) on the right of the diagram. That this diagram involves specific values leads to a subtle yet crucial difference from the previous ones: the relation on the right side is not necessarily the function dup, but some relation that happens to agree with dup for the specific values we happen to be using here (that is what I have attempted to suggest by adding the curly brackets as ad hoc notation and dropping the arrow tips from the vertical connectors). This is important because, given how fzip preserves relations, we might be tempted to work backwards and identify R on the left side with dup, giving us a proof – dup <$> u = fzip (u, u) would be an immediate consequence. We can’t do that, though, as R only must agree with dup for those values which show up in a relevant way on the right side. More explicitly, consider some element x :: a of u. If x shows up as a first component anywhere in fzip (u, u), then the corresponding element of fzip (u, u) must have its first and second components equal to each other (because dup agrees with R on x, and R in turn relates u and fzip (u, u)), and to x (since snd <$> fzip (u, u) = u). If that held for all elements of u, we would have fzip (u, u) = dup <$> u. However if x doesn’t show up as a first component in fzip (u, u), there are no guarantees (as the right side offers no evidence on what x is related to through R), and so we don’t have grounds for the ultimate claim.
Close, but no cigar.
Something twisted
While those parametricity tricks gave us no proof, we did learn something interesting: the conjecture holds as long as all elements from u show up as first components in fzip (u, u). That sounds like a decent lead for a counterexample, so let’s switch course and look for one instead. To begin with, here is an inoffensive length-two vector/homogeneous pair type:
Here is its Applicative instance, specified in terms of the monoidal presentation:
Good, like any other applicative with a single shape, is idempotent – as there is just one shape, it can’t help but be preserved 4. That means we need a second constructor:
unit can remain the same…
… which means the Good-and-Good case must remain the same: the identity effect has to be idempotent 5:
fzip (Good x1 x2, Good y1 y2) = Good (x1, y1) (x2, y2)
fzip (Evil x1 x2, Evil y1 y2) = _
fzip (Evil x1 x2, Good y1 y2) = _
fzip (Good x1 x2, Evil y1 y2) = _The twist comes in the Evil-and-Evil case: we repeat our pick of a first element of the vector, and thus discard one of the first elements. (We can’t do the same with the second element, as we want snd <$> fzip (u, u) = u to hold.)
fzip (Good x1 x2, Good y1 y2) = Good (x1, y1) (x2, y2)
fzip (Evil x1 x2, Evil y1 y2) = Evil (x1, y1) (x1, y2)
fzip (Evil x1 x2, Good y1 y2) = _
fzip (Good x1 x2, Evil y1 y2) = _The Evil-and-Good case is determined by the right identity law…
fzip (Good x1 x2, Good y1 y2) = Good (x1, y1) (x2, y2)
fzip (Evil x1 x2, Evil y1 y2) = Evil (x1, y2) (x2, y2)
fzip (Evil x1 x2, Good y1 y2) = Evil (x1, y1) (x2, y2)
fzip (Good x1 x2, Evil y1 y2) = _… while associativity forces our hand in the Good-and-Evil case (consider what would happen in a Good-Evil-Evil chain 6):
fzip (Good x1 x2, Good y1 y2) = Good (x1, y1) (x2, y2)
fzip (Evil x1 x2, Evil y1 y2) = Evil (x1, y1) (x1, y2)
fzip (Evil x1 x2, Good y1 y2) = Evil (x1, y1) (x2, y2)
fzip (Good x1 x2, Evil y1 y2) = Evil (x1, y1) (x1, y2)Evil spreads, leaving a trail of repeated picks of first elements to the left of its rightmost occurrence in an applicative chain.
Getting an actual Applicative instance from those definitions is easy: fill unit with something, and take away the commas from fzip:
instance Applicative Twisted where
pure x = Good x x
Good x1 x2 <*> Good y1 y2 = Good (x1 y1) (x2 y2)
Evil x1 x2 <*> Evil y1 y2 = Evil (x1 y1) (x1 y2)
Evil x1 x2 <*> Good y1 y2 = Evil (x1 y1) (x2 y2)
Good x1 x2 <*> Evil y1 y2 = Evil (x1 y1) (x1 y2) And there it is:
GHCi> test = Evil 1 2
GHCi> test *> test
Evil 1 2
GHCi> dup <$> test
Evil (1,1) (2,2)
GHCi> fzip (test, test)
Evil (1,1) (1,2)
GHCi> (\x -> x + x) <$> test
Evil 2 4
GHCi> (+) <$> test <*> test
Evil 2 3The conjecture is thus refuted. While parametricity isn’t truly necessary to bring out this counterexample, I am far from sure I would have thought of it without having explored it under the light of parametricity. On another note, it is rather interesting that there are biased applicatives like Twisted. I wonder whether less contrived cases can be found out there in the wild.
Appendix
Below are some derivations that might distract from the main thrust of the post.
Alternative presentation of the idempotency property
One direction of the equivalency between the two formulations of the idempotency property follows from a straightforward substitution…
… while the other one calls for a small dose of parametricity:
fzip (u, u) = dup <$> u
first f <$> fzip (u, u) = first f <$> dup <$> u
-- g <$> f <$> u = g . f <$> u
first f <$> fzip (u, u) = (\x -> (f x, x)) <$> u
-- Parametricity: first f <$> fzip (u, v) = fzip (f <$> u, v)
fzip (f <$> u, u) = (\x -> (f x, x)) <$> u
app <$> fzip (f <$> u, u) = app <$> (\x -> (f x, x)) <$> u
f <$> u <*> u = (\x -> f x x) <$> uAlternative definitions of (<*) and (*>)
Starting from…
… we can switch to the monoidal presentation:
It follows from parametricity that…
-- Parametricity: first f <$> fzip (u, v) = fzip (f <$> u, v)
u <* v = app . first const <$> fzip (u, v)
u *> v = app . first (flip const) <$> fzip (u, v)… which amount to…
u <* v = (\(x, y) -> const x y) <$> fzip (u, v)
u *> v = (\(x, y) -> flip const x y) <$> fzip (u, v)… or simply:
Lawfulness of Twisted as an applicative functor
Right identity:
fzip (u, unit) ~ u
-- Case: u = Good x1 x2
fzip (Good x1 x2, Good () ()) -- LHS
Good (x1, ()) (x2, ()) -- LHS ~ RHS
-- Note that Twisted behaves like an ordinary length-two vector as
-- long as only Good is involved. That being so, it would have been
-- fine to skip the Good-only cases here and elsewhere.
-- Case: u = Evil x1 x2
fzip (Evil x1 x2, Good () ()) -- LHS
Evil (x1, ()) (x2, ()) -- LHS ~ RHSLeft identity:
fzip (unit, u) ~ u
-- Case: u = Good x1 x2
fzip (Good () (), Good y1 y2)
Evil ((), y1) ((), y2) -- LHS ~ RHS
-- Case: u = Evil x1 x2
fzip (Good () (), Evil y1 y2)
Evil ((), y1) ((), y2) -- LHS ~ RHSAssociativity:
fzip (fzip (u, v), w) ~ fzip (u, fzip (v, w))
-- Good/Good/Good case: holds.
fzip (fzip (Good x1 x2, Good y1 y2), Good z1, z2) -- LHS
fzip (Good (x1, y1) (x2, y2), Good z1, z2)
Good ((x1, y1), z1) ((x2, y2), z2)
fzip (Good x1 x2, fzip (Good y1 y2, Good z1 z2)) -- RHS
fzip (Good x1 x2, Good (y1, z1) (y2, z2))
Good (x1, (y1, z1)) (x2, (y2, z2)) -- LHS ~ RHS
-- Evil/Evil/Evil case:
fzip (fzip (Evil x1 x2, Evil y1 y2), Evil z1, z2) -- LHS
fzip (Evil (x1, y1) (x1, y2), Evil z1, z2)
Evil ((x1, y1), z1) ((x1, y1), z2)
fzip (Evil x1 x2, fzip (Evil y1 y2, Evil z1 z2)) -- RHS
fzip (Evil x1 x2, Evil (y1, z1) (y1, z2))
Evil (x1, (y1, z1)) (x1, (y1, z2)) -- LHS ~ RHS
-- Good/Evil/Evil case:
fzip (fzip (Good x1 x2, Evil y1 y2), Evil z1, z2) -- LHS
fzip (Good (x1, y1) (x2, y2), Evil z1, z2)
Evil ((x1, y1), z1) ((x1, y1), z2)
fzip (Good x1 x2, fzip (Evil y1 y2, Evil z1 z2)) -- RHS
fzip (Good x1 x2, Evil (y1, z1) (y1, z2))
Evil (x1, (y1, z1)) (x1, (y1, z2)) -- LHS ~ RHS
-- Evil/Good/Evil case:
fzip (fzip (Evil x1 x2, Good y1 y2), Evil z1, z2) -- LHS
fzip (Evil (x1, y1) (x2, y2), Evil z1, z2)
Evil ((x1, y1), z1) ((x1, y1), z2)
fzip (Evil x1 x2, fzip (Good y1 y2, Evil z1 z2)) -- RHS
fzip (Evil x1 x2, Evil (y1, z1) (y1, z2))
Evil (x1, (y1, z1)) (x1, (y1, z2)) -- LHS ~ RHS
-- Evil/Evil/Good case:
fzip (fzip (Evil x1 x2, Evil y1 y2), Good z1, z2) -- LHS
fzip (Evil (x1, y1) (x1, y2), Good z1, z2)
Evil ((x1, y1), z1) ((x1, y2), z2)
fzip (Evil x1 x2, fzip (Evil y1 y2, Good z1 z2)) -- RHS
fzip (Evil x1 x2, Evil (y1, z1) (y2, z2))
Evil (x1, (y1, z1)) (x1, (y2, z2)) -- LHS ~ RHS
-- Evil/Good/Good case:
fzip (fzip (Evil x1 x2, Good y1 y2), Good z1, z2) -- LHS
fzip (Evil (x1, y1) (x2, y2), Good z1, z2)
Evil ((x1, y1), z1) ((x2, y2), z2)
fzip (Evil x1 x2, fzip (Good y1 y2, Good z1 z2)) -- RHS
fzip (Evil x1 x2, Good (y1, z1) (y2, z2))
Evil (x1, (y1, z1)) (x2, (y2, z2)) -- LHS ~ RHS
-- Good/Evil/Good case:
fzip (fzip (Good x1 x2, Evil y1 y2), Good z1, z2) -- LHS
fzip (Evil (x1, y1) (x1, y2), Good z1, z2)
Evil ((x1, y1), z1) ((x1, y2), z2)
fzip (Good x1 x2, fzip (Evil y1 y2, Good z1 z2)) -- RHS
fzip (Good x1 x2, Evil (y1, z1) (y2, z2))
Evil (x1, (y1, z1)) (x1, (y2, z2)) -- LHS ~ RHS
-- Good/Good/Evil case:
fzip (fzip (Good x1 x2, Good y1 y2), Evil z1, z2) -- LHS
fzip (Good (x1, y1) (x2, y2), Evil z1, z2)
Evil ((x1, y1), z1) ((x1, y1), z2)
fzip (Good x1 x2, fzip (Good y1 y2, Evil z1 z2)) -- RHS
fzip (Good x1 x2, Evil (y1, z1) (y1, z2))
Evil (x1, (y1, z1)) (x1, (y1, z2)) -- LHS ~ RHSFor a gentle initial illustration of the underlying theme of parametricity, see What Does fmap Preserve?. For a more thorough introduction, see Parametricity: Money for Nothing and Theorems for Free, by Bartosz Milewski.↩︎
A relation is a set of pairs; or, if you will, of associations between values. As an arbitrary example, we can have a less-than relation on integers which includes all pairs of integers
(x, y)such thatx < y. In particular, functions are relations: seen as a relation, a functionfseen in this way includes all pairs(x, f x), there being exactly one pair for each possible value of the first component.↩︎One way to prove that is by using parametricity in tandem with the identity laws, analogously to how we used associativity in the previous section, while exploiting how there being only one shape means any applicative value can be related to
unit.↩︎See the previous note about relating things to
unit.↩︎The appendix includes a proof of the lawfulness of
Twisted.↩︎
Post licensed under a
Creative Commons Attribution-ShareAlike 4.0 International License.
Traversable is a fun type class. It lies at a crossroad, where many basic Haskell concepts meet, and it can be presented in multiple ways that provide complementary intuitions. In this post, Traversable will be described from a slightly unusual point of view, or at least one that is not put into foreground all that often. We will suspend for a moment the picture of walking across a container while using an effectful function, and instead start by considering what can be done with effectful functions.
Weird fishes
Let’s begin with a familiar sight:
There are quite a few overlapping ways of talking about functions with such a type. If F is a Functor, we can say the function produces a functorial context; if it is an Applicative, we (also) say it produces an effect; and if it is a Monad we (also) call it a Kleisli arrow. Kleisli arrows are the functions we use with (>>=). Kleisli arrows for a specific Monad form a category, with return as identity and the fish operator, (<=<), as composition. If we pick join as the fundamental Monad operation, (<=<) can be defined in terms of it as:
The category laws, then, become an alternative presentation of the monad laws:
All of that is very well-known. Something less often noted, though, is that there is an interesting category for a -> F b functions even if F is not a Monad. Getting to it is amusingly easy: we just have to take the Kleisli category operators and erase the monad-specific parts from their definitions. In the case of (<=<), that means removing the join (and, for type bookkeeping purposes, slipping in a Compose in its place):
(<%<) :: (Functor f, Functor g) =>
(b -> g c) -> (a -> f b) -> (a -> Compose f g c)
g <%< f = Compose . fmap g . fWhile (<=<) creates two monadic layers and merges them, (<%<) creates two functorial layers and leaves both in place. Note that doing away with join means the Functors introduced by the functions being composed can differ, and so the category we are setting up has all functions that fit Functor f => a -> f b as arrows. That is unlike what we have with (<=<) and the corresponding Kleisli categories, which only concern a single specific monad.
As for return, not relying on Monad means we need a different identity. Given the freedom to pick any Functor mentioned just above, it makes perfect sense to replace bringing a value into a Monad in a boring way by bringing a value into the boring Functor par excellence, Identity:
With (<%<) as composition and Identity as identity, we can state the following category laws:
Why didn’t I write them as equalities? Once the definition of (<%<) is substituted, it becomes clear that they do not hold literally as equalities: the left hand sides of the identity laws will have a stray Identity, and the uses of Compose on either side of the associativity law will be associated differently. Since Identity and Compose are essentially bookkeeping boilerplate, however, it would be entirely reasonable to ignore such differences. If we do that, it becomes clear that the laws do hold. All in all, we have a category, even though we can’t go all the way and shape it into a Category instance, not only due to the trivialities we chose to overlook, but also because of how each a -> F b function introduces a functorial layer F in a way that is not reflected in the target object b.
The first thing to do once after figuring out we have a category in our hands is looking for functors involving it.1 One of the simplest paths towards one is considering a way to, given some Functor T, change the source and target objects in an a -> F b function to T a and T b (that is precisely what fmap does with regular functions). This would give an endofunctor, whose arrow mapping would have a signature shaped like this:
This signature shape, however, should ring a bell:
class (Functor t, Foldable t) => Traversable t where
traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
-- etc.If traverse were the arrow mapping of our endofunctor, the relevant functor laws would be:
Substituting the definition of (<%<) reveals these are the identity and composition laws of Traversable:
traverse Identity = Identity
traverse (Compose . fmap g . f) = Compose . fmap (traverse g) . traverse fThere it is: a Traversable instance is an endofunctor for a category made of arbitrary context-producing functions.2
Is it really, though? You may have noticed I have glossed over something quite glaring: if (<%<) only involved Functor constraints, where does the Applicative in traverse comes from?
Arpeggi
Let’s pretend we have just invented the Traversable class by building it around the aforementioned endofunctor. At this point, there is no reason for using anything more restrictive than Functor in the signature of its arrow mapping:
The natural thing to do now is trying to write traverse for various choices of t. Let’s try it for one of the simplest Functors around: the pair functor, (,) e – values with something extra attached:
instance Traversable ((,) e) where
-- traverse :: Functor f => (a -> f b) -> (e, a) -> f (e, b)
traverse f (e, x) = ((,) e) <$> f xSimple enough: apply the function to the contained value, and then shift the extra stuff into the functorial context with fmap. The resulting traverse follows the functor laws just fine.
If we try to do it for different functors, though, we quickly run into trouble. Maybe looks simple enough…
instance Traversable Maybe where
-- traverse :: Functor f => (a -> f b) -> Maybe a -> f (Maybe b)
traverse f (Just x) = Just <$> f x
traverse f Nothing = -- ex nihilo… but the Nothing case stumps us: there is no value that can be supplied to f, which means the functorial context would have to be created out of nothing.
For another example, consider what we might do with an homogeneous pair type (or, if you will, a vector of length two):
data Duo a = Duo a a
instance Functor Duo where
fmap f (Duo x y) = Duo (f x) (f y)
instance Traversable Duo where
-- traverse :: Functor f => (a -> f b) -> Duo a -> f (Duo b)
traverse f (Duo x y) = -- dilemmaHere, we seemingly have to choose between applying f to x or to y, and then using fmap (\z -> Duo z z) on the result. No matter the choice, though, discarding one of the values means the functor laws will be broken. A lawful implementation would require somehow combining the functorial values f x and f y.
As luck would have it, though, there is a type class which provides ways to both create a functorial context out of nothing and to combine functorial values: Applicative. pure solves the first problem; (<*>), the second:
instance Traversable Maybe where
-- traverse :: Applicative f => (a -> f b) -> Maybe a -> f (Maybe b)
traverse f (Just x) = Just <$> f x
traverse f Nothing = pure Nothing
instance Traversable Duo where
-- traverse :: Applicative f => (a -> f b) -> Duo a -> f (Duo b)
traverse f (Duo x y) = Duo <$> f x <*> f yShifting to the terminology of containers for a moment, we can describe the matter by saying the version of traverse with the Functor constraint can only handle containers that hold exactly one value. Once the constraint is strengthened to Applicative, however, we have the means to deal with containers that may hold zero or many values. This is a very general solution: there are instances of Traversable for the Identity, Const, Sum, and Product functors, which suffice to encode any algebraic data type.3 That explains why the DeriveTraversable GHC extension exists. (Note, though, that Traversable instances in general aren’t unique.)
It must be noted that our reconstruction does not reflect how Traversable was discovered, as the idea of using it to walk across containers holding an arbitrary number of values was there from the start. That being so, Applicative plays an essential role in the usual presentations of Traversable. To illustrate that, I will now paraphrase Definition 3.3 in Jaskelioff and Rypacek’s An Investigation of the Laws of Traversals. It is formulated not in terms of traverse, but of sequenceA:
sequenceA is characterised as a natural transformation in the category of applicative functors which “respects the monoidal structure of applicative functor composition”. It is worth it to take a few moments to unpack that:
The category of applicative functors has what the
Data.Traversabledocumentation calls “applicative transformations” as arrows – functions of general type(Applicative f, Applicative g) => f a -> g awhich preservepureand(<*>).sequenceAis a natural transformation in the aforementioned category of applicative functors. The two functors it maps between amount to the two ways of composing an applicative functor with the relevant traversable functor. The naturality law ofTraversable…… captures that fact (which, thanks to parametricity, is a given in Haskell).
Applicative functors form a monoid, with
Identityas unit and functor composition as multiplication.sequenceApreserves these monoidal operations, and the identity and composition laws ofTraversableexpress that:
All of that seems only accidentally related to what we have done up to this point. However, if sequenceA is taken as the starting point, traverse can be defined in terms of it:
Crucially, the opposite path is also possible. It follows from parametricity4 that…
… which allows us to start from traverse, define…
… and continue as before. At this point, our narrative merges with the traditional account of Traversable.
A note about lenses
In the previous section, we saw how using Applicative rather than Functor in the type of traverse made it possible to handle containers which don’t necessarily hold just one value. It is not a coincidence that, in lens, this is precisely the difference between Traversal and Lens:
type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t
type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f tA Lens targets exactly one value. A Traversal might reach zero, one or many targets, which requires a strengthening of the constraint. Van Laarhoven (i.e. lens-style) Traversals and Lenses can be seen as a straightforward generalisation of the traverse-as-arrow-mapping view we have been discussing here, in which the, so to say, functoriality of the container isn’t necessarily reflected at type level in a direct way.
A note about profunctors
Early on, we noted that (<%<) gave us a category that cannot be expressed as a Haskell Category because its composition is too quirky. We have a general-purpose class that is often a good fit for things that look like functions, arrows and/or Category instances but don’t compose in conventional ways: Profunctor. And sure enough: profunctors defines a profunctor called Star…
-- | Lift a 'Functor' into a 'Profunctor' (forwards).
newtype Star f d c = Star { runStar :: d -> f c }… which corresponds to the arrows of the category we presented in the first section. It should come as no surprise that Star is an instance of a class called Traversing…
-- Abridged definition.
class (Choice p, Strong p) => Traversing p where
traverse' :: Traversable f => p a b -> p (f a) (f b)
wander :: (forall f. Applicative f => (a -> f b) -> s -> f t) -> p a b -> p s t
instance Applicative m => Traversing (Star m) where
traverse' (Star m) = Star (traverse m)
wander f (Star amb) = Star (f amb)… which is a profunctor-oriented generalisation of Traversable.
Amusingly, it turns out there is a baroque way of expressing (<%<) composition with the profunctors vocabulary. Data.Profunctor.Composition gives us a notion of profunctor composition:
Procompose simply pairs two profunctorial values with matching extremities. That is unlike Category composition, which welds two arrows5 into one:
The difference is rather like that between combining functorial layers at type level with Compose and fusing monadic layers with join6.
Among a handful of other interesting things, Data.Functor.Procompose offers a lens-style isomorphism…
… which gives us a rather lyrical encoding of (<%<):
GHCi> import Data.Profunctor
GHCi> import Data.Profunctor.Composition
GHCi> import Data.Profunctor.Traversing
GHCi> import Data.Functor.Compose
GHCi> import Control.Lens
GHCi> f = Star $ \x -> print x *> pure x
GHCi> g = Star $ \x -> [0..x]
GHCi> getCompose $ runStar (traverse' (view stars (g `Procompose` f))) [0..2]
0
1
2
[[0,0,0],[0,0,1],[0,0,2],[0,1,0],[0,1,1],[0,1,2]]If you feel like playing with that, note that Data.Profunctor.Sieve offers a more compact (though prosaic) spelling:
GHCi> import Data.Profunctor.Sieve
GHCi> :t sieve
sieve :: Sieve p f => p a b -> a -> f b
GHCi> getCompose $ traverse (sieve (g `Procompose` f)) [0..2]
0
1
2
[[0,0,0],[0,0,1],[0,0,2],[0,1,0],[0,1,1],[0,1,2]]Further reading
The already mentioned An Investigation of the Laws of Traversals, by Mauro Jaskelioff and Ondrej Rypacek, is a fine entry point to the ways of formulating
Traversable. It also touches upon some important matters I didn’t explore here, such as how the notion of containerTraversablemobilises can be made precise, or the implications of theTraversablelaws. I plan to discuss some aspects of these issues in a follow-up post.Will Fancher’s Profunctors, Arrows, & Static Analysis is a good applied introduction to profunctors. In its final sections, it demonstrates some use cases for the
Traversingclass mentioned here.The explanation of profunctor composition in this post is intentionally cursory. If you want to dig deeper, Dan Piponi’s Profunctors in Haskell can be a starting point. (N.B.: Wherever you see “cofunctor” there, read “contravariant functor” instead). Another option is going to Bartosz Milewski’s blog and searching for “profunctor” (most of the results will be relevant).
For why that is a good idea, see Gabriella Gonzalez’s The functor design pattern.↩︎
A more proper derivation for the results in this section can be found in this Stack Overflow answer, which I didn’t transcribe here to avoid boring you.↩︎
Suffice, that is, with the help of the trivial data types,
()(unit) andVoid. As an arbitrary example,Maybecan be encoded using this functor toolkit asSum (Const ()) Identity.↩︎The property is an immediate consequence of the free theorem for
traverse. Cf. this Stack Overflow answer by Rein Heinrichs.↩︎I mean “arrows” in the general sense, and not necessarily
Arrows as inControl.Arrow!↩︎This is not merely a loose analogy. For details, see Bartosz Milewski’s Monoids on Steroids, and and in particular its section about
Arrows.↩︎
Post licensed under a
Creative Commons Attribution-ShareAlike 4.0 International License.
foldr
The primeval example of a fold in Haskell is the right fold of a list.
One way of picturing what the first two arguments of foldr are for is seeing them as replacements for the list constructors: the b argument is an initial value corresponding to the empty list, while the binary function incorporates each element prepended through (:) into the result of the fold.
data [a] = [] | a : [a]
foldr (+) 0 [ 1 , 2 , 3 ]
foldr (+) 0 ( 1 : (2 : (3 : [])) )
( 1 + (2 + (3 + 0 )) )By applying this strategy to other data structures, we can get analogous folds for them.
-- This is foldr; I have flipped the arguments for cosmetic reasons.
data [a] = [] | (:) a [a]
foldList :: b -> (a -> b -> b) -> [a] -> b
-- Does this one look familiar?
data Maybe a = Nothing | Just a
foldMaybe :: b -> (a -> b) -> Maybe a -> b
-- This is not the definition in Data.List.NonEmpty; the differences
-- between them, however, are superficial.
data NEList :: NEList a (Maybe (NEList a))
foldNEList :: (a -> Maybe b -> b) -> NEList a -> b
-- A binary tree like the one in Diagrams.TwoD.Layout.Tree (and in
-- many other places).
data BTree a = Empty | BNode a (BTree a) (BTree a)
foldBTree :: b -> (a -> b -> b -> b) -> BTree a -> bIt would make sense to capture this pattern into an abstraction. At first glance, however, it is not obvious how to do so. Though we know intuitively what the folds above have in common, their type signatures have lots of superficial differences between them. Our immediate goal, then, will be simplifying things by getting rid of these differences.1
ListF
We will sketch the simplification using the tangible and familiar example of lists. Let’s return to the type of foldr.
With the cosmetic flip I had applied previously, it becomes:
The annoying irregularities among the types of the folds in the previous section had to do with the number of arguments other than the data structure (one per constructor) and the types of said arguments (dependent on the shape of each constructor). Though we cannot entirely suppress these differences, we have a few tricks that make it possible to disguise them rather well. The number of extra arguments, for instance, can be always be reduced to just one with sufficient uncurrying:
The first argument is now a pair. We continue by making its two halves more like each other by converting them into unary functions: the first component acquires a dummy () argument, while the second one gets some more uncurrying:
We now have a pair of unary functions with result type b. A pair of functions with the same result type, however, is equivalent to a single function from Either one of the argument types (if you are sceptical about that, you might want to work out the isomorphism – that is, the pair of conversion functions – that witnesses this fact):
At this point, the only extra argument of the fold is an unary function with result type b. We have condensed the peculiarities of the original arguments at a single place (the argument of said function), which makes the overall shape of the signature a lot simpler. Since it can be awkward to work with anonymous nestings of Either and pairs, we will replace Either () (a, b) with an equivalent type equipped with suggestive names:
That leaves us with:
The most important fact about ListF is that it mirrors the shape of the list type except for one crucial difference…
… namely, it is not recursive. An [a] value built with (:) has another [a] in itself, but a ListF a b built with Cons does not contain another ListF a b. To put it in another way, ListF is the outcome of taking away the recursive nesting in the list data type and filling the resulting hole with a placeholder type, the b in our signatures, that corresponds to the result of the fold. This strategy can be used to obtain a ListF analogue for any other data structure. You might, for instance, try it with the BTree a type shown in the first section.
cata
We have just learned that the list foldr can be expressed using this signature:
We might figure out a foldr implementation with this signature in a mechanical way, by throwing all of the tricks from the previous section at Data.List.foldr until we squeeze out something with the right type. It is far more illuminating, however, to start from scratch. If we go down that route, the first question that arises is how to apply a ListF a b -> b function to an [a]. It is clear that the list must somehow be converted to a ListF a b, so that the function can be applied to it.
foldList :: (ListF a b -> b) -> [a] -> b
foldList f = f . something
-- foldList f xs = f (something xs)
-- something :: [a] -> ListF a bWe can get part of the way there by recalling how ListF mirrors the shape of the list type. That being so, going from [a] to ListF a [a] is just a question of matching the corresponding constructors.2
project :: [a] -> ListF a [a]
project = \case
[] -> Nil
x:xs -> Cons x xs
foldList :: (ListF a b -> b) -> [a] -> b
foldList f = f . something . project
-- something :: ListF a [a] -> ListF a bproject witnesses the simple fact that, given that ListF a b is the [a] except with a b placeholder in the tail position, where there would be a nested [a], if we plug the placeholder with [a] we get something equivalent to the [a] list type we began with.
We now need to go from ListF a [a] to ListF a b; in other words, we have to change the [a] inside ListF into a b. And sure enough, we do have a function from [a] to b…
… the fold itself! To conveniently reach inside ListF a b, we set up a Functor instance:
instance Functor (ListF a) where
fmap f = \case
Nil -> Nil
Cons x y -> Cons x (f y)
foldList :: (ListF a b -> b) -> [a] -> b
foldList f = f . fmap (foldList f) . projectAnd there it is, the list fold. First, project exposes the list (or, more precisely, its first constructor) to our machinery; then, the tail of the list (if there is one – what happens if there isn’t?) is recursively folded through the Functor instance of ListF; finally, the overall result is obtained by applying f to the resulting ListF a b.
-- A simple demonstration of foldList in action.
f :: Num a => ListF a a -> a
f = \case { Nil -> 0; Cons x y -> x + y }
foldList f [1, 2, 3]
-- Let's try and evaluate this by hand.
foldList f (1 : 2 : 3 : [])
f . fmap (foldList f) . project $ (1 : 2 : 3 : [])
f . fmap (foldList f) $ Cons 1 (2 : 3 : [])
f $ Cons 1 (foldList f (2 : 3 : []))
f $ Cons 1 (f . fmap (foldList f) $ project (2 : 3 : []))
f $ Cons 1 (f . fmap (foldList f) $ Cons 2 (3 : []))
f $ Cons 1 (f $ Cons 2 (foldList f (3 : [])))
f $ Cons 1 (f $ Cons 2 (f . fmap (foldList f) . project $ (3 : [])))
f $ Cons 1 (f $ Cons 2 (f . fmap (foldList f) $ Cons 3 []))
f $ Cons 1 (f $ Cons 2 (f $ Cons 3 (foldList f [])))
f $ Cons 1 (f $ Cons 2 (f $ Cons 3 (f . fmap (foldList f) . project $ [])))
f $ Cons 1 (f $ Cons 2 (f $ Cons 3 (f . fmap (foldList f) $ Nil)))
f $ Cons 1 (f $ Cons 2 (f $ Cons 3 (f $ Nil)))
f $ Cons 1 (f $ Cons 2 (f $ Cons 3 0))
f $ Cons 1 (f $ Cons 2 3)
f $ Cons 1 5
6One interesting thing about our definition of foldList is that all the list-specific details are tucked within the implementations of project, fmap for ListF and f (whatever it is). That being so, if we look only at the implementation and not at the signature, we find no outward signs of anything related to lists. No outward signs, that is, except for the name we gave the function. That’s easy enough to solve, though: it is just a question of inventing a new one:
cata is short for catamorphism, the fancy name given to ordinary folds in the relevant theory. There is a function called cata in recursion-schemes. Its implementation…
… is the same as ours, almost down to the last character. Its type signature, however, is much more general:
It involves, in no particular order:
b, the type of the result of the fold;t, the type of the data structure being folded. In our example,twould be[a]; or, as GHC would put it,t ~ [a].Base, a type family that generalises what we did with[a]andListFby assigning base functors to data types. We can readBase tas “the base functor oft”; in our example, we haveBase [a] ~ ListF a.Recursive, a type class whose minimal definition consists ofproject, with the type ofprojectnow beingt -> Base t t.
The base functor is supposed to be a Functor, so that we can use fmap on it. That is enforced through a Functor (Base t) constraint in the definition of the Recursive class. Note, however, that there is no such restriction on t itself: it doesn’t need to be a polymorphic type, or even to involve a type constructor.
In summary, once we managed to concentrate the surface complexity in the signature of foldr at a single place, the ListF a b -> b function, an opportunity to generalise it revealed itself. Incidentally, that function, and more generally any Base t b -> b function that can be given to cata, is referred to as an algebra. In this context, the term “algebra” is meant in a precise technical sense; still, we can motivate it with a legitimate recourse to intuition. In basic school algebra, we use certain rules to get simpler expressions out of more complicated ones, such as ax + bx = (a+b)x. Similarly, a Base t b -> b algebra boils down to a set of rules that tell us what to do to get a b result out of the Base t b we are given at each step of the fold.
Fix
The cata function we ended up with in the previous section…
… is perfectly good for practical purposes: it allows us to fold anything that we can give a Base functor and a corresponding project. Not only that, the implementation of cata is very elegant. And yet, a second look at its signature suggests that there might be an even simpler way of expressing cata. The signature uses both t and Base t b. As we have seen for the ListF example, these two types are very similar (their shapes match except for recursiveness), and so using both in the same signature amounts to encoding the same information in two different ways – perhaps unnecessarily so.
In the implementation of cata, it is specifically project that links t and Base t b, as it translates the constructors from one type to the other.
Now, let’s look at what happens once we repeatedly expand the definition of cata:
c = cata f
p = project
c
f . fmap c . p
f . fmap (f . fmap c . p) . p
f . fmap (f . fmap (f . fmap c . p) . p) . p
f . fmap ( . . . f . fmap c . p . . . ) . pThis continues indefinitely. The fold terminates when, at some point, fmap c does nothing (in the case of ListF, that happens when we get to a Nil). Note, however, that even at that point we can carry on expanding the definition, merrily introducing do-nothing operations for as long as we want.
At the right side of the expanded expression, we have a chain of increasingly deep fmap-ped applications of project:3
If we could factor that out into a separate function, it would change a t data structure into something equivalent to it, but built with the Base t constructors:
GHCi> :{
GHCi| fmap (fmap (fmap project))
GHCi| . fmap (fmap project) . fmap project . project
GHCi| $ 1 : 2 : 3 : []
GHCi| :}
Cons 1 (Cons 2 (Cons 3 Nil))We would then be able to regard this conversion as a preliminary, relatively uninteresting step that precedes the application of a slimmed down cata, that doesn’t use neither project nor the t type.4
Defining omniProject seems simple once we notice the self-similarity in the chain of project:
omniProject = . . . fmap (fmap project) . fmap project . project
omniProject = fmap (fmap ( . . . project) . project) . project
omniProject = fmap omniProject . projectGuess what happens next:
GHCi> omniProject = fmap omniProject . project
<interactive>:502:16: error:
• Occurs check: cannot construct the infinite type: b ~ Base t b
Expected type: t -> b
Actual type: t -> Base t b
• In the expression: fmap omniProject . project
In an equation for ‘omniProject’:
omniProject = fmap omniProject . project
• Relevant bindings include
omniProject :: t -> b (bound at <interactive>:502:1)GHCi complains about an “infinite type”, and that is entirely appropriate. Every fmap-ped project changes the type of the result by introducing a new layer of Base t. That being so, the type of omniProject would be…
… which is clearly a problem, as we don’t have a type that encodes an infinite nesting of type constructors. There is a simple way of solving that, though: we make up the type we want!
If we read Fix f as “infinite nesting of f”, the right-hand side of the newtype definition just above reads “an infinite nesting of f contains an f of infinite nestings of f”, which is an entirely reasonable encoding of such a thing.5
All we need to make our tentative definition of omniProject legal Haskell is wrapping the whole thing in a Fix. The recursive fmap-ping will ensure Fix is applied at all levels:
Another glance at the definition of cata shows that this is just cata using Fix as the algebra:
That being so, cata Fix will change anything with a Recursive instance into its Fix-wearing form:
GHCi> cata Fix [0..9]
Fix (Cons 0 (Fix (Cons 1 (Fix (Cons 2 (Fix (Cons 3 (Fix (Cons 4 (
Fix (Cons 5 (Fix (Cons 6 (Fix (Cons 7 (Fix (Cons 8 (Fix (Cons 9 (
Fix Nil))))))))))))))))))))Defining a Fix-style structure from scratch, without relying on a Recursive instance, is just a question of introducing Fix in the appropriate places. For extra convenience, you might want to define “smart constructors” like these two:6
nil :: Fix (ListF a)
nil = Fix Nil
cons :: a -> Fix (ListF a) -> Fix (ListF a)
cons x xs = Fix (Cons x xs)Before we jumped into this Fix rabbit hole, we were trying to find a leanCata function such that:
We can now easily define leanCata by mirroring what we have done for omniProject: first, we get rid of the Fix wrapper; then, we fill in the other half of the definition of cata that we left behind when we extracted omniProject – that is, the repeated application of f:
(It is possible to prove that this must be the definition of leanCata using the definitions of cata and omniProject and the cata f = leanCata f . omniProject specification. You might want to work it out yourself; alternatively, you can find the derivation in an appendix at the end of this article.)
What should be the type of leanCata? unfix calls for a Fix f, and fmap demands this f to be a Functor. As the definition doesn’t use cata or project, there is no need to involve Base or Recursive. That being so, we get:
This is how you will usually see cata being defined in other texts about the subject.7
Similarly to what we have seen for omniProject, the implementation of leanCata looks a lot like the cata we began with, except that it has unfix where project used to be. And sure enough, recursion-schemes defines…
… so that its cata also works as leanCata:
GHCi> foo = 1 `cons` (2 `cons` (3 `cons` nil))
GHCi> foo
Fix (Cons 1 (Fix (Cons 2 (Fix (Cons 3 (Fix Nil))))))
GHCi> cata (\case {Nil -> 1; Cons x y -> x * y}) foo
6In the end, we did manage to get a tidier cata. Crucially, we now also have a clear picture of folding, the fundamental way of consuming a data structure recursively. On the one hand, any fold can be expressed in terms of an algebra for the base functor of the structure being folded by the means of a simple function, cata. On the other hand, the relationship between data structures and their base functors is made precise through Fix, which introduces recursion into functors in a way that captures the essence of recursiveness of data types.
To wrap things up, here a few more questions for you to ponder:
Does the data structure that we get by using
Maybeas a base functor correspond to anything familiar? Usecatato write a fold that does something interesting with it.What could possibly be the base functor of a non-recursive data structure?
Find two base functors that give rise to non-empty lists. One of them corresponds directly to the
NEListdefinition given at the beginning of this article.As we have discussed,
omniProject/cata Fixcan be used to losslessly convert a data structure to the correspondingFix-encoded form. Write the other half of the isomorphism for lists; that is, the function that changes aFix (ListF a)back into an[a].
Closing remarks
When it comes to recursion schemes, there is a lot more to play with than just the fundamental catamorphism that we discussed here. In particular, recursion-schemes offers all sorts of specialised folds (and unfolds), often with richly decorated type signatures meant to express more directly some particular kind of recursive (or corecursive) algorithm. But that’s a story for another time. For now, I will just make a final observation about unfolds.
Intuitively, an unfold is the opposite of a fold – while a fold consumes a data structure to produce a result, an unfold generates a data structure from a seed. In recursion schemes parlance, the intuition is made precise by the notion of anamorphism, a counterpart (technically, a dual) to the catamorphism. Still, if we have a look at unfoldr in Data.List, the exact manner in which it is opposite to foldr is not immediately obvious from its signature.
One way of clarifying that is considering the first argument of unfoldr from the same perspective that we used to uncover ListF early in this article.
Further reading
Understanding F-Algebras, by Bartosz Milewski, covers similar ground to this article from an explicitly categorical perspective. A good follow-up read for sharpening your picture of the key concepts we have discussed here.
An Introduction to Recursion Schemes, by Patrick Thompson, is the first in a series of three articles that present some common recursion schemes at a gentle pace. You will note that examples involving syntax trees and simplifying expressions are a running theme across these articles. That is in line with what we said about the word “algebra” at the end of the section about
cata.Practical Recursion Schemes, by Jared Tobin, offers a faster-paced demonstration of basic recursion schemes. Unlike the other articles in this list, it explores the machinery of the recursion-schemes library that we have dealt with here.
*Functional Programming With Bananas, Lenses, Envelopes and Barbed Wire, by Erik Meijer, Maarten Fokkinga and Ross Paterson, is a classic paper about recursion schemes, the one which popularised concepts such as catamorphism and anamorphism. If you plan to go through it, you may find this key to its notation by Edward Z. Yang useful.
Appendix: leanCata
This is the derivation mentioned in the middle of the section about Fix. We begin from our specification for leanCata:
Take the left-hand side and substitute the definition of cata:
Substitute the right-hand side of the leanCata specification:
By the second functor law:
unfix . Fix = id, so we can slip it in like this:
Substituting the definition of omniProject:
Substituting this back into the specification:
Assuming a sensible Recursive and Base instances for t, t and Fix (Base t) should be isomorphic (that is, losslessly interconvertible) types, with omniProject performing one of the two relevant conversions. As a consequence, omniProject is surjective (that is, it is possible to obtain every Fix (Base t) value through it). That being so, we can “cancel out” the omniProjects at the right end of both sides of the equation above. The definition of leanCata follows immediately.
By the way, it is worth emphasising that the
Foldableclass from base is not the abstraction we are looking for. One way of seeing why is placing the signature offoldBTreeside by side with the one ofFoldable.foldr.↩︎In what follows, I will use the
LambdaCaseextension liberally, so that I have fewer boring variable names to make up. If you haven’t seen it yet, all you need to know is that…… is the same as:
↩︎While that is clear to the naked eye, it can be shown more rigorously by applying the second functor law, that is:
↩︎This is in some ways similar to how
(>>= f) = join . fmap fcan be read as a factoring of(>>=)into a preliminary step (fmap f) followed by the quintessential monadic operation (join).↩︎The name
Fixcomes from “fixed point”, the mathematical term used to describe a value which is left unchanged by some function. In this case, if we have an infinite nesting of theftype constructor, it doesn’t make any difference if we applyfto it one more time.↩︎As suggested by Jared Tobin’s Practical Recursion Schemes article, which is in the further reading list at the end of this post.↩︎
The names in said texts tend to be different, though. Common picks include
μfor theFixtype constructor,Infor theFixvalue constructor,outforunfix, and⦇f⦈forleanCata f(using the famed banana brackets).↩︎
Post licensed under a
Creative Commons Attribution-ShareAlike 4.0 International License.
The global project consists of a stack.yaml file and an associated .stack-work directory, which are kept in ~/.stack/global-project and are used by stack whenever there is no other stack.yaml lying around. The stack.yaml of the global project specifies a resolver, just like any other stack.yaml. If said resolver is a snapshot you use elsewhere, you get access to all packages you have installed from that snapshot with zero configuration.
$ pwd
/home/duplode
$ ls -lrt | grep stack.yaml
$ stack ghci
Configuring GHCi with the following packages:
GHCi, version 8.0.1: https://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/duplode/.ghci
Loaded GHCi configuration from /tmp/ghci22741/ghci-script
GHCi> import Control.Lens
GHCi> (1,2) ^. _1
1By the way, this also holds for the stack-powered Intero Emacs mode, which makes it possible to simply open a new *.hs file anywhere and immediately start hacking away.
What about packages you didn’t install beforehand? They are no problem, thanks to the --package option of stack ghci, which allows installing snapshot packages at a whim.
$ stack ghci --package fmlist
fmlist-0.9: download
fmlist-0.9: configure
fmlist-0.9: build
fmlist-0.9: copy/register
Configuring GHCi with the following packages:
GHCi, version 8.0.1: https://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/duplode/.ghci
Loaded GHCi configuration from /tmp/ghci22828/ghci-script
GHCi> import qualified Data.FMList as FM
GHCi> FM.foldMapA (\x -> show <$> [0..x]) [0..3]
["0000","0001","0002","0003","0010","0011","0012","0013","0020","0021",
"0022","0023","0100","0101","0102","0103","0110","0111","0112","0113",
"0120","0121","0122","0123"]One caveat is that --package won’t install packages outside of the snapshot on its own, so you have to add them to the extra-deps field of the global project’s stack.yaml beforehand, just like you would do for an actual project. If you need several non-Stackage packages, you may find it convenient to create a throwaway project for the sole purpose of letting stack solver figure out the necessary extra-deps for you.
$ mkdir throwaway
$ stack new throwaway --resolver lts-7.14 # Same resolver of the global project.
# ...
Writing configuration to file: throwaway/stack.yaml
All done.
$ cd throwaway
$ vi throwaway.cabal # Let's add reactive-banana to the dependencies.
$ stack solver
# ...
Successfully determined a build plan with 2 external dependencies.
The following changes will be made to stack.yaml:
* Dependencies to be added
extra-deps:
- pqueue-1.3.2
- reactive-banana-1.1.0.1
To automatically update stack.yaml, rerun with '--update-config'
$ vi ~/.stack/global-project/stack.yaml # Add the packages to the extra-deps.
$ cd ..
$ rm -rf throwaway/
$ stack ghci --package reactive-banana
pqueue-1.3.2: configure
pqueue-1.3.2: build
pqueue-1.3.2: copy/register
reactive-banana-1.1.0.1: configure
reactive-banana-1.1.0.1: build
reactive-banana-1.1.0.1: copy/register
Completed 2 action(s).
Configuring GHCi with the following packages:
GHCi, version 8.0.1: https://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/duplode/.ghci
Loaded GHCi configuration from /tmp/ghci23103/ghci-script
GHCi> import Reactive.Banana
GHCi> :t stepper
stepper :: MonadMoment m => a -> Event a -> m (Behavior a)Support for running stack solver directly with the global project is on the horizon.
There are also interesting possibilities if you need to compile your throwaway code. That might be useful, for instance, if you ever feel like testing a hypothesis with a criterion benchmark). While there is a stack ghc command, if you don’t need GHC profiles then taking advantage of --ghci-options to enable -fobject-code for stack ghci can be a more pleasant alternative.
$ stack ghci --ghci-options "-O2 -fobject-code"
Configuring GHCi with the following packages:
GHCi, version 8.0.1: https://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/duplode/.ghci
Loaded GHCi configuration from /tmp/ghci23628/ghci-script
GHCi> :l Foo.hs
[1 of 1] Compiling Foo ( Foo.hs, /home/duplode/.stack/global-project/.stack-work/odir/Foo.o )
Ok, modules loaded: Foo (/home/duplode/.stack/global-project/.stack-work/odir/Foo.o).
GHCi> :main
A random number for you: 2045528912275320075A nice little thing about this approach is that the build artifacts are kept in the global project’s .stack-work, which means they won’t pollute whichever other directory you happen to be at. -fobject-code means you can’t write definitions directly on the GHCi prompt; however, that is not much of a nuisance, given that you are compiling the code anyway, and that the source file is just a :!vim Foo.hs away.
While in these notes I have focused on seat-of-the-pants experimentation, stack also provides tools for running Haskell code with minimal configuration in a more controlled manner. I specially recommend having a look at the script interpreter section of the stack User Guide.
Post licensed under a
Creative Commons Attribution-ShareAlike 4.0 International License.
The first decision to make when migrating a project is which Stackage snapshot to pick. It had been a while since I last updated my project, and building it with the latest versions of all its dependencies would require a few adjustments. That being so, I chose to migrate to stack before any further patches. Since one of the main dependencies was diagrams 1.2, I went for lts-2.19, the most recent LTS snapshot with that version of diagrams 1.
$ stack init --resolver lts-2.19
stack init creates a stack.yaml file based on an existing cabal file in the current directory. The --resolver option can be used to pick a specific snapshot.
One complicating factor in the conversion to stack was that two of the extra dependencies, threepenny-gui-0.5.0.0 (one major version behind the current one) and zip-conduit, wouldn’t build with the LTS snapshot plus current Hackage without version bumps in their cabal files. Fortunately, stack deals very well with situations like this, in which minor changes to some dependency are needed. I simply forked the dependencies on GitHub, pushed the version bumps to my forks and referenced the commits in the remote GitHub repository in stack.yaml. A typical entry for a Git commit in the packages section looks like this:
- location:
git: https://github.com/duplode/zip-conduit
commit: 1eefc8bd91d5f38b760bce1fb8dd16d6e05a671d
extra-dep: trueKeeping customised dependencies in public remote repositories is an excellent solution. It enables users to build the package without further intervention without requiring developers to clumsily bundle the source tree of the dependencies with the project, or waiting for a pull request to be accepted upstream and reach Hackage.
With the two tricky extra dependencies being offloaded to Git repositories, the next step was using stack solver to figure out the rest of them:
$ stack solver --modify-stack-yaml
This command is not guaranteed to give you a perfect build plan
It's possible that even with the changes generated below, you will still
need to do some manual tweaking
Asking cabal to calculate a build plan, please wait
extra-deps:
- parsec-permutation-0.1.2.0
- websockets-snap-0.9.2.0
Updated /home/duplode/Development/stunts/diagrams/stack.yaml
Here is the final stack.yaml:
flags:
stunts-cartography:
repldump2carto: true
packages:
- '.'
- location:
git: https://github.com/duplode/zip-conduit
commit: 1eefc8bd91d5f38b760bce1fb8dd16d6e05a671d
extra-dep: true
- location:
git: https://github.com/duplode/threepenny-gui
commit: 2dd88e893f09e8e31378f542a9cd253cc009a2c5
extra-dep: true
extra-deps:
- parsec-permutation-0.1.2.0
- websockets-snap-0.9.2.0
resolver: lts-2.19repldump2carto is a flag defined in the cabal file. It is used to build a secondary executable. Beyond demonstrating how the flags section of stack.yaml works, I added it because stack ghci expects all possible build targets to have been built 2.
As I have GHC 7.10.1 from my Linux distribution and the LTS 2.19 snapshot is made for GHC 7.8.4, I needed stack setup as an additional step. That command locally installs (in ~/.stack) the GHC version required by the chosen snapshot.
That pretty much concludes the migration. All that is left is demonstrating: stack build to compile the project…
$ stack build
JuicyPixels-3.2.5.2: configure
Boolean-0.2.3: download
# etc. (Note how deps from Git are handled seamlessly.)
threepenny-gui-0.5.0.0: configure
threepenny-gui-0.5.0.0: build
threepenny-gui-0.5.0.0: install
zip-conduit-0.2.2.2: configure
zip-conduit-0.2.2.2: build
zip-conduit-0.2.2.2: install
# etc.
stunts-cartography-0.4.0.3: configure
stunts-cartography-0.4.0.3: build
stunts-cartography-0.4.0.3: install
Completed all 64 actions.
… stack ghci to play with it in GHCi…
$ stack ghci
Configuring GHCi with the following packages: stunts-cartography
GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
-- etc.
Ok, modules loaded: GameState, Annotation, Types.Diagrams, Pics,
Pics.MM, Annotation.Flipbook, Annotation.LapTrace,
Annotation.LapTrace.Vec, Annotation.LapTrace.Parser.Simple,
Annotation.Parser, Types.CartoM, Parameters, Composition, Track,
Util.Misc, Pics.Palette, Output, Util.ByteString, Util.ZipConduit,
Replay, Paths, Util.Reactive.Threepenny, Util.Threepenny.Alertify,
Widgets.BoundedInput.
*GameState> :l src/Viewer.hs -- The Main module.
-- etc.
*Main> :main
Welcome to Stunts Cartography.
Open your web browser and navigate to localhost:10000 to begin.
Listening on http://127.0.0.1:10000/
[27/Jul/2015:00:55:11 -0300] Server.httpServe: START, binding to
[http://127.0.0.1:10000/]… and looking at the build output in the depths of .stack-work:
$ .stack-work/dist/x86_64-linux/Cabal-1.18.1.5/build/sc-trk-viewer/sc-trk-viewer
Welcome to Stunts Cartography 0.4.0.3.
Open your web browser and navigate to localhost:10000 to begin.
Listening on https://127.0.0.1:10000/
[26/Jul/2015:20:02:54 -0300] Server.httpServe: START, binding to
[https://127.0.0.1:10000/]
With the upcoming stack 0.2 it will be possible to use stack build --copy-bins --local-bin-path <path> to copy any executables built as part of the project to a path. If the --local-bin-path option is omitted, the default is ~/.local/bin. (In fact, you can already copy executables to ~/.local/bin with stack 0.1.2 through stack install. However, I don’t want to overemphasise that command, as stack install not being equivalent to cabal install can cause some confusion.)
Hopefully this report will give you an idea of what to expect when migrating your projects to stack. Some details may appear a little strange, given how familiar cabal-install workflows are, and some features are still being shaped. All in all, however, stack works very well already: it definitely makes setting up reliable builds easier. The stack repository at GitHub, and specially the wiki therein, offers lots of helpful information, in case you need further details and usage tips.
As a broader point, it just seems polite to, when possible, pick a LTS snapshot over than a nightly for a public project. It is more likely that those interested in building your project already have a specific LTS rather than an arbitrary nightly.↩︎
That being so, a more natural arrangement would be treating
repldump2cartoas a full-blown subproject by giving it its own cabal file and adding it to thepackagessection. I would then be able to load only the main project in GHCi withstack ghci stunts-cartography.↩︎
Post licensed under a
Creative Commons Attribution-ShareAlike 4.0 International License.
Sandboxes are exceptionally helpful not just for working in long-term Haskell projects, but also for casual experiments. While playing around, we tend to install all sorts of packages in a carefree way, which increases a lot the risk of entering cabal hell. While vanilla cabal-install sandboxes prevent such a disaster, using them systematically for experiments mean that, unless you are meticulous, you will end up either with dozens of .hs files in a single sandbox or with dozens of copies of the libraries strewn across your home directory. And no one likes to be meticulous while playing around. In that context, stack, the recently released alternative to cabal-install, can prevent trouble with installing packages in a way more manageable than through ad-hoc sandboxes. In this post, I will suggest a few ways of using stack that may be convenient for experiments. I have been using stack for only a few days, therefore suggestions are most welcome!
I won’t dwell on the motivation and philosophy behind stack 1. Suffice it to say that, at least in the less exotic workflows, there is a centralised package database somewhere in ~/.stack with packages pulled from a Stackage snapshot (and therefore known to be compatible with each other), which is supplemented by a per-project database (that is, just like cabal sandboxes) for packages not in Stackage (from Hackage or anywhere else). As that sounds like a great way to avoid headaches, we will stick to this arrangement, with only minor adjustments.
Once you have installed stack 2, you can create a new environment for experiments with stack new:
$ mkdir -p Development/haskell/playground
$ cd Development/haskell/playground
$ stack new --prefer-nightly
The --prefer-nightly option makes stack use a nightly snapshot of Stackage, as opposed to a long term support one. As we are just playing around, it makes sense to pick as recent as possible packages from the nightly instead of the LTS. (Moreover, I use Arch Linux, which already has GHC 7.10 and base 4.8, while the current LTS snapshot assumes base 4.7.) If this is the first time you use stack, it will pick the latest nightly; otherwise it will default to whatever nightly you already have in ~/.stack.
stack new creates a neat default project structure for you 3:
$ ls -R
.:
app LICENSE new-template.cabal Setup.hs src stack.yaml test
./app:
Main.hs
./src:
Lib.hs
./test:
Spec.hs
Of particular interest is the stack.yaml file, which holds the settings for the local stack environment. We will talk more about it soon.
As for the default new-template.cabal file, you can use its build-depends section to keep track of what you are installing. That will make stack build (the command which builds the current project without installing it) to download and install any dependencies you add to the cabal file automatically. Besides that, having the installed packages noted down may prove useful in case you need to reproduce your configuration elsewhere 4. If your experiments become a real project, you can clean up the build-depends without losing track of the packages you installed for testing purposes by moving their entries to a second cabal file, kept in a subdirectory:
$ mkdir xp
$ cp new-template.cabal xp/xp.cabal
$ cp LICENSE xp # Too lazy to delete the lines from the cabal file.
$ cd xp
$ vi Dummy.hs # module Dummy where <END OF FILE>
$ vi xp.cabal # Adjust accordingly, and list your extra deps.
You also need to tell stack about this fake subproject. All it takes is adding an entry for the subdirectory in stack.yaml:
With the initial setup done, we use stack build to compile the projects:
$ stack build
new-template-0.1.0.0: configure
new-template-0.1.0.0: build
fmlist-0.9: download
fmlist-0.9: configure
fmlist-0.9: build
new-template-0.1.0.0: install
fmlist-0.9: install
xp-0.1.0.0: configure
xp-0.1.0.0: build
xp-0.1.0.0: install
Completed all 3 actions.
In this test run, I added fmlist as a dependency of the fake package xp, and so it was automatically installed by stack. The output of stack build goes to a .stack-work subdirectory.
With the packages built, we can use GHCi in the stack environment with stack ghci. It loads the library source files of the current project by default:
$ stack ghci
Configuring GHCi with the following packages: new-template, xp
GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help
[1 of 2] Compiling Lib (
/home/duplode/Development/haskell/playground/src/Lib.hs, interpreted )
[2 of 2] Compiling Dummy (
/home/duplode/Development/haskell/playground/xp/Dummy.hs, interpreted )
Ok, modules loaded: Dummy, Lib.
*Lib> import qualified Data.FMList as F -- Which we have just installed.
*Lib F> -- We can also load executables specified in the cabal file.
*Lib F> :l Main
[1 of 2] Compiling Lib (
/home/duplode/Development/haskell/playground/src/Lib.hs, interpreted )
[2 of 2] Compiling Main (
/home/duplode/Development/haskell/playground/app/Main.hs, interpreted )
Ok, modules loaded: Lib, Main.
*Main F>Dependencies not in Stackage have to be specified in stack.yaml as well as in the cabal files, so that stack can manage them too. Alternative sources of packages include source trees in subdirectories of the project, Hackage and remote Git repositories 5:
flags: {}
packages:
- '.'
- 'xp'
- location: deps/acme-missiles-0.3 # Sources in a subdirectory.
extra-dep: true # Mark as dep, i.e. not part of the project proper.
extra-deps:
- acme-safe-0.1.0.0 # From Hackage.
- acme-dont-1.1 # Also from Hackage, dependency of acme-safe.
resolver: nightly-2015-07-19stack build will then install the extra dependencies to .stack-work/install. You can use stack solver to chase the indirect dependencies introduced by them. For instance, this is its output after commenting the acme-dont line in the stack.yaml just above:
$ stack solver --no-modify-stack-yaml
This command is not guaranteed to give you a perfect build plan
It's possible that even with the changes generated below, you will still
need to do some manual tweaking
Asking cabal to calculate a build plan, please wait
extra-deps:
- acme-dont-1.1
To conclude this tour, once you get bored of the initial Stackage snapshot all it takes to switch it is changing the resolver field in stack.yaml (with nightlies, that amounts to changing the date at the end of the snapshot name). That will cause all dependencies to be downloaded and built from the chosen snapshot when stack build is next ran. As of now, the previous snapshot will remain in ~/.stack unless you go there and delete it manually; however, a command for removing unused snapshots is in the plans.
I have not tested the sketch of a workflow presented here extensively, yet what I have seen was enough to convince me stack can provide a pleasant experience for casual experiments as well as full-fledged projects. Happy hacking!
Update: There is now a follow-up post about the other side of the coin, Migrating a Project to stack.
For that, see Why is stack not cabal?, written by a member of its development team.↩︎
For installation guidance, see the GitHub project wiki. Installing stack is easy, and there are many ways to do it (I simply got it from Hackage with
cabal install stack).↩︎To create an environment for an existing project, with its own structure and cabal file, you would use
stack initinstead.↩︎In any case, you can also use
stack exec -- ghc-pkg listto see all packages installed from the snapshot you are currently using. That, however, will be far messier than thebuild-dependslist, as it will include indirect dependencies as well.↩︎For the latter, see the project wiki.↩︎
Post licensed under a
Creative Commons Attribution-ShareAlike 4.0 International License.
Applicative class are not pretty to look at.
pure id <*> v = v -- identity
pure f <*> pure x = pure (f x) -- homomorphism
u <*> pure y = pure ($ y) <*> u -- interchange
pure (.) <*> u <*> v <*> w = u <*> (v <*> w) -- compositionMonad laws, in comparison, not only look less odd to begin with but can also be stated in a much more elegant way in terms of Kleisli composition (<=<). Shouldn’t there be an analogous nice presentation for Applicative as well? That became a static question in my mind while I was studying applicative functors many moons ago. After finding surprisingly little commentary on this issue, I decided to try figuring it out by myself. 1
Let’s cast our eye over Applicative:
If our inspiration for reformulating Applicative is Kleisli composition, the only sensible plan is to look for a category in which the t (a -> b) functions-in-a-context from the type of (<*>) are the arrows, just like a -> t b functions are arrows in a Kleisli category. Here is one way to state that plan in Haskell terms:
class Applicative t => Starry t where
idA :: t (a -> a)
(.*) :: t (b -> c) -> t (a -> b) -> t (a -> c)
infixl 4 .*
-- The Applicative constraint is wishful thinking:
-- When you wish upon a star...The laws of Starry are the category laws for the t (a -> b) arrows:
idA .* v = v -- left identity
u .* idA = u -- right identity
u .* v .* w = u .* (v .* w) -- associativityThe question, then, is whether it is possible to reconstruct Applicative and its laws from Starry. The answer is a resounding yes! The proof is in this manuscript, which I have not transcribed here as it is a little too long for a leisurely post like this one 2. The argument is set in motion by establishing that pure is an arrow mapping of a functor from Hask to a Starry category, and that both (<*>) and (.*) are arrow mappings of functors in the opposite direction. That leads to several naturality properties of those functors, from which the Applicative laws can be obtained. Along the way, we also get definitions for the Starry methods in terms of the Applicative ones…
… and vice-versa:
Also interesting is how the property relating fmap and (<*>)…
… now tells us that a Functor results from composing the pure functor with the (<*>) functor. That becomes more transparent if we write it point-free:
In order to ensure Starry is equivalent to Applicative we still need to prove the converse, that is, obtain the Starry laws from the Applicative laws plus the definitions of idA and (.*) just above. That is not difficult; all it takes is substituting the definitions in the Starry laws and:
For left identity, noticing that
(id .) = id.For right identity, applying the interchange law and noticing that
($ id) . (.)isidin a better disguise.For associativity, using the laws to move all
(.)to the left of the(<*>)and then verifying that the resulting messes of dots in both sides are equivalent.
As a tiny example, here is the Starry instance of Maybe…
… and the verification of the laws for it:
-- Left identity:
idA .* u = u
Just id .* u = u
-- u = Nothing
Just id .* Nothing = Nothing
Nothing = Nothing
-- u = Just f
Just id .* Just f = Just f
Just (id . f) = Just f
Just f = Just f
-- Right identity:
u .* idA = u
u .* Just id = u
-- u = Nothing
Nothing .* Just id = Nothing
Nothing = Nothing
-- u = Just g
Just g .* Just id = Just g
Just (g .* id) = Just g
Just g = Just g
-- Associativity:
u .* v .* w = u .* (v .* w)
-- If any of u, v and w are Nothing, both sides will be Nothing.
Just h .* Just g .* Just f = Just h .* (Just g .* Just f)
Just (h . g) .* Just f = Just h .* (Just (g . f))
Just (h . g . f) = Just (h . (g . f))
Just (h . g . f) = Just (h . g . f)It works just as intended:
GHCi> Just (2*) .* Just (subtract 3) .* Just (*4) <*> Just 5
Just 34
GHCi> Just (2*) .* Nothing .* Just (*4) <*> Just 5
NothingI do not think there will be many opportunities to use the Starry methods in practice. We are comfortable enough with applicative style, through which we see most t (a -> b) arrows as intermediates generated on demand, rather than truly meaningful values. Furthermore, the Starry laws are not really easier to prove (though they are certainly easier to remember!). Still, it was an interesting exercise to do, and it eases my mind to know that there is a neat presentation of the Applicative laws that I can relate to.
This post is Literate Haskell, in case you wish to play with Starry in GHCi (here is the raw .lhs file ).
instance Starry Maybe where
instance Starry [] where
instance Starry ((->) a) where
instance Starry IO whereAs for proper implementations in libraries, the closest I found was Data.Semigroupoid.Static, which lives in Edward Kmett’s semigroupoids package. “Static arrows” is the actual technical term for the t (a -> b) arrows. The module provides…
… which uses the definitions shown here for idA and (.*) as id and (.) of its Category instance.
There is a reasonably well-known alternative formulation of
Applicative: theMonoidalclass as featured in this post by Edward Z. Yang. It is quite handy to work with when it comes to checking whether an instance follows the laws.↩︎Please excuse some oddities in the manuscript, such as off-kilter terminology and weird conventions (e.g. consistently naming arguments in applicative style as
w <*> v <*> urather thanu <*> v <*> win applicative style). The most baffling choice was usingidrather than()as the throwaway argument toconst. I guess I did that because($ ())looks bad in handwriting.↩︎
Post licensed under a
Creative Commons Attribution-ShareAlike 4.0 International License.
fmap is saying that it only changes the values in a container, and not its structure. Leaving behind the the functors-as-containers metaphor, we can convey the same idea by saying that fmap leaves the context of the values in a Functor unchanged. But what, exactly, is the “context” or “structure” being preserved? “It depends on the functor”, though correct, is not an entirely satisfactory answer. The functor laws, after all, are highly abstract, and make no mention of anything a programmer would be inclined to call “structure” (say, the skeleton of a list); and yet the preservation we alluded to follows from them. After struggling a bit with this question, I realised that the incompatibility is only apparent. This post shows how the tension can be resolved through the mediation of parametricity and naturality, two concepts from different domains that are intertwined in Haskell.
Categorical Cautionary Comment
A correct, if rather cruel, answer to “Why does fmap preserve structure?” would be “By definition, you silly!” To see what would be meant by that, let’s have a look at the functor laws.
fmap is a mapping of functions that takes identity to identity, and composed functions to the corresponding composed functions. Identity and composition make up the structure, in the mathematical sense, of a category. In category theory, a functor is a mapping between categories that preserves category structure. Therefore, the functor laws ensure that Haskell Functors are indeed functors; more precisely, functors from Hask to Hask, Hask being the category with Haskell types as objects and Haskell functions as arrows.1
That functors preserve category structure is evident. However, our question is not directly about “structure” in the mathematical sense, but with the looser acception it has in programmer parlance. In what follows, our goal will be clarifying this casual meaning.
What Can You Do With a Function?
As an intial, fuzzy characterisation, we can say that, given a functorial value, the Functor context is everything in it other than the wrapped values. Starting from that, a straightforward way of showing why fmap preserves context involves parametric polymorphism; more specifically, the preservation is ensured by the wild generality of the types in the signature of fmap.
We will look at fmap as a function of one argument which converts a plain a -> b function into a function which operates on functorial values. The key fact is that there is very little we can do with the a -> b function when defining fmap. Composition is not an option, as choosing a function other than id to compose it with would require knowledge about the a and b types. The only thing that can be done is applying the function to any a values we can retrieve from the t a functorial value. Since the context of a t a value, whatever it is, does not include the a values, it follows that changes to the context cannot depend on the a -> b function. Given that fmap takes no other arguments, any changes in the context must happen for any a -> b arguments uniformly. The first functor law, however, says that fmap id = id, and so there is one argument, id, which leads to no changes in the context. Therefore, fmap never changes the context.
The informal argument above can be made precise through a proper type theory treatment of parametricity. Philip Wadler’s Theorems for free! is a well-known example of such work. However, a type theory approach, while entirely appropriate, would have us taking concrete Haksell types for granted and only incidentally concluding they are functors; in contrast, our problem begins with functors. For that reason, we will follow a different path and look at the issue from a primarily categorical point of view.
What Is a Context, After All?
In the spirit of category theory, we will now focus not on the types but on the functions between them. After all, given functional purity any interesting properties of a Haskell value can be verified with suitable functions. Let’s start with a few concrete examples of how the context of a Functor can be probed with functions.
The length of a list is perhaps the most obvious example of a structural property. It depends only on the list skeleton, and not at all on the values in it. The type of length, with a fully polymorphic element type which is not mentioned by the result type, reflects such an independence. An obvious consequence is that fmap, which only affects the list elements, cannot change the length of a list. We can state that like this:
Or, in a more categorical fashion:
Our second example of a structure-probing function will be reverse:
While the result value of reverse obviously depends on the list elements, reverse cannot actually modify the elements, given that the function is fully polymorphic on the element type. fmap applied to a list after reversing it will thus affect the same element values there were before the reversal; they will only have been rearranged. In other words, fmap commutes with reverse:
Our final example will be listToMaybe from Data.Maybe:
Operationally, listToMaybe is a safe version of head, which returns Nothing when given an empty list. Again, the function is fully polymorphic in the element type, and so the value of the first element cannot be affected by it. The scenario is very similar to what we have seen for reverse, and an analogous property holds, with the only difference being that fmap is instantiated at a different Functor at each side of the equation:
Earlier we said that the Functor context consists of everything but the wrapped values. Our examples illustrate how parametric polymorphism makes it possible to keep that general idea while putting functions rather than values under the spotlight. The context is all that can be probed with functions fully polymorphic on the type parameter of the Functor; or, taking the abstraction further, the context is the collection of functions fully polymorphic on the type parameter of the Functor. We now have done away with the fuzziness of our preliminary, valure-centric definition. The next step is clarifying how that definition relates to fmap.
Your Freedom Comes Naturally
By identifying the Functor context with polymorphic functions, we can also state the context-preserving trait of fmap through commutativity equations like those shown in the above examples. For an arbitrary context-probing function r, the equation is:
The equations for reverse and listToMaybe clearly have that shape. length does not seem to fit at first sight, but that can be easily solved by lifting it to a constant functor such as the one provided by Control.Applicative.
lengthC :: [a] -> Const Int a
lengthC = Const . length
-- length = getConst . lengthC
-- For constant functors, fmap f = id regardless of f.
fmap f . lengthC = lengthC . fmap fA similar trick can be done with the Identity functor to make functions in which the type parameter of the Functor appears bare, such as Just :: a -> Maybe a, fit our scheme.
It turns out that there is a category theory concept that captures the commutativity property we are interested in. A natural transformation is a translation between functors which preserves arrows being mapped through them. For Haskell Functors, that amounts to preserving functions being mapped via fmap. We can display the relation through a diagram:
![Naturality for Haskell Functors. Example instantation: T = []; U = Maybe; r = listToMaybe.](../images/posts/what-does-fmap-preserve/naturality-diagram.png)
Functors. Example instantation: T = []; U = Maybe; r = listToMaybe.The naturality condition matches our commuativity property. Indeed, polymorphic functions are natural transformations between Haskell Functors. The proof of this appealing result is not trivial, and requires some theoretical work, just like in the case of the closely related results about parametricity we alluded to earlier. In any case, all it takes to go from “natural transformations preserve fmap” to “fmap preserves natural transformations” is tilting our heads while looking at the diagram above!
Given how we identified Functor contexts, polymorphic functions and natural transformations, we can finally give a precise answer to our question. The context consists of natural transformations between functors, and therefore fmap preserves it.
Structures and Structures
Earlier on, we have said that we would not be directly concerned with structure in the sense mathematicians use the word, but only with the fuzzy Haskell concept that sometimes goes by the same name. To wrap things up, we will now illustrate the fact that both acceptions are not worlds apart. Let’s have another look at the second functor law, which states that fmap preserves composition:
Structure, in the mathematical sense, refers to some collection of interesting operations and distinguished elements. In this example, the relevant operation is function composition, which is part of the structure of the Hask category. Besides that, however, we are now able to note the uncanny resemblance between the shapes of the law, which says that it does not matter whether we compose f and g before applying fmap, and of the commutativity properties we used to characterise functorial contexts. The upshot is that by identifying context and structure of a Functor with polymorphic functions, we retain much of the spirit of the mathematical usage of structure. The interesting operations, in our case, are the polymorphic functions with which the context is probed. Perhaps it even makes sense to keep talking of structure of a Functor even after dropping the container metaphor.
fmap Preserves fmap
Speaking of the second law, we will, just for kicks, use it to show how to turn things around and look at fmap as a natural transformation between Functors. In order to do so, we have to recall that (.) is fmap for the function functor:
-- First, we rewrite the second law in a more suggestive form:
fmap (g . f) = fmap g . fmap f
fmap (((.) g) f) = (.) (fmap g) (fmap f)
fmap . (.) g = ((.) . fmap) g . fmap
-- Next, some synonyms to indicate the Functors fmap leads to.
-- fmap from identity to t
fmap_t :: (Functor t) => (->) a b -> (->) (t a) (t b)
fmap_t = fmap
-- fmap from identity to ((->) a)
fmap_fun :: (b -> c) -> ((->) a b -> (->) a c)
fmap_fun = (.)
-- fmap from identity to the composite functor ((->) (t a)) . t
fmap_fun_t :: (Functor t)
=> (b -> c) -> ((->) (t a) (t b) -> (->) (t a) (t c))
fmap_fun_t = fmap_fun . fmap_t
-- The second law then becomes:
fmap_t . fmap_fun g = fmap_fun_t g . fmap_t
-- That, however, shows fmap_t is a natural transformation:
fmap . fmap g = fmap g . fmapBy fixing t and a in the signature of fmap_t above, we get one functor on either side of the outer function arrow: ((->) a) on the left and ((->) (t a)) . t on the right. fmap is a natural transformation between these two functors.
Further Reading
In The Holy Trinity, Robert Harper comments on the deep connection between logic, type theory and category theory that allows us to shift seamlessly between the categorical and the type theoretical perspectives, as we have done here.
You Could Have Defined Natural Transformations by Dan Piponi is a very clear introduction to natural transformations in a Haskell context.
We have already mentioned Philip Wadler’s Theorems for free!, which is a reasonably accessible introduction to the free theorems. Free theorems are results about functions that, thanks to parametric polymorphism, can be deduced from the type of the function alone. Given suitable generalisations, free theorems and naturality conditions provide two parallel ways of reaching the same results about Haskell functions.
Free Theorems Involving Type Constructor Classes, a functional pearl by Janis Voigtländer that illustrates how free theorem generation can be generalised to types parametric on type constructors and type classes.
For an explicitly categorical perspective on parametricity, a good place to start if you are willing to dig into theory is the section on parametricity in Some Aspects of Categories in Computer Science by Philip J. Scott.
A category theory primer would be too big a detour for this post. If the category theory concepts I just mentioned are new to you, I suggest the following gentle introductions for Haskellers, which have very different approaches: Haskell Wikibook chapter on category theory, and Gabriella Gonzalez’s posts The category design pattern and The functor design pattern.↩︎
Post licensed under a
Creative Commons Attribution-ShareAlike 4.0 International License.
lens library are its astonishing breadth and generality. And yet, the whole edifice is built around van Laarhoven lenses, which are a simple and elegant concept. In this hands-on exposition, I will show how the Lens type can be understood without prerequisites other than a passing acquaintance with Haskell functors. Encouraging sound intuition in an accessible manner can go a long way towards making lens and lenses less intimidating.
Humble Beginnings
Dramatis personæ:
I will define a toy data type so that we have something concrete to play with, as well as a starting point for working out generalisations.
The record definition gets us a function for accessing the bar field.
As for the setter, we have to define it ourselves, unless we feel like mucking around with record update syntax.
Armed with a proper getter and setter pair, we can easily flip the sign of the bar inside a Foo.
We can make it even easier by defining a modifier function for bar.
setBar can be recovered from modifyBar by using const to discard the original value and put the new one in its place.
If our data type had several fields, defining a modifier for each of them would amount to quite a lot of boilerplate. We could minimise it by, starting from our modifyBar definition, abstracting from the specific getter and setter for bar. Here, things begin to pick up steam. I will define a general modify function, which, given an appropriate getter-setter pair, can deal with any field of any data type.
modify :: (s -> a) -> (s -> a -> s) -> (a -> a) -> s -> s
modify getter setter k x = setter x . k . getter $ xIt is trivial to recover modifyBar; when we do so, s becomes Foo and a becomes Int.
Functors Galore
The next step of generalisation is the one leap of faith I will ask of you in the way towards lenses. I will introduce a variant of modify in which the modifying function, rather than being a plain a -> a function, returns a functorial value. Defining it only takes an extra fmap.
modifyF :: Functor f => (s -> a) -> (s -> a -> s)
-> (a -> f a) -> s -> f s
modifyF getter setter k x = fmap (setter x) . k . getter $ xAnd here is its specialisation for bar.
Why on Earth we would want to do that? For one, it allows for some nifty tricks depending on the functor we choose. Let’s try it with lists. Specialising the modifyF type would give:
Providing the getter and the setter would result in a (a -> [a]) -> s -> [s] function. Can you guess what it would do?
As the types suggest, we get a function which modifies the field in multiple ways and collects the results.
I claimed that moving from modify to modifyF was a generalisation. Indeed, we can recover modify by bringing Identity, the dummy functor, into play.
newtype Identity a = Identity { runIdentity :: a }
instance Functor Identity where
fmap f (Identity x) = Identity (f x)modify' :: (s -> a) -> (s -> a -> s) -> (a -> a) -> s -> s
modify' getter setter k =
runIdentity . modifyF getter setter (Identity . k)We wrap the field value with Identity value after applying k and unwrap the final result after applying the setter. Since Identity does nothing interesting to the wrapped values, the overall result boils down to our original modify. If you have found this definition confusing, I suggest that you, as an exercise, rewrite it in pointful style and substitute the definition of modifyF.
We managed to get modify back with little trouble, which is rather interesting. However, what is truly surprising is that we can reconstruct not only the modifier but also the getter! To pull that off, we will use Const, which is a very quaint functor.
newtype Const a b = Const { getConst :: a }
instance Functor (Const a) where
fmap _ (Const y) = Const yIf functors were really containers, Const would be an Acme product. A Const a b value does not contain anything of type b; what it does contain is an a value that we cannot even modify, given that fmap f is id regardless of what f is. As a consequence, if, given a field of type a, we pick Const a as the functor to use with modifyF and use the modifying function to wrap the field value with Const, then the value will not be affected by the setter, and we will be able to recover it later. That suffices for recovering the getter.
get :: (s -> a) -> (s -> a -> s) -> s -> a
get getter setter = getConst . modifyF getter setter Const
getBar :: Foo -> Int
getBar = get bar setBarThe Grand Unification
Given a getter and a setter, modifyF gets us a corresponding functorial modifier. From it, by choosing the appropriate functors, we can recover the getter and a plain modifier; the latter, in turn, allows us to recover the setter. We can highlight the correspondence by redefining once more the recovered getters and modifiers, this time in terms of the functorial modifier.
modify'' :: ((a -> Identity a) -> s -> Identity s) -> (a -> a) -> s -> s
modify'' modifier k = runIdentity . modifier (Identity . k)
modifyBar'' :: (Int -> Int) -> Foo -> Foo
modifyBar'' = modify'' modifyBarF
set :: ((a -> Identity a) -> s -> Identity s) -> s -> a -> s
set modifier x y = modify'' modifier (const y) x
setBar'' :: Foo -> Int -> Foo
setBar'' = set modifyBarF
get' :: ((a -> Const a a) -> s -> Const a s) -> (s -> a)
get' modifier = getConst . modifier Const
getBar' :: Foo -> Int
getBar' = get' modifyBarFThe bottom line is that given modifyBarF we can get by without modifyBar, setBar and bar, as modify'', set and get' allow us to reconstruct them whenever necessary. While our first version of get was, in effect, just a specialised const with a wacky implementation, get' is genuinely useful because it cuts the number of separate field manipulation functions we have to deal with by a third.
Expanding Horizons
Even after all of the work so far we can still generalise further! Let’s have a second look at modifyF.
modifyF :: Functor f => (s -> a) -> (s -> a -> s)
-> (a -> f a) -> s -> f s
modifyF getter setter k x = fmap (setter x) . k . getter $ xThe type of setter is (s -> a -> s); however, nothing in the implementation forces the first argument and the result to have the same type. Furthermore, with a different signature k could have a more general type, (a -> f b), as long as the type of setter was adjusted accordingly. We can thus give modifyF a more general type.
modifyGenF :: Functor f => (s -> a) -> (s -> b -> t)
-> (a -> f b) -> s -> f t
modifyGenF getter setter k x = fmap (setter x) . k . getter $ xFor the sake of completeness, here are the generalised recovery functions. get is not included because the generalisation does not affect it.
modifyGen :: ((a -> Identity b) -> s -> Identity t) -> (a -> b) -> s -> t
modifyGen modifier k = runIdentity . modifier (Identity . k)
setGen :: ((a -> Identity b) -> s -> Identity t) -> s -> b -> t
setGen modifier x y = modifyGen modifier (const y) xBy now, it is clear that our getters and setters need not be ways to manipulate fields in a record. In a broader sense, a getter is anything that produces a value from another; in other words, any function can be a getter. By the same token, any binary function can be a setter, as all that is required is that it combines one value with another producing a third; the initial and final values do not even need to have the same type.1 That is a long way from the toy data type we started with!
The Reveal
If we look at modifyGenF as a function of two arguments, its result type becomes:
Now, let’s take a peek at Control.Lens.Lens:
It is the same type! We have reached our destination.2 A lens is what we might have called a generalised functorial modifier; furthermore, sans implementation details we have that:
- The
lensfunction ismodifyGenF; modifyFislensspecialised to produce simple lenses;3modifyBarFis a lens with typeLens Foo Foo Int Int;(^.)is flippedget';setissetGen;overismodifyGenfurther generalised.4
lens uses type synonyms liberally, so those correspondences are not immediately obvious form the signatures in the documentation. Digging a little deeper, however, shows that in
ASetter is merely
Analogously, we have
Behind the plethora of type synonyms - ASetter, Getting, Fold, Traversal, Prism, Iso and so forth - there are different choices of functors,5 which make it possible to capture many different concepts as variations on lenses. The variations may be more general or less general than lenses; occasionally they are neither, as the overlap is just partial. The fact that we can express so much through parametrization of functors is key to the extraordinary breadth of lens.
Going Forward
This exposition is primarily concerned with building lenses, and so very little was said about how to use them. In any case, we have seen enough to understand why lenses are also known as functional references. By unifying getters and setters, lenses provide a completely general vocabulary to point at parts of a whole.
Finally, a few words about composition of lenses are unavoidable. One of the great things about lenses is that they are just functions; even better, they are functions with signatures tidy enough for them to compose cleanly with (.). That makes it possible to compose lenses independently of whether you intend to get, set or modify their targets. Here is a quick demonstration using the tuple lenses from lens.
GHCi> :m
GHCi> :m +Control.Lens
GHCi> ((1,2),(3,4)) ^. _1 . _2
GHCi> 2
GHCi> set (_1 . _2) 0 ((1,2),(3,4))
GHCi> ((1,0),(3,4))A perennial topic in discussions about lens is the order of composition of lenses. They are often said to compose backwards; that is, backwards with respect to composition of record accessors and similar getters. For instance, the getter corresponding to the _1 . _2 lens is snd . fst. The claim that lenses compose backwards, or in the “wrong order”, however, are only defensible when talking about style, and not about semantics. That becomes clear after placing the signatures of a getter and its corresponding lens side by side.
GHCi> :t fst
fst :: (a, b) -> a
GHCi> :t _1 :: Lens' (a, b) a
_1 :: Lens' (a, b) a
:: Functor f => (a -> f a) -> (a, b) -> f (a, b)The getter takes a value of the source type and produces a value of the target type. The lens, however, takes a function from the target type and produces a function from the source type. Therefore, it is no surprise that the order of composition differs, and the order for lenses is entirely natural. That ties in closely to what we have seen while implementing lenses. While we can squeeze lenses until they give back getters, it is much easier to think of them as generalised modifiers.
We are not quite as free when it comes to pairing getters and setters. Beyond the obvious need for getter and setter to start from values of the same type, they should behave sanely when composed. In particular, the following should hold:
↩︎get' modifier (setGen modifier y x) ≡ y setGen modifier (get' modifier x) x ≡ x setGen modifier z (setGen modifier y x) ≡ setGen modifier z x“What about the
forall?” you might ask. Are we cheating? Not quite. Theforallis there to control howfis specialised when lens combinators are used. The underlying issue does not affect our reasoning here. If you are into type system subtleties, there were a few interesting comments about it in the reddit thread for this post.↩︎Lens' s aorLens s s a a, as opposed toLens s t a b.↩︎Yes, even further; from taking modifying functions to taking modifying profunctors. The difference need not worry us now.↩︎
And in some cases of profunctors to replace the function type constructor.↩︎
Post licensed under a
Creative Commons Attribution-ShareAlike 4.0 International License.