[project @ 1999-08-31 08:49:00 by simonpj]
[ghc-hetmet.git] / ghc / docs / libraries / Concurrent.sgml
1 <sect> <idx/Concurrent/
2 <label id="sec:Concurrent">
3 <p>
4
5 <sect1> <idx/Concurrent Haskell/
6 <label id="sec:Concurrent Haskell">
7 <p>
8
9 GHC and Hugs both provide concurrency extensions, as described in
10 <url name="Concurrent Haskell"
11 url="http://research.microsoft.com/Users/simonpj/Papers/concurrent-haskell.ps.gz">.
12
13 Concurrency in GHC and Hugs is "lightweight", which means that both
14 thread creation and context switching overheads are extremely low.
15 Scheduling of Haskell threads is done internally in the Haskell
16 runtime system, and doesn't make use of any operating system-supplied
17 thread packages.
18
19 Haskell threads can communicate via <tt/MVar/s, a kind of synchronised
20 mutable variable.  Several common concurrency abstractions can be
21 built from <tt/MVar/s, and these are provided by the <tt/Concurrent/
22 library, which is described in the later sections.  Threads may also
23 communicate via exceptions.
24
25 <sect1>  <idx/Concurrency Basics/
26 <label id="sec:Concurrency Basics">
27 <p>
28
29 To gain access to the concurrency primitives, just  <tt/import Concurrent/
30 in your Haskell module.  In GHC, you also need to add the <tt/-syslib
31 concurrent/ option to the command line.
32
33 To create a new thread, use <tt/forkIO/:
34
35 <tscreen><verb>
36 forkIO :: IO () -> IO ThreadId
37 </verb></tscreen>
38
39 This sparks off a new thread to run the <tt/IO/ computation passed as the
40 first argument.  
41
42 The returned <tt/ThreadId/ is an abstract type representing a handle
43 to the newly created thread.  The <tt/ThreadId/ type is an instance of
44 both <tt/Eq/ and <tt/Ord/, where the <tt/Ord/ instance implements an
45 arbitrary total ordering over <tt/ThreadId/s.
46
47 Threads may also be killed via the <tt/ThreadId/:
48
49 <tscreen><verb>
50 killThread :: ThreadId -> IO ()
51 </verb></tscreen>
52
53 this terminates the given thread (Note: <tt/killThread/ is not
54 implemented in Hugs yet).  Any work already done by the thread isn't
55 lost: the computation is suspended until required by another thread.
56 The memory used by the thread will be garbage collected if it isn't
57 referenced from anywhere else.
58
59 More generally, an arbitrary exception (see Section <ref
60 id="sec:Exception" name="Exceptions">) may be raised in any thread for
61 which we have a <tt/ThreadId/, with <tt/raiseInThread/:
62
63 <tscreen><verb>
64 raiseInThread :: ThreadId -> Exception -> IO ()
65 </verb></tscreen>
66
67 Actually <tt/killThread/ just raises the <tt/ThreadKilled/ exception
68 in the target thread, the normal action of which is to just terminate
69 the thread.  The target thread will stop whatever it was doing (even
70 if it was blocked on an <tt/MVar/ or other computation) and handle the
71 exception.
72
73 The <tt/ThreadId/ for the current thread can be obtained with
74 <tt/myThreadId/:
75
76 <tscreen><verb>
77 myThreadId :: IO ThreadId
78 </verb></tscreen>
79
80 NOTE: if you have a <tt/ThreadId/, you essentially have a pointer to the
81 thread itself.  This means the thread itself can't be garbage
82 collected until you drop the <tt/ThreadId/.  This misfeature will
83 hopefully be corrected at a later date.
84
85 <sect1> Scheduling
86 <p>
87
88 GHC uses <em>preemptive multitasking</em>: context switches can occur
89 at any time.  At present, Hugs uses <em>cooperative multitasking</em>:
90 context switches only occur when you use one of the primitives defined
91 in this module.  This means that programs such as:
92
93 <tscreen><verb>
94 main = forkIO (write 'a') >> write 'b'
95  where write c = putChar c >> write c
96 </verb></tscreen>
97
98 will print either <tt/aaaaaaaaaaaaaa.../ or <tt/bbbbbbbbbbbb.../,
99 instead of some random interleaving of <tt/a/s and <tt/b/s.
100 In practice, cooperative multitasking is sufficient for writing simple
101 graphical user interfaces.
102
103 The <tt>yield</tt> action forces a context-switch to any other
104 currently runnable threads (if any), and is occasionally useful when
105 implementing concurrency abstractions:
106
107 <tscreen><verb>
108 yield :: IO ()
109 </verb></tscreen>
110
111 <sect2> <idx/Thread Waiting/
112 <p>
113
114 Finally, there are operations to delay a concurrent thread, and to
115 make one wait:<nidx>delay a concurrent thread</nidx>
116 <nidx>wait for a file descriptor</nidx>
117
118 <tscreen><verb>
119 threadDelay     :: Int -> IO () -- delay rescheduling for N microseconds
120 threadWaitRead  :: Int -> IO () -- wait for input on specified file descriptor
121 threadWaitWrite :: Int -> IO () -- (read and write, respectively).
122 </verb></tscreen>
123
124 The <tt/threadDelay/ operation will cause the current thread to
125 suspend for a given number of microseconds.  Note that the resolution
126 used by the Haskell runtime system's internal timer together with the
127 fact that the thread may take some time to be rescheduled after the
128 time has expired, means that the accuracy is more like 1/50 second.
129
130 <tt/threadWaitRead/ and <tt/threadWaitWrite/ can be used to block a
131 thread until I/O is available on a given file descriptor.  These
132 primitives are used by the I/O subsystem to ensure that a thread
133 waiting on I/O doesn't hang the entire system.
134
135 <sect2> <idx/Blocking/
136 <p>
137 Calling a foreign C procedure (such as <tt/getchar/) that blocks
138 waiting for input will block <em>all</em> threads, in both
139 GHC and Hugs.  The GHC I/O system uses non-blocking I/O internally to implement
140 thread-friendly I/O, so calling standard Haskell I/O functions blocks
141 only the thead making the call.
142
143
144 <sect1> <idx/Concurrency abstractions/
145 <label id="sec:Concurrency-abstractions">
146 <p>
147
148 <sect2> <idx/MVars/
149 <label id="sec:MVars">
150 <p>
151
152 The <tt/Concurrent/ interface provides access to ``M-Vars'', which are
153 <em>synchronising variables</em>.
154
155 <nidx>synchronising variables (Glasgow extension)</nidx>
156 <nidx>concurrency -- synchronising variables</nidx>
157
158 <tt/MVars/<nidx>MVars (Glasgow extension)</nidx> are rendezvous points,
159 mostly for concurrent threads.  They begin either empty or full, and
160 any attempt to read an empty <tt/MVar/ blocks.  When an <tt/MVar/ is
161 written, a single blocked thread may be freed.  Reading an <tt/MVar/
162 toggles its state from full back to empty.  Therefore, any value
163 written to an <tt/MVar/ may only be read once.  Multiple reads and writes
164 are allowed, but there must be at least one read between any two
165 writes. Interface:
166
167 <tscreen><verb>
168 data MVar a -- abstract
169 instance Eq (MVar a)
170
171 newEmptyMVar     :: IO (MVar a)
172 newMVar          :: a -> IO (MVar a)
173 takeMVar         :: MVar a -> IO a
174 putMVar          :: MVar a -> a -> IO ()
175 readMVar         :: MVar a -> IO a
176 swapMVar         :: MVar a -> a -> IO a
177 isEmptyMVar      :: MVar a -> IO Bool
178 </verb></tscreen>
179
180 The operation <tt/isEmptyMVar/ returns a flag indicating
181 whether the <tt/MVar/ is currently empty or filled in, i.e.,
182 will a thread block when performing a <tt/takeMVar/ on that
183 <tt/MVar/ or not?
184
185 Please notice that the Boolean value returned from <tt/isEmptyMVar/
186 represent just a snapshot of the state of the <tt/MVar/. By the
187 time a thread gets to inspect the result and act upon it, other
188 threads may have accessed the <tt/MVar/ and changed the 'filled-in'
189 status of the variable. 
190
191 The same proviso applies to <tt/isEmptyChan/ (next sub-section).
192
193 These two predicates are currently only supported by GHC.
194
195 <sect2> <idx/Channel Variables/
196 <label id="sec:CVars">
197 <p>
198
199 A <em>channel variable</em> (<tt/CVar/) is a one-element channel, as
200 described in the paper:
201
202 <tscreen><verb>
203 data CVar a
204 newCVar :: IO (CVar a)
205 putCVar :: CVar a -> a -> IO ()
206 getCVar :: CVar a -> IO a
207 </verb></tscreen>
208
209 <sect2> <idx/Channels/
210 <label id="sec:Channels">
211 <p>
212
213 A <tt/Channel/ is an unbounded channel:
214
215 <tscreen><verb>
216 data Chan a 
217 newChan         :: IO (Chan a)
218 putChan         :: Chan a -> a -> IO ()
219 getChan         :: Chan a -> IO a
220 dupChan         :: Chan a -> IO (Chan a)
221 unGetChan       :: Chan a -> a -> IO ()
222 getChanContents :: Chan a -> IO [a]
223 </verb></tscreen>
224
225 <sect2> <idx/Semaphores/
226 <label id="sec:Semaphores">
227 <p>
228
229 General and quantity semaphores:
230
231 <tscreen><verb>
232 data QSem
233 newQSem     :: Int   -> IO QSem
234 waitQSem    :: QSem  -> IO ()
235 signalQSem  :: QSem  -> IO ()
236
237 data QSemN
238 newQSemN    :: Int   -> IO QSemN
239 signalQSemN :: QSemN -> Int -> IO ()
240 waitQSemN   :: QSemN -> Int -> IO ()
241 </verb></tscreen>
242
243 <sect2> <idx/Merging Streams/
244 <label id="sec:Merging Streams">
245 <p>
246
247 Merging streams---binary and n-ary:
248
249 <tscreen><verb>
250 mergeIO  :: [a]   -> [a] -> IO [a]
251 nmergeIO :: [[a]] -> IO [a]
252 </verb></tscreen>
253
254 These actions fork one thread for each input list that concurrently
255 evaluates that list; the results are merged into a single output list.
256
257 Note: Hugs does not provide the functions <tt/mergeIO/ or
258 <tt/nmergeIO/ since these require preemptive multitasking.
259
260 <sect2> <idx/Sample Variables/
261 <label id="sec:Sample-Variables">
262 <p>
263
264 A <em>Sample variable</em> (<tt/SampleVar/) is slightly different from a
265 normal <tt/MVar/:
266
267 <itemize>
268 <item> Reading an empty <tt/SampleVar/ causes the reader to block
269     (same as <tt/takeMVar/ on empty <tt/MVar/).
270 <item> Reading a filled <tt/SampleVar/ empties it and returns value.
271     (same as <tt/takeMVar/)
272 <item> Writing to an empty <tt/SampleVar/ fills it with a value, and
273 potentially, wakes up a blocked reader  (same as for <tt/putMVar/ on empty <tt/MVar/).
274 <item> Writing to a filled <tt/SampleVar/ overwrites the current value.
275  (different from <tt/putMVar/ on full <tt/MVar/.)
276 </itemize>
277
278 <tscreen><verb>
279 type SampleVar a = MVar (Int, MVar a)
280
281 emptySampleVar :: SampleVar a -> IO ()
282 newSampleVar   :: IO (SampleVar a)
283 readSample     :: SampleVar a -> IO a
284 writeSample    :: SampleVar a -> a -> IO ()
285 </verb></tscreen>
286
287 <sect1> The <tt/Concurrent/ library interface
288 <p>
289
290 The full interface for the <tt/Concurrent/ library is given below for
291 reference:
292
293 <tscreen><verb>
294 module Concurrent where
295
296 data ThreadId    -- thread identifiers
297 instance Eq  ThreadId
298 instance Ord ThreadId
299
300 forkIO           :: IO () -> IO ThreadId
301 myThreadId       :: IO ThreadId
302 killThread       :: ThreadId -> IO ()
303 yield            :: IO ()
304
305 data MVar a      -- Synchronisation variables
306 instance Eq (MVar a)
307 newEmptyMVar     :: IO (MVar a)
308 newMVar          :: a -> IO (MVar a)
309 takeMVar         :: MVar a -> IO a
310 putMVar          :: MVar a -> a -> IO ()
311 swapMVar         :: MVar a -> a -> IO a
312 readMVar         :: MVar a -> IO a 
313 isEmptyMVar      :: MVar a -> IO Bool
314
315
316 data Chan a      -- channels
317 newChan          :: IO (Chan a)
318 writeChan        :: Chan a -> a -> IO ()
319 readChan         :: Chan a -> IO a
320 dupChan          :: Chan a -> IO (Chan a)
321 unReadChan       :: Chan a -> a -> IO ()
322 isEmptyChan      :: Chan a -> IO Bool
323 getChanContents  :: Chan a -> IO [a]
324 writeList2Chan   :: Chan a -> [a] -> IO ()
325                       
326 data CVar a       -- one element channels
327 newCVar          :: IO (CVar a)
328 putCVar          :: CVar a -> a -> IO ()
329 getCVar          :: CVar a -> IO a
330                       
331 data QSem        -- General/quantity semaphores
332 newQSem          :: Int  -> IO QSem
333 waitQSem         :: QSem -> IO ()
334 signalQSem       :: QSem -> IO ()
335                       
336 data QSemN       -- General/quantity semaphores
337 newQSemN         :: Int   -> IO QSemN
338 waitQSemN        :: QSemN -> Int -> IO ()
339 signalQSemN      :: QSemN -> Int -> IO ()
340
341 type SampleVar a -- Sample variables 
342 newEmptySampleVar:: IO (SampleVar a)
343 newSampleVar     :: a -> IO (SampleVar a)
344 emptySampleVar   :: SampleVar a -> IO ()
345 readSampleVar    :: SampleVar a -> IO a
346 writeSampleVar   :: SampleVar a -> a -> IO ()
347
348 threadDelay      :: Int -> IO ()
349 threadWaitRead   :: Int -> IO ()
350 threadWaitWrite  :: Int -> IO ()
351 </verb></tscreen>
352
353 <sect1> GHC-specific concurrency issues
354 <p>
355
356 In a standalone GHC program, only the main thread is required to
357 terminate in order for the process to terminate.  Thus all other
358 forked threads will simply terminate at the same time as the main
359 thread (the terminology for this kind of behaviour is ``daemonic
360 threads'').
361
362 If you want the program to wait for child threads to finish before
363 exiting, you need to program this yourself.  A simple mechanism is to
364 have each child thread write to an <tt/MVar/ when it completes, and
365 have the main thread wait on all the <tt/MVar/s before exiting:
366
367 <tscreen><verb>
368 myForkIO :: IO () -> IO (MVar ())
369 myForkIO io = do
370   mvar <- newEmptyMVar
371   forkIO (io `finally` putMVar mvar ())
372   return mvar
373 </verb></tscreen>
374
375 Note that we use <tt/finally/ from the <tt/Exception/ module to make
376 sure that the <tt/MVar/ is written to even if the thread dies or is
377 killed for some reason.
378
379 A better method is to keep a global list of all child threads which we
380 should wait for at the end of the program:
381
382 <tscreen><verb>
383 children :: MVar [MVar ()]
384 children = unsafePerformIO (newMVar [])
385
386 waitForChildren :: IO ()
387 waitForChildren = do
388   (mvar:mvars) <- takeMVar children
389   putMVar children mvars
390   takeMVar mvar
391   waitForChildren
392
393 forkChild :: IO () -> IO ()
394 forkChild io = do
395    mvar <- newEmptyMVar
396    forkIO (p `finally` putMVar mvar ())
397    childs <- takeMVar children
398    putMVar children (mvar:childs)
399
400 later = flip finally
401
402 main =
403   later waitForChildren $
404   ...
405 </verb></tscreen>