User:Duplode/State combined

From Wikibooks, open books for an open world
Jump to navigation Jump to search

Combined text[edit | edit source]

UM source text[edit | edit source]

Stateful computations are very common operations, but the way they are usually implemented in procedural or object-oriented languages cannot be replicated in Haskell. A State monad is introduced to allow states of any complexity to be represented.

The Problem with Haskell and State[edit | edit source]

If you programmed in any language before, chances are you wrote some functions that "kept state". In case you did not encounter the concept before, a state is one or more variables that are required to perform some computation, but are not among the arguments of the relevant function. In fact, object-oriented languages like C++ make extensive usage of state variables in objects in the form of member variables. Procedural languages like C use variables outside the current scope to keep track of state.

In Haskell we can very often keep track of state by passing parameters or by pattern matching of various sorts, but in some cases it is appropriate to find a more general solution. We will consider the common example of generation of pseudo-random numbers in pure functions.

Pseudo-Random Numbers[edit | edit source]

Generating actually random numbers is a very complicated subject; we will consider pseudo-random numbers. They are called "pseudo" because they are not really random, they only look like it. Starting from an initial state (commonly called the seed), they produce a sequence of numbers that have the appearance of being random.

Every time a pseudo-random number is requested, a global state is updated: that's the part we have problems with in Haskell, since it is a side effect from the point of view of the function requesting the number. Sequences of pseudo-random numbers can be replicated exactly if the initial seed and the algorithm is known.

Implementation in Haskell[edit | edit source]

Producing a pseudo-random number in most programming languages is very simple: there is usually a function, such as C or C++'s rand(), that provides a pseudo-random value (or a random one, depending on the implementation). Haskell has a similar one in the System.Random module:

> :module System.Random
> :type randomIO
randomIO :: (Random a) => IO a
> randomIO
-1557093684

Obviously, save eerie coincidences, the value you will obtain will be different. A disadvantage of randomIO is that it requires us to utilise the IO monad, which breaks purity requirements. Usage of the IO monad is dictated by the process of updating the global generator state, so that the next time we call randomIO the value will be different.

Implementation with Functional Purity[edit | edit source]

In general, we do not want to use the IO monad if we can help it, because of the loss of guarantees on no side effects and functional purity. Indeed, we can build a local generator (as opposed to the global generator, invisible to us, that randomIO uses) using mkStdGen, and use it as seed for the random function, which in turn returns a tuple with the pseudo-random number that we want and the generator to use the next time:

> :module System.Random
> let generator = mkStdGen 0 -- "0" is our seed
> random generator :: (Int, StdGen)
(2092838931,1601120196 1655838864)

And in this case, since we are using exactly the same generator, you will obtain the same value 2092838931, always the same no matter how many times you call random. We have now regained functional purity, but a function supposed to provide pseudo-random numbers that generates always the same value is not very helpful: what we need is a way to automate the extraction of the second member of the tuple (i.e. the new generator) and feed it to a new call to random; and that is where the State monad comes into the picture.

Definition of the State Monad[edit | edit source]

Note: in some package systems used for GHC, the Control.Monad.State module is in a separate package, usually indicated by MTL (Monad Transformer Library).

The Haskell type State is defined as a function that consumes state, and produces a result and the state after the result has been extracted. The definition is wrapped inside a newtype to avoid pattern matching, so that no one can explicitly pattern-match and extract state unless we allow it.

newtype State state result = State { runState :: state -> (result, state) }

The name State is actually a misnomer: it is not the state itself, but rather a state processor.

Instantiating the Monad[edit | edit source]

Note also that State has two type parameters, one for the state and one for the result: all other main types of monads have only one (Maybe, lists, IO). This means that, when we instantiate the monad, we are actually leaving the parameter for the state type:

instance Monad (State state_type)

This means that the "real" monad will be State String, State Int, or State SomeLargeDataStructure, not State itself.

The return function is implemented as:

return :: result -> State state result
return r = State ( \s -> (r, s) )

In words, giving a value to return produces a function, wrapped in the State constructor: this function takes a state value, and returns it unchanged as the second member of a tuple, together with the specified result value.

