[Haskell-cafe] Re[6]: Parallel combinator, performance advice

Bulat Ziganshin bulat.ziganshin at gmail.com
Tue Apr 7 12:40:06 EDT 2009


Hello Bulat,

Tuesday, April 7, 2009, 8:10:43 PM, you wrote:

>>> parallel_ (x1:xs) = do
>>>     sem <- newQSem $ 1 - length xs
>>>     forM_ xs $ \x ->
>>>         writeChan queue (x >> signalQSem sem, False)
>>>     x1
>>>     addWorker
>>>     waitQSem sem
>>>     writeChan queue (signalQSem sem, True)
>>>     waitQSem sem

>> Neil, executing x1 directly in parallel_ is incorrect idea.

> forget this. but it still a bit suboptimal...

i think i realized why you use this schema. my solution may lead to
N-1 worker threads in the system if last job is too small - after its
execution we finish one thread and have just N-1 working threads until
parallel_ will be finished

but problem i mentioned in previous letter may also take place
although it looks like less important. we may solve both problems by
allowing worker thread to actively select its death time: it should
die only at the moment when *last* job in bucket was finished - this
guarantees us exactly N worker threads at any time. so:

parallel_ (x1:xs) = do
    sem <- newQSem $ - length xs
    jobsLast <- newMVar (length xs)
    addWorker
    forM_ (x1:xs) $ \x -> do
        writeChan queue $ do
           x
           signalQSem sem
           modifyMVar jobsLast $ \jobs -> do
               return (jobs-1, jobs==0)
    --
    waitQSem sem

    
and modify last 3 lines of addWorker:

addWorker :: IO ()
addWorker = do
    forkIO $ f `E.catch` \(e :: SomeException) ->
        throwTo mainThread $ ErrorCall "Control.Concurrent.Parallel: parallel thread died."
    return ()
    where
        f :: IO ()
        f = do
            act <- readChan queue
            kill <- act
            unless kill f



-- 
Best regards,
 Bulat                            mailto:Bulat.Ziganshin at gmail.com



More information about the Haskell-Cafe mailing list