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