Go to the first, previous, next, last section, table of contents.

The `Concurrent' interface (recommended)

GHC provides a `Concurrent' module, a common interface to a collection of useful concurrency abstractions, including those mentioned in the "concurrent paper".

Just put `import Concurrent' into your modules, and away you go. NB: intended for use with the `-fhaskell-1.3' flag.

To create a "required thread":

forkIO :: IO a -> IO a

The `Concurrent' interface also provides access to "I-Vars" and "M-Vars", which are two flavours of synchronising variables.

`_IVars' are write-once variables. They start out empty, and any threads that attempt to read them will block until they are filled. Once they are written, any blocked threads are freed, and additional reads are permitted. Attempting to write a value to a full `_IVar' results in a runtime error. Interface:

type IVar a = _IVar a -- more convenient name

newIVar     :: IO (_IVar a)
readIVar    :: _IVar a -> IO a
writeIVar   :: _IVar a -> a -> IO ()

`_MVars' are rendezvous points, mostly for concurrent threads. They begin empty, 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:

type MVar a  = _MVar a -- more convenient name

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

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

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]

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 -- binary and n-ary:

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

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 ()

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

threadDelay :: Int -> IO () -- delay rescheduling for N microseconds
threadWait  :: Int -> IO () -- wait for input on specified file descriptor


Go to the first, previous, next, last section, table of contents.