This library provides the Concurrent Haskell extensions [concurrentHaskell:popl96].
We are grateful to the Glasgow Haskell Project for allowing us to redistribute their implementation of this module.
module Concurrent where
data ThreadId -- thread identifiers
instance Eq 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
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 ()
readChanContents :: 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:
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
has not been implemented yet on either system.
The plan is that killThread
will raise an IO 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.