
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) -}

On Apr 17, 2007, at 0:03 , oleg@pobox.com wrote:
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
For what it's worth, I got the impression that RWST was an example of a complex monad transformer --- not necessarily something useful. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Brandon S. Allbery KF8NH wrote:
On Apr 17, 2007, at 0:03 , oleg@pobox.com wrote:
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
For what it's worth, I got the impression that RWST was an example of a complex monad transformer --- not necessarily something useful.
I actually used RWS (not RWST in this case). The analysis and transformation of the regular expression parse tree in regex-tdfa is done by execRWS with monad type:
type PM = RWS (Maybe GroupIndex) [Either Tag GroupInfo] ([OP]->[OP],Tag)
And to make it more complicated, some of the operations are via GHC's recursive 'mdo' syntax. The reader is tracking which capture group we are inside (if any) and the writer collects two streams of included Tags and capture GroupInfo. The state is a difference list of all the OP's and the next available Tag. I use all of 'tell' 'listens' 'ask' 'local' 'get' 'put' -- Chris
participants (3)
-
Brandon S. Allbery KF8NH
-
Chris Kuklewicz
-
oleg@pobox.com