class Applicative_ t => Monad_ (t :: * -> *) where
andThen :: t a -> (a -> t b) -> t b
Laws (in addition to those for Functor
and
Applicative_
):
Left identity:
pure a `andThen` f
≡ f a
Right identity:
ma `andThen` pure
≡ ma
Associativity:
(ma `andThen` f) `andThen` g
≡ ma `andThen` (\x -> f x `andThen` g)
Recall andThenMaybe
:
instance Monad_ Maybe where
andThen :: Maybe a -> (a -> Maybe b) -> Maybe b
andThen (Just a) f = f a
andThen _ _ = Nothing
instance Monad_ [] where
andThen :: [a] -> (a -> [b]) -> [b]
-- andThen xs f = concatMap f xs
andThen = flip concatMap
(>>=) :: Monad_ m => m a -> (a -> m b) -> m b
(>>=) = andThen
(>>) :: Monad_ m => m a -> m b -> m b
ma >> mb = ma >>= \_ -> mb
(=<<) :: Monad_ m => (a -> m b) -> m a -> m b
(=<<) = flip (>>=)
(<=<) :: Monad_ m => (b -> m c) -> (a -> m b) -> a -> m c
f <=< g = \a -> g a >>= f
(>=>) :: Monad_ m => (a -> m b) -> (b -> m c) -> a -> m c
(>=>) = flip (<=<)
The first operator above doesn’t actually require
(>>=)
:
(*>) :: Applicative_ t => t a -> t b -> t b
ta *> tb = pure (curry snd) <*> ta <*> tb
(>>) :: Monad_ m => m a -> m b -> m b
(>>) = (*>)
Notice that, in the version of Monad_
below, there is an
additional member called join
(cf. joinMaybe
).
Each of the two members can be derived in terms of the other. Try them,
and then check the default definitions in Monad_.hs
.
class Applicative_ t => Monad_ (t :: * -> *) where
andThen :: t a -> (a -> t b) -> t b
join :: t (t a) -> t a
The characterization via join
can be thought of as
saying Monad_
s are fancy types t
such that
values that are twice as fancy (t (t a)
) are no better than
just fancy (t a
).
Recall sibling
.
class Monad_ t => MonadPlus_ t where
guardFalse :: t ()
guard :: Bool -> t ()
guard True = pure ()
guard False = guardFalse
The Maybe
and list types have natural ways to encode
errors:
instance MonadPlus_ Maybe where
-- guardFalse :: Maybe ()
guardFalse = Nothing
instance MonadPlus_ [] where
-- guardFalse :: [()]
guardFalse = []
Monad
The Monad
class defined in Control.Monad
— and exposed by Prelude
— uses the name
(>>=)
rather than andThen
. (We alluded
to this choice in the “Monad Roadmap”). It also
defines return
.
class Applicative m => Monad m where
-- fmap :: (a -> b) -> m a -> m b -- from Functor
-- (<*>) :: f (a -> b) -> m a -> m b -- from Applicative
(>>=) :: m a -> (a -> m b) -> m b -- Monad_.andThen
-- pure :: m -> m a -- from Applicative
return :: m -> m a
return = pure
There are several things to reconcile with our progression leading up
to Monad
.
The sequencing operation (>>=)
is pronounced
“bind”.
The word “bind” is overloaded (pun intended). First,
let x = e
binds e
to x
, and this
is a far more primitive notion than anything involving
Monad
.
Moreover, the statement x <- e
in a
do
-block binds the “result of the e
action” to
x
. As we will discuss shortly, this statement is
something very Monad
-specific, but it’s not simply
(>>=)
(“bind”) applied to x
and
e
.
Thus, I prefer the name andThen
, following the
nomenclature in Elm’s standard
libraries. (Elm doesn’t have a type class mechanism, but relevant
modules define this sequencing notion. For example, Maybe.andThen
and Json.Decode.andThen
.)
The alternative characterization, via join
, is provided
by the library function Control.Monad.join
.
The return
member is defined simply as
pure
. So why is it even there at all? This is a vestige of
previous versions of Haskell. The Monad
class had been
defined long before Applicative
was identified and defined
(in the mid-aughts).
At first, the Monad
class was not changed to include
Applicative
as a superclass constraint, in order to avoid
breaking changes. In version
7.10 from 2005, however, the superclass constraint was added, and
return
was kept around (with default implementation
pure
) for backward compatibility.
Conor McBride’s Applicative Programming
with Effects paper (JFP 2008) beautifully introduced
Applicative
functors to the world. And in case you would
like to learn some of the early history of Haskell, now is as good a
time as any for a few pointers:
A History of Haskell: Being Lazy with Class (Hudak, Hughes, Peyton Jones, and Wadler, HOPL 2017)
The Essence of Functional Programming (Wadler, POPL 1992)
Comprehending Monads (Wadler, LFP 1990)
How to Make Ad-Hoc Polymorphism Less Ad Hoc (Wadler and Blott, POPL 1989)
We’ll talk about the differences between MonadPlus_
and
MonadPlus
later. There’s some historical detritus there,
too.
(In the old days, Monad
also included a member called
fail :: String -> m a
that we will not talk about. But
if you’re curious, these days fail
lives in MonadFail
.)
Okay, no mo’ (monad) history for now!
The syntax and
desugaring of do
-notation “stitches together” actions
of some Monad type m using nested calls
to its (>>=)
method.
do { stmt_1; …; stmt_{n-1}; e_n }
::
m t_n
So, although the syntax looks imperative, do
-notation is
just syntactic sugar for a sequence of… er, binds. For example:
greatgrandparent :: Person -> Maybe Person
greatgrandparent p = do -- greatgrandparent p =
pp <- pure p -- pure p >>= \pp ->
ppp <- parent pp -- parent pp >>= \ppp ->
pppp <- parent ppp -- parent ppp >>= \pppp ->
pure pppp -- pure pppp
sibling :: Person -> Person -> Maybe ()
sibling x y = do -- sibling x y =
guard $ x /= y -- (guard $ x /= y) >>
px <- parent x -- parent x >>= \px ->
py <- parent y -- parent y >>= \py ->
guard $ px == py -- guard $ px == py
Recall the syntax of do-notation we saw earlier for IO
(here and here) —
IO
is just one instance of Monad
, and its
(primitive) implementation happens to perform a “real” side effect.
Haskell syntax allows writing semicolons in between statements in a
do
-block, so monads in Haskell may be thought of as “programmable
semicolons”.
Recall the translation of list comprehensions from before (here and here).
[ returnExp |
stmt_1 , … , stmt_n ]
Now we can comprehend (double pun intended) a list comprehension
simply as a do
-block for the []
instance of
Monad
and MonadPlus
(i.e. “in the
[]
monad”). See this translation.
For example, recall the smallPairs
function from
before:
smallPairs :: (Ord a, Num a) => [a] -> [a] -> [(a, a)]
smallPairs xs ys =
[ (x, y) | x <- xs, y <- ys, let sum = x + y, sum <= 5 ]
Now defined with a do
-block rather than a list
comprehension:
smallPairs :: (Ord a, Num a) => [a] -> [a] -> [(a, a)]
smallPairs xs ys =
do
x <- xs
y <- ys
let sum = x + y
guard $ sum <= 5
pure (x, y)
If you know that you will make T
a Monad
,
can implement the Monad
instance first…
instance Monad T where
return = ...
mx >>= f = ...
… and then define free Functor
and
Applicative
instances with the following boilerplate
definitions:
instance Functor T where
fmap f x = pure f <*> x
instance Applicative T where
pure = return
(<*>) = ap
Or, if you’re feeling really cheeky:
instance Functor T where {fmap f x = pure f <*> x}
instance Applicative T where {pure = return; (<*>) = ap}
Functor
and Applicative
are superclasses of
Monad
, but Haskell allows them to be defined “out of order”
like this. Think about how to implement ap
(and then look
it up in the library implementation).
Thus, pure
(a.k.a return
) and
(>>=)
are essentially a “minimal complete definition”
for the classes Functor
, Applicative
, and
Monad
, taken together.
Here’s a summary of the Functor
,
Applicative
, and Monad
classes:
class Functor m where
fmap :: (a -> b) -> m a -> m b
class Functor m => Applicative m where
-- fmap :: (a -> b) -> m a -> m b -- from Functor
(<*>) :: m (a -> b) -> m a -> m b
pure :: a -> m a
class Applicative m => Monad m where
-- fmap :: (a -> b) -> m a -> m b -- from Functor
-- (<*>) :: m (a -> b) -> m a -> m b -- from Applicative
-- (<<=) :: (a -> m b) -> m a -> m b -- flip (>>=)
(>>=) :: m a -> (a -> m b) -> m b
-- pure :: a -> m a -- from Applicative
return :: a -> m a
return = pure
class Monad m => MonadPlus m where
guard :: Bool -> m ()
Loop until empty line.
getLinesUntilEmpty :: IO ()
getLinesUntilEmpty = do
putStrLn "More to say?"
s <- getLine
if s /= "" then
getLinesUntilEmpty
else
putStrLn "Goodbye."
IO
IO
is in Monad
. The type definition lives
in GHC.Types
…
newtype IO a = IO ( ... RealWorld -> ( ... RealWorld, a ... ))
… and the instance definition lives in GHC.Base
:
instance Monad IO where
...
(>>=) = bindIO
bindIO :: IO a -> (a -> IO b) -> IO b
bindIO (IO m) k = ... unIO ..
unIO :: IO a -> (... RealWorld -> ( ... RealWorld, a ...))
unIO (IO a) = a
In Control.Monad.ST
:
data RealWorld :: *
“RealWorld is deeply magical. It is primitive… We never manipulate values of type RealWorld; it’s only used in the type system…”
However these primitive operations work, we can rest assured that
they satisfy the Monad
interface and laws.
Factor out common pattern:
-- doWhileM_ :: IO a -> (a -> Bool) -> IO ()
doWhileM_ :: (Monad m) => m a -> (a -> Bool) -> m ()
doWhileM_ action f = do
x <- action
if f x then
doWhileM_ action f
else
pure ()
getLinesUntilEmpty_ :: IO ()
getLinesUntilEmpty_ =
doWhileM_ (putStrLn "More to say?" >> getLine) (/= "")
Now let’s loop until empty line, and then reverse each line and print them in reverse order. Let’s start with:
doWhileM :: (Monad m) => m a -> (a -> Bool) -> m [a]
doWhileM action f = do
x <- action
if f x then do
xs <- doWhileM action f
pure (x : xs)
else
pure []
doWhileM_ :: (Monad m) => m a -> (a -> Bool) -> m ()
doWhileM_ action f =
doWhileM action f >> pure ()
repeatBackwards :: IO ()
repeatBackwards =
let getLinesUntilEmpty = doWhileM getLine (/= "") in
-- do {lines <- getLinesUntilEmpty; putStrLn $ unlines $ reverse $ map reverse lines}
-- getLinesUntilEmpty >>= \lines -> putStrLn $ unlines $ reverse $ map reverse lines
-- getLinesUntilEmpty >>= putStrLn . unlines . reverse . map reverse
putStrLn . unlines . reverse . map reverse =<< getLinesUntilEmpty
The last step uses (=<<)
(i.e. reverse bind) to
keep the “pipeline” flowing in one direction.
Alternatively, could use reverse (i.e. left-to-right) composition to write the pipeline left-to-right:
(>>>) = flip (.)
repeatBackwards =
let getLinesUntilEmpty = doWhileM getLine (/= "") in
getLinesUntilEmpty >>= map reverse >>> reverse >>> unlines >>> putStrLn
Note: The (>>>)
operator is defined in Control.Category
,
but with a different precedence level which requires writing more
parentheses in the definition above.
Exercise: Re-implement
doWhileM
so that it also returns the last result of
action
, the one that does not satisfy the predicate.
Further redefine it without using do
-notation.
The Control.Monad
library defines several common helpers, such as:
mapM :: (Monad m) => (a -> m b) -> [a] -> m [b]
mapM_ :: (Monad m) => (a -> m b) -> [a] -> m ()
forM :: (Monad m) => [a] -> (a -> m b) -> m [b]
forM_ :: (Monad m) => [a] -> (a -> m b) -> m ()
sequence :: (Monad m) => [m a] -> m [a]
sequence_ :: (Monad m) => [m a] -> m ()
Note: The actual types are more general
than these, operating not only on lists but other Foldable
or Traversable
types as well. We’ll talk more about these
type classes shortly.
Note: Remember mapIO_
? And
sequenceMaybes
?
Some people do not believe in do
(see Do-notation
Considered Harmful). Others believe that do
should do
even more (see Applicative
Do-notation). What do you think?