[project @ 1999-08-26 15:59:06 by simonmar]
[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 The <tt>yield</tt> action forces a context-switch to any other
86 currently runnable threads (if any), and is occasionally useful when
87 implementing concurrency abstractions:
88
89 <tscreen><verb>
90 yield :: IO ()
91 </verb></tscreen>
92
93 <sect1> <idx/Concurrency abstractions/
94 <label id="sec:Concurrency-abstractions">
95 <p>
96
97 <sect2> <idx/MVars/
98 <label id="sec:MVars">
99 <p>
100
101 The <tt/Concurrent/ interface provides access to ``M-Vars'', which are
102 <em>synchronising variables</em>.
103
104 <nidx>synchronising variables (Glasgow extension)</nidx>
105 <nidx>concurrency -- synchronising variables</nidx>
106
107 <tt/MVars/<nidx>MVars (Glasgow extension)</nidx> are rendezvous points,
108 mostly for concurrent threads.  They begin either empty or full, and
109 any attempt to read an empty <tt/MVar/ blocks.  When an <tt/MVar/ is
110 written, a single blocked thread may be freed.  Reading an <tt/MVar/
111 toggles its state from full back to empty.  Therefore, any value
112 written to an <tt/MVar/ may only be read once.  Multiple reads and writes
113 are allowed, but there must be at least one read between any two
114 writes. Interface:
115
116 <tscreen><verb>
117 data MVar a -- abstract
118 instance Eq (MVar a)
119
120 newEmptyMVar     :: IO (MVar a)
121 newMVar          :: a -> IO (MVar a)
122 takeMVar         :: MVar a -> IO a
123 putMVar          :: MVar a -> a -> IO ()
124 readMVar         :: MVar a -> IO a
125 swapMVar         :: MVar a -> a -> IO a
126 isEmptyMVar      :: MVar a -> IO Bool
127 </verb></tscreen>
128
129 The operation <tt/isEmptyMVar/ returns a flag indicating
130 whether the <tt/MVar/ is currently empty or filled in, i.e.,
131 will a thread block when performing a <tt/takeMVar/ on that
132 <tt/MVar/ or not?
133
134 Please notice that the Boolean value returned from <tt/isEmptyMVar/
135 represent just a snapshot of the state of the <tt/MVar/. By the
136 time a thread gets to inspect the result and act upon it, other
137 threads may have accessed the <tt/MVar/ and changed the 'filled-in'
138 status of the variable. 
139
140 The same proviso applies to <tt/isEmptyChan/.
141
142 These two predicates are currently only supported by GHC.
143
144 <sect2> <idx/Channel Variables/
145 <label id="sec:CVars">
146 <p>
147
148 A <em>channel variable</em> (<tt/CVar/) is a one-element channel, as
149 described in the paper:
150
151 <tscreen><verb>
152 data CVar a
153 newCVar :: IO (CVar a)
154 putCVar :: CVar a -> a -> IO ()
155 getCVar :: CVar a -> IO a
156 </verb></tscreen>
157
158 <sect2> <idx/Channels/
159 <label id="sec:Channels">
160 <p>
161
162 A <tt/Channel/ is an unbounded channel:
163
164 <tscreen><verb>
165 data Chan a 
166 newChan         :: IO (Chan a)
167 putChan         :: Chan a -> a -> IO ()
168 getChan         :: Chan a -> IO a
169 dupChan         :: Chan a -> IO (Chan a)
170 unGetChan       :: Chan a -> a -> IO ()
171 getChanContents :: Chan a -> IO [a]
172 </verb></tscreen>
173
174 <sect2> <idx/Semaphores/
175 <label id="sec:Semaphores">
176 <p>
177
178 General and quantity semaphores:
179
180 <tscreen><verb>
181 data QSem
182 newQSem     :: Int   -> IO QSem
183 waitQSem    :: QSem  -> IO ()
184 signalQSem  :: QSem  -> IO ()
185
186 data QSemN
187 newQSemN    :: Int   -> IO QSemN
188 signalQSemN :: QSemN -> Int -> IO ()
189 waitQSemN   :: QSemN -> Int -> IO ()
190 </verb></tscreen>
191
192 <sect2> <idx/Merging Streams/
193 <label id="sec:Merging Streams">
194 <p>
195
196 Merging streams---binary and n-ary:
197
198 <tscreen><verb>
199 mergeIO  :: [a]   -> [a] -> IO [a]
200 nmergeIO :: [[a]] -> IO [a]
201 </verb></tscreen>
202
203 Note: Hugs does not provide the functions <tt/mergeIO/ or
204 <tt/nmergeIO/ since these require preemptive multitasking.
205
206 <sect2> <idx/Sample Variables/
207 <label id="sec:Sample-Variables">
208 <p>
209
210 A <em>Sample variable</em> (<tt/SampleVar/) is slightly different from a
211 normal <tt/MVar/:
212
213 <itemize>
214 <item> Reading an empty <tt/SampleVar/ causes the reader to block
215     (same as <tt/takeMVar/ on empty <tt/MVar/).
216 <item> Reading a filled <tt/SampleVar/ empties it and returns value.
217     (same as <tt/takeMVar/)
218 <item> Writing to an empty <tt/SampleVar/ fills it with a value, and
219 potentially, wakes up a blocked reader  (same as for <tt/putMVar/ on empty <tt/MVar/).
220 <item> Writing to a filled <tt/SampleVar/ overwrites the current value.
221  (different from <tt/putMVar/ on full <tt/MVar/.)
222 </itemize>
223
224 <tscreen><verb>
225 type SampleVar a = MVar (Int, MVar a)
226
227 emptySampleVar :: SampleVar a -> IO ()
228 newSampleVar   :: IO (SampleVar a)
229 readSample     :: SampleVar a -> IO a
230 writeSample    :: SampleVar a -> a -> IO ()
231 </verb></tscreen>
232
233 <sect2> <idx/Thread Waiting/
234 <label id="sec:Channels">
235 <p>
236
237 Finally, there are operations to delay a concurrent thread, and to
238 make one wait:<nidx>delay a concurrent thread</nidx>
239 <nidx>wait for a file descriptor</nidx>
240
241 <tscreen><verb>
242 threadDelay     :: Int -> IO () -- delay rescheduling for N microseconds
243 threadWaitRead  :: Int -> IO () -- wait for input on specified file descriptor
244 threadWaitWrite :: Int -> IO () -- (read and write, respectively).
245 </verb></tscreen>
246
247 The <tt/threadDelay/ operation will cause the current thread to
248 suspend for a given number of microseconds.  Note that the resolution
249 used by the Haskell runtime system's internal timer together with the
250 fact that the thread may take some time to be rescheduled after the
251 time has expired, means that the accuracy is more like 1/50 second.
252
253 <tt/threadWaitRead/ and <tt/threadWaitWrite/ can be used to block a
254 thread until I/O is available on a given file descriptor.  These
255 primitives are used by the I/O subsystem to ensure that a thread
256 waiting on I/O doesn't hang the entire system.
257
258 <sect2> The <tt/Concurrent/ library interface
259 <p>
260
261 The full interface for the <tt/Concurrent/ library is given below for
262 reference:
263
264 <tscreen><verb>
265 module Concurrent where
266
267 data ThreadId    -- thread identifiers
268 instance Eq  ThreadId
269 instance Ord ThreadId
270
271 forkIO           :: IO () -> IO ThreadId
272 myThreadId       :: IO ThreadId
273 killThread       :: ThreadId -> IO ()
274 yield            :: IO ()
275
276 data MVar a      -- Synchronisation variables
277 instance Eq (MVar a)
278 newEmptyMVar     :: IO (MVar a)
279 newMVar          :: a -> IO (MVar a)
280 takeMVar         :: MVar a -> IO a
281 putMVar          :: MVar a -> a -> IO ()
282 swapMVar         :: MVar a -> a -> IO a
283 readMVar         :: MVar a -> IO a 
284 isEmptyMVar      :: MVar a -> IO Bool
285
286
287 data Chan a      -- channels
288 newChan          :: IO (Chan a)
289 writeChan        :: Chan a -> a -> IO ()
290 readChan         :: Chan a -> IO a
291 dupChan          :: Chan a -> IO (Chan a)
292 unReadChan       :: Chan a -> a -> IO ()
293 isEmptyChan      :: Chan a -> IO Bool
294 getChanContents  :: Chan a -> IO [a]
295 writeList2Chan   :: Chan a -> [a] -> IO ()
296                       
297 data CVar a       -- one element channels
298 newCVar          :: IO (CVar a)
299 putCVar          :: CVar a -> a -> IO ()
300 getCVar          :: CVar a -> IO a
301                       
302 data QSem        -- General/quantity semaphores
303 newQSem          :: Int  -> IO QSem
304 waitQSem         :: QSem -> IO ()
305 signalQSem       :: QSem -> IO ()
306                       
307 data QSemN       -- General/quantity semaphores
308 newQSemN         :: Int   -> IO QSemN
309 waitQSemN        :: QSemN -> Int -> IO ()
310 signalQSemN      :: QSemN -> Int -> IO ()
311
312 type SampleVar a -- Sample variables 
313 newEmptySampleVar:: IO (SampleVar a)
314 newSampleVar     :: a -> IO (SampleVar a)
315 emptySampleVar   :: SampleVar a -> IO ()
316 readSampleVar    :: SampleVar a -> IO a
317 writeSampleVar   :: SampleVar a -> a -> IO ()
318
319 threadDelay      :: Int -> IO ()
320 threadWaitRead   :: Int -> IO ()
321 threadWaitWrite  :: Int -> IO ()
322 </verb></tscreen>
323
324 <sect1> Pre-emptive vs. Cooperative multitasking
325 <p>
326
327 GHC uses preemptive multitasking: Context switches can occur at any
328 time, except if you call a C function (like <tt/getchar/) that blocks
329 waiting for input.  Haskell I/O is unaffected by blocking operations
330 (the GHC I/O system uses non-blocking I/O internally to implement
331 thread-friendly I/O).
332
333 Hugs uses cooperative multitasking: Context switches only occur when
334 you use one of the primitives defined in this module.  This means that
335 programs such as:
336
337 <tscreen><verb>
338 main = forkIO (write 'a') >> write 'b'
339  where write c = putChar c >> write c
340 </verb></tscreen>
341
342 will print either <tt/aaaaaaaaaaaaaa.../ or <tt/bbbbbbbbbbbb.../,
343 instead of some random interleaving of <tt/a/s and <tt/b/s.
344
345 In practice, cooperative multitasking is sufficient for writing simple
346 graphical user interfaces.
347
348 <sect1> GHC-specific concurrency issues
349 <p>
350
351 In a standalone GHC program, only the main thread is required to
352 terminate in order for the process to terminate.  Thus all other
353 forked threads will simply terminate at the same time as the main
354 thread (the terminology for this kind of behaviour is ``daemonic
355 threads'').
356
357 If you want the program to wait for child threads to finish before
358 exiting, you need to program this yourself.  A simple mechanism is to
359 have each child thread write to an <tt/MVar/ when it completes, and
360 have the main thread wait on all the <tt/MVar/s before exiting:
361
362 <tscreen><verb>
363 myForkIO :: IO () -> IO (MVar ())
364 myForkIO io = do
365   mvar <- newEmptyMVar
366   forkIO (io `finally` putMVar mvar ())
367   return mvar
368 </verb></tscreen>
369
370 Note that we use <tt/finally/ from the <tt/Exception/ module to make
371 sure that the <tt/MVar/ is written to even if the thread dies or is
372 killed for some reason.
373
374 A better method is to keep a global list of all child threads which we
375 should wait for at the end of the program:
376
377 <tscreen><verb>
378 children :: MVar [MVar ()]
379 children = unsafePerformIO (newMVar [])
380
381 waitForChildren :: IO ()
382 waitForChildren = do
383   (mvar:mvars) <- takeMVar children
384   putMVar children mvars
385   takeMVar mvar
386   waitForChildren
387
388 forkChild :: IO () -> IO ()
389 forkChild io = do
390    mvar <- newEmptyMVar
391    forkIO (p `finally` putMVar mvar ())
392    childs <- takeMVar children
393    putMVar children (mvar:childs)
394
395 later = flip finally
396
397 main =
398   later waitForChildren $
399   ...
400 </verb></tscreen>