| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Immortal.Queue
Description
This module uses the immortal library to build a pool of worker threads that process a queue of tasks asynchronously.
First build an ImmortalQueue for your task type and queue backend. Then
you can launch the pool using processImmortalQueue and stop the pool with
closeImmortalQueue.
import Control.Concurrent.STM (atomically)
import Control.Concurrent.STM.TQueue
import Control.Exception (Exception)
import Control.Immortal.Queue
data Task
= Print String
deriving (Show)
queueConfig :: TQueue Task -> ImmortalQueue Task
queueConfig queue =
ImmortalQueue
{ qThreadCount = 2
, qPollWorkerTime = 1000
, qPop = atomically $ readTQueue queue
, qPush = atomically . writeTQueue queue
, qHandler = performTask
, qFailure = printError
}
where
performTask :: Task -> IO ()
performTask t = case t of
Print str ->
putStrLn str
printError :: Exception e => Task -> e -> IO ()
printError t err =
let description = case t of
Print str ->
"print"
in putStrLn $ "Task `" ++ description ++ "` failed with: " ++ show err
main :: IO ()
main = do
queue <- newTQueueIO
workers <- processImmortalQueue $ queueConfig queue
atomically $ mapM_ (writeTQueue queue . Print) ["hello", "world"]
closeImmortalQueue workersSynopsis
- data ImmortalQueue a = ImmortalQueue {}
- processImmortalQueue :: forall a. ImmortalQueue a -> IO QueueId
- data QueueId
- closeImmortalQueue :: QueueId -> IO ()
- killImmortalQueue :: QueueId -> IO ()
Config
data ImmortalQueue a Source #
The configuration data required for initializing a worker pool.
Constructors
| ImmortalQueue | |
Fields
| |
Run
processImmortalQueue :: forall a. ImmortalQueue a -> IO QueueId Source #
Start a management thread that creates the queue-processing worker threads & return a QueueId that can be used to stop the workers.
An identifier created by a queue manager that can be used to stop the worker processes.
Stop
closeImmortalQueue :: QueueId -> IO () Source #
Cleanly close the worker pool, allowing them to complete their actions.
killImmortalQueue :: QueueId -> IO () Source #
Uncleanly close the worker pool, aborting current actions.