module Main where import Control.Monad.MultiLift import Control.Monad.MultiWrap import Control.Monad.Reader import Control.Monad.State import Control.Monad.Trans import Control.Monad.Wrap newtype Type1 = Type1 { unType1 :: String } type Reader1 = ReaderT Type1 IO newtype Type2 = Type2 { unType2 :: String } type Reader2 = ReaderT Type2 Reader1 type Outer = StateT () Reader2 r3 :: Outer () r3 = do -- Note that you have to specify the inner type s1 <- mlift (asks unType1 :: Reader1 String) liftIO $ putStrLn $ "s1: " ++ s1 s2 <- mlift (asks unType2 :: Reader2 String) liftIO $ putStrLn $ "s2: " ++ s2 r2 :: Outer () r2 = do mwrap (local augment :: Reader1 a -> Reader1 a) r3 where augment (Type1 s) = Type1 $ s ++ " (augmented)" r1 :: Reader2 () r1 = do liftM fst $ runStateT r3 () liftM fst $ runStateT r2 () -- runContWrapT r2 return main :: IO () main = do runReaderT (runReaderT r1 $ Type2 "this is the Reader2 contents") $ Type1 "this is the Reader1 contents"