Order of execution with Haskell's `mapM` - haskell

Consider the following Haskell statement:
mapM print ["1", "2", "3"]
Indeed, this prints "1", "2", and "3" in order.
Question: How do you know that mapM will first print "1", and then print "2", and finally print "3". Is there any guarantee that it will do this? Or is it a coincidence of how it is implemented deep within GHC?

If you evaluate mapM print ["1", "2", "3"] by expanding the definition of mapM you will arrive at (ignoring some irrelevant details)
print "1" >> print "2" >> print "3"
You can think of print and >> as abstract constructors of IO actions that cannot be evaluated any further, just as a data constructor like Just cannot be evaluated any further.
The interpretation of print s is the action of printing s, and the interpretation of a >> b is the action that first performs a and then performs b. So, the interpretation of
mapM print ["1", "2", "3"] = print "1" >> print "2" >> print "3"
is to first print 1, then print 2, and finally print 3.
How this is actually implemented in GHC is entirely a different matter which you shouldn't worry about for a long time.

There is no guarantee on the order of the evaluation but there is a guarantee on the order of the effects. For more information see this answer that discusses forM.
You need to learn to make the following, tricky distinction:
The order of evaluation
The order of effects (a.k.a. "actions")
What
forM, sequence and similar functions promise is that the effects will
be ordered from left to right. So for example, the following is
guaranteed to print characters in the same order that they occur in
the string...
Note: "forM is mapM with its arguments flipped. For a version that ignores the results see forM_."

