[project @ 1998-12-02 13:17:09 by simonm]
[ghc-hetmet.git] / ghc / docs / libraries / Concurrent.sgml
1 <sect> <idx/Concurrent/
2 <label id="sec:Concurrent">
3 <p>
4
5 This library provides the Concurrent Haskell extensions as described
6 in  <url name="Concurrent Haskell" url="http://research.microsoft.com/Users/simonpj/Papers/concurrent-haskell.ps.gz">.
7
8 <tscreen><verb>
9 module Concurrent where
10
11 data ThreadId    -- thread identifiers
12 instance Eq  ThreadId
13 instance Ord ThreadId
14
15 forkIO           :: IO () -> IO ThreadId
16 killThread       :: ThreadId -> IO ()
17
18 data MVar a      -- Synchronisation variables
19 newEmptyMVar     :: IO (MVar a)
20 newMVar          :: a -> IO (MVar a)
21 takeMVar         :: MVar a -> IO a
22 putMVar          :: MVar a -> a -> IO ()
23 swapMVar         :: MVar a -> a -> IO a
24 readMVar         :: MVar a -> IO a 
25 instance Eq (MVar a)
26
27 data Chan a      -- channels
28 newChan          :: IO (Chan a)
29 writeChan        :: Chan a -> a -> IO ()
30 readChan         :: Chan a -> IO a
31 dupChan          :: Chan a -> IO (Chan a)
32 unReadChan       :: Chan a -> a -> IO ()
33 getChanContents  :: Chan a -> IO [a]
34 writeList2Chan   :: Chan a -> [a] -> IO ()
35                       
36 data CVar a       -- one element channels
37 newCVar          :: IO (CVar a)
38 putCVar          :: CVar a -> a -> IO ()
39 getCVar          :: CVar a -> IO a
40                       
41 data QSem        -- General/quantity semaphores
42 newQSem          :: Int  -> IO QSem
43 waitQSem         :: QSem -> IO ()
44 signalQSem       :: QSem -> IO ()
45                       
46 data QSemN       -- General/quantity semaphores
47 newQSemN         :: Int   -> IO QSemN
48 waitQSemN        :: QSemN -> Int -> IO ()
49 signalQSemN      :: QSemN -> Int -> IO ()
50
51 type SampleVar a -- Sample variables 
52 newEmptySampleVar:: IO (SampleVar a)
53 newSampleVar     :: a -> IO (SampleVar a)
54 emptySampleVar   :: SampleVar a -> IO ()
55 readSampleVar    :: SampleVar a -> IO a
56 writeSampleVar   :: SampleVar a -> a -> IO ()
57 </verb></tscreen>
58
59 Notes:
60 <itemize>
61
62 <item> 
63   GHC uses preemptive multitasking:
64   Context switches can occur at any time, except if you call a C
65   function (like <tt/getchar/) that blocks waiting for input.
66
67   Hugs uses cooperative multitasking:
68   Context switches only occur when you use one of the primitives
69   defined in this module.  This means that programs such as:
70 s not been implemented yet on
71 Hugs
72 <tscreen><verb>
73 main = forkIO (write 'a') >> write 'b'
74  where write c = putChar c >> write c
75 </verb></tscreen>
76
77   will print either <tt/aaaaaaaaaaaaaa.../ or <tt/bbbbbbbbbbbb.../,
78   instead of some random interleaving of <tt/a/s and <tt/b/s.
79
80   In practice, cooperative multitasking is sufficient for writing 
81   simple graphical user interfaces.
82
83 <item>
84 Hugs does not provide the functions <tt/mergeIO/ or <tt/nmergeIO/ since these
85 require preemptive multitasking.
86
87 <item>
88 Thread identities and <tt/killThread/ have an experimental
89 implementation in GHC, but are not yet implemented in Hugs. 
90
91 Currently <tt/killThread/ simply kills the nominated thread, but the
92 plan is that in the future <tt/killThread/ will raise an exception in
93 the killed thread which it can catch --- perhaps allowing it to kill
94 its children before exiting.
95
96 <item>
97 The <tt/Ord/ instance for <tt/ThreadId/s provides an arbitrary total ordering
98 which might be used to build an ordered binary tree, say.  
99
100 </itemize>