[Haskell-cafe] Newbie: State monad example questions

Eric Stansifer stansife at caltech.edu
Thu May 22 10:22:19 EDT 2008


> So, are there any other simple motivating examples that show what
> state is really good for?

Here's an example from some code that I'm (trying to) write;  I am
writing a DSL for the Povray Scene Description Language.  This part of
my program creates a `String' which holds a piece of Povray SDL code.
I am using the state to keep track of an infinite list of unique
identifiers -- when I use an identifier I would like to avoid reusing
the same one later.

> type Identifier = String
> type Identifiers = [Identifier]
> all_identifiers :: Identifiers
> all_identifiers = map (\n -> "var" ++ show n) [0, 1..]

> next_id :: State Identifiers Identifier
> next_id = do
>   (a:as) <- get
>   put as
>   return a

I define a function "let_" so that if a user of my code writes something like:

> let_ value expr

For example, if a user said:

> let_ (vector (0, 0, 0))
>       (\origin ->
> let_ (vector (1, 2, 3))
>       (\p ->
>           union [box origin p, sphere origin (float 1), cylinder origin p (float 0.5)]))

it should be analogous to:

> union [box (vector (0, 0, 0)) (vector (1, 2, 3)), sphere (vector (0, 0, 0)) (float 1), cylinder (vector (0, 0, 0)) (vector (1, 2, 3)) (float 0.5)]

(Cf. http://www.haskell.org/pipermail/haskell-cafe/2008-February/039639.html
for details on what I'm trying to do here, but it has nothing to do
with my example usage of a state monad.)

In my definition of "let_", I extract a fresh, unused identifier which
is assigned to the value of "value".

> type Code x = State Identifiers String
> let_ :: Code x -> (Code x -> Code y) -> Code y
> let_ m_value m_expr = do
>   id <- next_id
>   value <- m_value
>   expr <- m_expr (return id)
>   return ("#declare " ++ id ++ " = " ++ value ++ ";\n" ++ expr)

Either of the expressions "m_value" or "m_expr" may require their own
unique identifiers, but the State monad takes care of threading my
`Identifiers' state so that the same identifier will not be used more
than once.

Later on, when I made a more sophisticated version of `Identifiers'
which kept of track of multiple different namespaces from which
identifiers could come, I only had to modify `next_id' without having
to worry about whether I would have to make changes in other parts of
the program (although I believe further changes would not have been
necessary even if I had not used State monads, the modularity of the
code is much more obvious when using the State monad instead of
explicitly writing out the state that is being passed around).

Eric


More information about the Haskell-Cafe mailing list