[Haskell-cafe] Nested Monads Questions

Joel Björnson joel.bjornson at gmail.com
Fri Aug 11 17:00:55 EDT 2006


2006/8/11, Stefan Aeschbacher <haskell at aeschbacher.ch>:
>
> 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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org//pipermail/haskell-cafe/attachments/20060811/dee5f7e4/attachment.htm


More information about the Haskell-Cafe mailing list