extra-1.4.9: Extra functions I use.

Safe HaskellSafe
LanguageHaskell2010

Control.Concurrent.Extra

Contents

Description

Extra functions for Control.Concurrent.

This module includes three new types of MVar, namely Lock (no associated value), Var (never empty) and Barrier (filled at most once). See this blog post for examples and justification.

If you need greater control of exceptions and threads see the slave-thread package. If you need elaborate relationships between threads see the async package.

Synopsis

Documentation

getNumCapabilities :: IO Int

Returns the number of Haskell threads that can run truly simultaneously (on separate physical processors) at any given time. To change this value, use setNumCapabilities.

Since: 4.4.0.0

setNumCapabilities :: Int -> IO ()

Set the number of Haskell threads that can run truly simultaneously (on separate physical processors) at any given time. The number passed to forkOn is interpreted modulo this value. The initial value is given by the +RTS -N runtime flag.

This is also the number of threads that will participate in parallel garbage collection. It is strongly recommended that the number of capabilities is not set larger than the number of physical processor cores, and it may often be beneficial to leave one or more cores free to avoid contention with other processes in the machine.

Since: 4.5.0.0

withNumCapabilities :: Int -> IO a -> IO a Source

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.

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

fork a thread and call the supplied function when the thread is about to terminate, with an exception or a returned value. The function is called with asynchronous exceptions masked.

forkFinally action and_then =
  mask $ \restore ->
    forkIO $ try (restore action) >>= and_then

This function is useful for informing the parent when a child terminates, for example.

Since: 4.6.0.0

once :: IO a -> IO (IO a) Source

Given an action, produce a wrapped action that runs at most once. If the function raises an exception, the same exception will be reraised each time.

let x ||| y = do t1 <- onceFork x; t2 <- onceFork y; t1; t2
\(x :: IO Int) -> void (once x) == return ()
\(x :: IO Int) -> join (once x) == x
\(x :: IO Int) -> (do y <- once x; y; y) == x
\(x :: IO Int) -> (do y <- once x; y ||| y) == x

onceFork :: IO a -> IO (IO a) Source

Like once, but immediately starts running the computation on a background thread.

\(x :: IO Int) -> join (onceFork x) == x
\(x :: IO Int) -> (do a <- onceFork x; a; a) == x

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 Lock Source

Create a new Lock.

withLock :: Lock -> IO a -> IO a Source

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 a Source

Read the current value of the Var.

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

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 b Source

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 throw an exception.

waitBarrier :: Barrier a -> IO a Source

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.