Preliminary note: The answers by Reid Barton and Dair are entirely correct and fully cover your practical concerns. I mention that because partway through this answer one might have the impression that it contradicts them, which is not the case, as will be clear by the time we get to the end. That being clear, it is time to indulge in some language lawyering.
Is there any guarantee that [mapM print] will [print the list elements in order]?
Yes, there is, as explained by the other answers. Here, I will discuss what might justify this guarantee.
In this day and age, mapM is, by default, merely traverse specialised to monads:
traverse
:: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b)
mapM
:: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
That being so, in what follows I will be primarily concerned with traverse, and how our expectations about the sequencing of effects relate to the Traversable class.
As far as the production of effects is concerned, traverse generates an Applicative effect for each value in the traversed container and combines all such effects through the relevant Applicative instance. This second part is clearly reflected by the type of sequenceA, through which the applicative context is, so to say, factored out of the container:
sequenceA :: (Traversable t, Applicative f) => t (f a) -> f (t a)
-- sequenceA and traverse are interrelated by:
traverse f = sequenceA . fmap f
sequenceA = traverse id
The Traversable instance for lists, for example, is:
instance Traversable [] where
{-# INLINE traverse #-} -- so that traverse can fuse
traverse f = List.foldr cons_f (pure [])
where cons_f x ys = (:) <$> f x <*> ys
It is plain to see that the combining, and therefore the sequencing, of effects is done through (<*>), so let's focus on it for a moment. Picking the IO applicative functor as an illustrative example, we can see (<*>) sequencing effects from left to right:
GHCi> -- Superfluous parentheses added for emphasis.
GHCi> ((putStrLn "Type something:" >> return reverse) <*> getLine) >>= putStrLn
Type something:
Whatever
revetahW
(<*>), however, sequences effects from left-to-right by convention, and not for any inherent reason. As witnessed by the Backwards wrapper from transformers, it is, in principle, always possible to implement (<*>) with right-to-left sequencing and still get a lawful Applicative instance. Without using the wrapper, it is also possible to take advantage of (<**>) from Control.Applicative to invert the sequencing:
(<**>) :: Applicative f => f a -> f (a -> b) -> f b
GHCi> import Control.Applicative
GHCi> (getLine <**> (putStrLn "Type something:" >> return reverse)) >>= putStrLn
Whatever
Type something:
revetahW
Given that it is so easy to flip the sequencing of Applicative effects, one might wonder whether this trick might transfer to Traversable. For instance, let's say we implement...
esrevart :: Applicative f => (a -> f b) -> [a] -> f [b]
... so that it is just like traverse for lists save for using Backwards or (<**>) to flip the sequencing of effects (I will leave that as an exercise for the reader). Would esrevart be a legal implementation of traverse? While we might figure it out by trying to prove the identity and composition laws of Traversable hold, that is actually not necessary: given that Backwards f for any applicative f is also applicative, an esrevart patterned after any lawful traverse will also follow the Traversable laws. The Reverse wrapper, also part of transformers, offers a general implementation of this reversal.
We have thus concluded that there can be legal Traversable instances that differ in the sequencing of effects. In particular, a list traverse that sequences effects from tail to head is conceivable. That doesn't make the possibility any less strange, though. To avoid utter bewilderment, Traversable instances are conventionally implemented with plain (<*>) and following the natural order in which the constructors are used to build the traversable container, which in the case of lists amounts to the expected head-to-tail sequencing of effects. One place where this convention shows up is in the automatic generation of instances by the DeriveTraversable extension.
A final, historical note. Couching this discussion, which is ultimately about mapM, in terms of the Traversable class would be a move of dubious relevance in a not so distant past. mapM was effectively subsumed by traverse only last year, but it has existed for much longer. For instance, the Haskell Report 1.3 from 1996, years before Applicative and Traversable came into being (not even ap is there, in fact), provides the following specification for mapM:
accumulate :: Monad m => [m a] -> m [a]
accumulate = foldr mcons (return [])
where mcons p q = p >>= \x -> q >>= \y -> return (x:y)
mapM :: Monad m => (a -> m b) -> [a] -> m [b]
mapM f as = accumulate (map f as)
The sequencing of effects, here enforced through (>>=), is left-to-right, for no other reason than it being the sensible thing to do.
P.S.: It is worth emphasising that, while it is possible to write a right-to-left mapM in terms of the Monad operations (in the Report 1.3 implementation quoted here, for instance, it merely requires exchanging p and q in the right-hand side of mcons), there is no such thing as a general Backwards for monads. Since f in x >>= f is a Monad m => a -> m b function which creates effects from values, the effects associated with f depend on x. As a consequence, a simple inversion of sequencing like that possible with (<*>) is not even guaranteed to be meaningful, let alone lawful.

Related

Monads: Determining if an arbitrary transformation is possible

There are quite a few of questions here about whether or not certain transformations of types that involve Monads are possible.
For instance, it's possible to make a function of type f :: Monad m => [m a] -> m [a], but impossible to make a function of type g :: Monad m => m [a] -> [m a] as a proper antifunction to the former. (IE: f . g = id)
I want to understand what rules one can use to determine if a function of that type can or cannot be constructed, and why these types cannot be constructed if they disobey these rules.
The way that I've always thought about monads is that a value of type Monad m => m a is some program of type m that executes and produces an a. The monad laws reinforce this notion by thinking of composition of these programs as "do thing one then do thing two", and produce some sort of combination of the results.
Right unit Taking a program and just returning its value should
be the same as just running the original program.
m >>= return = m
Left unit If you create a simple program that just returns a value,
and then pass that value to a function that creates a new program, then
the resulting program should just be as if you called the function on the
value.
return x >>= f = f x
Associativity If you execute a program m, feed its result into a function f that produces another program, and then feed that result into a third function g that also produces a program, then this is identical to creating a new function that returns a program based on feeding the result of f into g, and feeding the result of m into it.
(m >>= f) >>= g = m >>= (\x -> f x >>= g)
Using this intuition about a "program that creates a value" can come to some conclusions about what it means for the functions that you've provided in your examples.
Monad m => [m a] -> m [a] Deviating from the intuitive definition of what this function should do is hard: Execute each program in sequence and collect the results. This produces another program that produces a list of results.
Monad m => m [a] -> [m a] This doesn't really have a clear intuitive definition, since it's a program that produces a list. You can't create a list without getting access to the resulting values which in this case means executing a program. Certain monads, that have a clear way to extract a value from a program, and provide some variant of m a -> a, like the State monad, can have sane implementations of some function like this. It would have to be application specific though. Other monads, like IO, you cannot escape from.
Monad m => (a -> m b) -> m (a -> b) This also doesn't really have a clear intuitive definition. Here you have a function f that produces a program of type m b, but you're trying to return a function of type m (a -> b). Based on the a, f creates completely different programs with different executing semantics. You cannot encompass these variations in a single program of type m (a -> b), even if you can provide a proper mapping of a -> b in the programs resulting value.
This intuition doesn't really encompass the idea behind monads completely. For example, the monadic context of a list doesn't really behave like a program.
Something easy to remember is : "you can't escape from a Monad" (it's kind of design for it). Transforming m [a] to [m a] is a form of escape, so you can't.
On the other hand you can easily create a Monad from something (using return) so traversing ([m a] -> m [a]) is usually possible.
If you take a look at "Monad laws", monad only constrain you to define a composition function but not reverse function.
In the first example you can compose the list elements.
In the second one Monad m => m [a] -> [m a], you cannot split an action into multiple actions ( action composition is not reversible).
Example:
Let's say you have to read 2 values.
s1 <- action
s2 <- action
Doing so, action result s2 depends by the side effect made by s1.
You can bind these 2 actions in 1 action to be executed in the same order, but you cannot split them and execute action from s2 without s1 made the side effect needed by the second one.
Not really an answer, and much too informal for my linking, but nevertheless I have a few interesting observations that won't fit into a comment. First, let's consider this function you refer to:
f :: Monad m => [m a] -> m [a]
This signature is in fact stronger than it needs to be. The current generalization of this is the sequenceA function from Data.Traversable:
sequenceA :: (Traversable t, Applicative f) -> t (f a) -> f (t a)
...which doesn't need the full power of Monad, and can work with any Traversable and not just lists.
Second: the fact that Traversable only requires Applicative is I think really significant to this question, because applicative computations have a "list-like" structure. Every applicative computation can be rewritten to have the form f <$> a1 <*> ... <*> an for some f. Or, informally, every applicative computation can be seen as a list of actions a1, ... an (heterogeneous on the result type, homogeneous in the functor type), plus an n-place function to combine their results.
If we look at sequenceA through this lens, all it does is choose an f built out of the appropriate nested number of list constructors:
sequenceA [a1, ..., an] == f <$> a1 <*> ... <*> an
where f v1 ... vn = v1 : ... : vn : []
Now, I haven't had the chance to try and prove this yet, but my conjectures would be the following:
Mathematically speaking at least, sequenceA has a left inverse in free applicative functors. If you have a Functor f => [FreeA f a] and you sequenceA it, what you get is a list-like structure that contains those computations and a combining function that makes a list out of their results. I suspect however that it's not possible to write such a function in Haskell (unSequenceFreeA :: (Traversable t, Functor f) => FreeA f (t a) -> Maybe (t (Free f a))), because you can't pattern match on the structure of the combining function in the FreeA to tell that it's of the form f v1 ... vn = v1 : ... : vn : [].
sequenceA doesn't have a right inverse in a free applicative, however, because the combining function that produces a list out of the results from the a1, ... an actions may do anything; for example, return a constant list of arbitrary length (unrelated to the computations that the free applicative value performs).
Once you move to non-free applicative functors, there will no longer be a left inverse for sequenceA, because the non-free applicative functor's equations translate into cases where you can no longer tell apart which of two t (f a) "action lists" was the source for a given f (t a) "list-producing action."

Is Haskell designed to encourage Hungarian Notation?

I'm learning Haskell and started noticing common suffixes in functions like:
debugM
mapM_
mapCE
Which is known as Hungarian Notation. But at the same time I can use type classes to write non-ambiguous code like:
show
return
Since functions like map are so common and used in many contexts, why not let type checker to pick correct polymorphic version of map, fmap, mapM, mapM_ or mapCE?
There's a little bit of "Hungarian notation", but it's quite different. In short, Haskell's type system removes the need for most of it.
The map/mapM thing is a neat example. These two functions confer the exact same concept, but cannot be polymorphically represented because abstracting over the difference would be really noisy. So we pick a Hungarian notation instead.
To be clear, the two types are
map :: (a -> b) -> ([a] -> [b])
mapM :: Monad m => (a -> m b) -> ([a] -> m [b])
These look similar, all mapM does is add the monad, but not the same. The structure is revealed when you make the following synonyms
type Arr a b = a -> b
type Klei m a b = a -> m b
and rewrite the types as
map :: Arr a b -> Arr [a] [b]
mapM :: Monad m => Klei m a b -> Klei m [a] [b]
The thing to note is that Arr and Monad m => Klei m are often extremely similar things. They both form a certain structure known as a "category" which allows us to hoist all kinds of computation inside of it. [0]
What we'd like is to abstract over the choice of category with something like
class Mapping cat where
map :: cat a b -> cat [a] [b]
instance Mapping (->) where map = Prelude.map
instance Monad m => Mapping (Klei m) where map = mapM -- in spirit anyway
but it turns out that there is way more to be gained by abstracting over the list part with Functor [1]
class Functor f where
map :: (a -> b) -> (f a -> f b)
instance Functor [] where
map = Prelude.map
instance Functor Maybe where
map Nothing = Nothing
map (Just a) = Just (f a)
and so for simplicity's sake, we use Hungarian notation to make the difference of category instead of rolling it up into Haskell's polymorphism functionality.
[0] Notably, the fact that Klei m is a category implies m is a monad and the category laws become exactly the monad laws. In particular, that's my favorite way for remembering what the monad laws are.
[1] Technically, the sole method of Functor is called fmap not map, but it could and perhaps should have been called just map. The f was added so that the type signature for map remains simple (specialized to lists) and thus is a little less intimidating to beginners. Whether or not that was the right decision is a debate that continues today.
Your assumption is that all of these do roughly the same thing - they don't. map and fmap are pretty much the same function - map is just fmap specialized to the [] functor (either for historical reasons, or so that beginners would get less confusing type errors - I'm not sure).
mapM and mapM_ on the other hand are like map followed by sequence or sequence_ respectively - while what they're doing may look related, they're doing different things. Incidentally, the function that behaves like fmap for monads is... fmap (which is also aliased with a specialized signature to liftM, for historical reasons), as Monads are, by definition, also Functors; note that this is, right now, not enforced by the standard library - a historical oversight that should be corrected with GHC 7.10 if I'm not mistaken.
I don't know what to tell you about debugM and mapCE as I haven't seen these before.

Haskell - Is effect order deterministic in case of Applicative?

When executing the IO action defined by someFun <$> (a :: IO ()) <$> (b :: IO ()), is the execution of the a and b actions ordered? That is, can I count on that a is executed before b is?
For GHC, I can see the IO is implemented using State, and also see here that it is an Applicative instance, but can't find the source of the actual instance declaration. Being implemented through State suggests that different IO effects need to be sequential, but doesn't necessary defines their ordering.
Playing around in GHCi seems that Appliative retains effect order, but is that some universal guarantee, or GHC specific? I would be interested in details.
import System.Time
import Control.Concurrent
import Data.Traversable
let prec (TOD a b) = b
fmap (map prec) (sequenceA $ replicate 5 (threadDelay 1000 >> getClockTime))
[641934000000,642934000000,643934000000,644934000000,645934000000]
Thanks!
It's certainly deterministic, yes. It will always do the same thing for any specific instance. However, there's no inherent reason to choose left-to-right over right-to-left for the order of effects.
However, from the documentation for Applicative:
If f is also a Monad, it should satisfy pure = return and (<*>) = ap (which implies that pure and <*> satisfy the applicative functor laws).
The definition of ap is this, from Control.Monad:
ap :: (Monad m) => m (a -> b) -> m a -> m b
ap = liftM2 id
And liftM2 is defined in the obvious way:
liftM2 f m1 m2 = do { x1 <- m1; x2 <- m2; return (f x1 x2) }
What this means is that, for any functor that is a Monad as well as an Applicative, it is expected (by specification, since this can't be enforced in the code), that Applicative will work left-to-right, so that the do block in liftM2 does the same thing as liftA2 f x y = f <$> x <*> y.
Because of the above, even for Applicative instances without a corresponding Monad, by convention the effects are usually ordered left-to-right as well.
More broadly, because the structure of an Applicative computation is necessarily independent of the "effects", you can usually analyze the meaning of a program independently of how Applicative effects are sequenced. For example, if the instance for [] were changed to sequence right-to-left, any code using it would give the same results, just with the list elements in a different order.
Yes, the order is predefined by the Monad-Applicative correspondence. This is easy to see: The (*>) combinator needs to correspond to the (>>) combinator in a well-behaved Applicative instance for a monad, and its definition is:
a *> b = liftA2 (const id) a b
In other words, if b were executed before a, the Applicative instance would be ill-behaving.
Edit: As a side note: This is not explicitly specified anywhere, but you can find many other similar correspondences like liftM2 = liftA2, etc.
For the IO Applicative, this is certainly the case. But check out the async package for an example of an Applicative where in f <$> a <*> b the effects of a and b happen in parallel.

Can someone explain the traverse function in Haskell?

I am trying and failing to grok the traverse function from Data.Traversable. I am unable to see its point. Since I come from an imperative background, can someone please explain it to me in terms of an imperative loop? Pseudo-code would be much appreciated. Thanks.
traverse is the same as fmap, except that it also allows you to run effects while you're rebuilding the data structure.
Take a look at the example from the Data.Traversable documentation.
data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
The Functor instance of Tree would be:
instance Functor Tree where
fmap f Empty = Empty
fmap f (Leaf x) = Leaf (f x)
fmap f (Node l k r) = Node (fmap f l) (f k) (fmap f r)
It rebuilds the entire tree, applying f to every value.
instance Traversable Tree where
traverse f Empty = pure Empty
traverse f (Leaf x) = Leaf <$> f x
traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
The Traversable instance is almost the same, except the constructors are called in applicative style. This means that we can have (side-)effects while rebuilding the tree. Applicative is almost the same as monads, except that effects cannot depend on previous results. In this example it means that you could not do something different to the right branch of a node depending on the results of rebuilding the left branch for example.
For historical reasons, the Traversable class also contains a monadic version of traverse called mapM. For all intents and purposes mapM is the same as traverse - it exists as a separate method because Applicative only later became a superclass of Monad.
If you would implement this in an impure language, fmap would be the same as traverse, as there is no way to prevent side-effects. You can't implement it as a loop, as you have to traverse your data structure recursively. Here's a small example how I would do it in Javascript:
Node.prototype.traverse = function (f) {
return new Node(this.l.traverse(f), f(this.k), this.r.traverse(f));
}
Implementing it like this limits you to the effects that the language allows though. If you f.e. want non-determinism (which the list instance of Applicative models) and your language doesn't have it built-in, you're out of luck.
traverse turns things inside a Traversable into a Traversable of things "inside" an Applicative, given a function that makes Applicatives out of things.
Let's use Maybe as Applicative and list as Traversable. First we need the transformation function:
half x = if even x then Just (x `div` 2) else Nothing
So if a number is even, we get half of it (inside a Just), else we get Nothing. If everything goes "well", it looks like this:
traverse half [2,4..10]
--Just [1,2,3,4,5]
But...
traverse half [1..10]
-- Nothing
The reason is that the <*> function is used to build the result, and when one of the arguments is Nothing, we get Nothing back.
Another example:
rep x = replicate x x
This function generates a list of length x with the content x, e.g. rep 3 = [3,3,3]. What is the result of traverse rep [1..3]?
We get the partial results of [1], [2,2] and [3,3,3] using rep. Now the semantics of lists as Applicatives is "take all combinations", e.g. (+) <$> [10,20] <*> [3,4] is [13,14,23,24].
"All combinations" of [1] and [2,2] are two times [1,2]. All combinations of two times [1,2] and [3,3,3] are six times [1,2,3]. So we have:
traverse rep [1..3]
--[[1,2,3],[1,2,3],[1,2,3],[1,2,3],[1,2,3],[1,2,3]]
I think it's easiest to understand in terms of sequenceA, as traverse can be defined as
follows.
traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b)
traverse f = sequenceA . fmap f
sequenceA sequences together the elements of a structure from left to right, returning a structure with the same shape containing the results.
sequenceA :: (Traversable t, Applicative f) => t (f a) -> f (t a)
sequenceA = traverse id
You can also think of sequenceA as reversing the order of two functors, e.g. going from a list of actions into an action returning a list of results.
So traverse takes some structure, and applies f to transform every element in the structure into some applicative, it then sequences up the effects of those applicatives from left to right, returning a structure with the same shape containing the results.
You can also compare it to Foldable, which defines the related function traverse_.
traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f ()
So you can see that the key difference between Foldable and Traversable is that the latter allows you to preserve the shape of the structure, whereas the former requires you to fold the result up into some other value.
A simple example of its usage is using a list as the traversable structure, and IO as the applicative:
λ> import Data.Traversable
λ> let qs = ["name", "quest", "favorite color"]
λ> traverse (\thing -> putStrLn ("What is your " ++ thing ++ "?") *> getLine) qs
What is your name?
Sir Lancelot
What is your quest?
to seek the holy grail
What is your favorite color?
blue
["Sir Lancelot","to seek the holy grail","blue"]
While this example is rather unexciting, things get more interesting when traverse is used on other types of containers, or using other applicatives.
It's kind of like fmap, except that you can run effects inside the mapper function, which also changes the result type.
Imagine a list of integers representing user IDs in a database: [1, 2, 3]. If you want to fmap these user IDs to usernames, you can't use a traditional fmap, because inside the function you need to access the database to read the usernames (which requires an effect -- in this case, using the IO monad).
The signature of traverse is:
traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b)
With traverse, you can do effects, therefore, your code for mapping user IDs to usernames looks like:
mapUserIDsToUsernames :: (Num -> IO String) -> [Num] -> IO [String]
mapUserIDsToUsernames fn ids = traverse fn ids
There's also a function called mapM:
mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
Any use of mapM can be replaced with traverse, but not the other way around. mapM only works for monads, whereas traverse is more generic.
If you just want to achieve an effect and not return any useful value, there are traverse_ and mapM_ versions of these functions, both of which ignore the return value from the function and are slightly faster.
traverse is the loop. Its implementation depends on the data structure to be traversed. That might be a list, tree, Maybe, Seq(uence), or anything that has a generic way of being traversed via something like a for-loop or recursive function. An array would have a for-loop, a list a while-loop, a tree either something recursive or the combination of a stack with a while-loop; but in functional languages you do not need these cumbersome loop commands: you combine the inner part of the loop (in the shape of a function) with the data structure in a more directly manner and less verbose.
With the Traversable typeclass, you could probably write your algorithms more independent and versatile. But my experience says, that Traversable is usually only used to simply glue algorithms to existing data structures. It is quite nice not to need to write similar functions for different datatypes qualified, too.

