Combining IO and state monads

Tomasz Zielonka t.zielonka@students.mimuw.edu.pl
Thu, 15 May 2003 15:31:37 +0200


On Thu, May 15, 2003 at 12:14:31PM +0100, Graham Klyne wrote:
> I've written and tested a collection of Haskell functions, and now I want 
> to put them together into a "proper" program.
> 
> The pattern of evaluation that I envisage is a program which maintains a 
> workspace, and performs a sequence of read and write operations that 
> reference and update this workspace, eventually returning some value based 
> on the final state of the workspace.
> 
> The workspace would seem to be appropriately manipulated using a form of 
> state monad.  And the I/O operations would be performed through an IO 
> monad.  What I'm unsure about is the best way to combine these so that the 
> real-world state (IO) and workspace state are updated (threaded?) in 
> parallel.
>
> [...]
>
> I imagine that this is a common requirement, for which there exists an 
> appropriately packaged solution.  Is there a standard solution I should 
> look to for this kind of functionality?  Or is there some completely 
> different approach that I've overlooked?

You probably want Monad Transformers. Both GHC and Hugs provide a
library of monad transformers for adding state, continuations,
exceptions, etc. They can be smoothly use with IO monad. Here is an
example of using state monad transformer.

  import Control.Monad
  import Control.Monad.Trans
  import Control.Monad.State
  import IO (try)

  main :: IO ()
  main = runStateT m 0 >> return ()
    where
      m = do
	  r <- liftIO (try getLine)
	  either
	      (const $ return ())
	      (\l -> do
		  n <- next
		  liftIO (putStrLn (show n ++ ": " ++ l))
		  m)
	      r

      next = do
	  x <- fmap succ get
	  put x
	  return x

Googling for Monad Transformers should give you much info on this topic.

Regards,
Tom

-- 
.signature: Too many levels of symbolic links