[Haskell-cafe] state monad and continuation monads ...

minh thu noteed at gmail.com
Tue Sep 30 03:49:23 EDT 2008


2008/9/30 Galchin, Vasili <vigalchin at gmail.com>:
> Hello,
>
>    I would like to read
>
>     1) pedagogical examples of State monad and the Continuation monad
>
>     2) library usage of these monads ....

Regarding 1), there is a lot to find on the web. Maybe start on haskell.org.

In term of example, here is one I like :

----✁----------------------------------

module StateExample where

import Control.Monad.State

-- The state : it is threaded along each
-- command in MyMonad.
type MyState = Int

-- A particular use of the State monad :
-- simply to wrap a value of type MyState.
type MyMonad a = State MyState a

-- Inc increments the state.
-- The get function retrieves the state
-- and the put function replaces it.
-- The () in :: MyMonad () means that
-- inc doesn't return any (meaningful)
-- value. It just has a side effect (it changes
-- the wrapped state).
-- get has type MyMonad MyState and
-- put has type MyState -> MyMonad ().
inc :: MyMonad ()
inc = do
  v <- get
  put (v + 1)

-- Example usage of the State monad with
-- runState (see the docs for other such functions)).
-- It starts with the value 5 as the wrapped state.
-- THe it performs three times the 'inc' command.
-- Thus it produces 8 as the new state.
-- As noted aboved, it also returns ().
-- Try it in GHCi. Change the {...} and use
-- get and put. Implement something else than
-- the inc function.
example = runState (do {inc ; inc ; inc}) 5

----✁----------------------------------

Cheers,
Thu


More information about the Haskell-Cafe mailing list