Haskell/理解 Monad

维基教科书,自由的教学读本
Information

本頁正值覆寫,倘要翻閱前版,則請移步 斯處


Notes and TODOs[编辑]

Loose ends:

  • Explain monadic parser combinators! But in another chapter.
  • The basic triad "rock, scissors, paper" err, "reader, writer, state" is best introduced in another chapter, maybe entitled "A Zoo of Monads". Reader must include the famous function [(a->b)] -> a -> [b] also known as sequence!
  • The Random a is too cute to not elaborate it further to probabilistic functional programming. The Monty Hall problem can be solved with that. Key: the implementation can be changed, it effectively becomes the Set-Monad then. Extension: guard and backtracking.
  • Exceptions are a nice way to explain monads, too. See also [1].

介绍[编辑]

什么是Monad[编辑]

定义:Monad是一个三元组 由类型构造器 和两个多态函数

组成。两个函数符合下列三个定律:

右单元
左单元
结合律

操作符通常叫做"bind"。经常地,类型构造器也称作monad。

换句话说,一个monad就是一种类似队列或者有限映射的抽象数据类型,所包含的两个操作"bind"和"return"要满足三个特性。一个特别需要注意的地方是一个monad 不是一个类型,而是一个"类型构造器",类似于一个从类型到类型的函数。并且,monad是一个非常抽像的概念,正如我们要看到的,"bind" 可能有很多不同的含义。

在Haskell里,我们可以将其定义为一个类型类

 class Monad m where
   return :: a -> m a
   (>>=)  :: m a -> (a -> m b) -> m b

所有的Monad都假定满足上面的三个定律。这个类是Haskell Prelude 的一部分,是在标准库模块Control.Monad 里面定义的,并有一些扩展。

What use are Monads?[编辑]

After maturing in the mathematical discipline of category theory for some time, monads were introduced to programming when Eugenio Moggi showed[1] how they can unify the description of the semantics of different programming languages. Depending on the concrete monad chosen, different semantics emerge. For instance, mutable state can be modeled by the monad M a = s -> (a,s). Lists are a monad, too, and model nondeterminism and backtracking whereas the monad M a = Either e a models exceptions.

One aim of the chapters on monads is to exemplify many of these different forms of computation. Of course, it's not our main interest to study programming language semantics, but it was Philip Wadler who noticed[2] [3] that we can directly implement Moggi's monads in Haskell. This is a powerful idea since each monad is a little minilanguage specially suited for a particular task. For instance, to program a state transformer, we can use a monad to model state. To solve a logic problem, we use the list monad to transparently handle backtracking. To handle failure and exceptions easily, we have the Either e monad. And last but not least, there is the IO monad to perform input/output, something that did not seem to fit well into a purely functional language. This and subsequent chapters are to guide you to through these minilanguages and to show they can simplify and structure your daily Haskell code.

But how can the rather short definition of monads given above relate all these very different forms of computation? They all share a common use pattern, namely the ability to combine two computations and into a compound computation by first "executing" and "then" binding, i.e. feeding the result to . This is what the operator captures and that's why it's called "bind". In other words, is similar to function composition. Of course, depending on the underlying monad, "executing" and "then" may have quite different meanings. Don't worry if this seems too abstract now, we will detail the genesis of with our first example monad in the section Stateful Computations.

Stateful Computations[编辑]

We will introduce with a practical example of stateful computations: random number generation. First, we will explain how a deterministic computer can generate "random" numbers. Then, we will introduce bind and return as useful functions for combining random number generators. And last but not least, the IO monad will be introduced intuitively as a state transformer changing the "world state".

Random Number Generation[编辑]

Computers usually create random numbers by starting with a single random number (frequently called "seed") and applying some arithmetic operations to it to get a new random number. By repeating this process, we get a sequence of fairly random numbers. Of course, since each number is generated in a deterministic way from the previous one, they are not truly random, but pseudo-random numbers. But by choosing the arithmetic operations carefully to properly "scramble" the input number, they behave like real random numbers. To give an impression of how this "scrambling" works, here's an example function that generates a pseudo-random number from a previous one:

type Seed = Int

randomNext :: Seed -> Seed 
randomNext rand =
  if newRand > 0
    then newRand
    else newRand + 2147483647 
  where newRand = 16807 * lo - 2836 * hi
        (hi,lo) = rand `divMod` 127773

