On Wed, 15 Sep 1999 [EMAIL PROTECTED] wrote:

> 
> * stToIO . This is often necessary for programs that do stateful things as well
> as IO. A few years ago, having read all relevant papers, I was very perplexed by
> the problem of doing stateful things and IO at the same time. Eventually I
> realised it is not possible to nest monads,

But it is possible! You just need to use a monadtransformer:

class MonadTrans t where
  lift ::  Monad m => m a -> (t m) a


A requirement for this to work is that one of the monadic types can carry
the other monad inside, so to say. t m.

This is no solution to the problem of mixing ST and IO though, because
none of them can be instances of MonadTrans.

You can build own monads with this capability, here is an example
statemonad(transformer), which I use with IO.


newtype StateMT m a = SMT (Env' -> m (a,Env'))
unSMT (SMT e) = e

runSMT :: Monad m => StateMT m a -> m a
runSMT (SMT m) = m defaultSM >>= \ (a,e) -> return a


instance MonadTrans StateMT where
  lift m = SMT (\e -> m >>= \a -> return (a,e))

instance Monad m => Monad (StateMT m) where
  return x = SMT (\e -> return (x,e))
  SMT m >>= f = SMT (\e -> do ~(a,e') <- m e
                              unSMT (f a) e')


type Env' = Int

defaultSM::Env'
defaultSM = 1

myProg:: StateMT IO Int
myProg = return 5

main = do n <- runSMT myProg
          print n


/Lars L




Reply via email to