Re: [Haskell-cafe] implementing try for RWST ?

Jeremy Shaw wrote: : | However, I think this is buggy, because changes | to 's' and 'w' will be lost if 'm' raises an | exception. : That's determined by the way you stack your monad transformers when declaring the type: adding error handling to a writer monad, or adding writing to an error handling monad. For a concrete example, see the result types in the following. The first has the Either inside the tuple, and the second has the tuple inside the Either. Prelude> :t Control.Monad.Writer.runWriter . Control.Monad.Error.runErrorT Control.Monad.Writer.runWriter . Control.Monad.Error.runErrorT :: Control.Monad.Error.ErrorT e (Control.Monad.Writer.Writer w) a -> (Either e a, w) Prelude> :t either Left Right . Control.Monad.Writer.runWriterT either Left Right . Control.Monad.Writer.runWriterT :: Control.Monad.Writer.WriterT w (Either a) a1 -> Either a (a1, w) Regards, Tom

At Tue, 17 Apr 2007 09:46:19 +1200, tpledger@ihug.co.nz wrote: } } Jeremy Shaw wrote: } : } | However, I think this is buggy, because changes } | to 's' and 'w' will be lost if 'm' raises an } | exception. } : } } } That's determined by the way you stack your monad } transformers when declaring the type: adding error handling } to a writer monad, or adding writing to an error handling } monad. For a concrete example, see the result types in the } following. The first has the Either inside the tuple, and } the second has the tuple inside the Either. } } Prelude} :t Control.Monad.Writer.runWriter . } Control.Monad.Error.runErrorT } Control.Monad.Writer.runWriter . } Control.Monad.Error.runErrorT :: Control.Monad.Error.ErrorT } e (Control.Monad.Writer.Writer w) a } -} (Either e a, w) } Prelude} :t either Left Right . } Control.Monad.Writer.runWriterT } either Left Right . Control.Monad.Writer.runWriterT :: } Control.Monad.Writer.WriterT w (Either a) a1 -} Either a } (a1, w) Unfortunately, while that gets me closer, it don't think it does the whole job. I would like to be able to catch exceptions raised by |error|. Let me demonstrate:
import Control.Exception import Control.Monad import Control.Monad.Error import Control.Monad.RWS import Prelude hiding (catch)
Here I define ErrorT to be on the outside.
newtype DryRunIO a = DryRunIO { runDryRunIO :: ErrorT Exception (RWST Bool String Int IO) a } deriving (Monad, MonadIO, MonadFix, Functor, MonadReader Bool, MonadWriter String, MonadState Int, MonadError Exception)
I have to add some instances of Exception to Error, since there are none defined already.
instance Error Exception where strMsg msg = ErrorCall msg
Here is a straight-forward implementation of try.
-- |like |try| tryDR :: DryRunIO a -> DryRunIO (Either Exception a) tryDR m = catchError (m >>= return . Right) (return . Left)
A command to run my monad.
-- |turn a DryRunIO into IO run :: Bool -> DryRunIO a -> IO (Either Exception a, Int, String) run dryRun action = runRWST (runErrorT (runDryRunIO action)) dryRun 0
A simple helper function for the demo.
inc :: DryRunIO () inc = modify (+1)
This test does what we I would like, because it uses the facilities provided by ErrorT:
test1 = run False (tryDR (inc >> throwError (ErrorCall "whee")))
*Main> test1 (Right (Left whee),1,"") But this variation that calls |error| fails:
test2 = run False (tryDR (error "whee"))
*Main> test2 *** Exception: whee I can hack it a bit, if I use a wrapper function like this:
io :: (MonadIO t, MonadError Exception t) => IO a -> t a io action = do r <- liftIO (try action) case r of Left e -> throwError e Right r' -> return r'
This does what I want:
test3 = run False (tryDR (io $ error "whee"))
*Main> test3 (Right (Left whee),0,"") But, if I was going to do that, then I might as well just do:
test4 = run False (liftIO $ try (error "whee"))
*Main> test4 (Right (Left whee),0,"") Unfortunately, both those variations assume that error is being called inside the IO parts of my program, and not because someone did something silly like:
test5 = run False (tryDR $ head [])
*Main> test5 *** Exception: Prelude.head: empty list After some further investigation, I am not convinced that there is a solution. Instead of using the complicated RWST monad, I could demo the problem using the simpiler StateT monad. However, I can simplify even further for clarity. The |StateT IO a| monad is roughly equivalent to:
type StateIO state a = (state -> IO (a, state))
In other words, it is similar to a function that takes the current value of the state, and returns a value and a possibly updated state, both in the IO monad. If the state is a simple Counter, we can implement increment like this:
type Counter = Integer
-- |Increment the counter by 1 incIO :: (Counter -> IO ((), Counter)) incIO = \c -> let c' = c + 1 in do putStrLn ("Incrementing counter to: " ++ show c') return ((), c')
We can then implement |tryC| like this:
-- |similar to |try| tryC :: (Counter -> IO (a, Counter)) -> (Counter -> IO ((Either Exception a), Counter)) tryC f = \c -> catch (f c >>= \ (a, c') -> return (Right a, c')) (\e -> return (Left e, c))
And use them like this:
test = \c -> do ((), c1) <- incIO c (r, c2) <- (tryC die) c1 return (r, c2) where -- |increment the counter by one and then die die :: (Counter -> IO ((), Counter)) die = \c -> do ((), c') <- incIO c error "die!" return ((), c')
If we run the test function we will get this output: *Main> test 0 Incrementing counter to: 1 Incrementing counter to: 2 (Left die!,1) We see that the counter gets incremented twice, but the second incrementation is lost when the exception is thrown. So the final result is: (Left die!,1) but what we wanted was this: (Left die!,2) If you look at the above code, I think you will agree there is no way to write tryC so that the incrementation in |die| is not lost. What we need is a version of error that returns not only the error message, but also the current value of the counter. That is what using ErrorT does for us. But, that only works if everyone used throwError instead of error. Of course, that is not possible because they have different type signatures: throw :: Exception -> a throwError :: (MonadError e m) => e -> m a throwError can not be used in pure code, such as |head|. If error was *only* used for programming errors, (e.g. head []), then it might be reasonable to say that you can fix the problem by fixing the bugs in your code. However, many IO functions, like readFile, use exceptions as an error reporting facility. It may be the case that all instances of error that are not inside the IO monad indicated programming errors. If that is true, then I could use the 'io' function to handle exceptions raised in the IO monad, and for all other cases, fix the code to avoid error altogether. That is my current plan. j.
participants (2)
-
Jeremy Shaw
-
tpledger@ihug.co.nz