There is much research on constructing good pseudo-random number generators, but fortunately, the Haskell standard library module System.Random

already implements a ready-to-use generator for us. However, its interface is best explained with randomNext, so we will stick to that for now.

Let's implement a function that simulates a single roll of a die, i.e. that returns a random number from 1 to 6. But randomNext uses large numbers since they can be scrambled much better, so we need to convert a Seed to a number from 1 to 6. This can be done by dividing the Seed by 6 and taking the remainder

toDieRoll :: Seed -> Int 
toDieRoll seed = (seed `mod` 6) + 1

So, given an initial random Seed, we can roll a die with it

toDieRoll 362354 -- hand-crafted initial random seed :-) 3

But something is missing: what if we want to roll the die a second time? For that, we have to generate a new random Seed from the old one via randomNext. In other words, we have to change the current Seed, i.e. the state of our pseudo-random number generator. In Haskell, this can be accomplished by returning the new state in the result

rollDie :: Seed -> (Int, Seed)
rollDie seed = ((seed `mod` 6) + 1, randomNext seed)

This is the description of a state transformer: an initial state (the Seed) is transformed to a new one while yielding a result (the Int between 1 and 6). We can visualize it as:

To roll two dice and sum their pips, we can now feed the Seed from the first roll to the second roll. Of course, we have to return the new state from the second dice roll as well for our function sumTwoDice to be as useful as rollDie:

sumTwoDice :: Seed -> (Int, Seed)
sumTwoDice seed0 = 
  let (die1, seed1) = rollDie seed0
      (die2, seed2) = rollDie seed1
  in (die1 + die2, seed2)

Again, a picture shows clearly how the state is passed from one rollDie to the next. Note that randomNext does not appear in the definition of sumTwoDice, the state change it performs is already embedded in rollDie. The function sumTwoDice merely propagates the state updates.

This is the model that System.Random

employs, so we can now elaborate on its concrete interface. The library uses two type classes: RandomGen and Random. Any instance of the former acts similar to our Seed, it's just called "random number generator", not "seed". This makes sense since the seed may have more complicated internals than just an Int and is closely linked to the function that generates new pseudo-random numbers. In any case, the module exports a convenient random number generator StdGen and you most likely won't have to deal with the RandomGen-class at all.

The interesting functions are those of the class Random, in particular random and randomR. They are implemented for a few types like Bool, Char, Int etc. so you can use them to generate different random things than numbers. The function randomR returns a random number in a specified range, so that we can conveniently write import System.Random

rollDie :: StdGen -> (Int, StdGen) 
rollDie = randomR (1,6)

As a final note, you may want to compare random number creation in Haskell to its counterpart in imperative languages like C. In the latter, there usually is a "function" rand() that returns a different and random result at each call but internally updates the random seed. Since Haskell is pure, the result of a function is determined solely by its parameters and manipulating the random seed has to manifest itself in the type.

练习
  1. Roll two dice! With sumTwoDice that is :-) . Use fst to extract the result.
  2. Write a function rollNDice :: Int -> Seed -> ([Int],Seed) that rolls dice n times and returns a list of the n results. Extra: If you know about infinite lists, use unfoldr and take to get the result list (but without seed this time).
  3. Reimplement Seed and rollDie with StdGen and random from System.Random

.

  1. Now that you have random numbers, do some statistical experiments with the help of rollNDice. For example, do a sanity check that rollDie is not skewed and returns each number with equal likelyhood. How is the sum of pips of a double dice roll distributed? The difference? And triple rolls?

Threading the State with bind[编辑]

>> for the state monad is easier than >>=. But it's meaningless for random numbers :-/ PICTUREs for the plumbing! Somehow shorten the discussion, mainly introduce return more fluently. Expanding the definitions of the new combinators as exercises to check that the new code for sumTwoDice is the same as the old one.

In the last subsection, we've seen that state transformers like random number generators can be modeled by functions s -> (a,s) where s is the type of the state. Such a function takes a state and returns a result of type a and a transformed state. However, programming with these functions is a bit tedious since we have to explicitly pass the state from one computation to the next one like in the definition of sumTwoDice

sumTwoDice :: Seed -> (Int, Seed)
sumTwoDice = \seed0 ->
  let (die1, seed1) = rollDie seed0
      (die2, seed2) = rollDie seed1 
  in (die1 + die2, seed2)

