
Kurt, There are basically two ways of doing that, namely monad transformers and implicit parameters (we actually use both techniques in lambdabot). Implicit parameters save you a lot of conversions or explicit passing of variables because you only need one monad (the IO monad); however they are ghc-specific, disliked by some (not by me, though!) and the order in which they are type-checked is suboptimal, so be prepared for some scary error messages. They also don't allow the implementation to be hidden completely. If you decide to use a monad transformer, the pattern you described (using runReaderT) can be abstracted quite nicely: -- the names are bad, I know... class UnliftIO m where -- what we actually want is m (forall a. m a -> IO a), but that's -- impossible, so we are using cps instead. unliftIO :: ((forall a. m a -> IO a) -> IO b) -> m b -- unliftIO is not subsumed by getUnlifterIO, afaics. getUnlifterIO :: m (m a -> IO a) getUnlifterIO = unliftIO return instance UnliftIO (ReaderT r IO) where unliftIO f = ReaderT $ \r -> f (`runReaderT` r) Now printAndFork doesn't need to know anything about the internals of the monad transformer anymore: printAndFork :: String -> Integer -> MyReader () printAndFork _ 0 = return () printAndFork str n = do unlift <- getUnlifter mv <- ask lift $ do modifyMVar_ mv $ \i -> do print $ str ++ show i return (i + 1) forkIO . unlift $ justPrint ("inner " ++ str) printAndFork str (n - 1) It might also be worthwhile to wrap the monad transformer into a newtype newtype MyIO a = MyIO (ReaderT (MVar ...) IO a) deriving (Functor, Monad, MyReader, UnliftIO) where MyReader is a type class that provides only the 'get' method of the Reader class, so that the user cannot mess with the MVar. Or you could hide the fact that you are using MVars and provide only functions that manipulate the state (cf. the 'MS'-functions in lambdabot/LBState.hs). HTH, Thomas On Wed, 2005-11-16 at 11:51 -0500, Kurt Hutchinson wrote:
I'm writing a program that will be using multiple threads to handle network activity on multiple ports in a responsive way. The treads will all need access to some shared data, so I'm using an MVar. So far so good. The problem is that passing the MVar around everywhere is kind of a pain, so I was hoping to use a ReaderT monad on top of the IO monad to handle that for me. I have that working, but one piece seemed a bit out of place so I wondered if there was a better way. Below is a small test program that presents my question.
My program uses forkIO to create the separate threads (Set A), and some of *those* threads will need to create threads (Set B). In order for the ReaderT to handle the environment of the threads in Set B, do I have to perform another runReaderT when forking? Or is there a way to get the ReaderT environment automatically carried over to the newly created Set B thread? See the "NOTE" comment in the code below for the particular spot I'm asking about.