3

I am studying monad transformers, and I read this SO post about how to avoid lifts.

My thought was that MonadIO are monads in which IO can be embedded, and MonadWriter w are monads in which WriterT w can be embedded. So I wrote the code below (read, accumulate and record numbers until we get a zero), where a working version using explicit lift is in comments. But GHC complains. What am I doing wrong?

{-# LANGUAGE FlexibleContexts #-}
import Control.Monad.IO.Class
import Control.Monad.Writer.Class (MonadWriter)
import Control.Monad.Trans.Reader
import Control.Monad.Trans.Writer

-- f :: ReaderT Int (WriterT [String] IO) Int
-- m1 = ReaderT, m2 = WriterT
f :: (MonadWriter [String] m1, MonadIO m2) => m1 (m2 (IO Int))
f = do
    s <- liftIO getLine
    tell ["Input: " ++ s] -- lift $ tell ["Input: " ++ s]
    let i = read s :: Int
    if i == 0
       then ask
       else local (+i) f

main = do
    rst <- runWriterT $ runReaderT f 0
    print rst
Community
  • 1
  • 1
sqd
  • 1,485
  • 13
  • 23

1 Answers1

5

My thought was that MonadIO are monads in which IO can be embedded, and MonadWriter w are monads in which WriterT w can be embedded.

That's not completely correct. MonadIOs can use liftIO, and MonadWriter can use tell. Therefore, if you want to use liftIO, tell, ask and local in the same context/monad without lifting, the single monad you use must be an instance of all of them:

f :: ( MonadWriter [String] m -- monad supports  tell   :: [String] -> m ()
     , MonadReader Int      m -- monad supports  ask    ::             m Int
     , MonadIO              m -- monad supports  liftIO :: IO a     -> m a
     )         =>  m Int      -- only a single m

Note that you cannot use transformer, but mtl to get automatic lifting. Therefore, the imports also change:

import Control.Monad.Reader (runReaderT, MonadReader)
import Control.Monad.Writer (runWriterT, MonadWriter)
import Control.Monad.IO.Class (liftIO, MonadIO)

The import of MonadIO does not change since IO actions never get lifted automatically.

By the way, your use of runWriterT and runReaderT already removes all ambiguities the transformer stack, since this will use

ReaderT Int (WriterT [String] IO Int)
Zeta
  • 103,620
  • 13
  • 194
  • 236