
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

2006/8/11, Stefan Aeschbacher
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?
I will first try to explain why it is not possible to use lift. Short version : In the definition of MyM type MyM a = WriterT [Entry] (ReaderT MyData IO) a
WriterT is parameterized with a *fixed* monad type, namely (ReaderT MyData IO). But in order to be able to instantiate MonadTrans and defining lift, this value has to be a parameter. The parameter should then take on different values, depending on which monad to lift. I.e. MyM a = ... should instead look like MyM m a = ... Longer version: Looking at the definition of MonadTrans and lift one sees that lift, given a monadic value, produces a transformed version of this monad. class MonadTrans t where lift :: Monad m => m a -> t m a In the case with the 'doSomething function', we wish to lift an action of type (IO ()) into MyM. So, what is the generell type of 'lift (some IO () action)' , e.g lift (putStr "hello") ? Examining the definition of lift above (or using :t ) , concludes that : lift (putStr "hello") :: MonadTrans t => t IO (). Due to the type of 'doSomething' (doSomething :: MyM Int) the monad transformer 't' should have type MyM, making the result of the lift operation MyM IO (). However, this is where it fails. According to the definition of MyM it can´t be parameterised with more than one type (not with both IO and ()). But, a monad transformer MUST have kind ((* -> *) -> * -> *) in order to be able to create a valid return type for lift. So even if we wished to write our own instance for MonadTrans MyM, it wouldn't be possible. Compare with the following example which on the other hand does work with lift. type MyM2 m a = WriterT [Entry] m a doSomethingElse :: MyM2 IO Int doSomethingElse = do lift $ putStrLn "hello" return 2 Now, MyM2 has the right kind. And since (WriterT w) ,for any Monoid w, instantiates the MonadTrans class, it is possible to use the lift function to produce a value of type MyM2 IO (). So, why does liftIO work ? Consider the definition of MonadIO : class (Monad m) => MonadIO m where liftIO :: IO a -> m a The monad that should embed the IO action (m above) has kind (* -> *). This makes an instance for MyM possible. Because MyM is a synonym for a WriterT monad, an instance for this is allready defined in the Controll.Monad.WriterTmodule: instance (Monoid w, MonadIO m) => MonadIO (WriterT w m) where liftIO = lift . liftIO Actually it also requires that the inner monad, i.e. ReaderT in this case, also instantiates the MonadIO, which luckily it does :) Looking at this, It's not hard to get lost in the jungle of monads :)
From my own experience (which isn't long), I think the most effective way of learning is trying to write all definitions and instances by you're own, getting a feeling for what is really going on..
Hope that this will be of any help! - why is there no liftSTM function? Don't know about that, but someone else sure does.. Regards /Joel

On 8/11/06, Stefan Aeschbacher
I'm trying to understand Monad Transformers. The code below works as expected but I have the following questions: I'll take a shot.
- why can I use liftIO but not lift in the doSomething function? I fooled around a bit, and the answer I came up with is that lift is only able to lift through the first transformer, while liftIO is able to lift through them both. You'd need to use something like (lift . lift).
The difference is in what the parameters to the classes MonadTrans and MonadIO represent. MonadIO m means that m is a monad into which IO-actions can be lifted. MonadTrans t means that (t m) is a monad into which m-actions can be lifted. However, since the type class doesn't know about m, it's impossible to exprss that composition of two transformers is itself a transformer, whereas you can easily declare that the result of transforming a MonadIO with a certain transformer results in a MonadIO. It's not immediately clear to me how to express that composition of transformers results in a transformer even with multi-parameter type classes, but I'm not a type-hacking guru. I wouldn't be surprised if it's possible.
- why is there no liftSTM function? Because there is no MonadSTM typeclass specifying which monads can have STM actions properly lifted into them. You could write your own. here's a first pass:
class Monad m => MonadSTM m where liftSTM :: STM a -> m a instance MonadSTM STM where liftSTM = id instance (MonadSTM m) => MonadSTM (ReaderT m) where liftSTM = lift . liftSTM instance (MonadSTM m) => MonadSTM (WriterT m) where liftSTM = lift . liftSTM Et cetera... However, I have no idea if there were reasons why such a class was not included other than simple oversight. It's possible that lifting like the above may not work like you'd expect, and perhaps it's difficult to make it do so. But, if you're willing to be a guinea pig, go ahead and try those out. :) Enjoy. -- Dan

