[Haskell-cafe] implementing try for RWST ?
oleg at pobox.com
oleg at pobox.com
Tue Apr 17 00:03:09 EDT 2007
The examples presented so far seem to show that the computation will
eventually run in the IO monad. One may wonder then why do we need
RWST transformer, given that the IO monad can implement both the state
and writer. At the very least me need the reader transformer, which is
the least demanding monad. We can do away with the reader as well,
depending on the circumstances (e.g., one may use implicit
parameters or implicit configurations, or just pass IORefs).
The pure IO or ReaderIO solution has, besides simplicity, the
advantage of being more expressive. Monad transformers, besides
inefficiency, impose the rigid layering of effects, and so cannot
express some useful computations. The drawbacks of monad transformers
and their limited expressivity are not often discussed, unfortunately.
The following code shows Jeremy Shaw's example, with both persistent
and backed out state. The combinator tryC handles the exception and
preserves the state accumulated at the point of exception. In
contrast, tryBC undoes the changes to the state in case of
exception. Both combinators have their uses.
module T where
import Control.Monad.Reader
import Data.IORef
import Control.Exception
import Prelude hiding (catch)
type ReaderIO a v = ReaderT a IO v
type StateIO a v = ReaderIO (IORef a) v
type Counter = Integer
-- |Increment the counter by 1
incIO :: StateIO Counter ()
incIO = do
cref <- ask
c <- liftIO $ readIORef cref
let c' = c + 1
liftIO $ writeIORef cref c'
liftIO $ putStrLn ("Incrementing counter to: " ++ show c')
-- get the current value of the counter
getC :: StateIO Counter Counter
getC = ask >>= liftIO . readIORef
-- Try that preserves the state
tryC :: ReaderIO a v -> (Exception -> ReaderIO a v) -> ReaderIO a v
tryC action onerr = do
r <- ask
liftIO $ catch (runReaderT action r) (\e -> runReaderT (onerr e) r)
-- Try that backs up the state
tryBC :: StateIO a v -> (Exception -> StateIO a v) -> StateIO a v
tryBC action onerr = do
r <- ask
oldstate <- liftIO $ readIORef r
liftIO $ catch (runReaderT action r)
(\e -> do
writeIORef r oldstate
runReaderT (onerr e) r)
-- The run function
runC :: Counter -> StateIO Counter v -> IO v
runC v a = newIORef v >>= runReaderT a
test = runC 0 (do
incIO
v <- tryC (die >> (return $ Right "ok")) (return . Left . show)
c <- getC -- get the resulting counter
liftIO $ print (v,c))
where
-- |increment the counter by one and then die
die = incIO >> error "die!"
{-
*T> test
Incrementing counter to: 1
Incrementing counter to: 2
(Left "die!",2)
-}
-- the same but with backtrackable state
test2 = runC 0 (do
incIO
v <- tryBC (die >> (return $ Right "ok")) (return . Left . show)
c <- getC
liftIO $ print (v,c))
where
-- |increment the counter by one and then die
die = incIO >> error "die!"
{-
*T> test2
Incrementing counter to: 1
Incrementing counter to: 2
(Left "die!",1)
-}
More information about the Haskell-Cafe
mailing list