Binding is a bit intricate:

(>>=) :: State state result_a -> (result_a -> State state result_b) -> State state result_b
processor >>= processorGenerator = State $ \state -> 
                                   let (result, state') = runState processor state
                                   in runState (processorGenerator result) state'

The idea is that, given a state processor and a function that can generate another processor given the result of the first one, these two processors are combined to obtain a function that takes the initial state, and returns the second result and state (i.e. after the second function has processed them).

Setting and Accessing the State[edit | edit source]

The monad instantiation allows us to manipulate various state processors, but you may at this point wonder where exactly the state comes from in the first place. State state_type is also an instance of the MonadState class, which provides two additional functions:

put newState = State $ \_ -> ((), newState)

This function will generate a state processor given a state. The processor's input will be disregarded, and the output will be a tuple carrying the state we provided. Since we do not care about the result (we are discarding the input, after all), the first element of the tuple will be null.

The specular operation is to read the state. This is accomplished by get:

get = State $ \state -> (state, state)

The resulting state processor is going to produce the input state in both positions of the output tuple, as a result and as a state, so that it may be bound to other processors.

Getting Values and State[edit | edit source]

From the definition of State, we know that runState is an accessor to apply to a State a b value to get the state-processing function; this function, given an initial state, will return the extracted value and the new state. Other similar, useful functions are evalState and execState, which work in a very similar fashion.

Function evalState, given a State a b and an initial state, will return the extracted value only, whereas execState will return only the new state; it is possibly easiest to remember them as defined as:

evalState stateMonad value = fst ( runState stateMonad value )
execState stateMonad value = snd ( runState stateMonad value )

Example: Rolling Dice[edit | edit source]

randomRIO (1,6)

Suppose we are coding a game in which at some point we need an element of chance. In real-life games that is often obtained by means of dice, which we will now try to simulate with Haskell code. For starters, we will consider the result of throwing two dice: to do that, we resort to the function randomR, which allows to specify an interval from which the pseudo-random values will be taken; in the case of a die, it is randomR (1,6).

In case we are willing to use the IO monad, the implementation is quite simple, using the IO version of randomR:

import Control.Monad
import System.Random

rollDiceIO :: IO (Int, Int)
rollDiceIO = liftM2 (,) (randomRIO (1,6)) (randomRIO (1,6))

The two numbers will be returned as a tuple.

Exercises
  1. Implement a function rollNDiceIO :: Int -> IO [Int] that, given an integer, returns a list with that number of pseudo-random integers between 1 and 6.

Getting Rid of the IO Monad[edit | edit source]

Suppose that for some reason we do not want to use the IO monad: we may want the function to stay pure, or we may want a sequence of numbers that is the same in every run, for repeatability.

To do that, we can produce a generator using the mkStdGen function in the System.Random library:

> mkStdGen 0
1 1

The argument to mkStdGen is an Int that functions as a seed. With that, we can generate a pseudo-random integer number in the interval between 1 and 6 with:

> randomR (1,6) (mkStdGen 0)
(6,40014 40692)

We obtained a tuple with the result of the dice throw (6) and the new generator (40014 40692). A simple implementation that produces a tuple of two pseudo-random integers is then:

clumsyRollDice :: (Int, Int)
clumsyRollDice = (n, m)
        where
        (n, g) = randomR (1,6) (mkStdGen 0)
        (m, _) = randomR (1,6) g
Boxcars!

When we run the function, we get:

> clumsyRollDice
(6, 6)

The implementation of clumsyRollDice works, but we have to manually write the passing of generator g from one where clause to the other. This is pretty easy now, but will become increasingly cumbersome if we want to produce large sets of pseudo-random numbers. It is also error-prone: what if we pass one of the middle generators to the wrong line in the where clause?

Exercises
  1. Implement a function rollDice :: StdGen -> ((Int, Int), StdGen) that, given a generator, return a tuple with our random numbers as first element and the last generator as the second.

Introducing State[edit | edit source]

We will now try to solve the clumsiness of the previous approach introducing the State StdGen monad. For convenience, we give it a name with a type synonym:

type GeneratorState = State StdGen

Remember, however, that the type of GeneratorState Int is really StdGen -> (Int, StdGen), so it is not really the generator state, but a processor of the generator state. The generator state itself is produced by the mkStdGen function. Note that GeneratorState does not specify what type of values we are going to extract, only the type of the state.

We can now produce a function that, given a StdGen generator, outputs a number between 1 and 6:

rollDie :: GeneratorState Int
rollDie = do generator <- get
             let (value, newGenerator) = randomR (1,6) generator
             put newGenerator
             return value

The do notation is in this case much more readable; let's go through each of the steps:

  1. First, we take out the pseudo-random generator with get: the <- notation extracts the value from the GeneratorState monad, not the state; since it is the state we want, we use get, that extracts the state and outputs it as the value (look again at the definition of get above, if you have doubts).
  2. Then, we use the randomR function to produce an integer between 1 and 6 using the generator we took; we also store the new generator graciously returned by randomR.
  3. We then set the state to be the newGenerator using the put function, so that the next call will use a different pseudo-random generator;
  4. Finally, we inject the result into the GeneratorState monad using return.

We can finally use our monadic die:

> evalState rollDie (mkStdGen 0)
6

At this point, a legitimate question is why we have involved monads and built such an intricate framework only to do exactly what fst $ randomR (1,6) does. The answer is illustrated by the following function:

rollDice :: GeneratorState (Int, Int)
rollDice = liftM2 (,) rollDie rollDie

We obtain a function producing two pseudo-random numbers in a tuple. Note that these are in general different:

> evalState rollDice (mkStdGen 666)
(6,1)

That is because, under the hood, the monads are passing state to each other. This used to be very clunky using randomR (1,6), because we had to pass state manually; now, the monad is taking care of that for us. Assuming we know how to use the lifting functions, constructing intricate combinations of pseudo-random numbers (tuples, lists, whatever) has suddenly become much easier.

Exercises
  1. Similarly to what was done for rollNDiceIO, implement a function rollNDice :: Int -> GeneratorState [Int] that, given an integer, returns a list with that number of pseudo-random integers between 1 and 6.

Producing Pseudo-Random Values of Different Types: the Random class[edit | edit source]

Until now, absorbed in the die example, we considered only Int as the type of the produced pseudo-random number. However, already when we defined the GeneratorState monad, we noticed that it did not specify anything about the type of the returned value. In fact, there is one implicit assumption about it, and that is that we can produce values of such a type with a call to random.

Values that can be produced by random and similar function are of types that are instances of the Random class (capitalised). There are default implementations for Int, Char, Integer, Bool, Double and Float, so you can immediately generate any of those.

Since we noticed already that the GeneratorState is "agnostic" in regard to the type of the pseudo-random value it produces, we can write down a similarly "agnostic" function, analogous to rollDie, that provides a pseudo-random value of unspecified type (as long as it is an instance of Random):

getRandom :: Random a => GeneratorState a
getRandom = do generator <- get
               let (value, newGenerator) = random generator
               put newGenerator
               return value

Compared to rollDie, this function does not specify the Int type in its signature and uses random instead of randomR; otherwise, it is just the same. What is notable is that getRandom can be used for any instance of Random:

> evalState getRandom (mkStdGen 0) :: Bool
True
> evalState getRandom (mkStdGen 0) :: Char
'\64685'
> evalState getRandom (mkStdGen 0) :: Double
0.9872770354820595
> evalState getRandom (mkStdGen 0) :: Integer
2092838931

Indeed, it becomes quite easy to conjure all these at once:

allTypes :: GeneratorState (Int, Float, Char, Integer, Double, Bool, Int)
allTypes = liftM (,,,,,,) getRandom
                     `ap` getRandom
                     `ap` getRandom
                     `ap` getRandom
                     `ap` getRandom
                     `ap` getRandom
                     `ap` getRandom

Here we are forced to used the ap function, defined in Control.Monad, since there exists no liftM7. As you can see, its effect is to concatenate multiple monads into a lifting operation of the 7-element-tuple operator, (,,,,,,). To understand what ap does, look at its signature:

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

remember then that type a in Haskell can be a function as well as a value, and compare to:

>:type liftM (,,,,,,) getRandom
liftM (,,,,,) getRandom :: (Random a1) =>
                          State StdGen (b -> c -> d -> e -> f -> (a1, b, c, d, e, f))

The monad m is obviously State StdGen (which we "nicknamed" GeneratorState), while ap's first argument is function b -> c -> d -> e -> f -> (a1, b, c, d, e, f). Applying ap over and over (in this case 6 times), we finally get to the point where b is an actual value (in our case, a 7-element tuple), not another function.

So much for understanding the implementation. Function allTypes provides pseudo-random values for all default instances of Random; an additional Int is inserted at the end to prove that the generator is not the same, as the two Ints will be different.

> evalState allTypes (mkStdGen 0)
(2092838931,9.953678e-4,'\825586',-868192881,0.4188001483955421,False,316817438)
Exercises
  1. If you are not convinced that State is worth using, try to implement a function equivalent to evalState allTypes without making use of monads, i.e. with an approach similar to clumsyRollDice above.

AM source text[edit | edit source]

The State monad[edit | edit source]

The State monad actually makes a lot more sense when viewed as a computation, rather than a container. Computations in State represents computations that depend on and modify some internal state. For example, say you were writing a program to model the three body problem. The internal state would be the positions, masses and velocities of all three bodies. Then a function, to, say, get the acceleration of a specific body would need to reference this state as part of its calculations.

The other important aspect of computations in State is that they can modify the internal state. Again, in the three-body problem, you could write a function that, given an acceleration for a specific body, updates its position.

The State monad is quite different from the Maybe and the list monads, in that it doesn't represent the result of a computation, but rather a certain property of the computation itself.

What we do is model computations that depend on some internal state as functions which take a state parameter. For example, if you had a function f :: String -> Int -> Bool, and we want to modify it to make it depend on some internal state of type s, then the function becomes f :: String -> Int -> s -> Bool. To allow the function to change the internal state, the function returns a pair of (return value, new state). So our function becomes f :: String -> Int -> s -> (Bool, s)

It should be clear that this method is a bit cumbersome. However, the types aren't the worst of it: what would happen if we wanted to run two stateful computations, call them f and g, one after another, passing the result of f into g? The second would need to be passed the new state from running the first computation, so we end up 'threading the state':

fThenG :: (s -> (a, s)) -> (a -> s -> (b, s)) -> s -> (b, s)
fThenG f g s =
  let (v,  s' ) = f s    -- run f with our initial state s.
      (v', s'') = g v s' -- run g with the new state s' and the result of f, v.
  in (v', s'')           -- return the latest state and the result of g

All this 'plumbing' can be nicely hidden by using the State monad. The type constructor State takes two type parameters: the type of its environment (internal state), and the type of its output. (Even though the new state comes last in the result pair, the state type must come first in the type parameters, since the 'real' monad is bound to some particular type of state but lets the result type vary.) So State s a indicates a stateful computation which depends on, and can modify, some internal state of type s, and has a result of type a. How is it defined? Well, simply as a function that takes some state and returns a pair of (value, new state):

newtype State s a = State (s -> (a, s))

The above example of fThenG is, in fact, the definition of >>= for the State monad, which you probably remember from the first monads chapter.

The meaning of return[edit | edit source]

We mentioned earlier that return x was the computation that 'did nothing' and just returned x. This idea only really starts to take on any meaning in monads with side-effects, like State. That is, computations in State have the opportunity to change the outcome of later computations by modifying the internal state. It's a similar situation with IO (because, of course, IO is just a special case of State).

return x doesn't do this. A computation produced by return generally won't have any side-effects. The monad law return x >>= f == f x basically guarantees this, for most uses of the term 'side-effect'.

Further reading[edit | edit source]

  • A tour of the Haskell Monad functions by Henk-Jan van Tuyl
  • All about monads by Jeff Newbern explains well the concept of monads as computations, using good examples. It also has a section outlining all the major monads, explains each one in terms of this computational view, and gives a full example.
  • Monads by Eugene Kirpichov attempts to give a broader and more intuitive understanding of monads by giving non-trivial examples of them