Next Previous Contents

4. Concurrent

4.1 Concurrent Haskell

GHC and Hugs both provide concurrency extensions, as described in Concurrent Haskell.

Concurrency in GHC and Hugs 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. Several common concurrency abstractions can be built from MVars, and these are provided by the Concurrent library, which is described in the later sections. Threads may also communicate via exceptions.

4.2 Concurrency Basics

To gain access to the concurrency primitives, just import Concurrent in your Haskell module. In GHC, you also need to add the -syslib concurrent option to the command line.

To create a new thread, use forkIO:

forkIO :: IO () -> IO ThreadId

This sparks off a new thread to run the IO computation passed as the first argument.

The returned ThreadId is an abstract type representing a handle to the newly created thread. The ThreadId type is an instance of both Eq and Ord, where the Ord instance implements an arbitrary total ordering over ThreadIds.

Threads may also be killed via the ThreadId:

killThread :: ThreadId -> IO ()

this terminates the given thread (Note: killThread is not implemented in Hugs yet). 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 else.

More generally, an arbitrary exception (see Section Exceptions) may be raised in any thread for which we have a ThreadId, with raiseInThread:

raiseInThread :: ThreadId -> Exception -> IO ()

Actually killThread just raises the ThreadKilled exception in the target thread, the normal action of which is to just terminate the thread. The target thread will stop whatever it was doing (even if it was blocked on an MVar or other computation) and handle the exception.

The ThreadId for the current thread can be obtained with myThreadId:

myThreadId :: IO ThreadId

NOTE: 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.

4.3 Scheduling

GHC uses preemptive multitasking: context switches can occur at any time. At present, Hugs uses cooperative multitasking: 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.

The yield action forces a context-switch to any other currently runnable threads (if any), and is occasionally useful when implementing concurrency abstractions:

yield :: IO ()

Thread Waiting

Finally, there are operations to delay a concurrent thread, and to make one wait:

threadDelay     :: Int -> IO () -- delay rescheduling for N microseconds
threadWaitRead  :: Int -> IO () -- wait for input on specified file descriptor
threadWaitWrite :: Int -> IO () -- (read and write, respectively).

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 and threadWaitWrite can be used to block a thread until I/O is available on a given file descriptor. These primitives are used by the I/O subsystem to ensure that a thread waiting on I/O doesn't hang the entire system.

Blocking

Calling a foreign C procedure (such as getchar) that blocks waiting for input will block all threads, in both GHC and Hugs. The GHC 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.

4.4 Concurrency abstractions

MVars

The Concurrent interface provides access to ``M-Vars'', which are synchronising variables.

MVars are rendezvous points, mostly for concurrent threads. They begin either empty or full, and any attempt to read an empty MVar blocks. When an MVar is written, a single blocked thread may be freed. Reading an MVar toggles its state from full back to empty. Therefore, any value written to an MVar may only be read once. Multiple reads and writes are allowed, but there must be at least one read between any two writes. Interface:

data MVar a -- abstract
instance Eq (MVar a)

newEmptyMVar     :: IO (MVar a)
newMVar          :: a -> IO (MVar a)
takeMVar         :: MVar a -> IO a
putMVar          :: MVar a -> a -> IO ()
readMVar         :: MVar a -> IO a
swapMVar         :: MVar a -> a -> IO a
isEmptyMVar      :: MVar a -> IO Bool

The operation isEmptyMVar returns a flag indicating whether the MVar is currently empty or filled in, i.e., will a thread block when performing a takeMVar on that MVar or not?

Please notice that the Boolean value returned from isEmptyMVar represent just a snapshot of the state of the MVar. By the time a thread gets to inspect the result and act upon it, other threads may have accessed the MVar and changed the 'filled-in' status of the variable.

The same proviso applies to isEmptyChan (next sub-section).

These two predicates are currently only supported by GHC.

Channel Variables

