
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"])