module Control.CUtils.ThreadPool (
ThreadPool(..), Interruptible(..),
NoPool(..), BoxedThreadPool(..)) where
import Control.Concurrent
import Control.Monad
import Control.Monad.Loops
import Data.Word
import Data.Array.IO
import Data.IORef
data Pool = Pool
!Int
!(Chan(IO ()))
class ThreadPool pool where
addToPool :: pool -> IO () -> IO ()
class Interruptible pool where
stopPool :: pool -> IO ()
createPool :: Word32 -> Int -> IO Pool
createPool channelSize workers = do
chn <- newChan
stop <- newIORef False
let loop = whileM_(return True)$readChan chn>>=id
sequence_$replicate workers$forkIO loop
return$!Pool workers chn
instance ThreadPool Pool where
addToPool (Pool _ channel) m = writeChan channel m
instance Interruptible Pool where
stopPool (Pool n channel) = replicateM_ n$writeChan channel$myThreadId>>=killThread
data NoPool = NoPool
instance ThreadPool NoPool where
addToPool _ = void.forkIO
data BoxedThreadPool where
BoxedThreadPool :: (ThreadPool pool) => pool -> BoxedThreadPool
instance ThreadPool BoxedThreadPool where
addToPool (BoxedThreadPool pool) = addToPool pool