Stateful Functions (continued)

First, we’ll talk about the definition of StateFunc in the library. Then we’ll work through a second example with StateFuncs.

State Library

The State library in Control.Monad.State provides the functionality we implemented in StateFunc. Unlike our newtype definition, the library version is defined using rather more exotic features that we have not seen yet:

type State s = StateT s Identity

Despite the differences in name and representation, keep thinking of values of type State s a as “stateful functions that, when, run produce values of type a.”

The helper functions we defined for StateFunc are also provided by the State library, with appropriate renamings:

state     :: (s -> (a,s)) -> State s a  -- create a stateful comp.
get       :: State s s                  -- get state out
put       :: s -> State s ()            -- set "current" state
modify    :: (s -> s) -> State s ()     -- modify the state
evalState :: State s a -> s -> a        -- run and return final value
execState :: State s a -> s -> s        -- run and return final state

Note that the definition of State above is an alias, not a dataype; the library function state builds State values.

Also, beware that if you ask Haskell for the types of these functions, you’ll get more exotic types:

> :t state        -- MonadState s m => (s -> (a, s)) -> m a
> :t get          -- MonadState s m => m s
> :t put          -- MonadState s m => s -> m ()
> :t modify       -- MonadState s m => (s -> s) -> m ()

Don’t worry about this for now. Note that if we instantiate the m type with State s, these signatures match our understanding above.

> :t state  :: (s -> (a, s)) -> State s a
> :t get    :: State s s
> :t put    :: s -> State s ()
> :t modify :: (s -> s) -> State s ()

Example: Random Numbers

> import System.Random
> :t random                 -- (RandomGen g, Random a) => g -> (a, g)

> :info Random      -- describes types a that can take on random values
> :info RandomGen   -- describes types g that can act as source of randomness

Okay, so how do we get a StdGen?

> :t mkStdGen
> let g = mkStdGen 17

> :t random g
> :t fst $ random g
> fst $ random g            -- Haskell thinks we want an Int

> fst $ random g :: Int
> fst $ random g :: Bool
> fst $ random g :: Float

Can we get multiple random numbers?

> fst $ random g :: Int
> fst $ random g :: Int
> fst $ random g :: Int

Need to thread the StdGens through…

generateThree_ :: Random a => StdGen -> ((a,a,a), StdGen)
generateThree_ g0 =
  let
    (a1,g1) = random g0
    (a2,g2) = random g1
    (a3,g3) = random g2
  in
    ((a1, a2, a3), g3)

Look familiar?!?

The RandState monad

The type State StdGen a describes (wrapped) functions of type StdGen -> (a, StdGen). We will end up writing State StdGen over and over again, so we can choose to introduce an alias if we’d like.

type RandState a = State StdGen a
type RandState   = State StdGen

Start by writing a computation that produces a single Int.

generateOne :: Random a => State StdGen a
generateOne :: Random a => RandState a

generateOne = state $ \g0 ->
  let (a1,g1) = random g0 in
  (a1, g1)

Or simply:

generateOne = state random

Or, can rewrite with do-notation. (Arguably more confusing, because random takes StdGen arg.)

generateOne = do
  g0 <- get                   -- get >>= \g0 ->
  let (a,g1) = random g0      -- let (a,g1) = random g0 in
  put g1                      -- put g1 >>
  return a                    --   return a

Now we can easily sequence calls together.

generateThree :: Random a => State StdGen (a, a, a)
generateThree :: Random a => RandState (a, a, a)

generateThree =
  generateOne >>= \a1 ->
  generateOne >>= \a2 ->
  generateOne >>= \a3 ->
    return (a1,a2,a3)

Can rewrite with do-notation.

generateThree = do
  a1 <- generateOne
  a2 <- generateOne
  a3 <- generateOne
  return (a1, a2, a3)

Better yet, in applicative style:

generateThree = liftA3 (,,) generateOne generateOne generateOne

Okay, now how to run a RandState computation from an init state? First cut is to take a StdGen as input.

run_ :: RandState a -> StdGen -> a
run_ sb g = evalState sb g                    -- recall evalState

> run_ generateThree (mkStdGen 1)
> run_ generateThree (mkStdGen 2)
> run_ generateThree (mkStdGen 3)

But don’t want to have to explicitly pick a StdGen on each run. And anyway, how would be compute a random StdGen? Want Haskell to (randomly) pick one for us.

> :t getStdGen    -- IO StdGen

Notice the IO scarlet letter; there is communication with the world.

run :: RandState a -> IO a
run sa = do
  g <- getStdGen
  return $ evalState sa g

> run generateThree
> run generateThree
> run generateThree

Wait, still the same each time… The random StdGen is chosen when the process starts. And there is no “connection” between the calls to generateThrees.

There’s a way to “mutate” the “global” random number generator.

> :t newStdGen    -- IO StdGen

Replace the following:

run :: RandState a -> IO a
run sa = do
  g <- newStdGen
  return $ evalState sa g

> run' generateThree
> run' generateThree
> run' generateThree

Now we’re in business! And a bit of cleanup:

run :: RandState a -> IO a
run sa = evalState sa <$> newStdGen

Source Files