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?
There is a way, but let me first explain recovering state from errors in terms of
ErrorTandStateT, because I find that it illuminates the general case very well.Let's first imagine the case where
ErrorTis on the outside ofStateT. In other words:If you unwrap both the
ErrorTandStateTnewtypes you get:The unwrapped type says that we recover the final state, even if we receive an error. So just remember that
ErrorTon the outside ofStateTmeans we can recover from errors while still preserving the current state.Now, let's switch the order:
This type tells a different story: we only recover the ending state if our computation succeeds. So just remember that
ErrorTon the inside ofStateTmeans that we can't recover the state.This might seem curious to somebody familiar with the
mtl, which provides the followingMonadErrorinstance forStateT:How does
StateTrecover gracefully from errors after what I just said? Well, it turns out that it does not. If you write the following code:... then if
musesthrowError,fwill begin fromm's initial state, not the state thatmwas at when it threw the error.Okay, so now to answer your specific question. Think of
IOas having a built-inErrorTlayer by default. This means that if you can't get rid of thisErrorTlayer then it will always be inside yourStateTand when it throws errors you won't be able to recover the current state.Similarly, you can think of
IOas having a built-inStateTlayer by default that is below theErrorTlayer. This layer conceptually holds theIORefs, and because it is "inside" theErrorTlayer it always survives errors and preservesIORefvalues.This means that the only way you can use a
StateTlayer above theIOmonad and have it survive an exception is to get rid ofIOsErrorTlayer. There is only one way to do this:Wrap every
IOaction intryIOMask asynchronous exceptions and only unmask them in the middle of
tryIOstatements.My personal recommendation is to go the
IORefroute since there are some people who will not be happy about masking asynchronous exceptions outside oftryIOstatements, because then you cannot interrupt pure computations.