Difference between revisions of "State Monad"

From HaskellWiki
Jump to navigation Jump to search
(unless i'm mistaken.. i think there are other type mistakes here?)
m (Fixed definition of evalState/runState as pointed out in http://haskell.org//pipermail/haskell-cafe/2009-August/064964.html)
Line 162: Line 162:
 
<haskell>
 
<haskell>
 
evalState :: State s a -> s -> a
 
evalState :: State s a -> s -> a
evalState act = fst $ runState act
+
evalState act = fst . runState act
   
 
execState :: State s a -> s -> s
 
execState :: State s a -> s -> s
execState act = snd $ runState act
+
execState act = snd . runState act
 
</haskell>
 
</haskell>
   

Revision as of 09:00, 6 August 2009

The State Monad by Example

This is a short tutorial on the state monad. Emphasis is placed on intuition. The types have been simplified to protect the innocent.


Foundations

Primitives

runState (return 'X') 1

('X',1)

Return set the result value but left the state unchanged. Comments:

   return 'X' :: State Int Char
   runState (return 'X') :: Int -> (Char, Int)
   initial state = 1 :: Int
   final value = 'X' :: Char
   final state = 1 :: Int
   result = ('X', 1) :: (Char, Int)

runState get 1

(1,1)

Get set the result value to the state and left the state unchanged. Comments:

   get :: State Int Int
   runState get :: Int -> (Int, Int)
   initial state = 1 :: Int
   final value = 1 :: Int
   final state = 1 :: Int



runState (put 5) 1

((),5)

Put set the result value to () and set the state value. Comments:

   put 5 :: State Int ()
   runState (put 5) :: Int -> ((),Int)
   initial state = 1 :: Int
   final value = () :: ()
   final state = 5 :: Int

Combinations

Because (State s) forms a monad, values can be combined together with (>>=) or do{}.

runState (do { put 5; return 'X' }) 1

('X',5)

Comments:

   do { put 5; return 'X' } :: State Int Char 
   runState (do { put 5; return 'X' }) :: Int -> (Char,Int)
   initial state = 1 :: Int
   final value = 'X' :: Char
   final state = 5 :: Int



postincrement = do { x <- get; put (x+1); return x }
runState postincrement 1

(1,2)


predecriment = do { x <- get; put (x-1); get }
runState predecriment 1

(0,0)

Other Functions

runState (modify (+1)) 1

((),2)


runState (gets (+1)) 1

(2,1)


evalState (gets (+1)) 1

2


execState (gets (+1)) 1

1

Implementation

At its heart, a value of type (State s a) is a function from initial state s to final value a and final state s: (a,s). These are usually wrapped, but shown here unwrapped for simplicity.

Return leaves the state unchanged and sets the result:

-- ie: (return 5) 1 -> (5,1)
return :: a -> State s a
return x s = (x,s)

Get leaves state unchanged and sets the result to the state:

-- ie:  get 1 -> (1,1)
get :: State s s
get s = (s,s)

Put sets the result to () and sets the state:

-- ie: (put 5) 1 -> ((),5)
put :: s -> State s ()
put x s = ((),x)

The helpers are simple variations of these primitives:

modify :: (s -> s) -> State s ()
modify f = do { x <- get; put (f x) }

gets :: (s -> a) -> State s a
gets f = do { x <- get; return (f x) }

EvalState and execState just select one of the two values returned by runState. EvalState returns the final result while execState returns the final state:

evalState :: State s a -> s -> a
evalState act = fst . runState act

execState :: State s a -> s -> s
execState act = snd . runState act

Combining two states is the trickiest bit in the whole scheme. To combine do { x <- act1; act2 x } we need a function which takes an initial state, runs act1 to get an intermediate result and state, feeds the intermediate result to act2 and then runs that action with the intermediate state to get a final result and a final state:

(>>=) :: State s a -> (a -> State s b) -> State s b
(act1 >>= fact2) s = runState act2 is 
    where (iv,is) = runState act1 s
          act2 = fact2 iv