Domanda

It seems a lot easier to maintain state through exceptions by holding on to an IORef than to try to use the State Monad. Below we have 2 alternative State Monads. One uses StateT and the other ReaderT IORef. The ReaderT IORef can easily run a final handler on the last known state.

{-# LANGUAGE GeneralizedNewtypeDeriving, ScopedTypeVariables #-}
import Control.Monad.State (MonadState, execStateT, modify, StateT)
import Control.Applicative (Applicative)
import Control.Monad (void)
import Control.Monad.IO.Class ( MonadIO, liftIO )
import Data.IORef
import Control.Exception.Base
import Control.Monad.Reader (MonadReader, runReaderT, ask, ReaderT)

type StateRef = IORef Int
newtype ReadIORef a = ReadIORef { unStIORef :: ReaderT StateRef IO a } deriving (Functor, Applicative, Monad, MonadIO, MonadReader StateRef)
newtype St a        = StM       { unSt      :: StateT Int IO a } deriving (Functor, Applicative, Monad, MonadIO, MonadState Int)

eval :: St a -> Int -> IO Int
eval = execStateT . unSt

evalIORef :: ReadIORef a -> StateRef -> IO a
evalIORef = runReaderT . unStIORef

add1 :: St ()
add1 = modify (+ 1)

add1Error :: St ()
add1Error = do
  modify (+ 1)
  error "state modified"

add1IORef :: ReadIORef Int
add1IORef = do
  ioref <- ask
  liftIO $ do
    modifyIORef' ioref (+ 1)
    readIORef ioref

add1IORefError :: ReadIORef Int
add1IORefError = do
  ioref <- ask
  liftIO $ do
    modifyIORef' ioref (+ 1)
    void $ error "IORef modified"
    readIORef ioref

ignore :: IO a -> IO a
ignore action = catch action (\(_::SomeException) -> return $ error "ignoring exception")

main :: IO ()
main = do
  st <- newIORef 1
  resIO <- evalIORef add1IORef st >> evalIORef add1IORef st
  print resIO -- 3

  resSt <- eval add1 1 >>= eval add1
  print resSt -- 3

  stFinal <- newIORef 1
  void $ ignore $ finally (evalIORef add1IORefError stFinal) (evalIORef add1IORef stFinal)
  print =<< readIORef st -- 3

  -- how can the final handler function use the last state of the original?
  void $ ignore $ finally (eval add1Error 1) (eval add1 1)
  print "?"

So at the end of the main function, how can I run a final handler that has access to the last existing state of the State Monad even when an exception is thrown? Or is the ReaderT IORef optimal or is there a better alternative?

È stato utile?

Soluzione

There is a way, but let me first explain recovering state from errors in terms of ErrorT and StateT, because I find that it illuminates the general case very well.

Let's first imagine the case where ErrorT is on the outside of StateT. In other words:

m1 :: ErrorT e (StateT s m) r

If you unwrap both the ErrorT and StateT newtypes you get:

runErrorT m1
    :: StateT s m (Either e r)

runStateT (runErrorT m1)
    :: s -> m (Either e r, s)

The unwrapped type says that we recover the final state, even if we receive an error. So just remember that ErrorT on the outside of StateT means we can recover from errors while still preserving the current state.

Now, let's switch the order:

m2  :: StateT s (ErrorT e m r)

runStateT m2
    :: s -> ErrorT e m (r, s)

runErrorT . runStateT m2
    :: s -> m (Either e (r, s))

This type tells a different story: we only recover the ending state if our computation succeeds. So just remember that ErrorT on the inside of StateT means that we can't recover the state.

This might seem curious to somebody familiar with the mtl, which provides the following MonadError instance for StateT:

instance (MonadError e m) => MonadError e (StateT s m) where ...

How does StateT recover gracefully from errors after what I just said? Well, it turns out that it does not. If you write the following code:

(m :: StateT s (ErrorT e m) r) `catchError` f

... then if m uses throwError, f will begin from m's initial state, not the state that m was at when it threw the error.

Okay, so now to answer your specific question. Think of IO as having a built-in ErrorT layer by default. This means that if you can't get rid of this ErrorT layer then it will always be inside your StateT and when it throws errors you won't be able to recover the current state.

Similarly, you can think of IO as having a built-in StateT layer by default that is below the ErrorT layer. This layer conceptually holds the IORefs, and because it is "inside" the ErrorT layer it always survives errors and preserves IORef values.

This means that the only way you can use a StateT layer above the IO monad and have it survive an exception is to get rid of IOs ErrorT layer. There is only one way to do this:

  • Wrap every IO action in tryIO

  • Mask asynchronous exceptions and only unmask them in the middle of tryIO statements.

My personal recommendation is to go the IORef route since there are some people who will not be happy about masking asynchronous exceptions outside of tryIO statements, because then you cannot interrupt pure computations.

Altri suggerimenti

Are you throwing these exceptions, or is a library?

Because if it's the former, why not use an EitherT transformer to do the exception handling?

You just need to be careful of the order: StateT s (EitherT e IO) a won't let you see the final state if there's an error, but EitherT e (StateT s IO) a will.

StateT s (EitherT e IO) a ~ IO (Either e (s -> (a,s)))
EitherT e (StateT s IO) a ~ IO (s -> (Either e a, s))

If you're using a library that throws exceptions, and you want to maintain state then you'd need to capture the exceptions within the State monad, using lift $ catch libraryCall exceptionHandler.

If you try to catch the exception outside of the State monad, like you're doing here, then that's isomorphic to StateT s (EitherT e IO) a, as you're using the error capabilities within IO to do the catching. The state is unavailable at that level.

Autorizzato sotto: CC-BY-SA insieme a attribuzione
Non affiliato a StackOverflow
scroll top