
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 ()

On 23/03/06, Daniel McAllansmith
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?
Yeah, that's the somewhat informal terminology. Probably better would be that StateT is the outermost monad transformer, and IO is the transformed monad, or base monad.
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?
No, basically, applying ask will use the version of ask for your particular monad. (Including all transformers.) Various instances of MonadReader are used to automatically get reader instances on transformed monads in various cases involving the MTL transformers, but not in all cases. (Read the list of instances for MonadReader to find out exactly which monad transformers preserve it.) If there's no instance, you have to write one yourself. Also, when you're newtyping a monad which is an instance of MonadReader, you can use newtype deriving to get an instance for the newtype automatically.
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?
Lift is best understood via its type: lift :: (MonadTrans t, Monad m) => m a -> t m a it simply takes a value in the base monad, and lifts it into the transformed monad. When you have a stack of transformers, you may have to apply it multiple times if you want to lift something up from one monad, through a stack of transformations of that monad. For example, I might be working in the StateT Integer (ReaderT String IO) monad, and want to get an analogue of (print "Hello") which is of type IO () in my monad. First I apply lift to it, to get a value in (ReaderT String IO ()), then again to get something of type StateT Integer (ReaderT String IO) (). That's all it does - there's no magic with locating applications of transformers or anything like that, it just goes one level each time. However, there's also liftIO, which is a special case for when the base monad is IO -- this lifts an IO action into any monad which is an instance of MonadIO. This class is preserved by most monad transformers, and is satisfied by IO, so the end result is like applying lift enough times to bring an IO action up through as many transformers as necessary, but without having to know how many beforehand.
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.
I'm not completely sure what you're after here -- basically, you just lift things into whichever monad you're using. If you want to be polymorphic, but insist on a particular instance of MonadReader, that's easy enough, just put a constraint like (MonadReader String m) or something similar on your type.
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?
MonadTrans is only for monad transformers. Actual monads can't be turned into transformers into any automatic way. However, in a lot of cases, it's quite natural and obvious how to write a monad transformer, such that applying that transformer to the identity monad gives the monad you were thinking of (for example, writing code for StateT instead of State), and when this is the case, you usually should, since it's usually not much extra trouble, and it buys you a lot of extra flexibility later.
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?
It's safe, sure, though a little awkward. It's easy enough to lift whole IO computations later on anyway. The only benefit would be if you wanted to later intersperse actions into the code which came from a transformed version.
Q. 7) If it's safe to do, why aren't functions in the IO monad just typed in the MonadIO class instead?
First of all, historical reasons -- the MTL is newer than the IO monad by a good bit, and it doesn't exist in Haskell 98. While it would be nice to have automatically lifted IO actions, it's actually fairly rare that this actually gets in your way. The biggest problem is when you have to deal with functions like bracket which take IO actions as parameters -- in that case, it would be especially nice for it to take something in a MonadIO 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?
There's no nesting there: m () isn't a transformed monad -- while it might be implemented as such, you just don't know that. You can use polymorphic types with lift (just look at the type of lift itself), but usually that's not what you want anyway. Really, you don't want to do a whole lot of explicit lifting outside of the definitions of core functionality in your new monad. Sometimes it's necessary to do more than that, but I find it's usually much nicer if you can find some basic set of actions that you want in your new monad and pre-lift them all. Better yet, write a class for them, newtype your monad transformer stack to give it a pretty name, and then don't export the newtype constructor from your module. (Just the class and the type.) You then write an instance of your class which uses the newtype constructor. It's also possible that you might want to use newtype-deriving to get instances for MTL classes like MonadReader or MonadState, though quite often your own interface will do.
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.
[snip code]
The reason is that you don't have lifting instances to lift an instance of MonadCounter through the application of ReaderT or StateT. Here's a version of your code which I've cleaned up a bit. I turned your Counter and CounterT into newtypes (type synonyms will eventually cause you problems with defining overlapping instances), with Counter defined using CounterT with the Identity monad, and illustrated how you can get the behaviour I think you want: {-# OPTIONS_GHC -fglasgow-exts #-} module MonadCounter ( MonadCounter, increment, decrement, CounterT, runCounterT, Counter, runCounter ) where import Control.Monad import Control.Monad.Reader import Control.Monad.State import Control.Monad.Identity import Data.Word class (Monad m) => MonadCounter m where increment :: m Word decrement :: Word -> m () newtype CounterT m a = CounterT (StateT Word m a) deriving (Functor, Monad, MonadIO, MonadTrans, MonadReader r) -- etc... instance (Monad m) => MonadCounter (CounterT m) where increment = CounterT increment_ decrement = CounterT . decrement_ 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 () instance MonadCounter m => MonadCounter (ReaderT r m) where increment = lift increment decrement n = lift (decrement n) runCounterT :: (Monad m) => CounterT m a -> m a runCounterT (CounterT c) = evalStateT c 0 newtype Counter a = Counter (CounterT Identity a) deriving (Functor, Monad, MonadCounter) runCounter (Counter x) = runIdentity (runCounterT x) 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 ()

