2.4. Concurrency abstractions

2.4.1. Chan: Channels

A Channel is an unbounded channel:

data Chan a 
newChan         :: IO (Chan a)
writeChan       :: Chan a -> a -> IO ()
readChan        :: Chan a -> IO a
dupChan         :: Chan a -> IO (Chan a)
unGetChan       :: Chan a -> a -> IO ()
getChanContents :: Chan a -> IO [a]
writeList2Chan	:: Chan a -> [a] -> IO ()

2.4.2. CVar: Channel variables

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

data CVar a
newCVar   :: IO (CVar a)
writeCVar :: CVar a -> a -> IO ()
readCVar  :: CVar a -> IO a

2.4.3. MVar: Synchronising variables

The MVar interface provides access to “MVars” (pronounced “em-vars”), which are synchronising variables. An MVar is simply a box, which may be empty or full. The basic operations available over MVars are given below:

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
tryTakeMVar      :: MVar a -> IO (Maybe a)
tryPutMVar       :: MVar a -> a -> IO Bool
isEmptyMVar      :: MVar a -> IO Bool

newEmptyMVar, newMVar

New empty MVars can be created with newEmptyMVar. To create an MVar with an initial value, use newMVar.

takeMVar

The takeMVar operation returns the contents of the MVar if it was full, or waits until it becomes full otherwise.

putMVar

The putMVar operation puts a value into an empty MVar. Calling putMVar on an already full MVar will cause the calling thread to block until the MVar becomes empty again (NOTE: this is a change from the previous behaviour, where putMVar on a full MVar would raise an exception).

tryTakeMVar

The tryTakeMVar function is a non-blocking version of takeMVar. If the MVar is full, then it returns Just a (where a is the contents of the MVar) and empties the MVar. If the MVar is empty, it immediately returns Nothing.

tryPutMVar

The tryPutMVar function is a non-blocking version of putMVar. If the MVar is empty, then it behaves as putMVar, and returns True. If the MVar is full, instead of blocking it returns False immediately.

isEmptyMVar

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

readMVar

This is a combination of takeMVar and putMVar; ie. it takes the value from the MVar, puts it back, and also returns it.

swapMVar

swapMVar swaps the contents of an MVar for a new value.

2.4.4. QSem: General semaphores

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

2.4.5. QSemN: Quantity semaphores

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

2.4.6. SampleVar: 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 ()

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