Each state has to be named and we have to take care to not pass the wrong state to the next function by accident. Of course, we are Haskell programmers: if there are common patterns or boilerplate in our code, we should search for a way to abstract and capture them in a higher order function. Thus, we want to find something that can combine state transformers s -> (a,s) to larger ones by passing the state from one to the next. A first attempt is an operator named "then"

(>>) :: (Seed -> (a,Seed)) -> (Seed -> (b,Seed)) -> (Seed -> (b,Seed))

which passes the state from the first computation to the second

(>>) m n = \seed0 ->
  let (result1, seed1) = m seed0
      (result2, seed2) = n seed1
  in (result2, seed2)

By nesting it, we can already roll a die multiple times

rollDie >> (rollDie >> rollDie)

without seeing a single state! Unfortunately, (>>) doesn't allow us to use the result of the first die roll in the following ones, it's simply ignored. In other words, this combinaton changes the random seed three times but only returns the pips from the last die roll. Rather pointless for random numbers, but we're on the right track. PICTURE FOR (>>)! We somehow need a way to pass the result from the first computation to the second, "then" is not yet general enough to allow the implementation of sumTwoDice. But first, we should introduce a type synonym to simplify the type signatures

type Random a = Seed -> (a, Seed)

(>>) :: Random a -> Random b -> Random b
rollDie :: Random Int
sumTwoDice :: Random Int

Astonishingly, this gives an entirely new point of view: a value of type Random a can be seen as a value of type a that varies randomly. So, rollDie can be interpreted as a number between 1 and 6 that "fidgets" and is sometimes "here" and sometimes "there" when asked about is value. We will explore this idea further, but for now, let's stick to our initial goal that Random a is a simple shortcut for a state transformer. Just take a mental note about the observation that our aim of explicitely removing the state from our functions naturally asks for removing the state from our types, too. Now, how to pass the result from one computation to the next? Well, we may simply give it as parameter to the next one

(>>=) :: Random a -> (a -> Random b) -> Random b

In other words, the second state transformer is now replaced by a function so that its result of type b may depend on the previous result a. The implementation is almost that of >>

(>>=) m g = \seed0 ->
  let (result1, seed1) = m seed0
      (result2, seed2) = (g result1) seed1
  in (result2, seed2)

with the only difference being that g now takes result1 as parameter. PICTURE! This combinator named "bind" should finally allow us to implement sumTwoDice. Let's see: we roll the first die and feed the result to a function that adds a second die roll to that

sumTwoDice :: Random Int
sumTwoDice = rollDie >>= (\die1 -> addToDie die1)

Adding the second die roll uses the remaining code from our original definition of sumTwoDice.

addToDie :: Int -> Random Int
addToDie die1 = \seed1 ->
  let (die2, seed2) = rollDie seed1
  in (die1 + die2, seed2)

(Remember that Random Int = Seed -> (Int, Seed).) That's still unsatisfactory, since we would like to avoid all explicit state and just use >>= a second time to feed the second dice roll to the sum

addToDie die1 = rollDie >>= (\die2 -> addThem die2)
where addThem die2 = \seed2 -> (die1 + die2, seed2)

That's the same as

addToDie die1 = rollDie >>= (\die2 -> (\seed2 -> (die1 + die2, seed2)))

which is almost

addToDie die1 = rollDie >>= (\die2 -> (die1 + die2))

though not quite since the latter doesn't type check since the sum has type Int instead of the expected Random Int. But we can convert the former into the latter with a helper function called "return"!

addToDie die1 = rollDie >>= (\die2 -> return (die1 + die2))

return :: a -> Random a
return x = \seed0 -> (x, seed0)

So, return doesn't change the state but simply returns its argument as result. For random numbers, this means that return creates a number that isn't random at all. Last but not least, we can drop the definition of addToDie and directly write

sumTwoDice :: Random Int
sumTwoDice = rollDie >>= (\die1 -> 
               rollDie >>= (\die2 -> 
                 return (die1 + die2)))
练习
  1. Implement rollNDice :: Int -> Random [Int] from the previous subsection with >>= and return.

NOTE: Since >>= and return are already present in the Prelude

, you may want to use import Prelude hiding ((>>=),return) to avoid compilation errors.

