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.