|
Control.Concurrent | Portability | non-portable (concurrency) | Stability | experimental | Maintainer | libraries@haskell.org |
|
|
|
|
Contents |
- Concurrent Haskell
- Basic concurrency operations
- Scheduling
- Blocking
- Waiting
- Communication abstractions
- Merging of streams
- GHC's implementation of concurrency
- Terminating the program
- Pre-emption
|
|
Description |
A common interface to a collection of useful concurrency
abstractions.
|
|
Synopsis |
|
|
|
|
Concurrent Haskell |
|
The concurrency extension for Haskell is described in the paper
Concurrent Haskell
http://www.haskell.org/ghc/docs/papers/concurrent-haskell.ps.gz. Concurrency is "lightweight", which means that both thread creation
and context switching overheads are extremely low. Scheduling of
Haskell threads is done internally in the Haskell runtime system, and
doesn't make use of any operating system-supplied thread packages. Haskell threads can communicate via MVars, a kind of synchronised
mutable variable (see Control.Concurrent.MVar). Several common
concurrency abstractions can be built from MVars, and these are
provided by the Concurrent library. Threads may also communicate
via exceptions.
|
|
Basic concurrency operations |
|
data ThreadId |
A ThreadId is an abstract type representing a handle to a thread.
ThreadId is an instance of Eq, Ord and Show, where
the Ord instance implements an arbitrary total ordering over
ThreadIds. The Show instance lets you convert an arbitrary-valued
ThreadId to string form; showing a ThreadId value is occasionally
useful when debugging or diagnosing the behaviour of a concurrent
program. NOTE: in GHC, if you have a ThreadId, you essentially have
a pointer to the thread itself. This means the thread itself can't be
garbage collected until you drop the ThreadId.
This misfeature will hopefully be corrected at a later date.
| Instances | |
|
|
myThreadId :: IO ThreadId |
Returns the ThreadId of the calling thread. |
|
forkIO :: IO () -> IO ThreadId |
This sparks off a new thread to run the IO computation passed as the
first argument, and returns the ThreadId of the newly created
thread.
|
|
killThread :: ThreadId -> IO () |
killThread terminates the given thread (Note: killThread is
not implemented in Hugs). Any work already done by the thread isn't
lost: the computation is suspended until required by another thread.
The memory used by the thread will be garbage collected if it isn't
referenced from anywhere. The killThread function may be defined in
terms of throwTo: killThread tid = throwTo tid (AsyncException ThreadKilled)
|
|
throwTo :: ThreadId -> Exception -> IO () |
throwTo raises an arbitrary exception in the target thread. throwTo does not return until the exception has been raised in the
target thread. The calling thread can thus be certain that the target
thread has received the exception. This is a useful property to know
when dealing with race conditions: eg. if there are two threads that
can kill each other, it is guaranteed that only one of the threads
will get to kill the other. |
|
Scheduling |
|
Scheduling may be either pre-emptive or co-operative,
depending on the implementation of Concurrent Haskell (see below
for imformation related to specific compilers). In a co-operative
system, context switches only occur when you use one of the
primitives defined in this module. This means that programs such
as: main = forkIO (write 'a') >> write 'b'
where write c = putChar c >> write c will print either aaaaaaaaaaaaaa... or bbbbbbbbbbbb...,
instead of some random interleaving of as and bs. In
practice, cooperative multitasking is sufficient for writing
simple graphical user interfaces.
|
|
yield :: IO () |
The yield action allows (forces, in a co-operative multitasking
implementation) a context-switch to any other currently runnable
threads (if any), and is occasionally useful when implementing
concurrency abstractions. |
|
Blocking |
|
Calling a foreign C procedure (such as getchar) that blocks waiting
for input will block all threads, unless the threadsafe attribute
is used on the foreign call (and your compiler / operating system
supports it). GHC's I/O system uses non-blocking I/O internally to
implement thread-friendly I/O, so calling standard Haskell I/O
functions blocks only the thead making the call.
|
|
Waiting |
|
threadDelay :: Int -> IO () |
The threadDelay operation will cause the current thread to
suspend for a given number of microseconds. Note that the resolution
used by the Haskell runtime system's internal timer together with the
fact that the thread may take some time to be rescheduled after the
time has expired, means that the accuracy is more like 1/50 second. |
|
threadWaitRead :: Int -> IO () |
Block the current thread until data is available to read on the
given file descriptor. |
|
threadWaitWrite :: Int -> IO () |
Block the current thread until data can be written to the
given file descriptor. |
|
Communication abstractions |
|
module Control.Concurrent.MVar |
|
module Control.Concurrent.Chan |
|
module Control.Concurrent.QSem |
|
module Control.Concurrent.QSemN |
|
module Control.Concurrent.SampleVar |
|
Merging of streams |
|
mergeIO :: [a] -> [a] -> IO [a] |
|
nmergeIO :: [[a]] -> IO [a] |
|
The mergeIO and nmergeIO functions fork one thread for each
input list that concurrently evaluates that list; the results are
merged into a single output list. Note: Hugs does not provide these functions, since they require
preemptive multitasking. |
|
GHC's implementation of concurrency |
|
This section describes features specific to GHC's
implementation of Concurrent Haskell. |
|
Terminating the program |
|
In a standalone GHC program, only the main thread is
required to terminate in order for the process to terminate.
Thus all other forked threads will simply terminate at the same
time as the main thread (the terminology for this kind of
behaviour is "daemonic threads"). If you want the program to wait for child threads to
finish before exiting, you need to program this yourself. A
simple mechanism is to have each child thread write to an
MVar when it completes, and have the main
thread wait on all the MVars before
exiting: myForkIO :: IO () -> IO (MVar ())
myForkIO io = do
mvar \<- newEmptyMVar
forkIO (io \`finally\` putMVar mvar ())
return mvar Note that we use finally from the
Exception module to make sure that the
MVar is written to even if the thread dies or
is killed for some reason. A better method is to keep a global list of all child
threads which we should wait for at the end of the program: children :: MVar [MVar ()]
children = unsafePerformIO (newMVar [])
waitForChildren :: IO ()
waitForChildren = do
(mvar:mvars) \<- takeMVar children
putMVar children mvars
takeMVar mvar
waitForChildren
forkChild :: IO () -> IO ()
forkChild io = do
mvar \<- newEmptyMVar
forkIO (p \`finally\` putMVar mvar ())
childs \<- takeMVar children
putMVar children (mvar:childs)
later = flip finally
main =
later waitForChildren $
... The main thread principle also applies to calls to Haskell from
outside, using foreign export. When the foreign exported
function is invoked, it starts a new main thread, and it returns
when this main thread terminates. If the call causes new
threads to be forked, they may remain in the system after the
foreign exported function has returned.
|
|
Pre-emption |
|
GHC implements pre-emptive multitasking: the execution of
threads are interleaved in a random fashion. More specifically,
a thread may be pre-empted whenever it allocates some memory,
which unfortunately means that tight loops which do no
allocation tend to lock out other threads (this only seems to
happen with pathalogical benchmark-style code, however). The rescheduling timer runs on a 20ms granularity by
default, but this may be altered using the
-in RTS option. After a rescheduling
"tick" the running thread is pre-empted as soon as
possible. One final note: the
aaaa bbbb example may not
work too well on GHC (see Scheduling, above), due
to the locking on a Handle. Only one thread
may hold the lock on a Handle at any one
time, so if a reschedule happens while a thread is holding the
lock, the other thread won't be able to run. The upshot is that
the switch from aaaa to
bbbbb happens infrequently. It can be
improved by lowering the reschedule tick period. We also have a
patch that causes a reschedule whenever a thread waiting on a
lock is woken up, but haven't found it to be useful for anything
other than this example :-)
|
|
Produced by Haddock version 0.4 |