What is <*> called and what does it do? [closed]

Closed. This question is opinion-based. It is not currently accepting answers.
Closed 5 years ago.
Locked. This question and its answers are locked because the question is off-topic but has historical significance. It is not currently accepting new answers or interactions.
How do these functions in the Applicative typeclass work?
(<*>) :: f (a -> b) -> f a -> f b
(*>) :: f a -> f b -> f b
(<*) :: f a -> f b -> f a
(That is, if they weren't operators, what might they be called?)
As a side note, if you could rename pure to something more friendly to non-mathematicians, what would you call it?
Sorry, I don't really know my math, so I'm curious how to pronounce the functions in the Applicative typeclass
Knowing your math, or not, is largely irrelevant here, I think. As you're probably aware, Haskell borrows a few bits of terminology from various fields of abstract math, most notably Category Theory, from whence we get functors and monads. The use of these terms in Haskell diverges somewhat from the formal mathematical definitions, but they're usually close enough to be good descriptive terms anyway.
The Applicative type class sits somewhere between Functor and Monad, so one would expect it to have a similar mathematical basis. The documentation for the Control.Applicative module begins with:
This module describes a structure intermediate between a functor and a monad: it provides pure expressions and sequencing, but no binding. (Technically, a strong lax monoidal functor.)
Hmm.
class (Functor f) => StrongLaxMonoidalFunctor f where
. . .
Not quite as catchy as Monad, I think.
What all this basically boils down to is that Applicative doesn't correspond to any concept that's particularly interesting mathematically, so there's no ready-made terms lying around that capture the way it's used in Haskell. So, set the math aside for now.
If we want to know what to call (<*>) it might help to know what it basically means.
So what's up with Applicative, anyway, and why do we call it that?
What Applicative amounts to in practice is a way to lift arbitrary functions into a Functor. Consider the combination of Maybe (arguably the simplest non-trivial Functor) and Bool (likewise the simplest non-trivial data type).
maybeNot :: Maybe Bool -> Maybe Bool
maybeNot = fmap not
The function fmap lets us lift not from working on Bool to working on Maybe Bool. But what if we want to lift (&&)?
maybeAnd' :: Maybe Bool -> Maybe (Bool -> Bool)
maybeAnd' = fmap (&&)
Well, that's not what we want at all! In fact, it's pretty much useless. We can try to be clever and sneak another Bool into Maybe through the back...
maybeAnd'' :: Maybe Bool -> Bool -> Maybe Bool
maybeAnd'' x y = fmap ($ y) (fmap (&&) x)
...but that's no good. For one thing, it's wrong. For another thing, it's ugly. We could keep trying, but it turns out that there's no way to lift a function of multiple arguments to work on an arbitrary Functor. Annoying!
On the other hand, we could do it easily if we used Maybe's Monad instance:
maybeAnd :: Maybe Bool -> Maybe Bool -> Maybe Bool
maybeAnd x y = do x' <- x
y' <- y
return (x' && y')
Now, that's a lot of hassle just to translate a simple function--which is why Control.Monad provides a function to do it automatically, liftM2. The 2 in its name refers to the fact that it works on functions of exactly two arguments; similar functions exist for 3, 4, and 5 argument functions. These functions are better, but not perfect, and specifying the number of arguments is ugly and clumsy.
Which brings us to the paper that introduced the Applicative type class. In it, the authors make essentially two observations:
Lifting multi-argument functions into a Functor is a very natural thing to do
Doing so doesn't require the full capabilities of a Monad
Normal function application is written by simple juxtaposition of terms, so to make "lifted application" as simple and natural as possible, the paper introduces infix operators to stand in for application, lifted into the Functor, and a type class to provide what's needed for that.
All of which brings us to the following point: (<*>) simply represents function application--so why pronounce it any differently than you do the whitespace "juxtaposition operator"?
But if that's not very satisfying, we can observe that the Control.Monad module also provides a function that does the same thing for monads:
ap :: (Monad m) => m (a -> b) -> m a -> m b
Where ap is, of course, short for "apply". Since any Monad can be Applicative, and ap needs only the subset of features present in the latter, we can perhaps say that if (<*>) weren't an operator, it should be called ap.
We can also approach things from the other direction. The Functor lifting operation is called fmap because it's a generalization of the map operation on lists. What sort of function on lists would work like (<*>)? There's what ap does on lists, of course, but that's not particularly useful on its own.
In fact, there's a perhaps more natural interpretation for lists. What comes to mind when you look at the following type signature?
listApply :: [a -> b] -> [a] -> [b]
There's something just so tempting about the idea of lining the lists up in parallel, applying each function in the first to the corresponding element of the second. Unfortunately for our old friend Monad, this simple operation violates the monad laws if the lists are of different lengths. But it makes a fine Applicative, in which case (<*>) becomes a way of stringing together a generalized version of zipWith, so perhaps we can imagine calling it fzipWith?
This zipping idea actually brings us full circle. Recall that math stuff earlier, about monoidal functors? As the name suggests, these are a way of combining the structure of monoids and functors, both of which are familiar Haskell type classes:
class Functor f where
fmap :: (a -> b) -> f a -> f b
class Monoid a where
mempty :: a
mappend :: a -> a -> a
What would these look like if you put them in a box together and shook it up a bit? From Functor we'll keep the idea of a structure independent of its type parameter, and from Monoid we'll keep the overall form of the functions:
class (Functor f) => MonoidalFunctor f where
mfEmpty :: f ?
mfAppend :: f ? -> f ? -> f ?
We don't want to assume that there's a way to create an truly "empty" Functor, and we can't conjure up a value of an arbitrary type, so we'll fix the type of mfEmpty as f ().
We also don't want to force mfAppend to need a consistent type parameter, so now we have this:
class (Functor f) => MonoidalFunctor f where
mfEmpty :: f ()
mfAppend :: f a -> f b -> f ?
What's the result type for mfAppend? We have two arbitrary types we know nothing about, so we don't have many options. The most sensible thing is to just keep both:
class (Functor f) => MonoidalFunctor f where
mfEmpty :: f ()
mfAppend :: f a -> f b -> f (a, b)
At which point mfAppend is now clearly a generalized version of zip on lists, and we can reconstruct Applicative easily:
mfPure x = fmap (\() -> x) mfEmpty
mfApply f x = fmap (\(f, x) -> f x) (mfAppend f x)
This also shows us that pure is related to the identity element of a Monoid, so other good names for it might be anything suggesting a unit value, a null operation, or such.
That was lengthy, so to summarize:
(<*>) is just a modified function application, so you can either read it as "ap" or "apply", or elide it entirely the way you would normal function application.
(<*>) also roughly generalizes zipWith on lists, so you can read it as "zip functors with", similarly to reading fmap as "map a functor with".
The first is closer to the intent of the Applicative type class--as the name suggests--so that's what I recommend.
In fact, I encourage liberal use, and non-pronunciation, of all lifted application operators:
(<$>), which lifts a single-argument function into a Functor
(<*>), which chains a multi-argument function through an Applicative
(=<<), which binds a function that enters a Monad onto an existing computation
All three are, at heart, just regular function application, spiced up a little bit.
Since I have no ambitions of improving on C. A. McCann's technical answer, I'll tackle the more fluffy one:
If you could rename pure to something more friendly to podunks like me, what would you call it?
As an alternative, especially since there is no end to the constant angst-and-betrayal-filled cried against the Monad version, called "return", I propose another name, which suggests its function in a way that can satisfy the most imperative of imperative programmers, and the most functional of...well, hopefully, everyone can complain the same about: inject.
Take a value. "Inject" it into the Functor, Applicative, Monad, or what-have-you. I vote for "inject", and I approved this message.
In brief:
<*> you can call it apply. So Maybe f <*> Maybe a can be pronounced as apply Maybe f over Maybe a.
You could rename pure to of, like many JavaScript libraries do. In JS you can create a Maybe with Maybe.of(a).
Also, Haskell's wiki has a page on pronunciation of language operators here
(<*>) -- Tie Fighter
(*>) -- Right Tie
(<*) -- Left Tie
pure -- also called "return"
Source: Haskell Programming from First Principles, by Chris Allen and Julie Moronuki

Resources