ReaderT and concurrency

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.
import Control.Monad.Reader import Control.Concurrent
type MyReader a = ReaderT (MVar Integer) IO a
main = do mv <- newMVar 1 forkIO $ runReaderT (printAndFork "one" 5) mv forkIO $ runReaderT (printAndFork "two" 5) mv getChar -- Pause so the threads can print before program exit
printAndFork :: String -> Integer -> MyReader () printAndFork _ 0 = return () printAndFork str n = do mv <- ask lift $ do modifyMVar_ mv $ \i -> do print $ str ++ show i return (i + 1) -- NOTE: Is this runReaderT necessary to carry the -- environment to the new thread? Is there a better way? forkIO $ runReaderT (justPrint $ "inner " ++ str) mv printAndFork str (n - 1)
justPrint :: String -> MyReader () justPrint str = do mv <- ask lift $ do modifyMVar_ mv $ \i -> do print $ str ++ show i return (i + 1) return ()
Kurt Hutchinson

On Wed, Nov 16, 2005 at 11:51:19AM -0500, Kurt Hutchinson wrote:
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?
This is an unavoidable pain as far as I know. It would be nice if forkIO were defined in terms of MonadIO: forkIO :: MonadIO m => m () -> m ThreadId (Same with forkProcess.) I haven't thought too hard about it, but it seems that it should be possible. Andrew

On Wed, Nov 16, 2005 at 09:45:17AM -0800, Andrew Pimlott wrote:
On Wed, Nov 16, 2005 at 11:51:19AM -0500, Kurt Hutchinson wrote:
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?
This is an unavoidable pain as far as I know. It would be nice if forkIO were defined in terms of MonadIO:
forkIO :: MonadIO m => m () -> m ThreadId
(Same with forkProcess.) I haven't thought too hard about it, but it seems that it should be possible.
I think it wouldn't be possible using only methods in MonadIO. Besides, what should be the semantics of forkIO for (StateT s IO)? I can't think of anything reasonable. I played with this idea a bit, and below is the result. I'm not sure there are any meaningful instances of UnliftIO (bad name) other than the two below. class Monad m => UnliftIO m where unliftIO :: m a -> m (IO a) instance UnliftIO IO where unliftIO io = return io instance UnliftIO m => UnliftIO (ReaderT r m) where unliftIO m = do r <- ask lift (unliftIO (runReaderT m r)) forkIO' :: (UnliftIO m, MonadIO m) => m () -> m ThreadId forkIO' m = do io <- unliftIO m liftIO (forkIO io) Best regards Tomasz

On Wed, Nov 16, 2005 at 07:20:48PM +0100, Tomasz Zielonka wrote:
On Wed, Nov 16, 2005 at 09:45:17AM -0800, Andrew Pimlott wrote:
On Wed, Nov 16, 2005 at 11:51:19AM -0500, Kurt Hutchinson wrote:
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?
This is an unavoidable pain as far as I know. It would be nice if forkIO were defined in terms of MonadIO:
forkIO :: MonadIO m => m () -> m ThreadId
(Same with forkProcess.) I haven't thought too hard about it, but it seems that it should be possible.
I think it wouldn't be possible using only methods in MonadIO.
Here's what I had in mind for forkProcess. Recall that the fork syscall returns 0 to the child and a pid to the parent. forkProcess :: MonadIO m => m () -> m ProcessID forkProcess io = do pid <- liftIO forkSyscall if (pid == 0) then io >> exit else return pid But maybe the primitives used by forkIO do not allow this approach. I'm not sure.
Besides, what should be the semantics of forkIO for (StateT s IO)? I can't think of anything reasonable.
I don't see the problem--they would each get a copy of the state. Although I could be missing something, as I use System.Posix.Process more than Control.Concurrent. Andrew

On Wed, Nov 16, 2005 at 10:53:17AM -0800, Andrew Pimlott wrote:
On Wed, Nov 16, 2005 at 07:20:48PM +0100, Tomasz Zielonka wrote:
I think it wouldn't be possible using only methods in MonadIO.
Here's what I had in mind for forkProcess. Recall that the fork syscall returns 0 to the child and a pid to the parent.
forkProcess :: MonadIO m => m () -> m ProcessID forkProcess io = do pid <- liftIO forkSyscall if (pid == 0) then io >> exit else return pid
Well, yes, I haven't thought about it. I don't know forkSyscall and I can't say if it's a good idea or not.
But maybe the primitives used by forkIO do not allow this approach. I'm not sure.
I'm pretty sure they don't, but I may be wrong again. They could probably be extended to allow this. However, I'm not sure I would like this, because it would be too easy to break abstraction.
Besides, what should be the semantics of forkIO for (StateT s IO)? I can't think of anything reasonable.
I don't see the problem--they would each get a copy of the state. Although I could be missing something, as I use System.Posix.Process more than Control.Concurrent.
Yes, but the changes made in the child thread would be ignored in the parent. Best regards Tomasz

Hello Kurt, Wednesday, November 16, 2005, 7:51:19 PM, you wrote: KH> I'm writing a program that will be using multiple threads to handle KH> network activity on multiple ports in a responsive way. The treads KH> will all need access to some shared data, so I'm using an MVar. So far KH> so good. The problem is that passing the MVar around everywhere is KH> kind of a pain, so I was hoping to use a ReaderT monad on top of the KH> IO monad to handle that for me. there are two alternative solutions: 1) use global variables 2) use implicit parameters (ghc-specific) -- Best regards, Bulat mailto:bulatz@HotPOP.com

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.

In http://www.eecs.harvard.edu/~ccshan/prepose/prepose.pdf Oleg and I survey the approaches that others have mentioned and propose a new technique that is particularly relevant in concurrent programs. Ken -- Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig If debugging is the process of removing bugs, then programming must be the process of putting them in.
participants (6)
-
Andrew Pimlott
-
Bulat Ziganshin
-
Chung-chieh Shan
-
Kurt Hutchinson
-
Thomas Jäger
-
Tomasz Zielonka