Hi

I'm trying to understand Monad Transformers. The code below works as
expected but I have the following questions:
- why can I use liftIO but not lift in the doSomething function?
- why is there no liftSTM function?

now to the code:

module Main where

import Control.Monad.Reader
import Control.Monad.Writer
import Control.Concurrent.STM

type MyM a = WriterT [Entry] (ReaderT MyData IO) a
data MyData = MyData {myData::TVar String}
data Entry = Log String deriving (Eq, Show)

logMsg :: String -> MyM ()
logMsg s = tell [Log s]

doSomething :: MyM Int
doSomething = do
   dataRef <- asks myData
   logMsg "Writing"
   liftIO $ do
   --lift $ do
       mv <- atomically $ readTVar dataRef
       putStrLn mv
   logMsg "Written"
   return 1

main :: IO ()
main = do
   i <- atomically $ newTVar "2"
   log <- runReaderT (runWriterT doSomething) (MyData i)
   print log

regards and thanks

Stefan
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to