16

Applicative is a Monoidal Functor :

mappend :: f         -> f   -> f
$       ::  (a -> b) ->   a ->   b
<*>     :: f(a -> b) -> f a -> f b

But I don't see any reference about Monoid in the definition of the Applicative typeclass, could you tell me why ?

Definition :

class Functor f => Applicative (f :: * -> *) where
  pure :: a -> f a
  (<*>) :: f (a -> b) -> f a -> f b
  GHC.Base.liftA2 :: (a -> b -> c) -> f a -> f b -> f c
  (*>) :: f a -> f b -> f b
  (<*) :: f a -> f b -> f a
  {-# MINIMAL pure, ((<*>) | liftA2) #-}

No mention of that structural Monoid is provided in this definition, but when you do

> ("ab",(+1)) <*> ("cd", 5) 
>("abcd", 6)

You can clearly see the use of a Structural Monoid "(,) String" when implementing this instance of Applicative.

Another example to show that a "Structural Monoid" is used :

Prelude Data.Monoid> (2::Integer,(+1)) <*> (1::Integer,5)

<interactive>:35:1: error:
    • Could not deduce (Monoid Integer) arising from a use of ‘<*>’
      from the context: Num b
        bound by the inferred type of it :: Num b => (Integer, b)
        at <interactive>:35:1-36
    • In the expression: (2 :: Integer, (+ 1)) <*> (1 :: Integer, 5)
      In an equation for ‘it’:
          it = (2 :: Integer, (+ 1)) <*> (1 :: Integer, 5)
duplode
  • 33,731
  • 7
  • 79
  • 150
Nicolas Henin
  • 3,244
  • 2
  • 21
  • 42
  • 1
    `f` has the wrong kind to be `Monoid`. – Lee Jun 05 '18 at 14:51
  • yeah but how could we express it in Applicative ? are we limited by what haskell can do ? I'd like to understand why we see nothing about Monoid when we look at the definition.. – Nicolas Henin Jun 05 '18 at 14:55
  • 5
    Because the term "monoidal functor" is one chunk that can't be broken into to pieces, "a monoid and a functor". It means a functor that acts on a monoidal category and preserves the monoidal structure of that category; and again here "monoidal category" is a single term that can't be broken in two. – Daniel Wagner Jun 05 '18 at 15:06
  • See also: [definition of a monoidal functor](https://ncatlab.org/nlab/show/monoidal+functor), [Applicative functors as monoidal functors](https://stackoverflow.com/q/41400846/791604), and [Lax monoidal functors with a different monoidal structure](https://stackoverflow.com/questions/23316255/lax-monoidal-functors-with-a-different-monoidal-structure). Probably should be a dupe of one of the latter two, but not sure which; which one do you find more helpful? – Daniel Wagner Jun 05 '18 at 15:10
  • @DanielWagner I understand the definition but I don't understand why the implementation in ghc does not refer about Monoid in the definition of Applicative : Ex ("ab",(+1)) <*> ("cd", 5) gives ("abcd", 6), you can clearly see the use of a Monoid "(,) String", I like your links btw.. so can't we express the "monoidal natural transformation" of the functor structure in the definition of the Applicative typeclass ? – Nicolas Henin Jun 05 '18 at 15:21
  • @DanielWagner I don't understand why you are saying that a "monoidal functor" can't be broken into 2 concepts, isn'it what typeclass functor vs applicative are doing ? – Nicolas Henin Jun 05 '18 at 15:28
  • 2
    `Monoid` does not cover all monoids that can be expressed in Haskell, but only those on ordinary types (that is, things with `*` kind, as Lee alludes to). – duplode Jun 05 '18 at 15:32
  • @duplode look at my update (I use a Integer with an apply which has no Monoid instance), I'm showing that the concept of Monoid is used somewhere but not expressed in the signature of the typeclass. How it is possible ? – Nicolas Henin Jun 05 '18 at 15:43
  • 3
    @NicolasHenin It is expressed in the instance declaration for a particular `Applicative`, namely, `instance Monoid a => Applicative ((,) a)`; and the `Monoid` constraint in that instance declaration has no relation to the "monoidal-functor-ness" of `Applicative` as a concept. – Daniel Wagner Jun 05 '18 at 17:17
  • well @DanielWagner I disagree with you it's used as a part of the monoidal structure of the functor which is (,) a... – Nicolas Henin Jun 06 '18 at 18:50
  • you can have a look here where they are talking about the same think : https://stackoverflow.com/questions/45010424/how-are-monoid-and-applicative-connected – Nicolas Henin Jun 06 '18 at 18:51
  • @NicolasHenin Consider `Just (+1) <*> Just 5`. There is no `Monoid` in sight, and yet it works just fine. The structural monoid need not involve a `Monoid`. – duplode Jun 07 '18 at 03:31
  • You should read the chapter 17 about Applicative, I'm not inventing anything... (http://haskellbook.com/), The structural monoid here is that decision taken on the structure of the Functor Maybe where Just <> Just = Just and Nothing <> _ = Nothing, and where Just is the identity Element .... – Nicolas Henin Jun 07 '18 at 13:17
  • @NicolasHenin I'm not objecting to that. My point is that you appear to be confusing the concept of monoid (a kind of algebraic structure that shows up in many places across Haskell) with the `Monoid` type class (which is just one specific manifestation of that concept). – duplode Jun 07 '18 at 15:54
  • I'm not confusing... I wanted to know why the concept of Monoid (and not the typeclass Monoid) was not expressed in the Applicative typeclass... It's implicitly provided in the instances instead....Pigworker explained it to me.... Sorry but I have the impression I'm repeating myself... – Nicolas Henin Jun 07 '18 at 18:26
  • I would have used explicitly the term "Monoid Typeclass" if it was the case... – Nicolas Henin Jun 07 '18 at 18:33
  • @NicolasHenin Sorry if I'm being annoying or pedantic, but I don't feel "implicitly provided in the instances instead" says all that much. If it comes to that, we might also say that the monoids in the `Monoid` class are also "provided in the instances" -- after all, a misguided implementer might write an unlawful `Monoid` instance that isn't actually a monoid. I'd rather say that `Applicative` *inherently* expresses a certain sort of monoid, just like `Monoid` does. I'd say that is also the takeaway from pigworker's answer (in particular, cf. the very last paragraph). – duplode Jun 08 '18 at 17:17
  • You are not annoying or pedantic and I really appreciate your participation btw :-) Also I finally understood that difference between the "monoidal functor" and these others monoids used to squash the structure... I agree with what you are saying @duplode :-) I love haskell it's so cool :-) – Nicolas Henin Jun 09 '18 at 12:33