To conclude, the quest of automating the passing of state from one computation to the next led us to the two operations that define a monad. Of course, this is just the beginning. The reader is probably not yet accustomed to the >>=-combinator, how to program with it effectively? What about the three monad laws mentioned in the introduction? But before we embark to answer these questions in the next big section, let us emphasize the need for using >>= as a main primitive in a slightly different example in the next subsection.

Input/Output needs bind[编辑]

IO is the one type that requires the programmer to know what a monad is, the other monads are more or less optional. It makes abstract return and bind necessary. Explaining World -> (a, World) = IO a and the need to hide the World naturally leads to return and >>=. I guess we need to mention somewhere that main :: IO () is the link to the real world.

Performing input/output in a purely functional language like Haskell has long been a fundamental problem. How to implement operations like getChar which returns the latest character that the user has typed or putChar c which prints the character c on the screen? Giving getChar the type getChar :: Char is not an option, since a pure function with no arguments must be constant. We somehow have to capture that getChar also performs the side effect of interacting with the user. Likewise, a type putChar :: Char -> () is useless since the only value this function can return has to be ().

The breakthrough came when it was realized[4] that monads, i.e. the operations >>= and return can be used to elegantly deal with side effects. The idea is to give our two primitive operations the types

getChar :: IO Char 
putChar :: Char -> IO ()

and interpret a value of type IO a as a computation or action that performs a side effect before returning the value a. This is rather abstract, so a more concrete way is to interpret IO as a state transformer

type IO a = World -> (a, World)

that acts on and changes the "state of the world". In other words, printing a character takes the world and returns one where the character has been printed and reading a character returns a world where the character has been read. With this model, an action echo :: IO () that reads a character and immediately prints it to the screen would be written as

echo = \world0 ->
  let (c , world1) = getChar world0 
      ((), world2) = putChar c world1
  in ((), world2)

Of course, this is a case for the bind combinator that passes the state of the world for us:

echo = getChar >>= putChar

But for IO a, the use of >>= is not a convenience, it is mandatory. This is because by passing around the world explicitly, we could write (either accidentally or even consciously) something that duplicates the world:

havoc = \world0 ->
  let (c , world1) = getChar world0
      ((), world2) = putChar c world0
  in ((), world2)

Now, where does putChar get the character c from? Did the state of world roll back similar to a time travel? This makes no sense, we have to ensure that the world is used in a single-threaded way. But this is easy to achieve: we just make IO a an abstract data type and export only >>= and return for combining actions, together with primitive operations like putChar.

There's even more: the model World -> (a,World) for input/output just doesn't work, one of the exercises shows why. Also, there is no hope to extend it to concurrency and exceptions. In other words, it is imperative to make >>= for composing effectful computations IO a an abstract primitive operation.

练习
  1. Write a function putString :: String -> IO () that outputs a sequence of characters with the help of putChar.
  2. The program loop :: IO () loop = return () >> loop loops forever whereas loopX :: IO () loopX = putChar 'X' >> loopX prints an infinite sequence XXXXXX... of X-s. Clearly, a user can easily distinguish them by looking on the screen. However, show that the model IO a = World -> (a, World) gives the same denotation ⊥ for both. This means that we have to abandon this model as possible semantics for IO a.

Programming with bind and return[编辑]

Time to write programs! More complicated stuff for Random a. Examples to code: St.Petersburg paradox, Lewis Carroll's pillow problem. Somewhere make explicit instances of the Monad-class? Hm, we really need to incorporate the monad class in the type signatures. I'm not sure whether the nuclear waste metaphor is necessary?

In the last section, we showed how the two defining operations >>= and return of a monad arise as abstraction for composing state transformers. We now want to focus on how to program effectively with these.

Nuclear Waste Containers[编辑]

Random a as fuzzy a. Programming would be so much easier if we had extract :: Random a -> a, bind is sooo unwieldy. Mental prevention: think of monads as "Nuclear waste containers", the waste may not leak outside at any cost. The thing closest to extract we can have is join :: m (m a) -> m a. The text probably talks too much about "monads as containers", I'm not sure what to do.

We saw that the bind operation takes a computation, executes it, and feeds its result to the next, like in

echo =
  getChar >>=
    \char -> putChar char sumTwoDice = rollDie >>=
      \die1 -> rollDie >>=
        \die2 -> return (die1 + die2)

