Christopher Jeris wrote:
>
> A while ago someone mentioned the problem of several monads tending to
> coalesce into one big monad, and alluded to a solution to this problem
> called "monad transformers". I am struggling with this now in some code
> that I am trying to sketch out. Could someone give a quick explanation of
> how to keep several monads (say, a simulation-state monad and IO, which is
> what I have now) separated ?
Here is one way of doing this. You need to embed one monad inside
another. But you also need a way of getting access to the 'inside'
monad. A monad transformer is a way of doing this.
> class MonadTrans t where
> lift :: Monad m => m a -> t m a
(We'll see lift used in a moment)
Here is a parameterizable state monad.
> class (Monad m) => MonadState s m where
> get :: m s
> put :: s -> m ()
> modify :: (MonadState s m) => (s -> s) -> m ()
> modify f = do s <- get
> put (f s)
{- Our parameterizable state monad, with an inner monad
-}
> newtype StateT s m a = StateT { runStateT :: s -> m (a,s) }
{-
- The StateT Monad structure is paramterized over two things:
- s: The State itself.
- m: The inner monad.
-
- Here are some examples of use:
-
- (Parser from ParseLib with Hugs)
- type Parser a = StateT String [] a
- ==> StateT (String -> [(a,String)])
- For example, item can be written as:
- item = do (x:xs) <- get
- put xs
- return x
-
- type BoringState s a = StateT s Identity a
- ==> StateT (s -> Identity (a,s))
-
- type StateWithIO s a = StateT s IO a
- ==> StateT (s -> IO (a,s))
-
- type StateWithErr s a = StateT s Maybe a
- ==> StateT (s -> Maybe (a,s))
-}
> instance (Monad m) => Functor (StateT s m) where
> -- fmap :: (a -> b) -> StateT s m a -> StateT s m b
> fmap f p = StateT (\ s ->
> do (x,s') <- runStateT p s
> return (f x,s'))
>
> instance (Monad m) => Monad (StateT s m) where
> return v = StateT (\ s -> return (v,s))
> p >>= f = StateT (\ s -> do (r,s') <- runStateT p s
> runStateT (f r) s')
> fail str = StateT (\ s -> fail str)
>
> instance (MonadPlus m) => MonadPlus (StateT s m) where
> mzero = StateT (\ s -> mzero)
> p `mplus` q = StateT (\ s -> runStateT p s `mplus` runStateT q s)
>
> instance (Monad m) => MonadState s (StateT s m) where
> get = StateT (\ s -> return (s,s))
> put v = StateT (\ _ -> return ((),v))
>
> instance MonadTrans (StateT s) where
> lift f = StateT ( \ s -> do { r <- f ; runStateT (return r) s })
Here we see what lift does. It allows you to run something inside
the inner monad, without knowledge of the outer monad.
> mapStateT :: (m (a,s) -> n (b,s)) -> StateT s m a -> StateT s n b
> mapStateT f m = StateT (f . runStateT m)
>
> evalStateT :: (Monad m) => StateT s m a -> s -> m a
> evalStateT m s =
> do (r,_) <- runStateT m s
> return r
>
> execStateT :: (Monad m) => StateT s m a -> s -> m s
> execStateT m s =
> do (_,s) <- runStateT m s
> return s
I uses these combinators a lot for building state monads with embedded
monads. I got them from
<em>Functional Programming with Overloading and
Higher-Order Polymorphism</em>,
<A HREF="http://www.cse.ogi.edu/~mpj">Mark P Jones</a>,
Advanced School of Functional Programming, 1995.</>
There are also other papers of stacking monads. Look at the
work done at Yale. haskell.org is a great resource for finding
papers about Haskell.
Andy Gill