On 8/11/06, Dan Doel
The difference is in what the parameters to the classes MonadTrans and MonadIO represent. MonadIO m means that m is a monad into which IO-actions can be lifted. MonadTrans t means that (t m) is a monad into which m-actions can be lifted. However, since the type class doesn't know about m, it's impossible to exprss that composition of two transformers is itself a transformer, whereas you can easily declare that the result of transforming a MonadIO with a certain transformer results in a MonadIO. Apologies for replying to myself.
I played around a bit, and I was essentially able to express composition of transformers without extra class parameters. Ideally, it'd go something like this: type CombinatorT (t :: (* -> *) -> * -> *) (u :: (* -> *) -> * -> *) (m :: * -> *) (a :: *) = t (u m) a instance (MonadTrans t, MonadTrans u) => MonadTrans (CombinatorT t u) where lift = lift . lift This says that the combinator transformer is a monad transformer if t and u are. However, since the combinator transformer is just a type synonym, it would (I think) end up reducing to all combinations of transformers being transformers. However, partially applied type synonyms aren't allowed (for good reasons, I hear; this example is particularly weird; is it possible to write without using type synonym syntax? MonadTrans (forall m. t (u m)) ?), so instead, you have to use a data declaration (maybe a newtype? I don't know): data (MonadTrans t, MonadTrans u, Monad m) => CombinatorT t u m a = CombinatorT (m a) instance (MonadTrans t, MonadTrans u) => MonadTrans (CombinatorT t u) where lift = CombinatorT However, that doesn't really give the types we want, and obviously doesn't do the lift composition, so we need a way to get it out of the container: unC :: (MonadTrans t, MonadTrans u, Monad m, Monad (u m)) => CombinatorT t u m a -> t (u m) a unC (CombinatorT m)= lift (lift m) And for less typing: liftC = unC . lift And now an example, shamefully stolen from Mr. Kuklewicz type Foo a = (WriterT [Int] (ReaderT String [])) a foo :: Foo String foo = do x <- liftC [1, 2, 3] s <- ask tell [succ x] return (s ++ show x) test = runReaderT (runWriterT foo) "hello" *Transform> test [("hello1",[2]),("hello2",[3]),("hello3",[4])] Viola. -- Dan

On 8/12/06, Dan Doel
Viola. Egads!
In my haste, I failed to note that my mapping from the type synonym to the data constructor only works for a single nested transformer. lift will build arbitrarily nested CombinatorTs, but I'm not sure how to extract them into the component transformers. Hardly ideal. Perhaps someone more enterprising will fix my error, if it is indeed possible to do so. Until then, my apologies for triple posting.

I will try any make a simpler explanation:
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?
Replacing liftIO with (lift . lift) does work:
doSomething :: MyM Int doSomething = do dataRef <- asks myData logMsg "Writing" lift . lift $ do mv <- atomically $ readTVar dataRef putStrLn mv logMsg "Written" return 1
This is because lift only move you one level though the MonadTrans stack of types. Let's look at what MonadTrans means:
class MonadTrans (t::(* -> *) -> * -> *) where lift :: forall (m::* -> *) a. Monad m => m a -> t m a -- Imported from Control.Monad.Trans instance MonadTrans (ReaderT r) -- Imported from Control.Monad.Reader instance Monoid w => MonadTrans (WriterT w) -- Imported from Control.Monad.Writer
So the only thing MonadTrans does is provide the 'lift' function. Your type is
type MyM a = WriterT [Entry] (ReaderT MyData IO) a
To really see what (lift . lift) is doing, consider the most type specific:
-- lift :: (MonadTrans t, Monad m) => m a -> t m a
liftIOtoReader :: IO a -> (ReaderT MyData) IO a liftIOtoReader = lift
liftReaderToWriter :: (ReaderT MyData IO) a -> (WriterT [Entry]) (ReaderT MyData IO) a liftReaderToWriter = lift
doSomething :: MyM Int doSomething = do dataRef <- asks myData logMsg "Writing" liftReaderToWriter . liftIOtoReader $ do --lift $ do mv <- atomically $ readTVar dataRef putStrLn mv logMsg "Written" return 1
In liftIOToReader, "m" is "IO" and "t" is (ReaderT MyData) In liftReaderToWriter, "m" is (ReaderT MyData IO) and "t" is (WriterT [Entry]) So how does liftIO work? The effect of the instances of liftIO recursively expand liftIO to (lift . liftIO) to (lift . (lift . liftIO)) to (lift . (lift . (lift . liftIO))) until it reaches the IO monad, where liftIO = id. So it builds the correct number of composed calls to lift when it is compiled. And the same things could be done with STM or (ST s), or any other base monad. Writing that sentence made me realize I could make a liftBase function to be a superset of liftIO, liftSTM, liftST:
class (Monad m,Monad b) => MonadBase b m where liftBase :: b a -> m a
instance MonadBase IO IO where liftBase = id instance MonadBase (ST s) (ST s) where liftBase = id instance MonadBase STM STM where liftBase = id
instance (MonadBase b m,Monoid a) => MonadBase b (WriterT a m) where liftBase = lift . liftBase instance (MonadBase b m) => MonadBase b (ReaderT a m) where liftBase = lift . liftBase
And so this now works:
type MyM' s a = WriterT [String] (ReaderT Int (ST s)) a
testMyM' :: forall s. MyM' s Int testMyM' = do tell ["a"] foo <- lift (ask) tell ["b"++show foo] liftBase (go foo) where go :: Int -> ST s Int go f = do a <- newSTRef f modifySTRef a (+1) readSTRef a
main2 = do let q = runST (runReaderT (runWriterT (testMyM')) 17 ) print q
*Main> main2 (18,["a","b17"])

I put a more comprehensive MonadBase module on the wiki at: http://haskell.org/haskellwiki/NewMonads Nine Base Monads: IO STM ST ST.Lazy GenParser [] Maybe Either (->) Seven MonadTrans: ListT ContT ErrorT ReaderT StateT WriterT RWST

Hello Chris, Saturday, August 12, 2006, 4:05:44 AM, you wrote:
Nine Base Monads: IO STM ST ST.Lazy GenParser [] Maybe Either (->)
Seven MonadTrans: ListT ContT ErrorT ReaderT StateT WriterT RWST
i'm not sure, but isn't Id monad also required for completeness? at least it's included in MonadLib by Iavor S. Diatchki: http://www.csee.ogi.edu/~diatchki/monadLib/monadLib-2.0.tar.gz am i correctly understand that your module is update on Monad transformers lib already included in GHC? -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Chris,
Saturday, August 12, 2006, 4:05:44 AM, you wrote:
Nine Base Monads: IO STM ST ST.Lazy GenParser [] Maybe Either (->)
Seven MonadTrans: ListT ContT ErrorT ReaderT StateT WriterT RWST
i'm not sure, but isn't Id monad also required for completeness?
Yes, Identity is required for completeness. And I have added to http://haskell.org/haskellwiki/NewMonads#MonadBase this definition:
-- One can recover MonadIO and liftIO from MonadBase class (MonadBase IO m) => MonadIO' m where liftIO' :: IO a -> m a liftIO' = liftBase
Of course, the above is unneeded since you can always write liftBase instead of liftIO.
... at least it's included in MonadLib by Iavor S. Diatchki: http://www.csee.ogi.edu/~diatchki/monadLib/monadLib-2.0.tar.gz
Hah...I knew someone else had done this. Also, there is 2.0.1 version of monadLib at http://www.cse.ogi.edu/~diatchki/monadLib/ His version is called BaseM, and uses a fundep:
-- | Provides means to execute a computation in the base of a tower of monads. class (Monad m, Monad b) => BaseM m b | m -> b where inBase :: b a -> m a
instance BaseM IO IO where inBase x = x instance BaseM [] [] where inBase x = x instance BaseM Maybe Maybe where inBase x = x
I am not sure I like the "inBase" name. I think "fromBase" might be a better match to its type. The "inBase" seems more like "toBase" which is backwards. My small test did not need the fundep, and I wonder if there is some creative example that shows either that the fundep is useful or a counter example that shows something very very clever that would otherwise violate the fundep. I *might* be able to imagine a transformer stack that pretends to have different base monads.
am i correctly understand that your module is update on Monad transformers lib already included in GHC?
Essentially, that is exactly what it is. It completely replaces MonadIO. -- Chris
participants (5)
-
Bulat Ziganshin
-
Chris Kuklewicz
-
Dan Doel
-
Joel Björnson
-
Stefan Aeschbacher