Draft Chapter: Concurrency
Haskell supports concurrency, in the sense that a program can contain multiple threads of execution interacting non-deterministically. Precisely what we mean by this, and what guarantees the programmer is given, are described in this chapter. The material here is to be read concurrently with the description of the Control.Concurrent
library, in Chapter ??.
Threads
New threads are created by the forkIO
operation from the module Control.Concurrent
:
forkIO :: IO a -> IO ThreadId
The forkIO
operation creates a new thread to execute the supplied IO
action, and returns immediately to the caller with a value of type ThreadId
that can be used to identify the new thread (see 'The ThreadId
type', below).
Operations performed by multiple threads may be interleaved arbitrarily by the implementation, with the following restriction:
- A thread that is not blocked will not be indefinitely delayed by the implementation.
where
- a thread is blocked if it is waiting for an external resource that is currently not available (for example input
from the console), or it is performing an operation that involves a shared resource and another thread
currently has ownership of the resource (for example, output to a shared
Handle
).
This is called the fairness guarantee. An implementation technique that is often used to provide this fairness guarnatee is pre-emption: running threads are periodically pre-empted in software in order to let other threads proceed. There are other implementation techniques that also work; for example, hardware concurrency. (ToDo?: move this text to a footnote or separate section?)
ThreadId
type
The The ThreadId
type is abstract, and supports Eq
, Ord
, and Show
, with the following meanings:
-
Eq
: twoThreadId
values compare equal if and only if they were returned by the sameforkIO
call. -
Ord
: the implementation provides an arbitrary total ordering onThreadId
s. For example, the ordering may be used to contruct a
mapping with
ThreadId
as the domain. There are no guarantees other than that the ordering is total; the particular ordering might be different from run to run of the program.
-
Show
: the results are implementation-defined, this is mainly for debugging.
Communication between Threads
The basic facility for communication between threads is the MVar
type.
data MVar -- instance of Eq, Typeable, Typeable1
An MVar (pronounced "em-var") is a synchronising variable. It can be thought of as a a box, which may be empty or full. An MVar
may be created using one of the following two operations:
newEmptyMVar :: IO (MVar a)
newMVar :: a -> IO (MVar a)
newEmptyMVar
create an MVar which is initially empty; newMVar
create an MVar which contains the supplied value.
takeMVar :: MVar a -> IO a
The takeMVar
operation return the contents of the MVar
. If the MVar
is currently empty, takeMVar
will block until it is full. After a takeMVar
, the MVar
is left empty.
putMVar :: MVar a -> a -> IO ()
Put a value into an MVar
. If the MVar
is currently full, putMVar
will wait until it becomes empty.
There is an extension to the fairness guarantee as it applies to MVar
s:
- A thread blocked on an
MVar
will eventually proceed, as long as theMVar
is being filled infinitely often.
It is recommended that the implementation provide "single-wakeup" semantics for takeMVar
. That is, if there are multiple threads
blocked in takeMVar
on a particular MVar
, and the MVar
becomes full, only one thread will be woken up. The implementation
guarantees that the woken thread completes its takeMVar
operation. In fact, a single-wakeup implementation is usually a consequence of providing the fairness extension for MVar
s above: if multiple threads blocked on an MVar
were woken up simultaneously, it would be hard to guarantee that any particular thread would eventually gain access to the MVar
.
The full range of MVar
operations are described in the documentation for Control.Concurrent.MVar
, see ??. A range of concurrent communication facilities can be provided based on MVar
s, these are expected to be supplied as separate libraries.
ToDo? STM?
Concurrency and the FFI
Foreign calls (see Chapter ??) can be made as usual by concurrent threads. The fairness guarantee requires that a foreign call must not hold up the other threads in the system; this implies that the Haskell implementation must be able to make use of the operating system's native threads ("OS threads" from now on) in order to run a foreign call concurrently with other Haskell threads, and concurrently with other foreign calls.
However, it is not required that the Haskell implementation maintain a one-to-one mapping between native operating system threads and Haskell threads [cite: Conc/FFI paper]: indeed there are more efficient imlementations that multiplex many Haskell threads on to a few operating system threads. On such systems, it can be relatively expensive to make a foreign call that must be able to run concurrently with the other threads, and for this reason we allow a small exception to the fairness guarantee:
- A
foreign import
declaration annotated asnonconcurrent
(ToDo?: pick syntax) is not subject to the fairness guarantee. It may prevent progress of other threads until it returns.
In some implementations, nonconcurrent
foreign calls can be implemented much more efficiently.
Foreign calls may also invoke further Haskell functions by calling foreign export
ed functions. Allowing for this possibilty may also be expensive: a function exposed by foreign export
may be invoked at any time by an arbitrary OS thread, and the implementation must be ready to receive the call. However, if the implementation knows that a given foreign call cannot result in a callback (a call to a function exposed by foreign export
), then it can sometimes use a more efficient calling sequence for the foreign call. For this reason, we have another annotation:
- A
foreign import
declaration annotated asnonreentrant
(ToDo?: pick syntax) can be assumed by the implementation to refer to a foreign function that will never call a Haskell function, or any function in the C API described in Chapter ??.
Memory model
ToDo?.
- MVar operations can never be observed out-of-order
- Maybe: IORef operations also strongly ordered
- STM, if we have it: also strong ordering between transactions
Bound threads (optional)
Bound threads allow a Haskell program more control over the mapping between Haskell threads and OS threads. Such control is required for interacting with foreign code that makes use of thread-local state in the native OS threading model: when foreign code uses OS thread-local state, the Haskell programmer needs to restrict calls to that foreign code to happen in a particular OS thread. Bound threads provide a lightweight way to allow the programmer enough control without imposing burdens on the implementation that would significantly reduce efficiency.
Bound threads are an optional feature in Haskell'; the documentation for an implementation should state whether bound threads are supported or not.
A Haskell thread can be either bound or unbound, depending on how it was created:
-
forkIO
creates unbound threads -
Calls from foreign code to Haskell functions exposed by
foreign export
orforeign import "wrapper"
create a bound thread in which to run the computation.
Whether a thread is bound or unbound affects how foreign calls are made:
-
Foreign calls made by an unbound thread happen in an arbitrary OS thread.
-
Foreign calls made by a bound thread are always made by the OS thread that made the original call-in.
Note that a valid implementation of bound threads is one in which every Haskell thread is associated with a distinct OS thread, where in effect every thread is bound. However, the isCurrentThreadBound
operation (see below) should always return False
for threads created by forkIO
, regardless of the implementation, to aid portabilty.
Also note that the above property of foreign calls made by a bound thread is the only requirement of the relationship between OS threads and Haskell threads. It is completely unspecified which OS thread runs the Haskell code itself: the Haskell programmer has no way to observe the current OS thread aside from making a foreign call, so the implementation is free to choose among a number of strategies here.
The following operations exported by Control.Concurrent
are related to bound threads (ToDo? just link to the appropriate section of the library docs here?):
supportsBoundThreads :: Bool
This value is True
if the implementation supports bound threads (NB. this is called rtsSupportsBoundThreads
currently).
isCurrentThreadBound :: IO Bool
This operation returns False
if the current thread was created by forkIO
, and True
otherwise. If supportsBoundThreads
is False
, this function raises an exception (ToDo? which one?).
forkOS :: IO () -> IO ThreadId
Like forkIO
, forkOS
creates a new Haskell thread to run the supplied IO
action. However, in the case of forkOS
, the new Haskell thread is bound to a freshly created OS thread. This is achieved by making a foreign call to create the new OS thread, and having the new OS thread invoke the IO
action, thus creating a bound thread. If supportsBoundThreads
is False
, this function raises an exception (ToDo? which one?).