087baf68d68e2a61c85743a30676048c21ff5168
[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" 
7          url="http://research.microsoft.com/Users/simonpj/Papers/concurrent-haskell.ps.gz">.
8
9 <tscreen><verb>
10 module Concurrent where
11
12 data ThreadId    -- thread identifiers
13 instance Eq  ThreadId
14 instance Ord ThreadId
15
16 forkIO           :: IO () -> IO ThreadId
17 myThreadId       :: IO ThreadId
18 killThread       :: ThreadId -> IO ()
19 yield            :: IO ()
20
21 data MVar a      -- Synchronisation variables
22 newEmptyMVar     :: IO (MVar a)
23 newMVar          :: a -> IO (MVar a)
24 takeMVar         :: MVar a -> IO a
25 putMVar          :: MVar a -> a -> IO ()
26 swapMVar         :: MVar a -> a -> IO a
27 readMVar         :: MVar a -> IO a 
28 isEmptyMVar      :: MVar a -> IO Bool
29 instance Eq (MVar a)
30
31
32 data Chan a      -- channels
33 newChan          :: IO (Chan a)
34 writeChan        :: Chan a -> a -> IO ()
35 readChan         :: Chan a -> IO a
36 dupChan          :: Chan a -> IO (Chan a)
37 unReadChan       :: Chan a -> a -> IO ()
38 isEmptyChan      :: Chan a -> IO Bool
39 getChanContents  :: Chan a -> IO [a]
40 writeList2Chan   :: Chan a -> [a] -> IO ()
41                       
42 data CVar a       -- one element channels
43 newCVar          :: IO (CVar a)
44 putCVar          :: CVar a -> a -> IO ()
45 getCVar          :: CVar a -> IO a
46                       
47 data QSem        -- General/quantity semaphores
48 newQSem          :: Int  -> IO QSem
49 waitQSem         :: QSem -> IO ()
50 signalQSem       :: QSem -> IO ()
51                       
52 data QSemN       -- General/quantity semaphores
53 newQSemN         :: Int   -> IO QSemN
54 waitQSemN        :: QSemN -> Int -> IO ()
55 signalQSemN      :: QSemN -> Int -> IO ()
56
57 type SampleVar a -- Sample variables 
58 newEmptySampleVar:: IO (SampleVar a)
59 newSampleVar     :: a -> IO (SampleVar a)
60 emptySampleVar   :: SampleVar a -> IO ()
61 readSampleVar    :: SampleVar a -> IO a
62 writeSampleVar   :: SampleVar a -> a -> IO ()
63 </verb></tscreen>
64
65 Notes:
66 <itemize>
67
68 <item> 
69   GHC uses preemptive multitasking:
70   Context switches can occur at any time, except if you call a C
71   function (like <tt/getchar/) that blocks waiting for input.
72
73   Hugs uses cooperative multitasking:
74   Context switches only occur when you use one of the primitives
75   defined in this module.  This means that programs such as:
76
77 <tscreen><verb>
78 main = forkIO (write 'a') >> write 'b'
79  where write c = putChar c >> write c
80 </verb></tscreen>
81
82   will print either <tt/aaaaaaaaaaaaaa.../ or <tt/bbbbbbbbbbbb.../,
83   instead of some random interleaving of <tt/a/s and <tt/b/s.
84
85   In practice, cooperative multitasking is sufficient for writing 
86   simple graphical user interfaces.
87
88 <item>
89 The <tt>yield</tt> action forces a context-switch to any other
90 currently runnable threads (if any), and is occasionally useful when
91 implementing concurrency abstractions (especially so if the
92 implementation of Concurrent Haskell uses cooperative multitasking).
93
94 <item>
95 Hugs does not provide the functions <tt/mergeIO/ or <tt/nmergeIO/ since these
96 require preemptive multitasking.
97
98 <item>
99 Thread identities and <tt/killThread/ have an experimental
100 implementation in GHC, but are not yet implemented in Hugs. 
101
102 Currently <tt/killThread/ simply kills the nominated thread, but the
103 plan is that in the future <tt/killThread/ will raise an exception in
104 the killed thread which it can catch --- perhaps allowing it to kill
105 its children before exiting.
106
107 The action <tt/myThreadId/ returns the <tt/ThreadId/ of the thread
108 which performs it.
109
110 <item>
111 The <tt/Ord/ instance for <tt/ThreadId/s provides an arbitrary total ordering
112 which might be used to build an ordered binary tree, say.  
113
114 <item>
115 The operation <tt/isEmptyMVar/ returns a flag indicating
116 whether the <tt/MVar/ is currently empty or filled in, i.e.,
117 will a thread block when performing a <tt/takeMVar/ on that
118 <tt/MVar/ or not?
119
120 Please notice that the Boolean value returned from <tt/isEmptyMVar/
121 represent just a snapshot of the state of the <tt/MVar/. By the
122 time a thread gets to inspect the result and act upon it, other
123 threads may have accessed the <tt/MVar/ and changed the 'filled-in'
124 status of the variable. 
125
126 The same proviso applies to <tt/isEmptyChan/.
127
128 These two predicates are currently only supported by GHC.
129
130 </itemize>