Headline

A monad for state

Illustration

Let us put to work the State monad in a simple interpreter.

A baseline interpreter

There are these expression forms:

-- Simple Boolean expressions
data Expr = Constant Bool | And Expr Expr | Or Expr Expr
  deriving (Eq, Show, Read)

For instance, the following expression should evaluate to true:

sample = And (Constant True) (Or (Constant False) (Constant True))

Here is a simple interpreter, indeed:

-- A straightforward interpreter
eval :: Expr -> Bool
eval (Constant b) = b
eval (And e1 e2) = eval e1 && eval e2
eval (Or e1 e2) = eval e1 || eval e2

Adding counting to the interpreter

Now suppose that the interpreter should keep track of the number of operations applied. We count And and Oras operations. Thus, the sample term should count as 2. We may incorporate counting into the initial interpreter by essentially maintaing an extra result component for the counter. (We could also synthesize the count as output; see the illustration of the writer monad.)

To make the example a bit more interesting, let's add a construct Hide. The expectation is that operations under Hide are not counted.

data Expr
  = Constant Bool
  | And Expr Expr
  | Or Expr Expr
  | Hide Expr

Because of the use of Hide, we would count 2 instead of 3 operations in the following term:

sample =
  And
    (Constant True)
    (Or
      (Constant True)
      (Hide (And
        (Constant False)
        (Constant False))))

Here is the interpreter which incorporates counting:

-- Interpreter with counting operations
eval' :: Expr -> Int -> (Bool, Int)
eval' (Constant b) i = (b, i)
eval' (And e1 e2) i = 
  let 
   (b1,i') = eval' e1 i
   (b2,i'') = eval' e2 i'
  in (b1 && b2, i''+1) 
eval' (Or e1 e2) i = 
  let 
   (b1,i') = eval' e1 i
   (b2,i'') = eval' e2 i'
  in (b1 || b2, i''+1) 
eval' (Hide e) i = (fst (eval' e i), i)

Alas, the resulting interpreter is harder to understand. The threading of counts is entangled with the basic logic.

Monadic style

By conversion to monadic style, we can hide counting except when we need increment the counter. We use the State monad here so that we really track the operations counter along evaluation; this would be useful if we were adding an expression form for retrieving the count. We could also be using the writer monad, if we were only interested in the final count.

-- Monadic style interpreter
evalM :: Expr -> State Int Bool
evalM (Constant b) = return b
evalM (And e1 e2) = 
  evalM e1 >>= \b1 ->
  evalM e2 >>= \b2 ->
  modify (+1) >> 
  return (b1 && b2)
evalM (Or e1 e2) = 
  evalM e1 >>= \b1 ->
  evalM e2 >>= \b2 ->
  modify (+1) >> 
  return (b1 || b2)
evalM (Hide e) =
  get >>= \i ->
  evalM e >>= \b ->
  put i >>= \() ->
  return b

We can also use do notation:

-- Monadic style interpreter in do notation
evalM' :: Expr -> State Int Bool
evalM' (Constant b) = return b
evalM' (And e1 e2) = do
  b1 <- evalM' e1
  b2 <- evalM' e2
  modify (+1)
  return (b1 && b2)
evalM' (Or e1 e2) = do
  b1 <- evalM' e1
  b2 <- evalM' e2
  modify (+1)
  return (b1 || b2)
evalM' (Hide e) = do
  i <- get
  b <- evalM e
  put i
  return b

The State monad

The state monad is readily provided by the Haskell library (in Control.Monad.State.Lazy), but we may want to understand how it might have been implemented. The data type for the State monad could look like this:

-- Data type for the State monad
newtype State s a = State { runState :: s -> (a,s) }

Thus, a stateful computation is basically a function on state which also returns a value.

The corresponding instance of the type class Monad follows:

-- Monad instance for State
instance Monad (State s)
  where
    return x = State (\s -> (x, s))
    c >>= f = State (\s -> let (x,s') = runState c s in runState (f x) s')

The definition of return conveys that a pure computation preserves the state. The definition of bind conveys that the state is to be threaded from the first argument to the second. Finally, we need to define state-specific operations:

-- Important State operations: get/put state
get :: State s s
get = State (\s -> (s, s))

put :: s -> State s ()
put s = State (\_ -> ((), s))

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

In modern Haskell, we also need to make State an instance of Applicative (for applicative functors and Functor (for functors). This code is omitted here, but see GitHub for this page.


Ralf Lämmel edited this article at Fri, 14 Jul 2023 16:44:05 +0200
Compare revisions Compare revisions

User contributions

    This user never has never made submissions.

    User edits

    Syntax for editing wiki

    For you are available next options:

    will make text bold.

    will make text italic.

    will make text underlined.

    will make text striked.

    will allow you to paste code headline into the page.

    will allow you to link into the page.

    will allow you to paste code with syntax highlight into the page. You will need to define used programming language.

    will allow you to paste image into the page.

    is list with bullets.

    is list with numbers.

    will allow your to insert slideshare presentation into the page. You need to copy link to presentation and insert it as parameter in this tag.

    will allow your to insert youtube video into the page. You need to copy link to youtube page with video and insert it as parameter in this tag.

    will allow your to insert code snippets from @worker.

    Syntax for editing wiki

    For you are available next options:

    will make text bold.

    will make text italic.

    will make text underlined.

    will make text striked.

    will allow you to paste code headline into the page.

    will allow you to link into the page.

    will allow you to paste code with syntax highlight into the page. You will need to define used programming language.

    will allow you to paste image into the page.

    is list with bullets.

    is list with numbers.

    will allow your to insert slideshare presentation into the page. You need to copy link to presentation and insert it as parameter in this tag.

    will allow your to insert youtube video into the page. You need to copy link to youtube page with video and insert it as parameter in this tag.

    will allow your to insert code snippets from @worker.