Oh, and almost forgot, you can check out lots of examples of this not only in the mtl, but also on the (old) Haskell Wiki. I've written a lot of simple (sometimes trivial) examples for people to look at Unique values -- very simple http://www.haskell.org/hawiki/MonadUnique A supply of values, a slight generalisation of the above http://www.haskell.org/hawiki/MonadSupply Random number generation http://www.haskell.org/hawiki/MonadRandom A state monad transformer with undo/redo http://www.haskell.org/hawiki/MonadUndo Last but not least, check out my Sudoku solver (everyone has one of these nowadays). I wrote it by constructing a special monad, in which the problem becomes really easy to solve. (Basically, a state monad which enforces the sudoku rules, and handles nondeterminism automatically). http://www.haskell.org/hawiki/SudokuSolver hope this all helps :) - Cale

On Friday 24 March 2006 16:49, Cale Gibbard wrote:
Oh, and almost forgot, you can check out lots of examples of this not only in the mtl, but also on the (old) Haskell Wiki. I've written a lot of simple (sometimes trivial) examples for people to look at
I'll be sure to check them out.
Last but not least, check out my Sudoku solver
(everyone has one of these nowadays). Hey, easy does it. I appreciate the help and all, but there's no need to bring up my sudoku solver inadequacies. :)
hope this all helps :)
Sure does. Daniel

On Friday 24 March 2006 16:42, Cale Gibbard wrote: Excellent help thanks, Cale. A lot of my misunderstandings stemmed from not finding any 'instance MonadState ReaderT' when reading the code in Reader.hs, not realising that there was an instance defined in State.hs, and yet being able to use get on what I thought would just be a Reader. I think I will now have an enduring friendship with GHCi's ':info'.
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.
I'm not completely sure what you're after here -- basically, you just lift things into whichever monad you're using. If you want to be polymorphic, but insist on a particular instance of MonadReader, that's easy enough, just put a constraint like (MonadReader String m) or something similar on your type.
Not really a valid question now that I've cleared up my misconceptions of lifting, but... I meant something along the lines of i <- ((lift get) :: Int) --dig into the nearest Int state s <- ((lift get) :: String) --dig into the nearest String state
Q. 6) Is it safe to always use liftIO, even in plain IO monad?
It's safe, sure, though a little awkward. It's easy enough to lift whole IO computations later on anyway. The only benefit would be if you wanted to later intersperse actions into the code which came from a transformed version.
Yeah, I meant being able to go back and intersperse the use of state, or whatever, in a monadic expression that had, until then, only done IO. [snip various good suggestions and improved code] Good advice, thanks. Thanks Daniel
participants (2)
-
Cale Gibbard
-
Daniel McAllansmith