What is the correct way to use `ExceptT`

I am a little bit confused of the usage of ExceptT. It seems that this monad transformer add the ability to handle exceptions. But the problem is that it does not work very well with StateT. I modified an example from StackOverflow.

import Control.Applicative
import Control.Monad.Error
import Control.Monad.State
import Control.Monad.Trans.Except
import Data.Functor.Identity

test1 :: (MonadState Int m, MonadError String m) => m Bool
test1 = do
    put 1
    _ <- throwError "foobar"
    put 2
    return False

test2 :: (Alternative m, MonadState Int m, MonadError String m) => m Bool
test2 = do
    put 4
    test1 <|> return True

test3 :: (Alternative m, MonadState Int m, MonadError String m) => m Bool
test3 = do
    let handle = do
            x <- get
            if x == 4
                then put 40
                else put 50
            return True
    put 4
    test1 <|> handle

runStateExceptT :: s -> ExceptT e (StateT s m) a -> m (Either e a, s)
runStateExceptT s = flip runStateT s . runExceptT

runExceptStateT :: s -> StateT s (ExceptT e m) a -> m (Either e (a, s))
runExceptStateT s = runExceptT . flip runStateT s

main :: IO ()
main = do
    print $ runIdentity . runStateExceptT 3 $ test1
    print $ runIdentity . runExceptStateT 3 $ test1
    print $ runIdentity . runStateExceptT 3 $ test2
    print $ runIdentity . runExceptStateT 3 $ test2
    print $ runIdentity . runStateExceptT 3 $ test3
    print $ runIdentity . runExceptStateT 3 $ test3

and the result is

(Left "foobar",1)
Left "foobar"
(Right True,1)
Right (True,4)
(Right True,50)
Right (True,40)

It seems that ExceptT can only restore state that is “outside” the ExceptT. Otherwise it will carry wrong state around even if there is an exception.

My question is

  • What is the proper order to use ExceptT? Should I always put it to the innermost position.
  • Does it guarantee to stop execution once an exception is thrown? And is this ability affected by the position of it in the monad stack?

Thank you!

2 Likes

You should put ExceptT as the base monad then I believe you will get the functionality you expect. If IO is your base monad just go with normal exceptions.

The results of the other way are confusing but it is consistent.

test1 <|> handle

test1 modifies the state first then throwErrors, when exceptT is that base monad the state change in test1 is thrown out, but otherwise it is kept and this changes the result of handle

2 Likes

The proper order depends on what you want. If you want backtracking behaviour where it throws away state when the left expression of (<|>) fails and resumes with the state before that expression then you want to run StateT first then runExceptT. If you want the last state before the failure happened then you want the opposite order.

It’s not too clear what you mean by stop execution when exception is thrown because usually when someone says exception they mean the kind that comes from calling error or throwIO, and those will stop execution of the entire program if thrown in the main thread unless caught. On the other hand throwError will short circuit execution but only within the computation you are runExcepTing and if you use (<|>) inside that computation you can get those different recovery behaviours you saw.

2 Likes

Yes, it’s a well-known headache. I suggest effectful rather than monad transformers.

2 Likes

I never knew about this library. Definitely gonna to check it out. Thanks!

1 Like