A channel variable (CVar) is a one-element channel, as described in the paper:

data CVar a
newCVar :: IO (CVar a)
putCVar :: CVar a -> a -> IO ()
getCVar :: CVar a -> IO a

Channels

A Channel is an unbounded channel:

data Chan a 
newChan         :: IO (Chan a)
putChan         :: Chan a -> a -> IO ()
getChan         :: Chan a -> IO a
dupChan         :: Chan a -> IO (Chan a)
unGetChan       :: Chan a -> a -> IO ()
getChanContents :: Chan a -> IO [a]

Semaphores

General and quantity semaphores:

data QSem
newQSem     :: Int   -> IO QSem
waitQSem    :: QSem  -> IO ()
signalQSem  :: QSem  -> IO ()

data QSemN
newQSemN    :: Int   -> IO QSemN
signalQSemN :: QSemN -> Int -> IO ()
waitQSemN   :: QSemN -> Int -> IO ()

Merging Streams

Merging streams---binary and n-ary:

mergeIO  :: [a]   -> [a] -> IO [a]
nmergeIO :: [[a]] -> IO [a]

These actions 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 the functions mergeIO or nmergeIO since these require preemptive multitasking.

Sample Variables

A Sample variable (SampleVar) is slightly different from a normal MVar:

type SampleVar a = MVar (Int, MVar a)

emptySampleVar :: SampleVar a -> IO ()
newSampleVar   :: IO (SampleVar a)
readSample     :: SampleVar a -> IO a
writeSample    :: SampleVar a -> a -> IO ()

4.5 The Concurrent library interface

The full interface for the Concurrent library is given below for reference:

module Concurrent where

data ThreadId    -- thread identifiers
instance Eq  ThreadId
instance Ord ThreadId

forkIO           :: IO () -> IO ThreadId
myThreadId       :: IO ThreadId
killThread       :: ThreadId -> IO ()
yield            :: IO ()

data MVar a      -- Synchronisation variables
instance Eq (MVar a)
newEmptyMVar     :: IO (MVar a)
newMVar          :: a -> IO (MVar a)
takeMVar         :: MVar a -> IO a
putMVar          :: MVar a -> a -> IO ()
swapMVar         :: MVar a -> a -> IO a
readMVar         :: MVar a -> IO a 
isEmptyMVar      :: MVar a -> IO Bool


data Chan a      -- channels
newChan          :: IO (Chan a)
writeChan        :: Chan a -> a -> IO ()
readChan         :: Chan a -> IO a
dupChan          :: Chan a -> IO (Chan a)
unReadChan       :: Chan a -> a -> IO ()
isEmptyChan      :: Chan a -> IO Bool
getChanContents  :: Chan a -> IO [a]
writeList2Chan   :: Chan a -> [a] -> IO ()
                      
data CVar a       -- one element channels
newCVar          :: IO (CVar a)
putCVar          :: CVar a -> a -> IO ()
getCVar          :: CVar a -> IO a
                      
data QSem        -- General/quantity semaphores
newQSem          :: Int  -> IO QSem
waitQSem         :: QSem -> IO ()
signalQSem       :: QSem -> IO ()
                      
data QSemN       -- General/quantity semaphores
newQSemN         :: Int   -> IO QSemN
waitQSemN        :: QSemN -> Int -> IO ()
signalQSemN      :: QSemN -> Int -> IO ()

type SampleVar a -- Sample variables 
newEmptySampleVar:: IO (SampleVar a)
newSampleVar     :: a -> IO (SampleVar a)
emptySampleVar   :: SampleVar a -> IO ()
readSampleVar    :: SampleVar a -> IO a
writeSampleVar   :: SampleVar a -> a -> IO ()

threadDelay      :: Int -> IO ()
threadWaitRead   :: Int -> IO ()
threadWaitWrite  :: Int -> IO ()

4.6 GHC-specific concurrency issues

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 $
  ...

Next Previous Contents