[Haskell-cafe] Re: Thread pool in GHC

genneth genneth at gmail.com
Thu Aug 4 12:47:56 EDT 2005


Dinh Tien Tuan Anh <tuananhbirm <at> hotmail.com> writes:

> 
> 
>   Can thread pool be implemented in GHC ?
> 
> I have a program that is currently using about 12-15 threads (launch and 
> kill for infinite times) and when running, especially after Ctrl-C, my 
> computer got freezed up. And if i ran it several times, the "Stack 
> overflows" occurs.

I made the following a while back. Maybe it's useful...

limitedThreadsWithChannelMapM :: Integer -> (a -> IO b) -> [a] -> IO [MVar b]
limitedThreadsWithChannelMapM lim ioaction x = do
    threadpoolcounter <- atomically ( newTVar 0 )
    mapM (throttledFork threadpoolcounter . ioaction) x
    where
        throttledFork poolcount io = do
            atomically ( do
                prev <- readTVar poolcount
                if prev >= lim then 
                    retry
                    else writeTVar poolcount (prev+1) )
            mvar <- newEmptyMVar
            forkIO(
                finally
                    (io >>= putMVar mvar)
                    (atomically ( readTVar poolcount >>= writeTVar poolcount .
(subtract 1) ) ) )
            return mvar

> 
> Cheers
> TuanAnh
> 
> _________________________________________________________________
> Winks & nudges are here - download MSN Messenger 7.0 today! 
> http://messenger.msn.co.uk
> 






More information about the Haskell-Cafe mailing list