[Haskell-cafe] Building Monads from Monads

Daniel McAllansmith dagda at xtra.co.nz
Thu Mar 23 18:36:15 EST 2006


Hi, I've got a few (9) random questions, mainly about monads and building 
monads from existing monads, partly trying to confirm conclusions I've come 
to through experimentation.

Any, and all, attempts to enlighten me will be much appreciated.

Thanks
Daniel

First, terminology.  In
StateT s (ReaderT r IO) ()
Q. 1) StateT is referred to as the outermost monad, and IO as the innermost 
monad, correct?



Using a monadic function, eg MonadReader.ask, in a monadic expression will 
access the outermost monad of the appropriate class.
Q. 2) Does this work for all monad classes in all expressions?



How does Control.Monad.Trans.lift work?  It seems that a single application of 
lift will find the next outermost monad of the appropriate class, but if you 
want to dig deeper into the nest you need to apply lift according to the 
monads actual depth in the nest.
Q. 3) Why the different behaviour?

Q. 4) Is it possible to give a type to the lifted function so that the monad 
of the correct class _and_ type is used?  E.g. dig into a String Reader 
rather than an Int Reader.

Defining an instance of MonadTrans for a monad instance seems universally 
useful.
Q. 5) Are there obvious situations where it's not useful or possible?



Carrying out IO in a nested monadic expression requires liftIO.  Apart from 
having to type an extra 7-9 characters it seems good to use liftIO even in 
plain IO monad expressions so they can become nested expressions with no 
trouble later on.
Q. 6) Is it safe to always use liftIO, even in plain IO monad?
Q. 7) If it's safe to do, why aren't functions in the IO monad just typed in 
the MonadIO class instead?



It looks to me like types with class constraints are better than types 
specifying nests of monad instances.  So
g :: (MonadReader String m, MonadState Int m, Monad m) => m ()
is better than
g :: StateT Int (Reader String) ()
because you can change the instance of the monadic class at will.  Also you 
can change the nesting order of the monads, though maybe that's not useful in 
practice.
The disadvantage seems to be that you can't use lift to access nested monads.
Q. 8) Is it possible to get access to nested monads when using class 
constraint types?



In the following code, the test2 function is not valid because there is no 
instance for (MonadCounter (ReaderT [Char] (StateT Word IO))), which is a 
fair enough complaint.
Q. 9) What allows ReaderT and StateT to be nested in arbitrary order but not 
ReaderT and CounterT?  Especially given CounterT is actually a StateT.


class (Monad m) => MonadCounter m where
    increment :: m Word
    decrement :: Word -> m ()

type Counter = State Word

instance MonadCounter Counter where
    increment = increment_
    decrement = decrement_

runCounter :: Counter a -> a
runCounter c = evalState c 0

type CounterT m = StateT Word m

instance (Monad m) => MonadCounter (CounterT m) where
    increment = increment_
    decrement = decrement_

runCounterT :: (Monad m) => CounterT m a -> m a
runCounterT c = evalStateT c 0

increment_ :: (MonadState Word m) => m Word
increment_ = do
    w <- get
    put (w + 5)
    return w

decrement_ :: (MonadState Word m) => Word -> m ()
decrement_ w = do
    curW <- get
    if w > curW
        then put 0
        else put (curW - w)
    return ()

test1 :: IO ()
test1 = runReaderT (runCounterT bar) "blah"

--test2 :: IO ()
--test2 = runCounterT (runReaderT bar "blah")

bar :: (MonadReader String m, MonadCounter m, MonadIO m) => m ()
bar = do
    w <- increment
    s <- ask
    liftIO $ putStrLn $ (show w) ++ s
    return ()


More information about the Haskell-Cafe mailing list