9ef49681983dda585eb2c02180f9d38eeb2ecff5
[ghc-base.git] / Control / Parallel / Strategies.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Control.Parallel.Strategies
4 -- Copyright   :  (c) The University of Glasgow 2001
5 -- License     :  BSD-style (see the file libraries/base/LICENSE)
6 -- 
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  experimental
9 -- Portability :  non-portable
10 --
11 -- Parallel strategy combinators
12 --
13 -----------------------------------------------------------------------------
14 module Control.Parallel.Strategies where
15
16 -- based on hslibs/concurrent/Strategies.lhs; see it for more detailed
17 -- code comments. Original authors:
18 --
19 --      Phil Trinder, Hans-Wolfgang Loidl, Kevin Hammond et al. 
20 --
21 import Control.Parallel as Parallel
22 import Data.Ix
23 import Data.Array
24 import Data.Complex
25 import Data.Ratio
26
27 -- not a terribly portable way of getting at Ratio rep.
28 #ifdef __GLASGOW_HASKELL__
29 import GHC.Real (Ratio(..))     -- The basic defns for Ratio
30 #endif
31
32 #ifdef __HUGS__
33 import Hugs.Prelude(Ratio(..) )
34 #endif
35
36 #ifdef __NHC__
37 import Ratio (Ratio(..) )
38 #endif
39
40 infixl 0 `using`,`demanding`,`sparking`              -- weakest precedence!
41
42 infixr 2 >||                -- another name for par
43 infixr 3 >|                 -- another name for seq
44 infixl 6 $||, $|            -- strategic function application (seq and par)
45 infixl 9 .|, .||, -|, -||   -- strategic (inverse) function composition
46
47 ------------------------------------------------------------------------------
48 --                      Strategy Type, Application and Semantics              
49 ------------------------------------------------------------------------------
50 type Done = ()
51 type Strategy a = a -> Done
52
53 {-
54 A strategy takes a value and returns a dummy `done' value to indicate that
55 the specifed evaluation has been performed.
56
57 The basic combinators for strategies are @par@ and @seq@ but with types that 
58 indicate that they only combine the results of a strategy application. 
59
60 NB: This version can be used with Haskell 1.4 (GHC 2.05 and beyond), *but*
61     you won't get strategy checking on seq (only on par)!
62
63 The infix fcts >| and >|| are alternative names for `seq` and `par`.
64 With the introduction of a Prelude function `seq` separating the Prelude 
65 function from the Strategy function becomes a pain. The notation also matches
66 the notation for strategic function application.
67 -}
68
69 {-
70 par and seq have the same types as before; >| and >|| are more specific
71 and can only be used when composing strategies.
72 -}
73
74 (>|), (>||) :: Done -> Done -> Done 
75 {-# INLINE (>|) #-}
76 {-# INLINE (>||) #-}
77 (>|) = Prelude.seq
78 (>||) = Parallel.par
79
80 using :: a -> Strategy a -> a
81 using x s = s x `seq` x
82
83 {-
84 using takes a strategy and a value, and applies the strategy to the
85 value before returning the value. Used to express data-oriented parallelism
86
87 x `using` s is a projection on x, i.e. both
88
89   a retraction: x `using` s [ x
90                             -
91   and idempotent: (x `using` s) `using` s = x `using` s
92
93 demanding and sparking are used to express control-oriented
94 parallelism. Their second argument is usually a sequence of strategy
95 applications combined `par` and `seq`. Sparking should only be used
96 with a singleton sequence as it is not necessarily excuted
97 -}
98
99 demanding, sparking :: a -> Done -> a
100 demanding = flip Parallel.seq
101 sparking  = flip Parallel.par
102
103 {-
104 sPar and sSeq have been superceded by sparking and demanding: replace 
105   e `using` sPar x      with    e `sparking`  x 
106   e `using` sSeq x      with    e `demanding` x
107
108 sPar is a strategy corresponding to par. i.e. x `par` e <=> e `using` sPar x
109 -}
110
111 sPar :: a -> Strategy b
112 sPar x y = x `par` ()
113
114 {-
115 sSeq is a strategy corresponding to seq. i.e. x `seq` e <=> e `using` sSeq x
116 -}
117 sSeq :: a -> Strategy b
118 sSeq x y = x `seq` ()
119
120 -----------------------------------------------------------------------------
121 --                      Basic Strategies                                     
122 -----------------------------------------------------------------------------
123
124 -- r0 performs *no* evaluation on its argument.
125 r0 :: Strategy a 
126 r0 x = ()
127
128 --rwhnf reduces its argument to weak head normal form.
129 rwhnf :: Strategy a 
130 rwhnf x = x `seq` ()  
131
132 class NFData a where
133   -- rnf reduces its argument to (head) normal form
134   rnf :: Strategy a
135   -- Default method. Useful for base types. A specific method is necessay for
136   -- constructed types
137   rnf = rwhnf
138
139 class (NFData a, Integral a) => NFDataIntegral a
140 class (NFData a, Ord a) => NFDataOrd a
141
142 ------------------------------------------------------------------------------
143 --                      Strategic Function Application
144 ------------------------------------------------------------------------------
145
146 {-
147 The two  infix functions @$|@   and @$||@  perform sequential and  parallel
148 function application, respectively. They  are parameterised with a strategy
149 that is applied to the argument of the  function application.  This is very
150 handy when  writing  pipeline parallelism  as  a sequence of  @$@, @$|@ and
151 @$||@'s. There is no  need of naming intermediate values  in this case. The
152 separation  of algorithm from strategy  is  achieved by allowing strategies
153 only as second arguments to @$|@ and @$||@.
154 -}
155
156 ($|), ($||) :: (a -> b) -> Strategy a -> a -> b
157
158 f $| s  = \ x -> f x `demanding` s x
159 f $|| s = \ x -> f x `sparking`  s x
160
161 {-
162 The same thing for function composition (.| and .||) and inverse function
163 composition (-| and -||) for those who read their programs from left to 
164 right.
165 -}
166
167 (.|), (.||) :: (b -> c) -> Strategy b -> (a -> b) -> (a -> c)
168 (-|), (-||) :: (a -> b) -> Strategy b -> (b -> c) -> (a -> c)
169
170 (.|) f s g = \ x -> let  gx = g x 
171                     in   f gx `demanding` s gx
172 (.||) f s g = \ x -> let  gx = g x 
173                      in   f gx `sparking` s gx
174
175 (-|) f s g = \ x -> let  fx = f x 
176                     in   g fx `demanding` s fx
177 (-||) f s g = \ x -> let  fx = f x 
178                      in   g fx `sparking` s fx 
179
180 ------------------------------------------------------------------------------
181 --                      Marking a Strategy
182 ------------------------------------------------------------------------------
183
184 {-
185 Marking a strategy.
186
187 Actually, @markStrat@  sticks a label @n@  into the sparkname  field of the
188 thread executing strategy @s@. Together with a runtime-system that supports
189 propagation of sparknames to the children this means that this strategy and
190 all its children have  the sparkname @n@ (if the  static sparkname field in
191 the @parGlobal@ annotation contains the value 1). Note, that the @SN@ field
192 of starting the marked strategy itself contains the sparkname of the parent
193 thread. The END event contains @n@ as sparkname.
194 -}
195
196 #if 0
197 markStrat :: Int -> Strategy a -> Strategy a 
198 markStrat n s x = unsafePerformPrimIO (
199      _casm_ ``%r = set_sparkname(CurrentTSO, %0);'' n `thenPrimIO` \ z ->
200      returnPrimIO (s x))
201 #endif
202
203 -----------------------------------------------------------------------------
204 --                      Strategy Instances and Functions                     
205 -----------------------------------------------------------------------------
206
207 -----------------------------------------------------------------------------
208 --                      Tuples
209 -----------------------------------------------------------------------------
210
211 {-
212 We currently support up to 9-tuples. If you need longer tuples you have to 
213 add the instance explicitly to your program.
214 -}
215
216 instance (NFData a, NFData b) => NFData (a,b) where
217   rnf (x,y) = rnf x `seq` rnf y
218
219 instance (NFData a, NFData b, NFData c) => NFData (a,b,c) where
220   rnf (x,y,z) = rnf x `seq` rnf y `seq` rnf z 
221
222 instance (NFData a, NFData b, NFData c, NFData d) => NFData (a,b,c,d) where
223   rnf (x1,x2,x3,x4) = rnf x1 `seq` 
224                         rnf x2 `seq` 
225                         rnf x3 `seq` 
226                         rnf x4 
227
228 instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => 
229          NFData (a1, a2, a3, a4, a5) where
230   rnf (x1, x2, x3, x4, x5) =
231                   rnf x1 `seq`
232                   rnf x2 `seq`
233                   rnf x3 `seq`
234                   rnf x4 `seq`
235                   rnf x5
236
237 instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => 
238          NFData (a1, a2, a3, a4, a5, a6) where
239   rnf (x1, x2, x3, x4, x5, x6) =
240                   rnf x1 `seq`
241                   rnf x2 `seq`
242                   rnf x3 `seq`
243                   rnf x4 `seq`
244                   rnf x5 `seq`
245                   rnf x6
246
247 instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => 
248          NFData (a1, a2, a3, a4, a5, a6, a7) where
249   rnf (x1, x2, x3, x4, x5, x6, x7) =
250                   rnf x1 `seq`
251                   rnf x2 `seq`
252                   rnf x3 `seq`
253                   rnf x4 `seq`
254                   rnf x5 `seq`
255                   rnf x6 `seq`
256                   rnf x7
257
258 instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) => 
259          NFData (a1, a2, a3, a4, a5, a6, a7, a8) where
260   rnf (x1, x2, x3, x4, x5, x6, x7, x8) =
261                   rnf x1 `seq`
262                   rnf x2 `seq`
263                   rnf x3 `seq`
264                   rnf x4 `seq`
265                   rnf x5 `seq`
266                   rnf x6 `seq`
267                   rnf x7 `seq`
268                   rnf x8
269
270 instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8, NFData a9) => 
271          NFData (a1, a2, a3, a4, a5, a6, a7, a8, a9) where
272   rnf (x1, x2, x3, x4, x5, x6, x7, x8, x9) =
273                   rnf x1 `seq`
274                   rnf x2 `seq`
275                   rnf x3 `seq`
276                   rnf x4 `seq`
277                   rnf x5 `seq`
278                   rnf x6 `seq`
279                   rnf x7 `seq`
280                   rnf x8 `seq`
281                   rnf x9
282
283
284 seqPair :: Strategy a -> Strategy b -> Strategy (a,b)
285 seqPair strata stratb (x,y) = strata x `seq` stratb y 
286
287 parPair :: Strategy a -> Strategy b -> Strategy (a,b)
288 parPair strata stratb (x,y) = strata x `par` stratb y `par` ()
289
290 {-
291 The reason for the  second `par` is so that the strategy terminates 
292 quickly. This is important if the strategy is used as the 1st argument of a seq
293 -}
294
295 seqTriple :: Strategy a -> Strategy b -> Strategy c -> Strategy (a,b,c)
296 seqTriple strata stratb stratc p@(x,y,z) = 
297   strata x `seq` 
298   stratb y `seq`
299   stratc z 
300
301 parTriple :: Strategy a -> Strategy b -> Strategy c -> Strategy (a,b,c)
302 parTriple strata stratb stratc (x,y,z) = 
303   strata x `par` 
304   stratb y `par` 
305   stratc z `par`
306   ()
307
308 {-
309 Weak head normal form and normal form are identical for integers, so the 
310 default rnf is sufficient. 
311 -}
312 instance NFData Int 
313 instance NFData Integer
314 instance NFData Float
315 instance NFData Double
316
317 instance NFDataIntegral Int
318 instance NFDataOrd Int
319
320 --Rational and complex numbers.
321
322 instance (Integral a, NFData a) => NFData (Ratio a) where
323   rnf (x:%y) = rnf x `seq` 
324                rnf y `seq`
325                ()
326
327 instance (RealFloat a, NFData a) => NFData (Complex a) where
328   rnf (x:+y) = rnf x `seq` 
329                  rnf y `seq`
330                ()
331
332 instance NFData Char
333 instance NFData Bool
334 instance NFData ()
335
336 -----------------------------------------------------------------------------
337 --                      Lists                                               
338 ----------------------------------------------------------------------------
339
340 instance NFData a => NFData [a] where
341   rnf [] = ()
342   rnf (x:xs) = rnf x `seq` rnf xs
343
344 ----------------------------------------------------------------------------
345 --                        Lists: Parallel Strategies
346 ----------------------------------------------------------------------------
347
348 -- | Applies a strategy to every element of a list in parallel
349 parList :: Strategy a -> Strategy [a]
350 parList strat []     = ()
351 parList strat (x:xs) = strat x `par` (parList strat xs)
352
353 -- | Applies a strategy to the first  n elements of a list  in parallel
354 parListN :: (Integral b) => b -> Strategy a -> Strategy [a]
355 parListN n strat []     = ()
356 parListN 0 strat xs     = ()
357 parListN n strat (x:xs) = strat x `par` (parListN (n-1) strat xs)
358
359 -- | Evaluates N elements of the spine of the argument list and applies
360 -- `strat' to the Nth element (if there is one) in parallel with the
361 -- result. e.g. parListNth 2 [e1, e2, e3] evaluates e2
362 parListNth :: Int -> Strategy a -> Strategy [a]
363 parListNth n strat xs 
364   | null rest = ()
365   | otherwise = strat (head rest) `par` ()
366   where
367     rest = drop n xs
368
369 -- | 'parListChunk' sequentially applies a strategy to chunks
370 -- (sub-sequences) of a list in parallel. Useful to increase grain size
371 parListChunk :: Int -> Strategy a -> Strategy [a]
372 parListChunk n strat [] = ()
373 parListChunk n strat xs = seqListN n strat xs `par` 
374                             parListChunk n strat (drop n xs)
375
376 -- | 'parMap' applies a function to each element of the argument list in
377 -- parallel.  The result of the function is evaluated using `strat'
378 parMap :: Strategy b -> (a -> b) -> [a] -> [b]
379 parMap strat f xs       = map f xs `using` parList strat
380
381 -- | 'parFlatMap' uses 'parMap' to apply a list-valued function to each
382 -- element of the argument list in parallel.  The result of the function
383 -- is evaluated using `strat'
384 parFlatMap :: Strategy [b] -> (a -> [b]) -> [a] -> [b]
385 parFlatMap strat f xs = concat (parMap strat f xs)
386
387 -- | 'parZipWith' zips together two lists with a function z in parallel
388 parZipWith :: Strategy c -> (a -> b -> c) -> [a] -> [b] -> [c]
389 parZipWith strat z as bs = 
390   zipWith z as bs `using` parList strat
391
392 ----------------------------------------------------------------------------
393 --                        Lists: Sequential Strategies
394 ----------------------------------------------------------------------------
395
396 -- | Sequentially applies a strategy to each element of a list
397 seqList :: Strategy a -> Strategy [a]
398 seqList strat []     = ()
399 seqList strat (x:xs) = strat x `seq` (seqList strat xs)
400
401 -- | Sequentially applies a strategy to the first  n elements of a list
402 seqListN :: (Integral a) => a -> Strategy b -> Strategy [b]
403 seqListN n strat []     = ()
404 seqListN 0 strat xs     = ()
405 seqListN n strat (x:xs) = strat x `seq` (seqListN (n-1) strat xs)
406
407 -- | 'seqListNth' applies a strategy to the Nth element of it's argument
408 -- (if there is one) before returning the result. e.g. seqListNth 2 [e1,
409 -- e2, e3] evaluates e2
410 seqListNth :: Int -> Strategy b -> Strategy [b]
411 seqListNth n strat xs 
412   | null rest = ()
413   | otherwise = strat (head rest) 
414   where
415     rest = drop n xs
416
417 -- | Parallel n-buffer function added for the revised version of the strategies
418 -- paper. 'parBuffer' supersedes the older 'fringeList'. It has the same
419 -- semantics.
420 parBuffer :: Int -> Strategy a -> [a] -> [a]
421 parBuffer n s xs = 
422   return xs (start n xs)
423   where
424     return (x:xs) (y:ys) = (x:return xs ys) `sparking` s y
425     return xs     []     = xs
426
427     start n []     = []
428     start 0 ys     = ys
429     start n (y:ys) = start (n-1) ys `sparking` s y
430
431 {-
432  'fringeList' implements a `rolling buffer' of length n, i.e.applies a
433  strategy to the nth element of list when the head is demanded. More
434  precisely:
435
436    semantics:         fringeList n s = id :: [b] -> [b]
437    dynamic behaviour: evalutates the nth element of the list when the
438                       head is demanded.
439    
440  The idea is to provide a `rolling buffer' of length n.
441 fringeList :: (Integral a) => a -> Strategy b -> [b] -> [b]
442 fringeList n strat [] = []
443 fringeList n strat (r:rs) = 
444   seqListNth n strat rs `par`
445   r:fringeList n strat rs
446 -}
447
448 ------------------------------------------------------------------------------
449 --                      Arrays
450 ------------------------------------------------------------------------------
451 instance (Ix a, NFData a, NFData b) => NFData (Array a b) where
452   rnf x = rnf (bounds x) `seq` seqList rnf (elems x) `seq` ()
453
454 -- | Apply a strategy to all elements of an array in parallel. This can be done 
455 -- either in sequentially or in parallel (same as with lists, really).
456 seqArr :: (Ix b) => Strategy a -> Strategy (Array b a)
457 seqArr s arr = seqList s (elems arr)
458
459 parArr :: (Ix b) => Strategy a -> Strategy (Array b a)
460 parArr s arr = parList s (elems arr)
461
462 -- Associations maybe useful even without mentioning Arrays.
463
464 data  Assoc a b =  a := b  deriving ()
465
466 instance (NFData a, NFData b) => NFData (Assoc a b) where
467   rnf (x := y) = rnf x `seq` rnf y `seq` ()
468
469 ------------------------------------------------------------------------------
470 --                      Some strategies specific for Lolita     
471 ------------------------------------------------------------------------------
472
473 fstPairFstList :: (NFData a) => Strategy [(a,b)]
474 fstPairFstList = seqListN 1 (seqPair rwhnf r0)
475
476 -- Some HACKs for Lolita. AFAIK force is just another name for our rnf and
477 -- sforce is a shortcut (definition here is identical to the one in Force.lhs)
478
479 force :: (NFData a) => a -> a 
480 sforce :: (NFData a) => a -> b -> b
481
482 force = id $| rnf
483 sforce x y = force x `seq` y