[Haskell-cafe] ReaderT and concurrency

Kurt Hutchinson kelanslists at gmail.com
Wed Nov 16 11:51:19 EST 2005


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


More information about the Haskell-Cafe mailing list