add System.Posix.Types to default nhc98 build
[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, pseq,
17           seq, -- for backwards compatibility, 6.6 exported this
18 #if defined(__GRANSIM__)
19         , parGlobal, parLocal, parAt, parAtAbs, parAtRel, parAtForNow     
20 #endif
21     ) where
22
23 import Prelude
24
25 #ifdef __GLASGOW_HASKELL__
26 import qualified GHC.Conc       ( par, pseq )
27 #endif
28
29 #if defined(__GRANSIM__)
30 import PrelBase
31 import PrelErr   ( parError )
32 import PrelGHC   ( parGlobal#, parLocal#, parAt#, parAtAbs#, parAtRel#, parAtForNow# )
33
34 infixr 0 `par`
35
36 {-# INLINE parGlobal #-}
37 {-# INLINE parLocal #-}
38 {-# INLINE parAt #-}
39 {-# INLINE parAtAbs #-}
40 {-# INLINE parAtRel #-}
41 {-# INLINE parAtForNow #-}
42 parGlobal   :: Int -> Int -> Int -> Int -> a -> b -> b
43 parLocal    :: Int -> Int -> Int -> Int -> a -> b -> b
44 parAt       :: Int -> Int -> Int -> Int -> a -> b -> c -> c
45 parAtAbs    :: Int -> Int -> Int -> Int -> Int -> a -> b -> b
46 parAtRel    :: Int -> Int -> Int -> Int -> Int -> a -> b -> b
47 parAtForNow :: Int -> Int -> Int -> Int -> a -> b -> c -> c
48
49 parGlobal (I# w) (I# g) (I# s) (I# p) x y = case (parGlobal# x w g s p y) of { 0# -> parError; _ -> y }
50 parLocal  (I# w) (I# g) (I# s) (I# p) x y = case (parLocal#  x w g s p y) of { 0# -> parError; _ -> y }
51
52 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 }
53 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 }
54 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 }
55 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 }
56
57 #endif
58
59 -- Maybe parIO and the like could be added here later.
60
61 -- | Indicates that it may be beneficial to evaluate the first
62 -- argument in parallel with the second.  Returns the value of the
63 -- second argument.
64 -- 
65 -- @a `par` b@ is exactly equivalent semantically to @b@.
66 --
67 -- @par@ is generally used when the value of @a@ is likely to be
68 -- required later, but not immediately.  Also it is a good idea to
69 -- ensure that @a@ is not a trivial computation, otherwise the cost of
70 -- spawning it in parallel overshadows the benefits obtained by
71 -- running it in parallel.
72 --
73 -- Note that actual parallelism is only supported by certain
74 -- implementations (GHC with the @-threaded@ option, and GPH, for
75 -- now).  On other implementations, @par a b = b@.
76 --
77 par :: a -> b -> b
78 #ifdef __GLASGOW_HASKELL__
79 par = GHC.Conc.par
80 #else
81 -- For now, Hugs does not support par properly.
82 par a b = b
83 #endif
84
85 -- | Semantically identical to 'seq', but with a subtle operational
86 -- difference: 'seq' is strict in both its arguments, so the compiler
87 -- may, for example, rearrange @a `seq` b@ into @b `seq` a `seq` b@.
88 -- This is normally no problem when using 'seq' to express strictness,
89 -- but it can be a problem when annotating code for parallelism,
90 -- because we need more control over the order of evaluation; we may
91 -- want to evaluate @a@ before @b@, because we know that @b@ has
92 -- already been sparked in parallel with 'par'.
93 --
94 -- This is why we have 'pseq'.  In contrast to 'seq', 'pseq' is only
95 -- strict in its first argument (as far as the compiler is concerned),
96 -- which restricts the transformations that the compiler can do, and
97 -- ensures that the user can retain control of the evaluation order.
98 --
99 pseq :: a -> b -> b
100 #ifdef __GLASGOW_HASKELL__
101 pseq = GHC.Conc.pseq
102 #else
103 pseq = seq
104 #endif