(Note that for parsing, lambda expressions extend as far to the right as possible, so it's not necessary to put them in parantheses.) However, it could be tempting to "execute" a monadic action like IO a with some hypothetical function

extract :: IO a -> a

in order to conveniently formulate

echo = return (putChar (extract getChar))

Of course, such a function does not make sense. For state transformers like Random a = Seed -> (a, Seed), it would have to invent a state and discard it again, thus regressing from our goal of passing the new state to the next computation.

Here's a metaphor to strengthen your mind against extract:

  • Think of a monadic computation M a as a container for a value of type a that is unfortunately paired with highly dangerous nuclear waste. Under no circumstance should this tightly sealed container be opened to extract the a or the nuclear waste will leak out, resulting in a catastrophe!.

So, there are some like getChar :: IO Char or rollDie :: Random Int that produce a precious value but unfortunately cannot operate without tainting it with nuclear waste. But fortunately, we have our function

(>>=) :: Monad m => m a -> (a -> m b) -> m b

that nonetheless allows us to operate on the value contained in M a by entering the container and applying the given function to the value inside it. This way, eveything happens inside the container and no nuclear materials leak out. Arguably, this description of "bind" probably applies better to a function

fmap :: Monad m => (a -> b) -> m a -> m b
fmap f m = m >>= \x -> return (f x)

that takes a pure function into the container to transform the value within. You may notice that this is the defining mapping for functors, i.e. every monad is a functor. Apparently, fmap is less general than >>= since the latter expects the function to be lifted into the container to produce nuclear waste, too. The best what fmap can do is

fmap' :: Monad m => (a -> (m b)) -> m a -> m (m b)

to produce a nested container. Of course, it is safe to open the inner container since the outer container still shields the environment from the nuclear waste

join :: Monad m => m (m a) -> m a
join m = m >>= id

In other words, we can describe the operation of >>= as

m >>= g = join (fmap g m)

i.e. it lifts a waste-producing computation into the container and flattens the resulting nested containers.

We will explore this futher in #Monads as Containers.

Of course, we shouldn't take the nuclear waste metaphor too literally, since there usually is some way to "run" the computation. For instance, random numbers can be observed as an infinite list of random numbers produced by an initial random seed.

run :: Random a -> (Seed -> [a])

Only the IO monad is a primitive in Haskell. How do we "run" it, then? The answer is that the link of a Haskell program to outside world is the function

main :: IO ()

which will be run by the operating system. In other words, the Haskell program itself ultimately produces nuclear waste, so there is no need to extract IO a -> a.

练习
  1. Implement run with unfoldr.

do-Notation[编辑]

A common way to write the composition of multiple monadic computations is

sumTwoDice = do 
  die1 <-
    rollDie die2 <-
      rollDie return (die1 + die2)

Control Structures[编辑]

Needs a better title. Introduce sequence, fmap, liftMn, forM, mapM and friends.

The three Monad Laws[编辑]

In the state monad, return doesn't touch the state. That can be formulated abstractly with the first two monad laws. Hm, what about the third? How to motivate that? The third is intuitive: in the context of passing things around, order, not grouping matters (associativity).

Monads as containers[编辑]

Needs a better title. Introduce the second instances of monads, namely [a] and Maybe a. Shows that the operations return and bind are applicable to quite a range of problems. The more "exotic" example

data Tree a = Leaf a | Branch (Tree a) (Tree a)

belongs here, too, probably as exercise.

Lists[编辑]

concatMap and sequence..

Maybe[编辑]

Maybe Either, too?


References[编辑]

  1. Moggi, Eugenio (1991). "Notions of Computation and Monads". Information and Computation 93 (1).
  2. w:Philip Wadler. Comprehending Monads. Proceedings of the 1990 ACM Conference on LISP and Functional Programming, Nice. 1990.
  3. w:Philip Wadler. The Essence of Functional Programming. Conference Record of the Nineteenth Annual ACM SIGPLAN-SIGACT Symposium on Principles of Programming Languages. 1992.
  4. Simon Peyton Jones, Philip Wadler (1993). "Imperative functional programming". 20'th Symposium on Principles of Programming Languages.



理解 Monad
习题解答
Monads

理解 Monad  >> 高级 Monad  >> Monad 进阶  >> MonadPlus  >> Monadic parser combinators  >> Monad transformers  >> Monad 实务


Haskell

Haskell基础 >> 初级Haskell >> Haskell进阶 >> Monads
高级Haskell >> 类型的乐趣 >> 理论提升 >> Haskell性能


库参考 >> 普通实务 >> 特殊任务