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