[project @ 1999-07-14 11:33:10 by simonmar]
[ghc-hetmet.git] / ghc / docs / users_guide / parallel.vsgml
1 % both concurrent and parallel
2 %************************************************************************
3 %*                                                                      *
4 <sect1>Concurrent and Parallel Haskell
5 <label id="concurrent-and-parallel">
6 <p>
7 <nidx>Concurrent Haskell</nidx>
8 <nidx>Parallel Haskell</nidx>
9 %*                                                                      *
10 %************************************************************************
11
12 Concurrent and Parallel Haskell are Glasgow extensions to Haskell
13 which let you structure your program as a group of independent
14 `threads'.
15
16 Concurrent and Parallel Haskell have very different purposes.
17
18 Concurrent Haskell is for applications which have an inherent
19 structure of interacting, concurrent tasks (i.e. `threads').  Threads
20 in such programs may be <em>required</em>.  For example, if a concurrent
21 thread has been spawned to handle a mouse click, it isn't
22 optional---the user wants something done!
23
24 A Concurrent Haskell program implies multiple `threads' running within
25 a single Unix process on a single processor.
26
27 You will find at least one paper about Concurrent Haskell hanging off
28 of <url name="Simon Peyton Jones's Web page"
29 url="http://www.dcs.gla.ac.uk/~simonpj/">.
30
31 Parallel Haskell is about <em>speed</em>---spawning threads onto multiple
32 processors so that your program will run faster.  The `threads'
33 are always <em>advisory</em>---if the runtime system thinks it can
34 get the job done more quickly by sequential execution, then fine.
35
36 A Parallel Haskell program implies multiple processes running on
37 multiple processors, under a PVM (Parallel Virtual Machine) framework.
38
39 Parallel Haskell is still relatively new; it is more about ``research
40 fun'' than about ``speed.'' That will change.
41
42 Again, check Simon's Web page for publications about Parallel Haskell
43 (including ``GUM'', the key bits of the runtime system).
44
45 Some details about Concurrent and Parallel Haskell follow.
46
47 %************************************************************************
48 %*                                                                      *
49 <sect2>Language features specific to Concurrent Haskell
50 <label id="concurrent-haskell">
51 <p>
52 <nidx>Concurrent Haskell---features</nidx>
53 %*                                                                      *
54 %************************************************************************
55
56 %************************************************************************
57 %*                                                                      *
58 <sect3>The @Concurrent@ interface (recommended)
59 <label id="concurrent-interface">
60 <p>
61 <nidx>Concurrent interface</nidx>
62 %*                                                                      *
63 %************************************************************************
64
65 GHC provides a @Concurrent@ module, a common interface to a
66 collection of useful concurrency abstractions, including those
67 mentioned in the ``concurrent paper''.
68
69 Just add the flag @-syslib concurrent@ to your GHC command line and
70 put @import Concurrent@ into your modules, and away you go.  To create
71 a ``required thread'':
72
73 <tscreen><verb>
74 forkIO :: IO () -> IO ThreadId
75 </verb></tscreen>
76
77 where @ThreadId@ is an abstract type representing a handle to the
78 newly created thread.  Threads may also be killed:
79
80 <tscreen><verb>
81 killThread :: ThreadId -> IO ()
82 </verb></tscreen>
83
84 this terminates the given thread.  Any work already done by the thread
85 isn't lost: the computation is suspended until required by another
86 thread.  The memory used by the thread will be garbage collected if it
87 isn't referenced from anywhere else.
88
89 More generally, an arbitrary exception may be raised in any thread for
90 which we have a <tt/ThreadId/, with <tt/raiseInThread/:
91
92 <tscreen><verb>
93 raiseInThread :: ThreadId -> Exception -> IO ()
94 </verb></tscreen>
95
96 Actually <tt/killThread/ just raises the <tt/ThreadKilled/ exception
97 in the target thread, the normal action of which is to just terminate
98 the thread.  The target thread will stop whatever it was doing (even
99 if it was blocked on an <tt/MVar/ or other computation) and handle the
100 exception.
101
102 The <tt/ThreadId/ for the current thread can be obtained with
103 <tt/myThreadId/:
104
105 <tscreen><verb>
106 myThreadId :: IO ThreadId
107 </verb></tscreen>
108
109 NOTE: if you have a @ThreadId@, you essentially have a pointer to the
110 thread itself.  This means the thread itself can't be garbage
111 collected until you drop the @ThreadId@.  This misfeature will
112 hopefully be corrected at a later date.
113
114 The @Concurrent@ interface also provides access to ``M-Vars'', which
115 are <em>synchronising variables</em>.  
116
117 <nidx>synchronising variables (Glasgow extension)</nidx>
118 <nidx>concurrency -- synchronising variables</nidx>
119
120 @MVars@<nidx>MVars (Glasgow extension)</nidx> are rendezvous points,
121 mostly for concurrent threads.  They begin either empty or full, and
122 any attempt to read an empty @MVar@ blocks.  When an @MVar@ is
123 written, a single blocked thread may be freed.  Reading an @MVar@
124 toggles its state from full back to empty.  Therefore, any value
125 written to an @MVar@ may only be read once.  Multiple reads and writes
126 are allowed, but there must be at least one read between any two
127 writes. Interface:
128
129 <tscreen><verb>
130 newEmptyMVar :: IO (MVar a)
131 newMVar      :: a -> IO (MVar a)
132 takeMVar     :: MVar a -> IO a
133 putMVar      :: MVar a -> a -> IO ()
134 readMVar     :: MVar a -> IO a
135 swapMVar     :: MVar a -> a -> IO a
136 </verb></tscreen>
137
138 A <em>channel variable</em> (@CVar@) is a one-element channel, as
139 described in the paper:
140
141 <tscreen><verb>
142 data CVar a
143 newCVar :: IO (CVar a)
144 putCVar :: CVar a -> a -> IO ()
145 getCVar :: CVar a -> IO a
146 </verb></tscreen>
147
148 A @Channel@ is an unbounded channel:
149
150 <tscreen><verb>
151 data Chan a 
152 newChan         :: IO (Chan a)
153 putChan         :: Chan a -> a -> IO ()
154 getChan         :: Chan a -> IO a
155 dupChan         :: Chan a -> IO (Chan a)
156 unGetChan       :: Chan a -> a -> IO ()
157 getChanContents :: Chan a -> IO [a]
158 </verb></tscreen>
159
160 General and quantity semaphores:
161
162 <tscreen><verb>
163 data QSem
164 newQSem     :: Int   -> IO QSem
165 waitQSem    :: QSem  -> IO ()
166 signalQSem  :: QSem  -> IO ()
167
168 data QSemN
169 newQSemN    :: Int   -> IO QSemN
170 signalQSemN :: QSemN -> Int -> IO ()
171 waitQSemN   :: QSemN -> Int -> IO ()
172 </verb></tscreen>
173
174 Merging streams---binary and n-ary:
175
176 <tscreen><verb>
177 mergeIO  :: [a]   -> [a] -> IO [a]
178 nmergeIO :: [[a]] -> IO [a]
179 </verb></tscreen>
180
181 A <em>Sample variable</em> (@SampleVar@) is slightly different from a
182 normal @MVar@:
183
184 <itemize>
185 <item> Reading an empty @SampleVar@ causes the reader to block
186     (same as @takeMVar@ on empty @MVar@).
187 <item> Reading a filled @SampleVar@ empties it and returns value.
188     (same as @takeMVar@)
189 <item> Writing to an empty @SampleVar@ fills it with a value, and
190 potentially, wakes up a blocked reader  (same as for @putMVar@ on empty @MVar@).
191 <item> Writing to a filled @SampleVar@ overwrites the current value.
192  (different from @putMVar@ on full @MVar@.)
193 </itemize>
194
195 <tscreen><verb>
196 type SampleVar a = MVar (Int, MVar a)
197
198 emptySampleVar :: SampleVar a -> IO ()
199 newSampleVar   :: IO (SampleVar a)
200 readSample     :: SampleVar a -> IO a
201 writeSample    :: SampleVar a -> a -> IO ()
202 </verb></tscreen>
203
204 Finally, there are operations to delay a concurrent thread, and to
205 make one wait:<nidx>delay a concurrent thread</nidx>
206 <nidx>wait for a file descriptor</nidx>
207 <tscreen><verb>
208 threadDelay     :: Int -> IO () -- delay rescheduling for N microseconds
209 threadWaitRead  :: Int -> IO () -- wait for input on specified file descriptor
210 threadWaitWrite :: Int -> IO () -- (read and write, respectively).
211 </verb></tscreen>
212
213 %************************************************************************
214 %*                                                                      *
215 <sect2>Features specific to Parallel Haskell
216 <nidx>Parallel Haskell---features</nidx>
217 <p>
218 %*                                                                      *
219 %************************************************************************
220
221 %************************************************************************
222 %*                                                                      *
223 <sect3>The @Parallel@ interface (recommended)
224 <nidx>Parallel interface</nidx>
225 <p>
226 %*                                                                      *
227 %************************************************************************
228
229 GHC provides two functions for controlling parallel execution, through
230 the @Parallel@ interface:
231
232 <tscreen><verb>
233 interface Parallel where
234 infixr 0 `par`
235 infixr 1 `seq`
236
237 par :: a -> b -> b
238 seq :: a -> b -> b
239 </verb></tscreen>
240
241 The expression @(x `par` y)@ <em>sparks</em> the evaluation of @x@
242 (to weak head normal form) and returns @y@.  Sparks are queued for
243 execution in FIFO order, but are not executed immediately.  At the
244 next heap allocation, the currently executing thread will yield
245 control to the scheduler, and the scheduler will start a new thread
246 (until reaching the active thread limit) for each spark which has not
247 already been evaluated to WHNF.
248
249 The expression @(x `seq` y)@ evaluates @x@ to weak head normal
250 form and then returns @y@.  The @seq@ primitive can be used to
251 force evaluation of an expression beyond WHNF, or to impose a desired
252 execution sequence for the evaluation of an expression.
253
254 For example, consider the following parallel version of our old
255 nemesis, @nfib@:
256
257 <tscreen><verb>
258 import Parallel
259
260 nfib :: Int -> Int
261 nfib n | n <= 1 = 1
262        | otherwise = par n1 (seq n2 (n1 + n2 + 1))
263                      where n1 = nfib (n-1) 
264                            n2 = nfib (n-2)
265 </verb></tscreen>
266
267 For values of @n@ greater than 1, we use @par@ to spark a thread
268 to evaluate @nfib (n-1)@, and then we use @seq@ to force the
269 parent thread to evaluate @nfib (n-2)@ before going on to add
270 together these two subexpressions.  In this divide-and-conquer
271 approach, we only spark a new thread for one branch of the computation
272 (leaving the parent to evaluate the other branch).  Also, we must use
273 @seq@ to ensure that the parent will evaluate @n2@ <em>before</em>
274 @n1@ in the expression @(n1 + n2 + 1)@.  It is not sufficient to
275 reorder the expression as @(n2 + n1 + 1)@, because the compiler may
276 not generate code to evaluate the addends from left to right.
277
278 %************************************************************************
279 %*                                                                      *
280 <sect3>Underlying functions and primitives
281 <nidx>parallelism primitives</nidx>
282 <nidx>primitives for parallelism</nidx>
283 <p>
284 %*                                                                      *
285 %************************************************************************
286
287 The functions @par@ and @seq@ are wired into GHC, and unfold
288 into uses of the @par#@ and @seq#@ primitives, respectively.  If
289 you'd like to see this with your very own eyes, just run GHC with the
290 @-ddump-simpl@ option.  (Anything for a good time...)
291
292 %************************************************************************
293 %*                                                                      *
294 <sect3>Scheduling policy for concurrent/parallel threads
295 <nidx>Scheduling---concurrent/parallel</nidx>
296 <nidx>Concurrent/parallel scheduling</nidx>
297 <p>
298 %*                                                                      *
299 %************************************************************************
300
301 Runnable threads are scheduled in round-robin fashion.  Context
302 switches are signalled by the generation of new sparks or by the
303 expiry of a virtual timer (the timer interval is configurable with the
304 @-C[<num>]@<nidx>-C&lt;num&gt; RTS option (concurrent,
305 parallel)</nidx> RTS option).  However, a context switch doesn't
306 really happen until the current heap block is full.  You can't get any
307 faster context switching than this.
308
309 When a context switch occurs, pending sparks which have not already
310 been reduced to weak head normal form are turned into new threads.
311 However, there is a limit to the number of active threads (runnable or
312 blocked) which are allowed at any given time.  This limit can be
313 adjusted with the @-t<num>@<nidx>-t &lt;num&gt; RTS option (concurrent, parallel)</nidx>
314 RTS option (the default is 32).  Once the
315 thread limit is reached, any remaining sparks are deferred until some
316 of the currently active threads are completed.