extra-0.3.1: Extra functions I use.

Safe HaskellSafe-Inferred

Control.Concurrent.Extra

Contents

Description

Extra functions for Control.Concurrent. These fall into a few categories:

  • Some functions manipulate the number of capabilities.
  • The forkFinally function - if you need greater control of exceptions and threads see the slave-thread package.
  • Three new types of MVar, namely Lock (no associated value), Var (never empty) and Barrier (filled at most once). See this blog post for more examples.

Synopsis

Documentation

withNumCapabilities :: Int -> IO a -> IO aSource

On GHC 7.6 and above with the -threaded flag, brackets a call to setNumCapabilities. On lower versions (which lack setNumCapabilities) this function just runs the argument action.

setNumCapabilities :: Int -> IO ()

forkFinally :: IO a -> (Either SomeException a -> IO ()) -> IO ThreadId

Lock

data Lock Source

Like an MVar, but has no value. Used to guarantees single-threaded access, typically to some system resource. As an example:

 lock <- newLock
 let output = withLock . putStrLn
 forkIO $ do ...; output "hello"
 forkIO $ do ...; output "world"

Here we are creating a lock to ensure that when writing output our messages do not get interleaved. This use of MVar never blocks on a put. It is permissible, but rare, that a withLock contains a withLock inside it - but if so, watch out for deadlocks.

newLock :: IO LockSource

Create a newLock.

withLock :: Lock -> IO a -> IO aSource

Perform some operation while holding Lock. Will prevent all other operations from using the Lock while the action is ongoing.

withLockTry :: Lock -> IO a -> IO (Maybe a)Source

Like withLock but will never block. If the operation cannot be executed immediately it will return Nothing.

Var

data Var a Source

Like an MVar, but must always be full. Used to on a mutable variable in a thread-safe way. As an example:

 hits <- newVar 0
 forkIO $ do ...; modifyVar_ hits (+1); ...
 i <- readVar hits
 print (HITS,i)

Here we have a variable which we modify atomically, so modifications are not interleaved. This use of MVar never blocks on a put. No modifyVar operation should ever block, and they should always complete in a reasonable timeframe. A Var should not be used to protect some external resource, only the variable contained within. Information from a readVar should not be subsequently inserted back into the Var.

newVar :: a -> IO (Var a)Source

Create a new Var with a value.

readVar :: Var a -> IO aSource

Read the current value of the Var.

modifyVar :: Var a -> (a -> IO (a, b)) -> IO bSource

Modify a Var producing a new value and a return result.

modifyVar_ :: Var a -> (a -> IO a) -> IO ()Source

Modify a Var, a restricted version of modifyVar.

withVar :: Var a -> (a -> IO b) -> IO bSource

Perform some operation using the value in the Var, a restricted version of modifyVar.

Barrier

data Barrier a Source

Starts out empty, then is filled exactly once. As an example:

 bar <- newBarrier
 forkIO $ do ...; val <- ...; signalBarrier bar val
 print =<< waitBarrier bar

Here we create a barrier which will contain some computed value. A thread is forked to fill the barrier, while the main thread waits for it to complete. A barrier has similarities to a future or promise from other languages, has been known as an IVar in other Haskell work, and in some ways is like a manually managed thunk.

newBarrier :: IO (Barrier a)Source

Create a new Barrier.

signalBarrier :: Barrier a -> a -> IO ()Source

Write a value into the Barrier, releasing anyone at waitBarrier. Any subsequent attempts to signal the Barrier will be silently ignored.

waitBarrier :: Barrier a -> IO aSource

Wait until a barrier has been signaled with signalBarrier.

waitBarrierMaybe :: Barrier a -> IO (Maybe a)Source

A version of waitBarrier that never blocks, returning Nothing if the barrier has not yet been signaled.