
Hello, Rob.
We are using forkProcess for similar reason: "share" complex immutable
state, that takes much time to be created, and process isolation. I wrote
"share" because big part of the structure is not in pinned memory, thus it
would be shared up to GC, that will relocate this structures. But in our
case its OK, because we can allow multiplying of structure, and reduced
initialization time outterweights other problems.
However in case if we need real sharing then we'd had to use other
structures based on the storage pinned memory.
We never experienced deadlocks in our case. However there are known
problems with forkProcess like:
https://ghc.haskell.org/trac/ghc/ticket/9347
and there were few topics in this mailing list, so you could get in a
problematic case.
--
Alexander
On Feb 21, 2015 3:59 AM, "Rob Leslie"
Hi folks,
I’d love to get a sense of the prevailing wisdom with respect to forkProcess from System.Posix.Process.
I’m building a multithreaded (STM) application with potentially many threads simultaneously reading and writing to pieces of (an otherwise rather large) shared state. Occasionally I would like to record a whole snapshot of that state, and it seems to me a natural way to accomplish this is to fork a process (eliminating all the other threads) and perform a read-only dump of the state. This dump can be time-consuming, which is why I’d rather not have contention with other threads that may be trying to modify the state while I’m dumping.
My experience with forkProcess so far is that sometimes it works brilliantly, and other times it just deadlocks. I’m at a loss to understand what the problem is, but the deadlock seems to occur before the new process gets any control -- certainly before it has started to access any of the shared state.
I’m aware of the giant warning in the forkProcess documentation, but I’m not sure if or how it could explain the behavior I’m seeing. Has anyone else used forkProcess successfully?
It’s possible too that I’m running into something related to the way I’m setting up a pipe to receive messages from the forked process. Here is what I’m doing:
runInForkedProcess :: ((Text -> IO ()) -> IO ()) -> Consumer Text IO () -> IO Bool runInForkedProcess iof consumer = do process <- newEmptyMVar result <- newEmptyMVar
let handler = Catch $ do status <- getProcessStatus False False =<< readMVar process case status of Just (Exited code) -> void $ tryPutMVar result (code == ExitSuccess) Just Terminated{} -> void $ tryPutMVar result False _ -> return ()
bracket (installHandler processStatusChanged handler Nothing) (\former -> installHandler processStatusChanged former Nothing) $ \_ -> do
(input, output) <- createPipe
processId <- forkProcess $ do closeFd input bracket (fdToHandle output) hClose $ \outHandle -> do hSetBuffering outHandle NoBuffering iof (hPutStrLn outHandle) putMVar process processId
closeFd output
bracket (fdToHandle input) hClose $ \inHandle -> do hSetBuffering inHandle NoBuffering runEffect $ fromHandle inHandle >-> for cat (yield . T.pack) >-> consumer
takeMVar result
Does anyone have any advice?
Many thanks,
-- Rob Leslie rob@mars.org
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe