This library provides the Concurrent Haskell extensions as described in Concurrent Haskell.
module Concurrent where
data ThreadId -- thread identifiers
instance Eq ThreadId
instance Ord ThreadId
forkIO :: IO () -> IO ThreadId
killThread :: ThreadId -> IO ()
data MVar a -- Synchronisation variables
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
instance Eq (MVar a)
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 ()
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 ()
Notes:
getchar
) that blocks waiting for input.
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:
s not been implemented yet on
Hugs
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 a
s and b
s.
In practice, cooperative multitasking is sufficient for writing
simple graphical user interfaces.
mergeIO
or nmergeIO
since these
require preemptive multitasking.
killThread
have an experimental
implementation in GHC, but are not yet implemented in Hugs.
Currently killThread
simply kills the nominated thread, but the
plan is that in the future killThread
will raise an exception in
the killed thread which it can catch --- perhaps allowing it to kill
its children before exiting.
Ord
instance for ThreadId
s provides an arbitrary total ordering
which might be used to build an ordered binary tree, say.
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.