`par` should be infixr 0
[haskell-directory.git] / Control / Parallel.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Control.Parallel
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 Constructs
12 --
13 -----------------------------------------------------------------------------
14
15 module Control.Parallel (
16           par, seq -- re-exported
17 #if defined(__GRANSIM__)
18         , parGlobal, parLocal, parAt, parAtAbs, parAtRel, parAtForNow     
19 #endif
20     ) where
21
22 import Prelude
23
24 #ifdef __GLASGOW_HASKELL__
25 import qualified GHC.Conc       ( par )
26 #endif
27
28 #if defined(__GRANSIM__)
29 import PrelBase
30 import PrelErr   ( parError )
31 import PrelGHC   ( parGlobal#, parLocal#, parAt#, parAtAbs#, parAtRel#, parAtForNow# )
32
33 infixr 0 `par`
34
35 {-# INLINE parGlobal #-}
36 {-# INLINE parLocal #-}
37 {-# INLINE parAt #-}
38 {-# INLINE parAtAbs #-}
39 {-# INLINE parAtRel #-}
40 {-# INLINE parAtForNow #-}
41 parGlobal   :: Int -> Int -> Int -> Int -> a -> b -> b
42 parLocal    :: Int -> Int -> Int -> Int -> a -> b -> b
43 parAt       :: Int -> Int -> Int -> Int -> a -> b -> c -> c
44 parAtAbs    :: Int -> Int -> Int -> Int -> Int -> a -> b -> b
45 parAtRel    :: Int -> Int -> Int -> Int -> Int -> a -> b -> b
46 parAtForNow :: Int -> Int -> Int -> Int -> a -> b -> c -> c
47
48 parGlobal (I# w) (I# g) (I# s) (I# p) x y = case (parGlobal# x w g s p y) of { 0# -> parError; _ -> y }
49 parLocal  (I# w) (I# g) (I# s) (I# p) x y = case (parLocal#  x w g s p y) of { 0# -> parError; _ -> y }
50
51 parAt       (I# w) (I# g) (I# s) (I# p) v x y = case (parAt#       x v w g s p y) of { 0# -> parError; _ -> y }
52 parAtAbs    (I# w) (I# g) (I# s) (I# p) (I# q) x y = case (parAtAbs#  x q w g s p y) of { 0# -> parError; _ -> y }
53 parAtRel    (I# w) (I# g) (I# s) (I# p) (I# q) x y = case (parAtRel#  x q w g s p y) of { 0# -> parError; _ -> y }
54 parAtForNow (I# w) (I# g) (I# s) (I# p) v x y = case (parAtForNow# x v w g s p y) of { 0# -> parError; _ -> y }
55
56 #endif
57
58 -- Maybe parIO and the like could be added here later.
59
60 -- | Indicates that it may be beneficial to evaluate the first
61 -- argument in parallel with the second.  Returns the value of the
62 -- second argument.
63 -- 
64 -- @a `par` b@ is exactly equivalent semantically to @b@.
65 --
66 -- @par@ is generally used when the value of @a@ is likely to be
67 -- required later, but not immediately.  Also it is a good idea to
68 -- ensure that @a@ is not a trivial computation, otherwise the cost of
69 -- spawning it in parallel overshadows the benefits obtained by
70 -- running it in parallel.
71 --
72 -- Note that actual parallelism is only supported by certain
73 -- implementations (GHC with the @-threaded@ option, and GPH, for
74 -- now).  On other implementations, @par a b = b@.
75 --
76 par :: a -> b -> b
77 #ifdef __GLASGOW_HASKELL__
78 par = GHC.Conc.par
79 #else
80 -- For now, Hugs does not support par properly.
81 par a b = b
82 #endif