StateT example (an encore performance)

I noticed a few bits lacking in the Control.Monad.State documentation. I think an example of using StateT to encapsulate IO would be a useful addition... In order to make StateT more interesting, the trick is to use a lift inside a function that returns StateT, so you can actually perform IO. I would guess that this is the kind of use case that most people would want to use StateT, but lift isn't mentioned in the docs. Also, the types of "runStateT" and "runState" are a little confusing, since they're actually field accessor functions, so I'd like to make a note on that. So how 'bout I add an example like the following to the State documentation? module Main where import Control.Monad.State type MyState a = StateT Int IO a stateFun :: MyState String stateFun = do modify (+100) liftIO (putStrLn "Hello!") return "foo" main = do (s, n) <- runStateT (stateFun >> stateFun) 0 putStrLn $ "n: " ++ (show n) ++ " s: " ++ s peace, isaac

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

On Fri, Apr 15, 2005 at 08:17:13PM -0700, Isaac Jones wrote:
Can anyone help me explain this behavior?
I'm not sure this will be a satisfactory explanation, but if you look at StateT's implementation it is quite obvious that is must work this way: newtype StateT s m a = StateT {runStateT :: (s -> m (a, s))} for m = IO and s = Int this is StateT {runStateT :: (Int -> IO (a, Int))} The new state is returned as part of IO action result. If there is an exception, you don't get the new state.
Is this because it's not really "safe" to embed the IO monad in a StateT monad?
I guess it depends on what you mean by "safe". In some situations this might be the expected behaviour.
The strange thing I see is that the errorHandler function is the only one whose modifications to the state persist. If this is a problem, maybe try catching the exception deeper, for example: (s, n) <- runStateT (stateFun 1 >> catchError stateErr errorHandler >> stateFun 10) 0
Best regards Tomasz
participants (2)
-
Isaac Jones
-
Tomasz Zielonka