3 Answers3

18

The monoid that's referred to with “monoidal functor” is not a Monoid monoid, i.e. a value-level monoid. It's a type-level monoid instead. Namely, the boring product monoid

type Mempty = ()
type a <> b = (a,b)

(You may notice that this is not strictly speaking a monoid; it's only if you consider ((a,b),c) and (a,(b,c)) as the same type. They are sure enough isomorphic.)

To see what this has to do with Applicative, resp. monoidal functors, we need to write the class in other terms.

class Functor f => Monoidal f where
  pureUnit :: f Mempty
  fzip :: f a -> f b -> f (a<>b)

-- an even more “general nonsense”, equivalent formulation is
-- upure :: Mempty -> f Mempty
-- fzipt :: (f a<>f b) -> f (a<>b)
-- i.e. the functor maps a monoid to a monoid (in this case the same monoid).
-- That's really the mathematical idea behind this all.

IOW

class Functor f => Monoidal f where
  pureUnit :: f ()
  fzip :: f a -> f b -> f (a,b)

It's a simple exercise to define a generic instance of the standard Applicative class in terms of Monoidal, vice versa.


Regarding ("ab",(+1)) <*> ("cd", 5): that doesn't have much to do with Applicative in general, but only with the writer applicative specifically. The instance is

instance Monoid a => Monoidal ((,) a) where
  pureUnit = (mempty, ())
  fzip (p,a) (q,b) = (p<>q, (a,b))
leftaroundabout
  • 117,950
  • 5
  • 174
  • 319
  • Categorical monoids are only associative up to isomorphism, so it's OK. – n. m. could be an AI Jun 05 '18 at 15:53
  • I always find it awkward to pick a name (or an operator symbol) to talk about the `f a -> f b -> f (a,b)` combinator (or its uncurried version). `fzip` is not half bad -- in fact, I might end up adopting it. – duplode Jun 06 '18 at 05:58
  • 1
    @duplode well, I thought a lot about these names when I wrote the [constrained `Applicative` class](http://hackage.haskell.org/package/constrained-categories-0.3.1.0/docs/Control-Applicative-Constrained.html#t:Monoidal). (There I actually had to use uncurried and category-agnostic signatures, which makes it a whole lot more awkward.) – leftaroundabout Jun 06 '18 at 07:07
  • @leftaroundabout I had forgotten about looking in your *constrained-categories* while looking for existing names on Hackage (and, as you can imagine, my Hoogle/Hayoo searches by type signature didn't lead me to it). – duplode Jun 06 '18 at 12:59
  • It's a actually a concept of multiplication where you factorize the f, and this is maybe where the * from <*> is coming from.... and actually that operation of factorization is the application of the monoid on the functor structure I was talking about earlier... "that doesn't have much to do with Applicative in general," @leftaroundabout, I disagree with that statement, the functor in that context is (a,_) and then you need to provide a way to do that factorization with (,) and a together... This is why when you implement a applicative for tuple, a needs to be a monoid. – Nicolas Henin Jun 06 '18 at 13:32
  • have a look here : https://stackoverflow.com/questions/41400846/applicative-functors-as-monoidal-functors – Nicolas Henin Jun 06 '18 at 13:36
  • and look at that one as well : https://stackoverflow.com/questions/45010424/how-are-monoid-and-applicative-connected – Nicolas Henin Jun 06 '18 at 13:39
  • @NicolasHenin well yeah, that “multiplication” is basically the type product `(,)`. But, there is nothing intrinsic to monoidal functors which has more to do with multiplication than with addition; in category theory “product” and “coproduct” are very abstract. — Please elaborate what you disagree with; at the moment you have merely re-stated what I already wrote in my answer. (I'm not sure if the confusion stems from the fact that we're discussing both `(,)` as the product operator, and the `(a,)` functor. These uses of the tuple type are actually unrelated, we might better discuss `Writer`.) – leftaroundabout Jun 06 '18 at 13:42
  • OK I understand the misunderstanding (I guess :-))... this is coming from that book : http://haskellbook.com/, with that statement "So, with Applicative, we have a Monoid for our structure and function application for our values!", the origin of this post was to ask what are the reasons why haskell didn't abstract this notion of "moinoid in the structure" in the typeclass Applicative. The exemple with tuple was just to show, that these laws for the structure are not enforced or expressed in the typeclass itself... – Nicolas Henin Jun 06 '18 at 14:26
  • and the constraint added (Monoid under a) is a direct application of the general notion of Applicative. If we would write an Applicative for a bigger tuple let's say (a,b,c,d) I would add a constraint Monoid under a,b,c to implement the instance to respect the laws of an Applicative. Is it improving the misunderstanding ? – Nicolas Henin Jun 06 '18 at 14:26
  • I didn't express it clearly about ("ab",(+1)) <*> ("cd", 5) sorry – Nicolas Henin Jun 06 '18 at 14:33
  • Hm. I think it's better to think of the occurence of these `Monoid`s in the class of monoidal functors as a coincidence. This only works because the `(,)` type-level monoid happens to support `const mempty :: Monoid a => Mempty -> a` and `uncurry (<>) :: Monoid a => (a,a) -> a`. If working in a category where the type-monoid is something else, say, `Either`, then none of this makes any sense. — Of course, it's _not_ really a coincidence that `(,)` works this way, but at any rate, it's much more specific and only works with monoidal **Hask** endofunctors, not with general monoidal functors. – leftaroundabout Jun 06 '18 at 14:45
  • @leftaroundabout about Either, that's the way I would see it : https://stackoverflow.com/questions/22264376/is-there-a-standard-name-or-implementation-of-the-purely-applicative-either , Same idea, you define a "monoidal structure" for Either a – Nicolas Henin Jun 06 '18 at 19:29
  • but yeah there are also maybe multiples moinoid for that structure, it's not implemented that way in Data.Either though... – Nicolas Henin Jun 06 '18 at 19:29
  • @NicolasHenin that's a completely different subject, you're talking again about applicative _instances_ of `Either e`. I meant `Either` as a type-level monoid. Can be used, but with it, `Monoidal` comes out completely different from `Applicative`. – leftaroundabout Jun 06 '18 at 19:53
  • @NicolasHenin If you use `Either` as a type-level monoid in the way leftaroundabout suggests, [you get `Alternative`](http://h2.jaguarpaw.co.uk/posts/alternatives-convert-products-to-sums/). – duplode Jun 07 '18 at 03:53
  • @leftaroundabout, the point of that post was to say that apparently in haskell you can't define that concept of monoidal structure, so instead of being clearly define in the Applicative typeclass, it is implicitly defined in the Applicative Instances... This is what it is explained in that book (http://haskellbook.com/) chapter 17, around 100 pages on that subject with many examples. So there are 2 conflictual views on the subject, the one from the book looks the right one in my opinion. we can't just pretend that they implement that in the instances just for the fun of it, can we ? – Nicolas Henin Jun 07 '18 at 13:26
  • @leftaroundabout, that post about Applicative Either e, shows you the logic of the monoidal structure that I'm talking about, the logic of merge Left and Right together, Right and Right together and how you merge Left and Left togteher, because the e is part of the functor, then e has to be a monoid as well... It was to clearly showing you an example of that implicit Monoidal structure defined in the instance.... – Nicolas Henin Jun 07 '18 at 13:34
  • "Applicative provides a way to squash the structure of a functor together." => the monoid of the structure, that's how Christopher Allen,Julie Moronuki explain it. It's a super clean and simple way to see it and it explains How Applicative List ,Maybe,Either, Tuple... works – Nicolas Henin Jun 07 '18 at 13:42
  • I haven't read it so I don't really want to judge, but I reckon they're wrong about the theory part. The reason that monoidal functors are named thus is deeper and more general than the `Applicative` class (which is rooted in **Hask** and pigworker is right that restricting yourself to that category is a bad idea – though I don't consider the term itself inappropriate). Only in **Hask** do you get the effect that monoidal functors spawn all kinds of value-level monoids; as I said the reason is that `const mempty` and `uncurry (<>)` link the type- and value-level monoids. – leftaroundabout Jun 07 '18 at 13:46
  • That doesn't mean it's a bad view to say “Applicative provides a way to squash the structure of a functor together”. It does that, and this is very much a monoid-thing. It's just not a direct consequence of the monoidalness of the functors. – leftaroundabout Jun 07 '18 at 13:53
  • @leftaroundabout I finally understood that "monoidalness of the functors" with this monoidal natural transformation F a x F b -> F (a # b), my apologies for that stubbornness, but I had a conflictual version with my book... I wanted to understand :-) btw I have contacted the author to clarify his reasoning... – Nicolas Henin Jun 07 '18 at 20:41
13

Perhaps the monoid you're looking for is this one.

newtype AppM f m = AppM (f m) deriving Show

instance (Applicative f, Monoid m) => Monoid (AppM f m) where
  mempty                      = AppM (pure mempty)
  mappend (AppM fx) (AppM fy) = AppM (pure mappend <*> fx <*> fy)

As a comment, below, observes, it can be found in the reducers library under the name Ap. It's fundamental to Applicative, so let's unpack it.

Note, in particular, that because () is trivially a Monoid, AppM f () is a Monoid, too. And that's the monoid lurking behind Applicative f.

We could have insisted on Monoid (f ()) as a superclass of Applicative, but that would have fouled things up royally.

> mappend (AppM [(),()]) (AppM [(),(),()])
AppM [(),(),(),(),(),()]

The monoid underlying Applicative [] is multiplication of natural numbers, whereas the ‘obvious’ monoidal structure for lists is concatenation, which specialises to addition of natural numbers.

Mathematics warning. Dependent types warning. Fake Haskell warning.

One way to see what's going on is to consider those Applicatives which happen to be containers in the dependently typed sense of Abbott, Altenkirch and Ghani. We'll have these in Haskell sometime soon. I'll just pretend the future has arrived.

data (<|) (s :: *)(p :: s -> *) (x :: *) where
  (:<|:) :: pi (a :: s) -> (p a -> x) -> (s <| p) x

The data structure (s <| p) is characterised by

  • Shapes s which tell you what the container looks like.
  • Positions p which tell you for a given shape where you can put data.

The above type says that to give data for such a structure is to pick a shape, then fill all the positions with data.

The container presentation of [] is Nat <| Fin where

data Nat = Z | S Nat
data Fin (n :: Nat) where
  FZ :: Fin (S n)
  FS :: Fin n -> Fin (S n)

so that Fin n has exactly n values. That is, the shape of a list is its length, and that tells you how many elements you need to fill up the list.

You can find the shapes for a Haskell Functor f by taking f (). By making the data trivial, the positions don't matter. Constructing the GADT of positions generically in Haskell is rather more difficult.

Parametricity tells us that a polymorphic function between containers in

forall x. (s <| p) x -> (s' <| p') x

must be given by

  • a function f :: s -> s' mapping input shapes to output shapes
  • a function g :: pi (a :: s) -> p' (f a) -> p a mapping (for a given input shape) output positions back to the input positions where the output element will come from.

morph f g (a :<|: d) = f a :<|: (d . g a)

(Secretly, those of us who have had our basic Hancock training also think of "shapes" as "commands" and "positions" as "valid responses". A morphism between containers is then exactly a "device driver". But I digress.)

Thinking along similar lines, what does it take to make a container Applicative? For starters,

pure :: x -> (s <| p) x

which is equivalently

pure :: (() <| Const ()) x -> (s <| p) x

That has to be given by

f :: () -> s   -- a constant in s
g :: pi (a :: ()) -> p (f ()) -> Const () a  -- trivial

where f = const neutral for some

neutral :: s

Now, what about

(<*>) :: (s <| p) (x -> y) -> (s <| p) x -> (s <| p) y

? Again, parametricity tells us two things. Firstly, the only useful data for calculating the output shapes are the two input shapes. We must have a function

outShape :: s -> s -> s

Secondly, the only way we can fill an output position with a y is to pick a position from the first input to find a function in `x -> y' and then a position in the second input to obtain its argument.

inPos :: pi (a :: s)(b :: s) -> p (outShape a b) -> (p a, p b)

That is, we can always identify the pair of input positions which determine the output in an output position.

The applicative laws tell us that neutral and outShape must obey the monoid laws, and that, moreover, we can lift monoids as follows

mappend (a :<|: f) (b :<|: g) = outShape a b :<|: \ z ->
  let (x, y) = inPos a b z
  in  mappend (f x) (g y)

There's something more to say here, but for that, I need to contrast two operations on containers.

Composition

(s <| p) . (s' <| p')  =  ((s <| p) s') <| \ (a :<|: f) -> Sigma (p a) (p' . f)

where Sigma is the type of dependent pairs

data Sigma (p :: *)(q :: p -> *) where
  Pair :: pi (a :: p) -> q a -> Sigma p q

What on earth does that mean?

  • you choose an outer shape
  • you choose an inner shape for each outer position
  • a composite position is then the pair of an outer position and an inner position appropriate to the inner shape that sits there

Or, in Hancock

  • you choose an outer command
  • you can wait to see the outer response before choosing the inner command
  • a composite response is then a response to the outer command, followed by a response to the inner command chosen by your strategy

Or, more blatantly

  • when you make a list of lists, the inner lists can have different lengths

The join of a Monad flattens a composition. Lurking behind it is not just a monoid on shapes, but an integration operator. That is,

join :: ((s <| p) . (s <| p)) x -> (s <| p) x

requires

integrate :: (s <| p) s -> s

Your free monad gives you strategy trees, where you can use the result of one command to choose the rest of your strategy. As if you're interacting at a 1970s teletype.

Meanwhile...

Tensor

The tensor (also due to Hancock) of two containers is given by

(s <| p) >< (s' <| p')  =  (s, s') <| \ (a, b) -> (p a, p' b)

That is

  • you choose two shapes
  • a position is then a pair of positions, one for each shape

or

  • you choose two commands, without seeing any responses
  • a response is then the pair of responses

or

  • [] >< [] is the type of rectangular matrices: the ‘inner’ lists must all have the same length

The latter is a clue to why >< is very hard to get your hands on in Haskell, but easy in the dependently typed setting.

Like composition, tensor is a monoid with the identity functor as its neutral element. If we replace the composition underlying Monad by tensor, what do we get?

pure :: Id x -> (s <| p) x
mystery :: ((s <| p) >< (s <| p)) x -> (s <| p) x

But whatever can mystery be? It's not a mystery, because we know there's a rather rigid way to make polymorphic functions between containers. There must be

f :: (s, s) -> s
g :: pi ((a, b) :: (s, s)) -> p (f (a, b)) -> (p a, p b)

and those are exactly what we said determined <*> earlier.

Applicative is the notion of effectful programming generated by tensor, where Monad is generated by composition. The fact that you don't get to/need to wait for the outer response to choose the inner command is why Applicative programs are more readily parallelizable.

Seeing [] >< [] as rectangular matrices tells us why <*> for lists is built on top of multiplication.

The free applicative functor is the free monoid with knobs on. For containers,

Free (s <| p) = [s] <| All p

where

All p [] = ()
All p (x : xs) = (p x, All p xs)

So a "command" is a big list of commands, like a deck of punch cards. You don't get to see any output before you choose your card deck. The "response" is your lineprinter output. It's the 1960s.

So there you go. The very nature of Applicative, tensor not composition, demands an underlying monoid, and a recombination of elements compatible with monoids.

pigworker
  • 43,025
  • 18
  • 121
  • 214
  • Who is the Hancock you are referencing? – Max New Jun 06 '18 at 11:25
  • One library that offers the `AppM` newtype at the very beginning of this answer is [*reducers*, where it is called `Ap`](https://hackage.haskell.org/package/reducers-3.12.1/docs/Data-Semigroup-Applicative.html#t:Ap). – duplode Jun 06 '18 at 13:11
  • @pigworker are you referring to that document (https://www.sciencedirect.com/science/article/pii/S0304397505003373?via%3Dihub) when speaking about Abbott, Altenkirch and Ghani ? – Nicolas Henin Jun 06 '18 at 15:27
  • I mean [Peter Hancock](https://dblp.uni-trier.de/pers/hd/h/Hancock:Peter), who did a lot of work on modelling interaction in type theory at the same time as the container gang modelled data structures, using many of the same tools. – pigworker Jun 06 '18 at 16:18
  • And yes, that's the correct "Abbott, Altenkirch and Ghani", who were based in Leicester and Nottingham in the mid 2000s and colloquially referred to as the "East Midlands Container Consortium". I joined in for the subsequent papers. Peter Morris and Peter Hancock got involved, too. – pigworker Jun 06 '18 at 16:21
  • Some of this reminds me of Edward Kmett's talk on `Applicative` as a monoid object in the category of Hask endofunctors. https://youtu.be/cB8DapKQz-I – dfeuer Jun 06 '18 at 17:36
  • Will check that later, but it sounds likely. I wish people wouldn't call it "Hask", though: it threatens to limit the imagination. – pigworker Jun 06 '18 at 18:11
  • I hope that subject about **Hask** will be discussed [in that dedicated question asked today](https://stackoverflow.com/questions/50735311/categorical-structure-in-haskell). But, the more I think about it the more it seems you're being hypocritical, in particular here, when you want to dethrone **Hask** but on the other hand say things like “the monoid... `Ap`...Is fundamental to `Applicative`”. I think there's nothing fundamental about this, instead it's a consequence of the particular properties of **Hask**, namely, of it being cartesian closed. That's also what allows this container stuff. – leftaroundabout Jun 07 '18 at 14:19
  • @leftaroundabout I feel this is not so much about dethroning **Hask**, but rather a matter of presentation. It is not uncommon to see folks new to the categorical aspects of Haskell ask themselves questions like "Where does X fit in [whatever they happen to believe to be *the* Haskell category]" and end up confused as a result of the shoehorning attempt. On a related note, this discussion reminds me of [this recent answer](https://stackoverflow.com/a/50595873/2751851), which tries to address the matter by talking about "[the] default ambient category-esque structure". – duplode Jun 08 '18 at 18:55
  • [`Ap`](https://hackage.haskell.org/package/base-4.16.1.0/docs/Data-Monoid.html#t:Ap) is now in base. – Iceland_jack Apr 26 '22 at 17:11
5

I wanted to complement Conor McBride's (pigworker) instructive answer with some more examples of Monoids found in Applicatives. It has been observed that the Applicative instance of some functors resembles a corresponding Monoid instance; for example, we have the following analogies:

Applicative → Monoid
---------------------
List        → Product
Maybe       → All
Either a    → First a
State s     → Endo s

Following Conor's comment, we can understand why we have these correspondences. We use the following observations:

  1. The shape of an Applicative container forms a Monoid under the application operation <*>.
  2. The shape of a functor F is given by F 1 (where 1 denotes the unit ()).

For each of the Applicative functors listed above, we compute their shape by instantiating the functor with the unit element. We get that...

List has the shape of Nat:

List a = μ r . 1 + a × r
List 1 = μ r . 1 + 1 × r
       ≅ μ r . 1 + r
       ≅ Nat

Maybe has the shape of Bool:

Maybe a = 1 + a
Maybe 1 = 1 + 1
        ≅ Bool

Either has the shape of Maybe:

Either a b = a + b
Either a 1 = a + 1
           ≅ Maybe a

State has the shape of Endo:

State s a = (a × s) ^ s
State s 1 = (1 × s) ^ s
          ≅ s ^ s
          ≅ Endo s

The types of the shapes match precisely the types underlying the Monoids listed in the beginning. One thing still puzzles me: some of these types admit multiple Monoid instances (e.g., Bool can be made into a Monoid as All or Any) and I'm not entirely sure why we get one of the instances and not the other. My guess would be that this is related to the applicative laws and how they interact with the other component of the container – its positions.

Dan Oneață
  • 968
  • 7
  • 14
  • 1
    To get one of these with `Any` shapes, you also have to consider the positions. `All False` having zero positions and `All True` having one is fine because `All False <> All True` gives `All False`, and so you aren't forced to produce a pair of positions when you have just one of them to begin with. One way to make `Any` work is swapping `True` and `False`. Another is having one position in both cases -- `a + a`, which amounts to `Sum Identity Identity`, or `Writer Any`, etc. – duplode Oct 02 '18 at 00:23
  • @duplode Thanks for your comment! Do you think that the general statement is true: given any `Monoid`, there exists an `Applicative` whose shape matches the given `Monoid`? In fact, as you have shown for `Any`, for some `Monoid`s there is more than a single corresponding `Applicative`. – Dan Oneață Oct 02 '18 at 06:59
  • 1
    If you are okay with a trivial one, there is `Monoid m => Applicative (Const m)`. My gut feeling is that there is no guarantee of having something non-trivial -- for instance, I'm having trouble to see a reasonable way of getting some other `Applicative` out of the `Sum` `Monoid`. – duplode Oct 02 '18 at 08:17
  • Right – we can always get an `Applicative` for `Const m`, provided `m` is a `Monoid`! – Dan Oneață Oct 02 '18 at 15:05
  • Regarding the non-trivial instance of `Applicative` for the `Sum` `Monoid`, I was kinda hoping to be possible, as I stumbled upon [this puzzle](https://stackoverflow.com/a/32825891/474311) from Conor, in which he asks for "at least four behaviourally distinct instances of `Applicative`" for non-empty lists. I was expecting that he targeted the four main `Monoid`s on `Nat` (the shape of lists) – `Sum`, `Product`, `Min`, `Max` – but, of course, the puzzle doesn't imply that. In fact, for non-empty lists is not possible to obtain the empty list which would correspond to zero, the unit on `Sum`. – Dan Oneață Oct 02 '18 at 15:06
  • 1
    I suspect some of those instances in the puzzle differ by sequencing of effects. (Also, I wonder how would that translate to the vantage point taken by Conor's answer here.) – duplode Oct 03 '18 at 13:08
  • 1
    I believe two extra instances for that puzzle have just sprung forth in a /r/haskell thread: [one](https://old.reddit.com/r/haskell/comments/bcaead/how_to_derive_pure_f_x_fmap_f_x/ekpo69v/) and [the other](https://old.reddit.com/r/haskell/comments/bcaead/how_to_derive_pure_f_x_fmap_f_x/ekrgm6i/). – duplode Apr 13 '19 at 21:48