StateT + IO behavior

Isaac Jones ijones at syntaxpolice.org
Fri Apr 15 23:17:13 EDT 2005


Can anyone help me explain this behavior?  Is this because it's not
really "safe" to embed the IO monad in a StateT monad?  The strange
thing I see is that the errorHandler function is the only one whose
modifications to the state persist.

The behavior seems funny to me since of course the IO actually does
happen.  Was there a thread on this some time back?

> module Main where

> import Control.Monad.State
> import Control.Monad.Trans(liftIO)
> import Control.Monad.Error (throwError, catchError)
> import System.IO.Error(userError)

Use an Int as the state and encapsulate the IO monad.

> type IntStateWithIO a = StateT Int IO a

> stateFun :: Int -> IntStateWithIO String
> stateFun i = do 
>   modify (+i) -- increase the state by 100
>   liftIO (putStrLn $ "Hello State: " ++ (show i))
>   return "foo"

This function is similar, but it throws an error:

> stateErr :: IntStateWithIO String
> stateErr  = do 
>   modify (+88) -- increase the state by 100
>   liftIO (putStrLn "Hello State Error.")
>   throwError $ userError "error in stateErr."
>   return "foo from stateErr!"

> errorHandler :: IOError -> IntStateWithIO String
> errorHandler theError = do liftIO $ putStrLn (show theError) -- handle error
>                            stateFun 100            -- continue

How to thread the state and handle errors:

> main :: IO ()
> main = do
>   (s, n) <- runStateT (catchError (stateFun 1 >> stateErr  >> stateFun 10)
>                                   errorHandler)
>                        0
>   putStrLn $ "n: " ++ (show n) ++ " s: " ++ s

outputs: 

Hello State: 1
Hello State Error.
user error (error in stateErr.)
Hello State: 100
n: 100 s: foo


More information about the Libraries mailing list