Wed 26 Dec 2012
Abstracting with Applicatives
Posted by Gershom Bazerman under Category Theory , Data Structures , Monoids[56] Comments
Consider the humble Applicative. More than a functor, less than a monad. It gives us such lovely syntax. Who among us still prefers to write liftM2 foo a b when we could instead write foo <$> a <*> b? But we seldom use the Applicative as such — when Functor is too little, Monad is too much, but a lax monoidal functor is just right. I noticed lately a spate of proper uses of Applicative —Formlets (and their later incarnation in the reform library), OptParse-Applicative (and its competitor library CmdTheLine), and a post by Gergo Erdi on applicatives for declaring dependencies of computations. I also ran into a very similar genuine use for applicatives in working on the Panels library (part of jmacro-rpc), where I wanted to determine dependencies of a dynamically generated dataflow computation. And then, again, I stumbled into an applicative while cooking up a form validation library, which turned out to be a reinvention of the same ideas as formlets.
Given all this, It seems post on thinking with applicatives is in order, showing how to build them up and reason about them. One nice thing about the approach we'll be taking is that it uses a "final" encoding of applicatives, rather than building up and then later interpreting a structure. This is in fact how we typically write monads (pace operational, free, etc.), but since we more often only determine our data structures are applicative after the fact, we often get some extra junk lying around (OptParse-Applicative, for example, has a GADT that I think is entirely extraneous).
So the usual throat clearing:
{-# LANGUAGE TypeOperators, MultiParamTypeClasses, FlexibleInstances, StandaloneDeriving, FlexibleContexts, UndecidableInstances, GADTs, KindSignatures, RankNTypes #-} module Main where import Control.Applicative hiding (Const) import Data.Monoid hiding (Sum, Product) import Control.Monad.Identity instance Show a => Show (Identity a) where show (Identity x) = "(Identity " ++ show x ++ ")"
And now, let's start with a classic applicative, going back to the Applicative Programming With Effects paper:
data Const mo a = Const mo deriving Show instance Functor (Const mo) where fmap _ (Const mo) = Const mo instance Monoid mo => Applicative (Const mo) where pure _ = Const mempty (Const f) < *> (Const x) = Const (f <> x)
(Const lives in transformers as the Constant functor, or in base as Const)
Note that Const is not a monad. We've defined it so that its structure is independent of the `a` type. Hence if we try to write (>>=) of type Const mo a -> (a -> Const mo b) -> Const mo b, we'll have no way to "get out" the first `a` and feed it to our second argument.
One great thing about Applicatives is that there is no distinction between applicative transformers and applicatives themselves. This is to say that the composition of two applicatives is cleanly and naturally always also an applicative. We can capture this like so:
newtype Compose f g a = Compose (f (g a)) deriving Show instance (Functor f, Functor g) => Functor (Compose f g) where fmap f (Compose x) = Compose $ (fmap . fmap) f x instance (Applicative f, Applicative g) => Applicative (Compose f g) where pure = Compose . pure . pure (Compose f) < *> (Compose x) = Compose $ (< *>) < $> f < *> x
(Compose also lives in transformers)
Note that Applicatives compose two ways. We can also write:
data Product f g a = Product (f a) (g a) deriving Show instance (Functor f, Functor g) => Functor (Product f g) where fmap f (Product x y) = Product (fmap f x) (fmap f y) instance (Applicative f, Applicative g) => Applicative (Product f g) where pure x = Product (pure x) (pure x) (Product f g) < *> (Product x y) = Product (f < *> x) (g < *> y)
(Product lives in transformers as well)
This lets us now construct an extremely rich set of applicative structures from humble beginnings. For example, we can reconstruct the Writer Applicative.
type Writer mo = Product (Const mo) Identity tell :: mo -> Writer mo () tell x = Product (Const x) (pure ())
-- tell [1] *> tell [2] -- > Product (Const [1,2]) (Identity ())
Note that if we strip away the newtype noise, Writer turns into (mo,a) which is isomorphic to the Writer monad. However, we've learned something along the way, which is that the monoidal component of Writer (as long as we stay within the rules of applicative) is entirely independent from the "identity" component. However, if we went on to write the Monad instance for our writer (by defining >>=), we'd have to "reach in" to the identity component to grab a value to hand back to the function yielding our monoidal component. Which is to say we would destroy this nice seperation of "trace" and "computational content" afforded by simply taking the product of two Applicatives.
Now let's make things more interesting. It turns out that just as the composition of two applicatives may be a monad, so too the composition of two monads may be no stronger than an applicative!
We'll see this by introducing Maybe into the picture, for possibly failing computations.
type FailingWriter mo = Compose (Writer mo) Maybe tellFW :: Monoid mo => mo -> FailingWriter mo () tellFW x = Compose (tell x *> pure (Just ())) failFW :: Monoid mo => FailingWriter mo a failFW = Compose (pure Nothing)
-- tellFW [1] *> tellFW [2] -- > Compose (Product (Const [1,2]) (Identity Just ())) -- tellFW [1] *> failFW *> tellFW [2] -- > Compose (Product (Const [1,2]) (Identity Nothing))
Maybe over Writer gives us the same effects we'd get in a Monad — either the entire computation fails, or we get the result and the trace. But Writer over Maybe gives us new behavior. We get the entire trace, even if some computations have failed! This structure, just like Const, cannot be given a proper Monad instance. (In fact if we take Writer over Maybe as a Monad, we get only the trace until the first point of failure).
This seperation of a monoidal trace from computational effects (either entirely independent of a computation [via a product] or independent between parts of a computation [via Compose]) is the key to lots of neat tricks with applicative functors.
Next, let's look at Gergo Erdi's "Static Analysis with Applicatives" that is built using free applicatives. We can get essentially the same behavior directly from the product of a constant monad with an arbitrary effectful monad representing our ambient environment of information. As long as we constrain ourselves to only querying it with the takeEnv function, then we can either read the left side of our product to statically read dependencies, or the right side to actually utilize them.
type HasEnv k m = Product (Const [k]) m takeEnv :: (k -> m a) -> k -> HasEnv k m a takeEnv f x = Product (Const [x]) (f x)
If we prefer, we can capture queries of a static environment directly with the standard Reader applicative, which is just a newtype over the function arrow. There are other varients of this that perhaps come closer to exactly how Erdi's post does things, but I think this is enough to demonstrate the general idea.
data Reader r a = Reader (r -> a) instance Functor (Reader r) where fmap f (Reader x) = Reader (f . x) instance Applicative (Reader r) where pure x = Reader $ pure x (Reader f) < *> (Reader x) = Reader (f < *> x) runReader :: (Reader r a) -> r -> a runReader (Reader f) = f takeEnvNew :: (env -> k -> a) -> k -> HasEnv k (Reader env) a takeEnvNew f x = Product (Const [x]) (Reader $ flip f x)
So, what then is a full formlet? It's something that can be executed in one context as a monoid that builds a form, and in another as a parser. so the top level must be a product.
type FormletOne mo a = Product (Const mo) Identity a
Below the product, we read from an environment and perhaps get an answer. So that's reader with a maybe.
type FormletTwo mo env a = Product (Const mo) (Compose (Reader env) Maybe) a
Now if we fail, we want to have a trace of errors. So we expand out the Maybe into a product as well to get the following, which adds monoidal errors:
type FormletThree mo err env a = Product (Const mo) (Compose (Reader env) (Product (Const err) Maybe)) a
But now we get errors whether or not the parse succeeds. We want to say either the parse succeeds or we get errors. For this, we can turn to the typical Sum functor, which currently lives as Coproduct in comonad-transformers, but will hopefully be moving as Sum to the transformers library in short order.
data Sum f g a = InL (f a) | InR (g a) deriving Show instance (Functor f, Functor g) => Functor (Sum f g) where fmap f (InL x) = InL (fmap f x) fmap f (InR y) = InR (fmap f y)
The Functor instance is straightforward for Sum, but the applicative instance is puzzling. What should "pure" do? It needs to inject into either the left or the right, so clearly we need some form of "bias" in the instance. What we really need is the capacity to "work in" one side of the sum until compelled to switch over to the other, at which point we're stuck there. If two functors, F and G are in a relationship such that we can always send f x -> g x in a way that "respects" fmap (that is to say, such that (fmap f . fToG == ftoG . fmap f) then we call this a natural transformation. The action that sends f to g is typically called "eta". (We actually want something slightly stronger called a "monoidal natural transformation" that respects not only the functorial action fmap but the applicative action <*>, but we can ignore that for now).
Now we can assert that as long as there is a natural transformation between g and f, then Sum f g can be made an Applicative, like so:
class Natural f g where eta :: f a -> g a instance (Applicative f, Applicative g, Natural g f) => Applicative (Sum f g) where pure x = InR $ pure x (InL f) < *> (InL x) = InL (f < *> x) (InR g) < *> (InR y) = InR (g < *> y) (InL f) < *> (InR x) = InL (f < *> eta x) (InR g) < *> (InL x) = InL (eta g < *> x)
The natural transformation we'll tend to use simply sends any functor to Const.
instance Monoid mo => Natural f (Const mo) where
    eta = const (Const mempty)
However, there are plenty of other natural transformations that we could potentially make use of, like so:
instance Applicative f => Natural g (Compose f g) where eta = Compose . pure instance (Applicative g, Functor f) => Natural f (Compose f g) where eta = Compose . fmap pure instance (Natural f g) => Natural f (Product f g) where eta x = Product x (eta x) instance (Natural g f) => Natural g (Product f g) where eta x = Product (eta x) x instance Natural (Product f g) f where eta (Product x _ ) = x instance Natural (Product f g) g where eta (Product _ x) = x instance Natural g f => Natural (Sum f g) f where eta (InL x) = x eta (InR y) = eta y instance Natural Identity (Reader r) where eta (Identity x) = pure x
In theory, there should also be a natural transformation that can be built magically from the product of any other two natural transformations, but that will just confuse the Haskell typechecker hopelessly. This is because we know that often different "paths" of typeclass choices will often be isomorphic, but the compiler has to actually pick one "canonical" composition of natural transformations to compute with, although multiple paths will typically be possible.
For similar reasons of avoiding overlap, we can't both have the terminal homomorphism that sends everything to "Const" and the initial homomorphism that sends "Identity" to anything like so:
-- instance Applicative g => Natural Identity g where -- eta (Identity x) = pure x
We choose to keep the terminal transformation around because it is more generally useful for our purposes. As the comments below point out, it turns out that a version of "Sum" with the initial transformation baked in now lives in transformers as Lift.
In any case we can now write a proper Validation applicative:
type Validation mo = Sum (Const mo) Identity validationError :: Monoid mo => mo -> Validation mo a validationError x = InL (Const x)
This applicative will yield either a single result, or an accumulation of monoidal errors. It exists on hackage in the Validation package.
Now, based on the same principles, we can produce a full Formlet.
type Formlet mo err env a = Product (Const mo) (Compose (Reader env) (Sum (Const err) Identity)) a
All the type and newtype noise looks a bit ugly, I'll grant. But the idea is to think with structures built with applicatives, which gives guarantees that we're building applicative structures, and furthermore, structures with certain guarantees in terms of which components can be interpreted independently of which others. So, for example, we can strip away the newtype noise and find the following:
type FormletClean mo err env a = (mo, env -> Either err a)
Because we built this up from our basic library of applicatives, we also know how to write its applicative instance directly.
Now that we've gotten a basic algebraic vocabulary of applicatives, and especially now that we've produced this nifty Sum applicative (which I haven't seen presented before), we've gotten to where I intended to stop.
But lots of other questions arise, on two axes. First, what other typeclasses beyond applicative do our constructions satisfy? Second, what basic pieces of vocabulary are missing from our constructions — what do we need to add to flesh out our universe of discourse? (Fixpoints come to mind).
Also, what statements can we make about "completeness" — what portion of the space of all applicatives can we enumerate and construct in this way? Finally, why is it that monoids seem to crop up so much in the course of working with Applicatives? I plan to tackle at least some of these questions in future blog posts.

December 26th, 2012 at 8:43 pm
It seems to me that the reason that Const c is not a monad is because of return, not bind. Const c >>= f = Const c should do the trick.
December 26th, 2012 at 8:46 pm
Oh, I see. You couldn’t define bind in a way that is consistent with the Applicative instance (and we had Monoid c anyway so return wouldn’t have been a problem). Sloppy reading :-/
December 26th, 2012 at 8:52 pm
Const c >>= f doesn’t work
return a >>= f = f a is a Monad law.
Consider:
return a >>= \ _ -> Const “hello”
But from that definition
return a >>= \ _ -> Const “hello” = Const “”
but
(\ _ -> Const “hello”) a = Const “hello”
Your proposal only works when mempty is the only value of your monoid. It works for Const (), but nothing else really.
December 27th, 2012 at 5:05 am
Great article!
I came across the Sum applicative for the first time just two days ago in this comment on Stack Overflow by Conor McBride [1]. There he notes Identity is the initial Applicative functor, so you can replace that last Natural instance with:
instance Applicative g => Natural Identity g where
eta (Identity x) = pure x
[1] http://stackoverflow.com/questions/14022791/what-is-control-applicative-lift-useful-for/14022871#comment19369023_14022871
December 27th, 2012 at 11:53 am
In the example of the FailingWriter, you write ‘runFailingWriter $ …’, but don’t provide a definition of it. From the actual output, I don’t think you actually meant to write it, as the current output makes it seem that the definition would just be `id`. Or perhaps you meant to provide a definition that would yield a different output, perhaps (monoid, Maybe a), stripping away the newtype noise?
December 27th, 2012 at 12:45 pm
Thanks for the comments — I’ve fixed the post appropriately. I came across “Sum” on my own, and I wasn’t familiar with the “Lift” specialization of it in transformers. Not surprised that Conor and Ross beat me to it!
As the edited post notes, we can’t actually add that Identity instance for Natural without overlapping too often with the Const instance. The poor typechecker can’t decide if it should send everything to Const, or Identity to anything.
December 29th, 2012 at 10:18 am
Cool post, reminds me about a similar observation I made about the writer monad (http://blog.ezyang.com/2012/10/generalizing-the-programmable-semicolon/); namely, that the tracing behaviour of writer is independent of the computational component.
November 8th, 2013 at 10:45 pm
[...] was suggested, but I wondered if this could be modeled more generally via applicative functors. In Abstracting with Applicatives, Bazerman shows us that the sum of two applicative functors is also an applicative functor, with [...]
May 19th, 2014 at 9:47 am
webpage…
The Comonad.Reader » Abstracting with Applicatives…
September 23rd, 2022 at 5:21 am
Viagra 20 mg best price https://500px.com/p/skulogovid/?view=groups...
You actually revealed that fantastically….
September 24th, 2022 at 2:31 am
Viagra 20 mg https://reallygoodemails.com/canadianpharmaceuticalsonlineusa...
Whoa loads of excellent material!…
September 24th, 2022 at 6:04 am
Viagra reviews https://www.provenexpert.com/canadian-pharmaceuticals-online-usa/...
Cheers, I like this….
September 24th, 2022 at 11:10 am
Buy viagra https://sanangelolive.com/members/pharmaceuticals...
You actually stated this effectively….
September 26th, 2022 at 10:11 am
Viagra canada https://melaninterest.com/user/canadian-pharmaceuticals-online/?view=likes...
Awesome knowledge. Thank you!…
September 26th, 2022 at 2:12 pm
Buy viagra online https://haikudeck.com/canadian-pharmaceuticals-online-personal-presentation-827506e003...
Whoa quite a lot of useful facts!…
September 26th, 2022 at 6:20 pm
Viagra tablets https://buyersguide.americanbar.org/profile/420642/0...
You expressed this exceptionally well!…
September 27th, 2022 at 2:01 am
Tadalafil 5mg https://experiment.com/users/canadianpharmacy...
Thanks! A lot of data.
…
September 27th, 2022 at 7:58 am
canadian pharmacy meds https://slides.com/canadianpharmaceuticalsonline...
Thanks a lot. Ample material.
…
September 27th, 2022 at 11:39 am
Viagra tablets australia https://challonge.com/esapenti...
Wonderful content. Appreciate it….
September 27th, 2022 at 4:05 pm
Viagra tablets australia https://challonge.com/gotsembpertvil...
You reported this perfectly!…
September 28th, 2022 at 5:48 am
Online viagra https://challonge.com/citlitigolf...
Effectively spoken without a doubt. ….
September 28th, 2022 at 9:21 am
ivermectina dosis https://order-stromectol-over-the-counter.estranky.cz/clanky/order-stromectol-over-the-counter.html...
With thanks, I appreciate this….
September 28th, 2022 at 3:48 pm
ivermectin for humans https://soncheebarxu.estranky.cz/clanky/stromectol-for-head-lice.html...
This is nicely put. ….
September 29th, 2022 at 9:05 am
Viagra 5 mg https://dsdgbvda.zombeek.cz/...
Truly all kinds of useful knowledge!…
September 29th, 2022 at 3:34 pm
Viagra sans ordonnance https://inflavnena.zombeek.cz/...
Very well spoken of course! !…
September 30th, 2022 at 9:48 am
canadian pharmacy online https://www.myscrsdirectory.com/profile/421708/0...
Thanks! Lots of content.
…
September 30th, 2022 at 5:02 pm
Viagra manufacturer coupon https://supplier.ihrsa.org/profile/421717/0...
Nicely put. Kudos….
October 1st, 2022 at 7:22 am
Online viagra https://wefbuyersguide.wef.org/profile/421914/0...
Wonderful postings. Regards!…
October 1st, 2022 at 11:25 am
Viagra tablets australia https://legalmarketplace.alanet.org/profile/421920/0...
Terrific data. With thanks….
October 2nd, 2022 at 4:59 am
Viagra uk https://moaamein.nacda.com/profile/422018/0...
You explained this fantastically….
October 2nd, 2022 at 9:25 am
Tadalafil tablets https://www.audiologysolutionsnetwork.org/profile/422019/0...
Wow plenty of useful data!…
October 2nd, 2022 at 12:43 pm
Low cost viagra 20mg https://network.myscrs.org/profile/422020/0...
Effectively expressed certainly. !…
October 3rd, 2022 at 6:28 am
Viagra generico https://sanangelolive.com/members/canadianpharmaceuticalsonlineusa...
Beneficial write ups. Thanks a lot!…
October 3rd, 2022 at 9:56 am
Viagra sans ordonnance https://sanangelolive.com/members/girsagerea...
Thanks. Terrific stuff….
October 4th, 2022 at 8:45 am
Interactions for viagra https://www.ecosia.org/search?q=“My Canadian Pharmacy – Extensive Assortment of Medications – 2022″…
You stated this wonderfully….
October 4th, 2022 at 12:54 pm
canada drug pharmacy https://www.mojomarketplace.com/user/Canadianpharmaceuticalsonline-EkugcJDMYH...
This is nicely put! !…
October 4th, 2022 at 4:55 pm
Viagra generika https://seedandspark.com/user/canadian-pharmaceuticals-online...
You made your point!…
October 5th, 2022 at 9:57 am
Viagra generico online https://www.giantbomb.com/profile/canadapharmacy/blog/canadian-pharmaceuticals-online/265652/...
Awesome facts, Many thanks….
October 5th, 2022 at 1:50 pm
Viagra 20 mg https://feeds.feedburner.com/bing/Canadian-pharmaceuticals-online...
Very good write ups, Cheers….
October 5th, 2022 at 6:33 pm
canadian prescriptions online https://search.gmx.com/web/result?q=“My Canadian Pharmacy – Extensive Assortment of Medications – 2022″…
Really plenty of helpful data….
October 6th, 2022 at 3:38 am
Viagra 5mg https://search.seznam.cz/?q=“My Canadian Pharmacy – Extensive Assortment of Medications – 2022″…
You reported that fantastically….
October 6th, 2022 at 7:21 am
Tadalafil 5mg https://sanangelolive.com/members/unsafiri...
Amazing plenty of beneficial info!…
October 6th, 2022 at 11:35 am
Canadian viagra …
Awesome data. Thanks….
October 6th, 2022 at 5:32 pm
Viagra alternative https://swisscows.com/en/web?query=“My Canadian Pharmacy – Extensive Assortment of Medications – 2022″…
With thanks! I like it….
October 7th, 2022 at 5:02 am
Viagra 5mg prix https://www.dogpile.com/serp?q=“My Canadian Pharmacy – Extensive Assortment of Medications – 2022″…
You explained it superbly!…
October 7th, 2022 at 12:11 pm
Viagra tablets australia …
Seriously many of useful data….
October 8th, 2022 at 8:05 am
Viagra manufacturer coupon https://search.givewater.com/serp?q=“My Canadian Pharmacy – Extensive Assortment of Medications – 2022″…
Truly a good deal of wonderful information!…
October 8th, 2022 at 1:34 pm
Viagra manufacturer coupon https://www.bakespace.com/members/profile/Сanadian pharmaceuticals for usa sales/1541108/…
Nicely put. Thanks a lot….
October 9th, 2022 at 6:42 am
trust pharmacy canada …
Thanks a lot, I value this….
October 9th, 2022 at 11:50 am
Tadalafil tablets https://results.excite.com/serp?q=“My Canadian Pharmacy – Extensive Assortment of Medications – 2022″…
Lovely material, Thanks a lot!…
October 9th, 2022 at 4:21 pm
canadian viagra https://www.infospace.com/serp?q=“My Canadian Pharmacy – Extensive Assortment of Medications – 2022″…
Valuable info. With thanks….
October 10th, 2022 at 8:37 am
Buy viagra online https://headwayapp.co/canadianppharmacy-changelog...
Thank you. I like it….
October 11th, 2022 at 6:37 am
canadian drugstore https://results.excite.com/serp?q=“My Canadian Pharmacy – Extensive Assortment of Medications – 2022″…
With thanks! Fantastic stuff!…
October 11th, 2022 at 12:02 pm
cialis canadian pharmacy https://canadianpharmaceuticalsonline.as.me/schedule.php...
Really a lot of helpful data!…
October 13th, 2022 at 1:54 pm
Viagra vs viagra https://feeds.feedburner.com/bing/stromectolnoprescription...
Really all kinds of superb material!…
October 14th, 2022 at 6:18 am
Viagra 5mg https://reallygoodemails.com/orderstromectoloverthecounterusa...
Valuable data. Regards….