[Haskell-cafe] A useful function for forking a thread, but letting the parent do setup first

Joey Adams joeyadams3.14159 at gmail.com
Wed Jul 18 12:34:40 CEST 2012


Here's a useful little function:

    -- | Fork a thread, but wait for the main thread to perform a setup action
    -- using the child's 'ThreadID' before beginning work in the child thread.
    forkSetup :: (ThreadId -> IO (Maybe a, r))
                 -- ^ Setup action to be called before the thread begins working
              -> (a -> IO b)
                 -- ^ What to do in the worker thread
              -> IO r
    forkSetup setup inner =
        mask $ \restore -> do
            mv <- newEmptyMVar
            tid <- forkIO $ join $ takeMVar mv
            (ma, r) <- setup tid `onException` putMVar mv (return ())
            case ma of
                Nothing -> putMVar mv $ return ()
                Just a  -> putMVar mv $ restore $ inner a >> return ()
            return r

A question about 'mask': is it safe to use the 'restore' callback in a
forked thread?  Or might this be invalid in a future version of GHC?
I'm aware that if forkSetup itself is called with exceptions masked,
the child thread will also have exceptions masked.  This seems
reasonable, given that forkIO behaves the same way.

Is a function like this available in some existing library?  If not,
where would be a good home for it?

Thanks for the input!



More information about the Haskell-Cafe mailing list